Remove/Cleanup unused/deprecated MTEL stuff

pull/51/head
Lennart Spitzner 2017-08-06 16:28:41 +02:00
parent b39997fcfa
commit 41beeb9723
6 changed files with 2 additions and 51 deletions

View File

@ -385,7 +385,6 @@ layoutBriDoc ast briDoc = do
, _lstate_comments = filteredAnns , _lstate_comments = filteredAnns
, _lstate_commentCol = Nothing , _lstate_commentCol = Nothing
, _lstate_addSepSpace = Nothing , _lstate_addSepSpace = Nothing
, _lstate_inhibitMTEL = False
} }
state' <- MultiRWSS.withMultiStateS state $ layoutBriDocM briDoc' state' <- MultiRWSS.withMultiStateS state $ layoutBriDocM briDoc'

View File

@ -152,8 +152,7 @@ layoutBriDocM = \case
BDAnnotationPrior annKey bd -> do BDAnnotationPrior annKey bd -> do
state <- mGet state <- mGet
let m = _lstate_comments state let m = _lstate_comments state
let allowMTEL = not (_lstate_inhibitMTEL state) let allowMTEL = Data.Either.isRight (_lstate_curYOrAddNewline state)
&& Data.Either.isRight (_lstate_curYOrAddNewline state)
mAnn <- do mAnn <- do
let mAnn = ExactPrint.annPriorComments <$> Map.lookup annKey m let mAnn = ExactPrint.annPriorComments <$> Map.lookup annKey m
mSet $ state mSet $ state
@ -252,22 +251,6 @@ layoutBriDocM = \case
BDNonBottomSpacing bd -> layoutBriDocM bd BDNonBottomSpacing bd -> layoutBriDocM bd
BDSetParSpacing bd -> layoutBriDocM bd BDSetParSpacing bd -> layoutBriDocM bd
BDForceParSpacing bd -> layoutBriDocM bd BDForceParSpacing bd -> layoutBriDocM bd
BDProhibitMTEL bd -> do
-- set flag to True for this child, but disable afterwards.
-- two hard aspects
-- 1) nesting should be allowed. this means that resetting at the end must
-- not indiscriminantely set to False, but take into account the
-- previous value
-- 2) nonetheless, newlines cancel inhibition. this means that if we ever
-- find the flag set to False afterwards, we must not return it to
-- the previous value, which might be True in the case of testing; it
-- must remain False.
state <- mGet
mSet $ state { _lstate_inhibitMTEL = True }
layoutBriDocM bd
state' <- mGet
when (_lstate_inhibitMTEL state') $ do
mSet $ state' { _lstate_inhibitMTEL = _lstate_inhibitMTEL state }
BDDebug s bd -> do BDDebug s bd -> do
mTell $ Text.Builder.fromText $ Text.pack $ "{-" ++ s ++ "-}" mTell $ Text.Builder.fromText $ Text.pack $ "{-" ++ s ++ "-}"
layoutBriDocM bd layoutBriDocM bd
@ -302,7 +285,6 @@ briDocLineLength briDoc = flip StateS.evalState False $ rec briDoc
return $ maximum $ ls <&> \l -> StateS.evalState (rec l) x return $ maximum $ ls <&> \l -> StateS.evalState (rec l) x
BDLines [] -> error "briDocLineLength BDLines []" BDLines [] -> error "briDocLineLength BDLines []"
BDEnsureIndent _ bd -> rec bd BDEnsureIndent _ bd -> rec bd
BDProhibitMTEL bd -> rec bd
BDSetParSpacing bd -> rec bd BDSetParSpacing bd -> rec bd
BDForceParSpacing bd -> rec bd BDForceParSpacing bd -> rec bd
BDNonBottomSpacing bd -> rec bd BDNonBottomSpacing bd -> rec bd
@ -336,7 +318,6 @@ briDocIsMultiLine briDoc = rec briDoc
BDLines [_ ] -> False BDLines [_ ] -> False
BDLines [] -> error "briDocIsMultiLine BDLines []" BDLines [] -> error "briDocIsMultiLine BDLines []"
BDEnsureIndent _ bd -> rec bd BDEnsureIndent _ bd -> rec bd
BDProhibitMTEL bd -> rec bd
BDSetParSpacing bd -> rec bd BDSetParSpacing bd -> rec bd
BDForceParSpacing bd -> rec bd BDForceParSpacing bd -> rec bd
BDNonBottomSpacing bd -> rec bd BDNonBottomSpacing bd -> rec bd

View File

@ -146,7 +146,6 @@ layoutWriteNewlineBlock = do
state <- mGet state <- mGet
mSet $ state { _lstate_curYOrAddNewline = Right 1 mSet $ state { _lstate_curYOrAddNewline = Right 1
, _lstate_addSepSpace = Just $ lstate_baseY state , _lstate_addSepSpace = Just $ lstate_baseY state
, _lstate_inhibitMTEL = False
} }
-- layoutMoveToIndentCol :: ( MonadMultiState LayoutState m -- layoutMoveToIndentCol :: ( MonadMultiState LayoutState m
@ -222,7 +221,6 @@ layoutWriteNewline = do
Left{} -> Right 1 Left{} -> Right 1
Right i -> Right (i + 1) Right i -> Right (i + 1)
, _lstate_addSepSpace = Nothing , _lstate_addSepSpace = Nothing
, _lstate_inhibitMTEL = False
} }
layoutWriteEnsureNewlineBlock layoutWriteEnsureNewlineBlock
@ -239,7 +237,6 @@ layoutWriteEnsureNewlineBlock = do
Left{} -> Right 1 Left{} -> Right 1
Right i -> Right $ max 1 i Right i -> Right $ max 1 i
, _lstate_addSepSpace = Just $ lstate_baseY state , _lstate_addSepSpace = Just $ lstate_baseY state
, _lstate_inhibitMTEL = False
, _lstate_commentCol = Nothing , _lstate_commentCol = Nothing
} }

