Fix comments moving after "where"
parent
ebe85a5949
commit
2fef44559e
|
@ -895,3 +895,37 @@ fieldWith
|
||||||
-> ToBriDocM BriDocNumbered
|
-> ToBriDocM BriDocNumbered
|
||||||
)
|
)
|
||||||
-> [ToBriDocM BriDocNumbered]
|
-> [ToBriDocM BriDocNumbered]
|
||||||
|
|
||||||
|
#test comment-before-where
|
||||||
|
briDocLineLength briDoc = flip StateS.evalState False $ go briDoc
|
||||||
|
-- the state encodes whether a separator was already
|
||||||
|
-- appended at the current position.
|
||||||
|
where
|
||||||
|
go = \case
|
||||||
|
BDEmpty -> return $ 0
|
||||||
|
BDLit t -> StateS.put False $> Text.length t
|
||||||
|
BDSeq bds -> sum <$> go `mapM` bds
|
||||||
|
|
||||||
|
#test where-funbind-no-empty-lines
|
||||||
|
alignColsLines layoutBriDocM bridocs = do -- colInfos `forM_` \colInfo -> do
|
||||||
|
-- tellDebugMess ("alignColsLines: at " ++ take 100 (show $ briDocToDoc $ head bridocs))
|
||||||
|
case () of
|
||||||
|
_ -> do
|
||||||
|
-- tellDebugMess ("colInfos:\n" ++ List.unlines [ "> " ++ prettyColInfos "> " x | x <- colInfos])
|
||||||
|
-- tellDebugMess ("processedMap: " ++ show processedMap)
|
||||||
|
sequence_
|
||||||
|
$ List.intersperse layoutWriteEnsureNewlineBlock
|
||||||
|
$ colInfos <&> processInfo layoutBriDocM colMax processedMap
|
||||||
|
where
|
||||||
|
(colInfos, finalState) =
|
||||||
|
StateS.runState (mergeBriDocs bridocs) (ColBuildState IntMapS.empty 0)
|
||||||
|
-- maxZipper :: [Int] -> [Int] -> [Int]
|
||||||
|
-- maxZipper [] ys = ys
|
||||||
|
-- maxZipper xs [] = xs
|
||||||
|
-- maxZipper (x:xr) (y:yr) = max x y : maxZipper xr yr
|
||||||
|
colAggregation :: [Int] -> Int
|
||||||
|
colAggregation [] = 0 -- this probably cannot happen the way we call
|
||||||
|
-- this function, because _cbs_map only ever
|
||||||
|
-- contains nonempty Seqs.
|
||||||
|
colAggregation xs = maximum [ x | x <- xs, x <= minimum xs + alignMax' ]
|
||||||
|
where alignMax' = max 0 alignMax
|
||||||
|
|
|
@ -182,7 +182,7 @@ layoutIPBind lipbind@(L _ bind) = case bind of
|
||||||
binderDoc
|
binderDoc
|
||||||
(Just ipName)
|
(Just ipName)
|
||||||
(Left expr)
|
(Left expr)
|
||||||
Nothing
|
(id, Nothing)
|
||||||
hasComments
|
hasComments
|
||||||
|
|
||||||
|
|
||||||
|
@ -196,7 +196,8 @@ bindOrSigtoSrcSpan (BagSig (L (SrcSpanAnn _ l) _)) = l
|
||||||
layoutLocalBinds
|
layoutLocalBinds
|
||||||
:: HsLocalBindsLR GhcPs GhcPs
|
:: HsLocalBindsLR GhcPs GhcPs
|
||||||
-> ToBriDocM
|
-> ToBriDocM
|
||||||
( Maybe
|
( ToBriDocM BriDocNumbered -> ToBriDocM BriDocNumbered
|
||||||
|
, Maybe
|
||||||
( ToBriDocM BriDocNumbered -> ToBriDocM BriDocNumbered
|
( ToBriDocM BriDocNumbered -> ToBriDocM BriDocNumbered
|
||||||
, [BriDocNumbered]
|
, [BriDocNumbered]
|
||||||
)
|
)
|
||||||
|
@ -207,23 +208,23 @@ layoutLocalBinds binds = case binds of
|
||||||
-- x@(HsValBinds (ValBindsIn{})) ->
|
-- x@(HsValBinds (ValBindsIn{})) ->
|
||||||
-- Just . (:[]) <$> unknownNodeError "HsValBinds (ValBindsIn _ (_:_))" x
|
-- Just . (:[]) <$> unknownNodeError "HsValBinds (ValBindsIn _ (_:_))" x
|
||||||
HsValBinds epAnn (ValBinds _ bindlrs sigs) -> do
|
HsValBinds epAnn (ValBinds _ bindlrs sigs) -> do
|
||||||
let locWhere = obtainAnnPos epAnn AnnWhere
|
let locWhere = obtainAnnPos epAnn AnnWhere
|
||||||
let unordered =
|
let unordered =
|
||||||
[ BagBind b | b <- Data.Foldable.toList bindlrs ]
|
[ BagBind b | b <- Data.Foldable.toList bindlrs ]
|
||||||
++ [ BagSig s | s <- sigs ]
|
++ [ BagSig s | s <- sigs ]
|
||||||
ordered = List.sortOn (ExactPrint.rs . bindOrSigtoSrcSpan) unordered
|
ordered = List.sortOn (ExactPrint.rs . bindOrSigtoSrcSpan) unordered
|
||||||
ds <- docHandleComms epAnn $ join <$> ordered `forM` \case
|
ds <- join <$> ordered `forM` \case
|
||||||
BagBind b -> either id return <$> layoutBind b
|
BagBind b -> either id return <$> layoutBind b
|
||||||
BagSig s@(L _ sig) -> do
|
BagSig s@(L _ sig) -> do
|
||||||
doc <- layoutSig s sig
|
doc <- layoutSig s sig
|
||||||
pure [doc]
|
pure [doc]
|
||||||
pure $ Just (docHandleComms locWhere, ds)
|
pure $ (docHandleComms epAnn, Just (docHandleComms locWhere, ds))
|
||||||
-- x@(HsValBinds (ValBindsOut _binds _lsigs)) ->
|
-- x@(HsValBinds (ValBindsOut _binds _lsigs)) ->
|
||||||
HsValBinds _ (XValBindsLR{}) -> error "brittany internal error: XValBindsLR"
|
HsValBinds _ (XValBindsLR{}) -> error "brittany internal error: XValBindsLR"
|
||||||
HsIPBinds epAnn (IPBinds _ bb) -> do
|
HsIPBinds epAnn (IPBinds _ bb) -> do
|
||||||
ds <- docHandleComms epAnn $ mapM layoutIPBind bb
|
ds <- mapM layoutIPBind bb
|
||||||
pure $ Just (id, ds) -- TODO92 do we need to replace id?
|
pure $ (docHandleComms epAnn, Just (id, ds)) -- TODO92 do we need to replace id?
|
||||||
EmptyLocalBinds NoExtField -> return $ Nothing
|
EmptyLocalBinds NoExtField -> return $ (id, Nothing)
|
||||||
|
|
||||||
layoutGrhs
|
layoutGrhs
|
||||||
:: LGRHS GhcPs (LHsExpr GhcPs)
|
:: LGRHS GhcPs (LHsExpr GhcPs)
|
||||||
|
@ -323,14 +324,15 @@ layoutPatternBindFinal
|
||||||
-> BriDocNumbered
|
-> BriDocNumbered
|
||||||
-> Maybe BriDocNumbered
|
-> Maybe BriDocNumbered
|
||||||
-> Either (LHsExpr GhcPs) [LGRHS GhcPs (LHsExpr GhcPs)]
|
-> Either (LHsExpr GhcPs) [LGRHS GhcPs (LHsExpr GhcPs)]
|
||||||
-> ( Maybe
|
-> ( ToBriDocM BriDocNumbered -> ToBriDocM BriDocNumbered
|
||||||
|
, Maybe
|
||||||
( ToBriDocM BriDocNumbered -> ToBriDocM BriDocNumbered
|
( ToBriDocM BriDocNumbered -> ToBriDocM BriDocNumbered
|
||||||
, [BriDocNumbered]
|
, [BriDocNumbered]
|
||||||
)
|
)
|
||||||
)
|
)
|
||||||
-> Bool
|
-> Bool
|
||||||
-> ToBriDocM BriDocNumbered
|
-> ToBriDocM BriDocNumbered
|
||||||
layoutPatternBindFinal alignmentToken binderDoc mPatDoc clauses mWhereDocs hasComments
|
layoutPatternBindFinal alignmentToken binderDoc mPatDoc clauses (wrapBinds, mWhereDocs) hasComments
|
||||||
= do
|
= do
|
||||||
let
|
let
|
||||||
patPartInline = case mPatDoc of
|
patPartInline = case mPatDoc of
|
||||||
|
@ -354,14 +356,14 @@ layoutPatternBindFinal alignmentToken binderDoc mPatDoc clauses mWhereDocs hasCo
|
||||||
Just (wrapWhere, [w]) -> pure . pure <$> docAlt
|
Just (wrapWhere, [w]) -> pure . pure <$> docAlt
|
||||||
[ docEnsureIndent BrIndentRegular
|
[ docEnsureIndent BrIndentRegular
|
||||||
$ docSeq
|
$ docSeq
|
||||||
[ wrapWhere $ docLit $ Text.pack "where"
|
[ wrapBinds $ wrapWhere $ docLit $ Text.pack "where"
|
||||||
, docSeparator
|
, docSeparator
|
||||||
, docForceSingleline $ return w
|
, docForceSingleline $ return w
|
||||||
]
|
]
|
||||||
, -- docMoveToKWDP annKeyWhere AnnWhere False -- TODO92
|
, -- docMoveToKWDP annKeyWhere AnnWhere False -- TODO92
|
||||||
docEnsureIndent whereIndent
|
docEnsureIndent whereIndent
|
||||||
$ docLines
|
$ docLines
|
||||||
[ docLit $ Text.pack "where"
|
[ wrapBinds $ wrapWhere $ docLit $ Text.pack "where"
|
||||||
, docEnsureIndent whereIndent
|
, docEnsureIndent whereIndent
|
||||||
$ docSetIndentLevel
|
$ docSetIndentLevel
|
||||||
$ docNonBottomSpacing
|
$ docNonBottomSpacing
|
||||||
|
@ -373,7 +375,7 @@ layoutPatternBindFinal alignmentToken binderDoc mPatDoc clauses mWhereDocs hasCo
|
||||||
-- $ docMoveToKWDP annKeyWhere AnnWhere False -- TODO92
|
-- $ docMoveToKWDP annKeyWhere AnnWhere False -- TODO92
|
||||||
$ docEnsureIndent whereIndent
|
$ docEnsureIndent whereIndent
|
||||||
$ docLines
|
$ docLines
|
||||||
[ wrapWhere $ docLit $ Text.pack "where"
|
[ wrapBinds $ wrapWhere $ docLit $ Text.pack "where"
|
||||||
, docEnsureIndent whereIndent
|
, docEnsureIndent whereIndent
|
||||||
$ docSetIndentLevel
|
$ docSetIndentLevel
|
||||||
$ docNonBottomSpacing
|
$ docNonBottomSpacing
|
||||||
|
@ -397,7 +399,7 @@ layoutPatternBindFinal alignmentToken binderDoc mPatDoc clauses mWhereDocs hasCo
|
||||||
Nothing -> Just docEmpty
|
Nothing -> Just docEmpty
|
||||||
Just (wrapWhere, [w]) -> Just $ docSeq
|
Just (wrapWhere, [w]) -> Just $ docSeq
|
||||||
[ docSeparator
|
[ docSeparator
|
||||||
, wrapWhere $ appSep $ docLit $ Text.pack "where"
|
, wrapBinds $ wrapWhere $ appSep $ docLit $ Text.pack "where"
|
||||||
, docSetIndentLevel $ docForceSingleline $ return w
|
, docSetIndentLevel $ docForceSingleline $ return w
|
||||||
]
|
]
|
||||||
_ -> Nothing
|
_ -> Nothing
|
||||||
|
|
|
@ -585,7 +585,7 @@ layoutExpr lexpr@(L _ expr) = do
|
||||||
binderDoc
|
binderDoc
|
||||||
Nothing
|
Nothing
|
||||||
(Right cases)
|
(Right cases)
|
||||||
Nothing
|
(id, Nothing)
|
||||||
hasComments
|
hasComments
|
||||||
)
|
)
|
||||||
HsLet epAnn binds exp1 -> docHandleComms epAnn $ do
|
HsLet epAnn binds exp1 -> docHandleComms epAnn $ do
|
||||||
|
@ -593,7 +593,7 @@ layoutExpr lexpr@(L _ expr) = do
|
||||||
let hasComments = hasAnyCommentsBelow lexpr
|
let hasComments = hasAnyCommentsBelow lexpr
|
||||||
let wrapLet = docHandleComms spanLet
|
let wrapLet = docHandleComms spanLet
|
||||||
let wrapIn = docHandleComms spanIn
|
let wrapIn = docHandleComms spanIn
|
||||||
mBindDocs <- callLayouter layout_localBinds binds
|
(wrapBinds, mBindDocs) <- callLayouter layout_localBinds binds
|
||||||
let ifIndentFreeElse :: a -> a -> a
|
let ifIndentFreeElse :: a -> a -> a
|
||||||
ifIndentFreeElse x y = case indentPolicy of
|
ifIndentFreeElse x y = case indentPolicy of
|
||||||
IndentPolicyLeft -> y
|
IndentPolicyLeft -> y
|
||||||
|
@ -614,7 +614,7 @@ layoutExpr lexpr@(L _ expr) = do
|
||||||
Just [bindDoc] -> runFilteredAlternative $ do
|
Just [bindDoc] -> runFilteredAlternative $ do
|
||||||
addAlternativeCond (not hasComments) $ docSeq
|
addAlternativeCond (not hasComments) $ docSeq
|
||||||
[ appSep $ letDoc
|
[ appSep $ letDoc
|
||||||
, appSep $ docForceSingleline (pure bindDoc)
|
, wrapBinds $ appSep $ docForceSingleline (pure bindDoc)
|
||||||
, appSep $ inDoc
|
, appSep $ inDoc
|
||||||
, docForceSingleline expDoc1
|
, docForceSingleline expDoc1
|
||||||
]
|
]
|
||||||
|
@ -622,11 +622,13 @@ layoutExpr lexpr@(L _ expr) = do
|
||||||
[ docAlt
|
[ docAlt
|
||||||
[ docSeq
|
[ docSeq
|
||||||
[ appSep $ letDoc
|
[ appSep $ letDoc
|
||||||
, ifIndentFreeElse docSetBaseAndIndent docForceSingleline
|
, wrapBinds
|
||||||
|
$ ifIndentFreeElse docSetBaseAndIndent docForceSingleline
|
||||||
$ pure bindDoc
|
$ pure bindDoc
|
||||||
]
|
]
|
||||||
, docAddBaseY BrIndentRegular
|
, docAddBaseY BrIndentRegular $ docPar
|
||||||
$ docPar (letDoc) (docSetBaseAndIndent $ pure bindDoc)
|
(letDoc)
|
||||||
|
(wrapBinds $ docSetBaseAndIndent $ pure bindDoc)
|
||||||
]
|
]
|
||||||
, docAlt
|
, docAlt
|
||||||
[ docSeq
|
[ docSeq
|
||||||
|
@ -658,7 +660,9 @@ layoutExpr lexpr@(L _ expr) = do
|
||||||
let noHangingBinds =
|
let noHangingBinds =
|
||||||
[ docNonBottomSpacing $ docAddBaseY BrIndentRegular $ docPar
|
[ docNonBottomSpacing $ docAddBaseY BrIndentRegular $ docPar
|
||||||
(letDoc)
|
(letDoc)
|
||||||
(docSetBaseAndIndent $ docLines $ pure <$> bindDocs)
|
( wrapBinds
|
||||||
|
$ docSetBaseAndIndent $ docLines $ pure <$> bindDocs
|
||||||
|
)
|
||||||
, docSeq
|
, docSeq
|
||||||
[ wrapIn $ docLit $ Text.pack "in "
|
[ wrapIn $ docLit $ Text.pack "in "
|
||||||
, docAddBaseY BrIndentRegular $ docForceParSpacing expDoc1
|
, docAddBaseY BrIndentRegular $ docForceParSpacing expDoc1
|
||||||
|
@ -671,7 +675,7 @@ layoutExpr lexpr@(L _ expr) = do
|
||||||
[ -- TODO92 docNodeAnnKW lexpr (Just AnnLet) $
|
[ -- TODO92 docNodeAnnKW lexpr (Just AnnLet) $
|
||||||
docSeq
|
docSeq
|
||||||
[ appSep $ letDoc
|
[ appSep $ letDoc
|
||||||
, docSetBaseAndIndent $ docLines $ pure <$> bindDocs
|
, wrapBinds $ docSetBaseAndIndent $ docLines $ pure <$> bindDocs
|
||||||
]
|
]
|
||||||
, docSeq
|
, docSeq
|
||||||
[ appSep $ wrapIn $ docLit $ Text.pack "in "
|
[ appSep $ wrapIn $ docLit $ Text.pack "in "
|
||||||
|
@ -682,12 +686,13 @@ layoutExpr lexpr@(L _ expr) = do
|
||||||
[ -- TODO92 docNodeAnnKW lexpr (Just AnnLet) $
|
[ -- TODO92 docNodeAnnKW lexpr (Just AnnLet) $
|
||||||
docAddBaseY BrIndentRegular $ docPar
|
docAddBaseY BrIndentRegular $ docPar
|
||||||
(letDoc)
|
(letDoc)
|
||||||
(docSetBaseAndIndent $ docLines $ pure <$> bindDocs)
|
(wrapBinds $ docSetBaseAndIndent $ docLines $ pure <$> bindDocs)
|
||||||
, docAddBaseY BrIndentRegular
|
, docAddBaseY BrIndentRegular
|
||||||
$ docPar (inDoc) (docSetBaseY $ expDoc1)
|
$ docPar (inDoc) (docSetBaseY $ expDoc1)
|
||||||
]
|
]
|
||||||
_ -> docSeq
|
_ -> docSeq
|
||||||
[ docForceSingleline $ docSeq [letDoc, docSeparator, inDoc]
|
[ docForceSingleline $ docSeq
|
||||||
|
[letDoc, docSeparator, wrapBinds $ inDoc]
|
||||||
, docSeparator
|
, docSeparator
|
||||||
, expDoc1
|
, expDoc1
|
||||||
]
|
]
|
||||||
|
@ -696,10 +701,11 @@ layoutExpr lexpr@(L _ expr) = do
|
||||||
docHandleComms epAnn $ do
|
docHandleComms epAnn $ do
|
||||||
case stmtCtx of
|
case stmtCtx of
|
||||||
DoExpr _ -> do
|
DoExpr _ -> do
|
||||||
|
let locDo = obtainAnnPos epAnn AnnDo
|
||||||
stmtDocs <- docHandleComms stmtEpAnn $ do
|
stmtDocs <- docHandleComms stmtEpAnn $ do
|
||||||
stmts `forM` docHandleListElemComms (callLayouter layout_stmt)
|
stmts `forM` docHandleListElemComms (callLayouter layout_stmt)
|
||||||
docSetParSpacing $ docAddBaseY BrIndentRegularForce $ docPar
|
docSetParSpacing $ docAddBaseY BrIndentRegularForce $ docPar
|
||||||
(docLit $ Text.pack "do")
|
(docHandleComms locDo $ docLit $ Text.pack "do")
|
||||||
( docSetBaseAndIndent
|
( docSetBaseAndIndent
|
||||||
$ docNonBottomSpacing
|
$ docNonBottomSpacing
|
||||||
$ docLines
|
$ docLines
|
||||||
|
|
|
@ -49,7 +49,8 @@ layoutStmt lstmt@(L _ stmt) = do
|
||||||
LetStmt epAnn binds -> docHandleComms epAnn $ do
|
LetStmt epAnn binds -> docHandleComms epAnn $ do
|
||||||
let isFree = indentPolicy == IndentPolicyFree
|
let isFree = indentPolicy == IndentPolicyFree
|
||||||
let indentFourPlus = indentAmount >= 4
|
let indentFourPlus = indentAmount >= 4
|
||||||
callLayouter layout_localBinds binds >>= \case
|
(wrapBinds, bindrDocsMay) <- callLayouter layout_localBinds binds
|
||||||
|
case bindrDocsMay of
|
||||||
Nothing -> docLit $ Text.pack "let"
|
Nothing -> docLit $ Text.pack "let"
|
||||||
-- i just tested the above, and it is indeed allowed. heh.
|
-- i just tested the above, and it is indeed allowed. heh.
|
||||||
Just (_, []) -> docLit $ Text.pack "let" -- this probably never happens
|
Just (_, []) -> docLit $ Text.pack "let" -- this probably never happens
|
||||||
|
@ -65,13 +66,13 @@ layoutStmt lstmt@(L _ stmt) = do
|
||||||
IndentPolicyMultiple
|
IndentPolicyMultiple
|
||||||
| indentFourPlus -> docSetBaseAndIndent
|
| indentFourPlus -> docSetBaseAndIndent
|
||||||
| otherwise -> docForceSingleline
|
| otherwise -> docForceSingleline
|
||||||
in f $ return bindDoc
|
in wrapBinds $ f $ return bindDoc
|
||||||
]
|
]
|
||||||
, -- let
|
, -- let
|
||||||
-- bind = expr
|
-- bind = expr
|
||||||
docAddBaseY BrIndentRegular $ docPar
|
docAddBaseY BrIndentRegular $ docPar
|
||||||
(docLit $ Text.pack "let")
|
(docLit $ Text.pack "let")
|
||||||
(docSetBaseAndIndent $ return bindDoc)
|
(wrapBinds $ docSetBaseAndIndent $ return bindDoc)
|
||||||
]
|
]
|
||||||
Just (_, bindDocs) -> runFilteredAlternative $ do
|
Just (_, bindDocs) -> runFilteredAlternative $ do
|
||||||
-- let aaa = expra
|
-- let aaa = expra
|
||||||
|
@ -83,7 +84,7 @@ layoutStmt lstmt@(L _ stmt) = do
|
||||||
f = if indentFourPlus
|
f = if indentFourPlus
|
||||||
then docEnsureIndent BrIndentRegular
|
then docEnsureIndent BrIndentRegular
|
||||||
else docSetBaseAndIndent
|
else docSetBaseAndIndent
|
||||||
in f $ docLines $ return <$> bindDocs
|
in wrapBinds $ f $ docLines $ return <$> bindDocs
|
||||||
]
|
]
|
||||||
-- let
|
-- let
|
||||||
-- aaa = expra
|
-- aaa = expra
|
||||||
|
@ -93,7 +94,7 @@ layoutStmt lstmt@(L _ stmt) = do
|
||||||
$ docAddBaseY BrIndentRegular
|
$ docAddBaseY BrIndentRegular
|
||||||
$ docPar
|
$ docPar
|
||||||
(docLit $ Text.pack "let")
|
(docLit $ Text.pack "let")
|
||||||
(docSetBaseAndIndent $ docLines $ return <$> bindDocs)
|
(wrapBinds $ docSetBaseAndIndent $ docLines $ return <$> bindDocs)
|
||||||
RecStmt epAnn (L _ stmts) _ _ _ _ _ ->
|
RecStmt epAnn (L _ stmts) _ _ _ _ _ ->
|
||||||
docHandleComms epAnn $ runFilteredAlternative $ do
|
docHandleComms epAnn $ runFilteredAlternative $ do
|
||||||
-- rec stmt1
|
-- rec stmt1
|
||||||
|
|
|
@ -218,7 +218,8 @@ data Layouters = Layouters
|
||||||
-> BriDocNumbered
|
-> BriDocNumbered
|
||||||
-> Maybe BriDocNumbered
|
-> Maybe BriDocNumbered
|
||||||
-> Either (GHC.LHsExpr GhcPs) [GHC.LGRHS GhcPs (GHC.LHsExpr GhcPs)]
|
-> Either (GHC.LHsExpr GhcPs) [GHC.LGRHS GhcPs (GHC.LHsExpr GhcPs)]
|
||||||
-> ( Maybe
|
-> ( ToBriDocM BriDocNumbered -> ToBriDocM BriDocNumbered
|
||||||
|
, Maybe
|
||||||
( ToBriDocM BriDocNumbered -> ToBriDocM BriDocNumbered
|
( ToBriDocM BriDocNumbered -> ToBriDocM BriDocNumbered
|
||||||
, [BriDocNumbered]
|
, [BriDocNumbered]
|
||||||
)
|
)
|
||||||
|
@ -228,7 +229,8 @@ data Layouters = Layouters
|
||||||
, layout_localBinds
|
, layout_localBinds
|
||||||
:: GHC.HsLocalBindsLR GhcPs GhcPs
|
:: GHC.HsLocalBindsLR GhcPs GhcPs
|
||||||
-> ToBriDocM
|
-> ToBriDocM
|
||||||
( Maybe
|
( ToBriDocM BriDocNumbered -> ToBriDocM BriDocNumbered
|
||||||
|
, Maybe
|
||||||
( ToBriDocM BriDocNumbered -> ToBriDocM BriDocNumbered
|
( ToBriDocM BriDocNumbered -> ToBriDocM BriDocNumbered
|
||||||
, [BriDocNumbered]
|
, [BriDocNumbered]
|
||||||
)
|
)
|
||||||
|
|
|
@ -386,68 +386,68 @@ withAlloc lastFlag f = do
|
||||||
return info
|
return info
|
||||||
|
|
||||||
briDocLineLength :: BriDoc -> Int
|
briDocLineLength :: BriDoc -> Int
|
||||||
briDocLineLength briDoc = flip StateS.evalState False $ rec briDoc
|
briDocLineLength briDoc = flip StateS.evalState False $ go briDoc
|
||||||
-- the state encodes whether a separator was already
|
-- the state encodes whether a separator was already
|
||||||
-- appended at the current position.
|
-- appended at the current position.
|
||||||
where
|
where
|
||||||
rec = \case
|
go = \case
|
||||||
BDEmpty -> return $ 0
|
BDEmpty -> return $ 0
|
||||||
BDLit t -> StateS.put False $> Text.length t
|
BDLit t -> StateS.put False $> Text.length t
|
||||||
BDSeq bds -> sum <$> rec `mapM` bds
|
BDSeq bds -> sum <$> go `mapM` bds
|
||||||
BDCols _ bds -> sum <$> rec `mapM` bds
|
BDCols _ bds -> sum <$> go `mapM` bds
|
||||||
BDSeparator -> StateS.get >>= \b -> StateS.put True $> if b then 0 else 1
|
BDSeparator -> StateS.get >>= \b -> StateS.put True $> if b then 0 else 1
|
||||||
BDAddBaseY _ bd -> rec bd
|
BDAddBaseY _ bd -> go bd
|
||||||
BDBaseYPushCur bd -> rec bd
|
BDBaseYPushCur bd -> go bd
|
||||||
BDIndentLevelPushCur bd -> rec bd
|
BDIndentLevelPushCur bd -> go bd
|
||||||
BDIndentLevelPop bd -> rec bd
|
BDIndentLevelPop bd -> go bd
|
||||||
BDPar _ line _ -> rec line
|
BDPar _ line _ -> go line
|
||||||
BDAlt{} -> error "briDocLineLength BDAlt"
|
BDAlt{} -> error "briDocLineLength BDAlt"
|
||||||
BDForceAlt _ bd -> rec bd
|
BDForceAlt _ bd -> go bd
|
||||||
BDForwardLineMode bd -> rec bd
|
BDForwardLineMode bd -> go bd
|
||||||
BDExternal _ t -> return $ Text.length t
|
BDExternal _ t -> return $ Text.length t
|
||||||
BDPlain t -> return $ Text.length t
|
BDPlain t -> return $ Text.length t
|
||||||
BDQueueComments _ bd -> rec bd
|
BDQueueComments _ bd -> go bd
|
||||||
BDFlushCommentsPrior _ bd -> rec bd
|
BDFlushCommentsPrior _ bd -> go bd
|
||||||
BDFlushCommentsPost _ _ bd -> rec bd
|
BDFlushCommentsPost _ _ bd -> go bd
|
||||||
BDLines ls@(_ : _) -> do
|
BDLines ls@(_ : _) -> do
|
||||||
x <- StateS.get
|
x <- StateS.get
|
||||||
return $ maximum $ ls <&> \l -> StateS.evalState (rec l) x
|
return $ maximum $ ls <&> \l -> StateS.evalState (go l) x
|
||||||
BDEntryDelta _dp bd -> rec bd
|
BDEntryDelta _dp bd -> go bd
|
||||||
BDLines [] -> error "briDocLineLength BDLines []"
|
BDLines [] -> error "briDocLineLength BDLines []"
|
||||||
BDEnsureIndent _ bd -> rec bd
|
BDEnsureIndent _ bd -> go bd
|
||||||
BDDebug _ bd -> rec bd
|
BDDebug _ bd -> go bd
|
||||||
|
|
||||||
briDocIsMultiLine :: BriDoc -> Bool
|
briDocIsMultiLine :: BriDoc -> Bool
|
||||||
briDocIsMultiLine briDoc = rec briDoc
|
briDocIsMultiLine briDoc = go briDoc
|
||||||
where
|
where
|
||||||
rec :: BriDoc -> Bool
|
go :: BriDoc -> Bool
|
||||||
rec = \case
|
go = \case
|
||||||
BDEmpty -> False
|
BDEmpty -> False
|
||||||
BDLit _ -> False
|
BDLit _ -> False
|
||||||
BDSeq bds -> any rec bds
|
BDSeq bds -> any go bds
|
||||||
BDCols _ bds -> any rec bds
|
BDCols _ bds -> any go bds
|
||||||
BDSeparator -> False
|
BDSeparator -> False
|
||||||
BDAddBaseY _ bd -> rec bd
|
BDAddBaseY _ bd -> go bd
|
||||||
BDBaseYPushCur bd -> rec bd
|
BDBaseYPushCur bd -> go bd
|
||||||
BDIndentLevelPushCur bd -> rec bd
|
BDIndentLevelPushCur bd -> go bd
|
||||||
BDIndentLevelPop bd -> rec bd
|
BDIndentLevelPop bd -> go bd
|
||||||
BDPar{} -> True
|
BDPar{} -> True
|
||||||
BDAlt{} -> error "briDocIsMultiLine BDAlt"
|
BDAlt{} -> error "briDocIsMultiLine BDAlt"
|
||||||
BDForceAlt _ bd -> rec bd
|
BDForceAlt _ bd -> go bd
|
||||||
BDForwardLineMode bd -> rec bd
|
BDForwardLineMode bd -> go bd
|
||||||
BDExternal _ t | [_] <- Text.lines t -> False
|
BDExternal _ t | [_] <- Text.lines t -> False
|
||||||
BDExternal{} -> True
|
BDExternal{} -> True
|
||||||
BDPlain t | [_] <- Text.lines t -> False
|
BDPlain t | [_] <- Text.lines t -> False
|
||||||
BDPlain _ -> True
|
BDPlain _ -> True
|
||||||
BDQueueComments _ bd -> rec bd
|
BDQueueComments _ bd -> go bd
|
||||||
BDFlushCommentsPrior _ bd -> rec bd
|
BDFlushCommentsPrior _ bd -> go bd
|
||||||
BDFlushCommentsPost _ _ bd -> rec bd
|
BDFlushCommentsPost _ _ bd -> go bd
|
||||||
BDEntryDelta _dp bd -> rec bd
|
BDEntryDelta _dp bd -> go bd
|
||||||
BDLines (_ : _ : _) -> True
|
BDLines (_ : _ : _) -> True
|
||||||
BDLines [_] -> False
|
BDLines [_] -> False
|
||||||
BDLines [] -> error "briDocIsMultiLine BDLines []"
|
BDLines [] -> error "briDocIsMultiLine BDLines []"
|
||||||
BDEnsureIndent _ bd -> rec bd
|
BDEnsureIndent _ bd -> go bd
|
||||||
BDDebug _ bd -> rec bd
|
BDDebug _ bd -> go bd
|
||||||
|
|
||||||
briDocToColInfo :: Bool -> BriDoc -> StateS.State ColBuildState ColInfo
|
briDocToColInfo :: Bool -> BriDoc -> StateS.State ColBuildState ColInfo
|
||||||
briDocToColInfo lastFlag = \case
|
briDocToColInfo lastFlag = \case
|
||||||
|
|
Loading…
Reference in New Issue