View File

@ -334,8 +334,6 @@ transformAlts briDoc =
BDFNonBottomSpacing bd -> rec bd BDFNonBottomSpacing bd -> rec bd
BDFSetParSpacing bd -> rec bd BDFSetParSpacing bd -> rec bd
BDFForceParSpacing bd -> rec bd BDFForceParSpacing bd -> rec bd
BDFProhibitMTEL bd ->
reWrap . BDFProhibitMTEL <$> rec bd
BDFDebug s bd -> do BDFDebug s bd -> do
acp :: AltCurPos <- mGet acp :: AltCurPos <- mGet
tellDebugMess $ "transformAlts: BDFDEBUG " ++ s ++ " (node-id=" ++ show brDcId ++ "): acp=" ++ show acp tellDebugMess $ "transformAlts: BDFDEBUG " ++ s ++ " (node-id=" ++ show brDcId ++ "): acp=" ++ show acp
@ -490,7 +488,6 @@ getSpacing !bridoc = rec bridoc
BDFForceParSpacing bd -> do BDFForceParSpacing bd -> do
mVs <- rec bd mVs <- rec bd
return $ [ vs | vs <- mVs, _vs_parFlag vs || _vs_paragraph vs == VerticalSpacingParNone ] return $ [ vs | vs <- mVs, _vs_parFlag vs || _vs_paragraph vs == VerticalSpacingParNone ]
BDFProhibitMTEL bd -> rec bd
BDFDebug s bd -> do BDFDebug s bd -> do
r <- rec bd r <- rec bd
tellDebugMess $ "getSpacing: BDFDebug " ++ show s ++ " (node-id=" ++ show brDcId ++ "): mVs=" ++ show r tellDebugMess $ "getSpacing: BDFDebug " ++ show s ++ " (node-id=" ++ show brDcId ++ "): mVs=" ++ show r
@ -758,7 +755,6 @@ getSpacings limit bridoc = preFilterLimit <$> rec bridoc
BDFForceParSpacing bd -> do BDFForceParSpacing bd -> do
mVs <- preFilterLimit <$> rec bd mVs <- preFilterLimit <$> rec bd
return $ [ vs | vs <- mVs, _vs_parFlag vs || _vs_paragraph vs == VerticalSpacingParNone ] return $ [ vs | vs <- mVs, _vs_parFlag vs || _vs_paragraph vs == VerticalSpacingParNone ]
BDFProhibitMTEL bd -> rec bd
BDFDebug s bd -> do BDFDebug s bd -> do
r <- rec bd r <- rec bd
tellDebugMess $ "getSpacings: BDFDebug " ++ show s ++ " (node-id=" ++ show brDcId ++ "): vs=" ++ show (take 9 r) tellDebugMess $ "getSpacings: BDFDebug " ++ show s ++ " (node-id=" ++ show brDcId ++ "): vs=" ++ show (take 9 r)

View File

@ -129,7 +129,6 @@ transformSimplifyColumns = Uniplate.rewrite $ \case
BDAnnotationKW{} -> Nothing BDAnnotationKW{} -> Nothing
BDAnnotationRest{} -> Nothing BDAnnotationRest{} -> Nothing
BDEnsureIndent{} -> Nothing BDEnsureIndent{} -> Nothing
BDProhibitMTEL{} -> Nothing
BDSetParSpacing{} -> Nothing BDSetParSpacing{} -> Nothing
BDForceParSpacing{} -> Nothing BDForceParSpacing{} -> Nothing
BDDebug{} -> Nothing BDDebug{} -> Nothing

View File

@ -62,17 +62,10 @@ data LayoutState = LayoutState
, _lstate_addSepSpace :: Maybe Int -- number of spaces to insert if anyone , _lstate_addSepSpace :: Maybe Int -- number of spaces to insert if anyone
-- writes (any non-spaces) in the -- writes (any non-spaces) in the
-- current line. -- current line.
, _lstate_inhibitMTEL :: Bool
-- ^ inhibit move-to-exact-location.
-- normally, processing a node's annotation involves moving to the exact
-- (vertical) location of the node. this ensures that newlines in the
-- input are retained in the output.
-- While this flag is on, this behaviour will be disabled.
-- The flag is automatically turned off when inserting any kind of
-- newline.
-- , _lstate_isNewline :: NewLineState -- , _lstate_isNewline :: NewLineState
-- -- captures if the layouter currently is in a new line, i.e. if the -- -- captures if the layouter currently is in a new line, i.e. if the
-- -- current line only contains (indentation) spaces. -- -- current line only contains (indentation) spaces.
-- this is mostly superseeded by curYOrAddNewline, iirc.
} }
lstate_baseY :: LayoutState -> Int lstate_baseY :: LayoutState -> Int
@ -91,7 +84,6 @@ instance Show LayoutState where
++ ",indLevelLinger=" ++ show (_lstate_indLevelLinger state) ++ ",indLevelLinger=" ++ show (_lstate_indLevelLinger state)
++ ",commentCol=" ++ show (_lstate_commentCol state) ++ ",commentCol=" ++ show (_lstate_commentCol state)
++ ",addSepSpace=" ++ show (_lstate_addSepSpace state) ++ ",addSepSpace=" ++ show (_lstate_addSepSpace state)
++ ",inhibitMTEL=" ++ show (_lstate_inhibitMTEL state)
++ "}" ++ "}"
-- data NewLineState = NewLineStateInit -- initial state. we do not know if in a -- data NewLineState = NewLineStateInit -- initial state. we do not know if in a
@ -243,11 +235,6 @@ data BriDoc
| BDSetParSpacing BriDoc | BDSetParSpacing BriDoc
| BDForceParSpacing BriDoc | BDForceParSpacing BriDoc
-- pseudo-deprecated -- pseudo-deprecated
| BDProhibitMTEL BriDoc -- move to exact location
-- TODO: this constructor is deprecated. should
-- still work, but i should probably completely
-- remove it, as i have no proper usecase for
-- it anymore.
| BDDebug String BriDoc | BDDebug String BriDoc
deriving (Data.Data.Data, Eq, Ord) deriving (Data.Data.Data, Eq, Ord)
@ -289,11 +276,6 @@ data BriDocF f
| BDFNonBottomSpacing (f (BriDocF f)) | BDFNonBottomSpacing (f (BriDocF f))
| BDFSetParSpacing (f (BriDocF f)) | BDFSetParSpacing (f (BriDocF f))
| BDFForceParSpacing (f (BriDocF f)) | BDFForceParSpacing (f (BriDocF f))
| BDFProhibitMTEL (f (BriDocF f)) -- move to exact location
-- TODO: this constructor is deprecated. should
-- still work, but i should probably completely
-- remove it, as i have no proper usecase for
-- it anymore.
| BDFDebug String (f (BriDocF f)) | BDFDebug String (f (BriDocF f))
-- deriving instance Data.Data.Data (BriDocF Identity) -- deriving instance Data.Data.Data (BriDocF Identity)
@ -327,7 +309,6 @@ instance Uniplate.Uniplate BriDoc where
uniplate (BDNonBottomSpacing bd) = plate BDNonBottomSpacing |* bd uniplate (BDNonBottomSpacing bd) = plate BDNonBottomSpacing |* bd
uniplate (BDSetParSpacing bd) = plate BDSetParSpacing |* bd uniplate (BDSetParSpacing bd) = plate BDSetParSpacing |* bd
uniplate (BDForceParSpacing bd) = plate BDForceParSpacing |* bd uniplate (BDForceParSpacing bd) = plate BDForceParSpacing |* bd
uniplate (BDProhibitMTEL bd) = plate BDProhibitMTEL |* bd
uniplate (BDDebug s bd) = plate BDDebug |- s |* bd uniplate (BDDebug s bd) = plate BDDebug |- s |* bd
newtype NodeAllocIndex = NodeAllocIndex Int newtype NodeAllocIndex = NodeAllocIndex Int
@ -359,7 +340,6 @@ unwrapBriDocNumbered tpl = case snd tpl of
BDFNonBottomSpacing bd -> BDNonBottomSpacing $ rec bd BDFNonBottomSpacing bd -> BDNonBottomSpacing $ rec bd
BDFSetParSpacing bd -> BDSetParSpacing $ rec bd BDFSetParSpacing bd -> BDSetParSpacing $ rec bd
BDFForceParSpacing bd -> BDForceParSpacing $ rec bd BDFForceParSpacing bd -> BDForceParSpacing $ rec bd
BDFProhibitMTEL bd -> BDProhibitMTEL $ rec bd
BDFDebug s bd -> BDDebug (s ++ "@" ++ show (fst tpl)) $ rec bd BDFDebug s bd -> BDDebug (s ++ "@" ++ show (fst tpl)) $ rec bd
where where
rec = unwrapBriDocNumbered rec = unwrapBriDocNumbered
@ -395,7 +375,6 @@ briDocSeqSpine = \case
BDNonBottomSpacing bd -> briDocSeqSpine bd BDNonBottomSpacing bd -> briDocSeqSpine bd
BDSetParSpacing bd -> briDocSeqSpine bd BDSetParSpacing bd -> briDocSeqSpine bd
BDForceParSpacing bd -> briDocSeqSpine bd BDForceParSpacing bd -> briDocSeqSpine bd
BDProhibitMTEL bd -> briDocSeqSpine bd
BDDebug _s bd -> briDocSeqSpine bd BDDebug _s bd -> briDocSeqSpine bd
briDocForceSpine :: BriDoc -> BriDoc briDocForceSpine :: BriDoc -> BriDoc