Compare commits

...

10 Commits

14 changed files with 353 additions and 274 deletions

View File

@ -2,13 +2,10 @@
#test monad-comprehension-case-of #test monad-comprehension-case-of
func = func = foooooo
foooooo $ [ case foooooooooooooooooooooooooooooooooooooooooooooooooooooooooooooooo of
$ [ case _ -> True
foooooooooooooooooooooooooooooooooooooooooooooooooooooooooooooooo ]
of
_ -> True
]
#test operatorprefixalignment-even-with-multiline-alignbreak #test operatorprefixalignment-even-with-multiline-alignbreak
func = func =

View File

@ -164,12 +164,14 @@ doop =
#expected #expected
-- brittany { lconfig_fixityBasedAddAlignParens: True } -- brittany { lconfig_fixityBasedAddAlignParens: True }
doop = doop =
( some long invocation == loooooooooongman + (third nested expression) - 4 ( ( some long invocation == loooooooooongman + (third nested expression) - 4
&& {- meow -} 5 - 6 > 7 `mod` loooooooooongwoman && {- meow -} 5 - 6 > 7 `mod` loooooooooongwoman
)
|| ill just invoke a function with these args || ill just invoke a function with these args
|| ( foo || ( foo
&& dooasdoiaosdoi ** oaisdoioasido && ( dooasdoiaosdoi ** oaisdoioasido
<= asduiuaisduiasdu + asdahjsd + ahsjdhjhasd <= asduiuaisduiasdu + asdahjsd + ahsjdhjhasd
)
) )
) )

View File

@ -237,7 +237,8 @@ showPackageDetailedInfo pkginfo =
, entry "Cached" haveTarball alwaysShow dispYesNo , entry "Cached" haveTarball alwaysShow dispYesNo
, if not (hasLib pkginfo) , if not (hasLib pkginfo)
then empty then empty
else text "Modules:" else
text "Modules:"
$+$ nest 4 (vcat (map disp . sort . modules $ pkginfo)) $+$ nest 4 (vcat (map disp . sort . modules $ pkginfo))
] ]
@ -303,25 +304,24 @@ func _ = 3
#test listcomprehension-case-of #test listcomprehension-case-of
parserCompactLocation = parserCompactLocation =
[ try [ try
$ [ ParseRelAbs (Text.Read.read digits) _ _ $ [ ParseRelAbs (Text.Read.read digits) _ _
| digits <- many1 digit | digits <- many1 digit
, rel1 :: Maybe (Either Int (Ratio Int)) <- , rel1 :: Maybe (Either Int (Ratio Int)) <-
optionMaybe optionMaybe
[ case divPart of [ case divPart of
Nothing -> Left $ Text.Read.read digits Nothing -> Left $ Text.Read.read digits
Just ddigits -> Just ddigits ->
Right $ Text.Read.read digits % Text.Read.read ddigits Right $ Text.Read.read digits % Text.Read.read ddigits
| digits <- many1 digit | digits <- many1 digit
, divPart <- optionMaybe (string "/" *> many1 digit) , divPart <- optionMaybe (string "/" *> many1 digit)
] ]
] ]
] ]
#test opapp-specialcasing-1 #test opapp-specialcasing-1
func = func = fooooooooooooooooooooooooooooooooo
fooooooooooooooooooooooooooooooooo $ foooooooooooooooooooooooooooooooo foooooooooooooooooooooooooooooooo
$ foooooooooooooooooooooooooooooooo foooooooooooooooooooooooooooooooo foooooooooooooooooooooooooooooooo
foooooooooooooooooooooooooooooooo
#test opapp-specialcasing-2 #test opapp-specialcasing-2
func = func =
@ -445,8 +445,8 @@ layoutPatternBindFinal alignmentToken binderDoc mPatDoc clauseDocs = do
] ]
++ -- two-line solution + where in next line(s) ++ -- two-line solution + where in next line(s)
[ docLines [ docLines
$ [ docForceSingleline $ [ docForceSingleline $ docSeq
$ docSeq (patPartInline ++ [guardPart, return binderDoc]) (patPartInline ++ [guardPart, return binderDoc])
, docEnsureIndent BrIndentRegular , docEnsureIndent BrIndentRegular
$ docForceSingleline $ docForceSingleline
$ return body $ return body
@ -872,6 +872,7 @@ instance HasDependencies SomeDataModel where
= (SomeOtherDataModelId, SomeOtherOtherDataModelId) = (SomeOtherDataModelId, SomeOtherOtherDataModelId)
#test stupid-do-operator-combination #test stupid-do-operator-combination
#pending
func = func =
do do
@ -895,3 +896,45 @@ 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
#test type-signature comment-after-context
tzejubuVxairoy
:: (VwzuyApikd.VwzuyApikd zub, ZxtbaKospaKwqnuw Defg.Xeqpgko.Xeqpgko m)
-- foo bar
=> CUR.Ozuzcak zub
-> m ()

View File

@ -1176,7 +1176,8 @@ showPackageDetailedInfo pkginfo =
, entry "Cached" haveTarball alwaysShow dispYesNo , entry "Cached" haveTarball alwaysShow dispYesNo
, if not (hasLib pkginfo) , if not (hasLib pkginfo)
then empty then empty
else text "Modules:" else
text "Modules:"
$+$ nest 4 (vcat (map disp . sort . modules $ pkginfo)) $+$ nest 4 (vcat (map disp . sort . modules $ pkginfo))
] ]
@ -1249,18 +1250,18 @@ func _ = 3
#test listcomprehension-case-of #test listcomprehension-case-of
parserCompactLocation = parserCompactLocation =
[ try [ try
$ [ ParseRelAbs (Text.Read.read digits) _ _ $ [ ParseRelAbs (Text.Read.read digits) _ _
| digits <- many1 digit | digits <- many1 digit
, rel1 :: Maybe (Either Int (Ratio Int)) <- , rel1 :: Maybe (Either Int (Ratio Int)) <-
optionMaybe optionMaybe
[ case divPart of [ case divPart of
Nothing -> Left $ Text.Read.read digits Nothing -> Left $ Text.Read.read digits
Just ddigits -> Just ddigits ->
Right $ Text.Read.read digits % Text.Read.read ddigits Right $ Text.Read.read digits % Text.Read.read ddigits
| digits <- many1 digit | digits <- many1 digit
, divPart <- optionMaybe (string "/" *> many1 digit) , divPart <- optionMaybe (string "/" *> many1 digit)
] ]
] ]
] ]
#test opapp-specialcasing-1 #test opapp-specialcasing-1
@ -1370,8 +1371,8 @@ layoutPatternBindFinal alignmentToken binderDoc mPatDoc clauseDocs = do
] ]
++ -- two-line solution + where in next line(s) ++ -- two-line solution + where in next line(s)
[ docLines [ docLines
$ [ docForceSingleline $ [ docForceSingleline $ docSeq
$ docSeq (patPartInline ++ [guardPart, return binderDoc]) (patPartInline ++ [guardPart, return binderDoc])
, docEnsureIndent BrIndentRegular , docEnsureIndent BrIndentRegular
$ docForceSingleline $ docForceSingleline
$ return body $ return body

View File

@ -223,7 +223,9 @@ hardcodedFixity allowUnqualify = \case
"!" -> Just $ Fixity NoSourceText 9 InfixL "!" -> Just $ Fixity NoSourceText 9 InfixL
"//" -> Just $ Fixity NoSourceText 9 InfixL "//" -> Just $ Fixity NoSourceText 9 InfixL
"<>" -> Just $ Fixity NoSourceText 6 InfixR "<>" -> Just $ Fixity NoSourceText 6 InfixR
"<+>" -> Just $ Fixity NoSourceText 5 InfixR
"<$" -> Just $ Fixity NoSourceText 4 InfixL "<$" -> Just $ Fixity NoSourceText 4 InfixL
"$>" -> Just $ Fixity NoSourceText 4 InfixL
"<$>" -> Just $ Fixity NoSourceText 4 InfixL "<$>" -> Just $ Fixity NoSourceText 4 InfixL
"<&>" -> Just $ Fixity NoSourceText 1 InfixL "<&>" -> Just $ Fixity NoSourceText 1 InfixL
"&" -> Just $ Fixity NoSourceText 1 InfixL "&" -> Just $ Fixity NoSourceText 1 InfixL
@ -245,6 +247,7 @@ hardcodedFixity allowUnqualify = \case
"`shiftR`" -> Just $ Fixity NoSourceText 8 InfixL "`shiftR`" -> Just $ Fixity NoSourceText 8 InfixL
"`rotateL`" -> Just $ Fixity NoSourceText 8 InfixL "`rotateL`" -> Just $ Fixity NoSourceText 8 InfixL
"`rotateR`" -> Just $ Fixity NoSourceText 8 InfixL "`rotateR`" -> Just $ Fixity NoSourceText 8 InfixL
"+#" -> Just $ Fixity NoSourceText 6 InfixL
".^." -> Just $ Fixity NoSourceText 6 InfixL ".^." -> Just $ Fixity NoSourceText 6 InfixL
".>>." -> Just $ Fixity NoSourceText 8 InfixL ".>>." -> Just $ Fixity NoSourceText 8 InfixL
".<<." -> Just $ Fixity NoSourceText 8 InfixL ".<<." -> Just $ Fixity NoSourceText 8 InfixL
@ -265,6 +268,8 @@ hardcodedFixity allowUnqualify = \case
".>" -> Just $ Fixity NoSourceText 9 InfixL ".>" -> Just $ Fixity NoSourceText 9 InfixL
":?" -> Just $ Fixity NoSourceText 7 InfixN ":?" -> Just $ Fixity NoSourceText 7 InfixN
":-" -> Just $ Fixity NoSourceText 9 InfixR ":-" -> Just $ Fixity NoSourceText 9 InfixR
".:" -> Just $ Fixity NoSourceText 9 InfixR
".=" -> Just $ Fixity NoSourceText 8 InfixR
str -> case (Safe.headMay str, Safe.lastMay str) of str -> case (Safe.headMay str, Safe.lastMay str) of
(Just '\'', _) -> hardcodedFixity False (drop 1 str) (Just '\'', _) -> hardcodedFixity False (drop 1 str)

View File

@ -242,6 +242,19 @@ hasCommentsBetween ast left right = do
) )
ast ast
startsWithComments :: EpAnn a -> Bool
startsWithComments = \case
EpAnnNotUsed -> False
EpAnn (GHC.Anchor srcSpan _) _ comms -> case comms of
EpaComments cs -> anyCheck cs
EpaCommentsBalanced comms1 comms2 -> anyCheck comms1 || anyCheck comms2
where
anyCheck cs =
any
(\(L _ (GHC.EpaComment _ commSpan)) ->
GHC.realSrcSpanStart srcSpan == GHC.realSrcSpanStart commSpan
)
cs
-- mAnn <- astAnn ast -- mAnn <- astAnn ast
@ -523,6 +536,10 @@ instance DocHandleComms (EpAnn a) (ToBriDocM BriDocNumbered) where
) )
EpAnnNotUsed -> bdm EpAnnNotUsed -> bdm
instance DocHandleComms (Maybe (EpAnn a)) (ToBriDocM BriDocNumbered) where
docHandleComms Nothing = id
docHandleComms (Just epAnn) = docHandleComms epAnn
instance DocHandleComms (GHC.RealSrcSpan) (ToBriDocM BriDocNumbered) where instance DocHandleComms (GHC.RealSrcSpan) (ToBriDocM BriDocNumbered) where
docHandleComms loc = docHandleComms (GHC.realSrcSpanStart loc) docHandleComms loc = docHandleComms (GHC.realSrcSpanStart loc)

View File

@ -289,7 +289,7 @@ layoutBriDocM = \case
PlannedSameline{} -> False PlannedSameline{} -> False
PlannedNewline{} -> True PlannedNewline{} -> True
PlannedDelta{} -> True PlannedDelta{} -> True
-- traceShow (ExactPrint.pos2delta p1 p2) $ pure () -- traceShow (m, ExactPrint.pos2delta p1 p2) $ pure ()
case ExactPrint.pos2delta p1 p2 of case ExactPrint.pos2delta p1 p2 of
SameLine{} -> pure () SameLine{} -> pure ()
DifferentLine n _ | newlinePlanned -> layoutWriteNewlines n DifferentLine n _ | newlinePlanned -> layoutWriteNewlines n
@ -326,10 +326,14 @@ printComments comms = do
Anchor span UnchangedAnchor -> do Anchor span UnchangedAnchor -> do
let dp = ExactPrint.ss2deltaEnd prior span let dp = ExactPrint.ss2deltaEnd prior span
layoutWriteComment True isBlock dp 1 (Text.pack s) layoutWriteComment True isBlock dp 1 (Text.pack s)
layoutUpdateMarker $ realSrcSpanEnd span if isBlock
then layoutSetMarker $ Just $ realSrcSpanEnd span
else layoutUpdateMarker $ realSrcSpanEnd span
Anchor span (MovedAnchor dp) -> do Anchor span (MovedAnchor dp) -> do
layoutWriteComment False isBlock dp 1 (Text.pack s) layoutWriteComment False isBlock dp 1 (Text.pack s)
layoutUpdateMarker $ realSrcSpanEnd span if isBlock
then layoutSetMarker $ Just $ realSrcSpanEnd span
else layoutUpdateMarker $ realSrcSpanEnd span
comms `forM_` \(L anch (EpaComment tok prior)) -> case tok of comms `forM_` \(L anch (EpaComment tok prior)) -> case tok of
EpaDocCommentNext s -> addComment False s anch prior EpaDocCommentNext s -> addComment False s anch prior
EpaDocCommentPrev s -> addComment False s anch prior EpaDocCommentPrev s -> addComment False s anch prior

View File

@ -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,28 +208,28 @@ 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)
-> ToBriDocM -> ToBriDocM
( ToBriDocM BriDocNumbered -> ToBriDocM BriDocNumbered ( Maybe (EpAnn GrhsAnn)
, [BriDocNumbered] , [BriDocNumbered]
, BriDocNumbered , BriDocNumbered
) )
@ -238,7 +239,7 @@ layoutGrhs (L _ (GRHS epAnn guards body)) = do
[] -> pure [] [] -> pure []
_ -> docFlushCommsPost False posArrow $ callLayouter layout_stmt `mapM` guards _ -> docFlushCommsPost False posArrow $ callLayouter layout_stmt `mapM` guards
bodyDoc <- callLayouter layout_expr body bodyDoc <- callLayouter layout_expr body
return (docHandleComms epAnn, guardDocs, bodyDoc) return (Just epAnn, guardDocs, bodyDoc)
layoutPatternBind layoutPatternBind
:: Maybe Text :: Maybe Text
@ -259,7 +260,7 @@ layoutPatternBind funId binderDoc lmatch@(L _ match) = do
let t' = fixPatternBindIdentifier match t let t' = fixPatternBindIdentifier match t
docLit t' docLit t'
_ -> pure Nothing _ -> pure Nothing
patDoc <- docHandleComms lmatch $ case (mIdDoc, patDocs) of patDoc <- docHandleComms lmatch $ case (mIdDoc, patDocs) of -- TODO92 we use lmatch twice here!
(Just idDoc, p1 : p2 : pr) | isInfix -> if null pr (Just idDoc, p1 : p2 : pr) | isInfix -> if null pr
then docCols then docCols
ColPatternsFuncInfix ColPatternsFuncInfix
@ -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,13 @@ 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 , docEnsureIndent whereIndent
docEnsureIndent whereIndent
$ docLines $ docLines
[ docLit $ Text.pack "where" [ wrapBinds $ wrapWhere $ docLit $ Text.pack "where"
, docEnsureIndent whereIndent , docEnsureIndent whereIndent
$ docSetIndentLevel $ docSetIndentLevel
$ docNonBottomSpacing $ docNonBottomSpacing
@ -370,10 +371,9 @@ layoutPatternBindFinal alignmentToken binderDoc mPatDoc clauses mWhereDocs hasCo
] ]
Just (wrapWhere, ws) -> Just (wrapWhere, ws) ->
fmap (pure . pure) fmap (pure . pure)
-- $ 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 +397,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
@ -407,17 +407,24 @@ layoutPatternBindFinal alignmentToken binderDoc mPatDoc clauses mWhereDocs hasCo
clauseDocs <- case clauses of clauseDocs <- case clauses of
Left expr -> do Left expr -> do
e <- callLayouter layout_expr expr e <- callLayouter layout_expr expr
pure [(id, [], e)] pure [(Nothing, [], e)]
Right grhss -> layoutGrhs `mapM` grhss Right grhss -> layoutGrhs `mapM` grhss
let multipleClauses = not $ null clauseDocs
runFilteredAlternative $ do runFilteredAlternative $ do
case clauseDocs of case clauseDocs of
[(wrapClause, guards, body)] -> do [(grhsEpAnn, guards, body)] -> do
let guardPart = wrapClause $ singleLineGuardsDoc guards let grhsHasComms = hasAnyCommentsBelow grhsEpAnn
let guardPart = docHandleComms grhsEpAnn $ singleLineGuardsDoc guards
-- func x | null x = x + a + 2 where a = 1
-- or
-- func x | null x = x + a + b where
-- a = 1
-- b = 2
forM_ wherePart $ \wherePart' -> forM_ wherePart $ \wherePart' ->
-- one-line solution addAlternativeCond (not hasComments && not grhsHasComms) $ docCols
addAlternativeCond (not hasComments) $ docCols
(ColBindingLine alignmentToken) (ColBindingLine alignmentToken)
[ docSeq (patPartInline ++ [guardPart]) [ docSeq (patPartInline ++ [guardPart])
, docSeq , docSeq
@ -426,14 +433,29 @@ layoutPatternBindFinal alignmentToken binderDoc mPatDoc clauses mWhereDocs hasCo
, wherePart' , wherePart'
] ]
] ]
-- one-line solution + where in next line(s)
addAlternativeCond (Data.Maybe.isJust mWhereDocs) -- any below have this pattern:
-- …
-- where a = 1
-- or
-- …
-- where
-- a = 1
-- b = 1
-- func x | null x = do
-- stmt x
addAlternativeCond (not $ maybe False startsWithComments grhsEpAnn)
$ docLines $ docLines
$ [ docCols $ [ docCols
(ColBindingLine alignmentToken) (ColBindingLine alignmentToken)
[ docSeq (patPartInline ++ [guardPart]) [ docSeq (patPartInline ++ [guardPart])
, docSeq , docSeq
[ appSep $ return binderDoc [ appSep $ return binderDoc
-- TODO I did it this way just to reduce test breakage,
-- but arguably we should modify tests instead.
-- I _think_ we really want to drop this alternative
-- when grhsHasComms
, docForceParSpacing , docForceParSpacing
$ docAddBaseY BrIndentRegular $ docAddBaseY BrIndentRegular
$ return body $ return body
@ -441,7 +463,8 @@ layoutPatternBindFinal alignmentToken binderDoc mPatDoc clauses mWhereDocs hasCo
] ]
] ]
++ wherePartMultiLine ++ wherePartMultiLine
-- two-line solution + where in next line(s) -- func x | null x =
-- x + a + 2
addAlternative addAlternative
$ docLines $ docLines
$ [ docForceSingleline $ [ docForceSingleline
@ -451,8 +474,10 @@ layoutPatternBindFinal alignmentToken binderDoc mPatDoc clauses mWhereDocs hasCo
$ return body $ return body
] ]
++ wherePartMultiLine ++ wherePartMultiLine
-- pattern and exactly one clause in single line, body as par; -- func x | null x
-- where in following lines -- = do
-- stmt x
-- log "abc"
addAlternative addAlternative
$ docLines $ docLines
$ [ docCols $ [ docCols
@ -471,7 +496,10 @@ layoutPatternBindFinal alignmentToken binderDoc mPatDoc clauses mWhereDocs hasCo
-- , docAddBaseY BrIndentRegular $ return body -- , docAddBaseY BrIndentRegular $ return body
-- ] -- ]
++ wherePartMultiLine ++ wherePartMultiLine
-- pattern and exactly one clause in single line, body in new line. -- func x | null x =
-- do
-- stmt1
-- stmt2 x
addAlternative addAlternative
$ docLines $ docLines
$ [ docSeq (patPartInline ++ [guardPart, return binderDoc]) $ [ docSeq (patPartInline ++ [guardPart, return binderDoc])
@ -485,19 +513,18 @@ layoutPatternBindFinal alignmentToken binderDoc mPatDoc clauses mWhereDocs hasCo
_ -> return () -- no alternatives exclusively when `length clauseDocs /= 1` _ -> return () -- no alternatives exclusively when `length clauseDocs /= 1`
case mPatDoc of case mPatDoc of
Nothing -> return () Just patDoc | multipleClauses, indentPolicy == IndentPolicyFree ->
Just patDoc ->
-- multiple clauses added in-paragraph, each in a single line -- multiple clauses added in-paragraph, each in a single line
-- example: foo | bar = baz -- func x | null x = baz
-- | lll = asd -- | otherwise = asd
addAlternativeCond (indentPolicy == IndentPolicyFree) addAlternative
$ docLines $ docLines
$ [ docSeq $ [ docSeq
[ appSep $ docForceSingleline $ return patDoc [ appSep $ docForceSingleline $ return patDoc
, docSetBaseY , docSetBaseY
$ docLines $ docLines
$ clauseDocs $ clauseDocs
<&> \(wrapClause, guardDocs, bodyDoc) -> wrapClause $ do -- TODO92 <&> \(epAnn, guardDocs, bodyDoc) -> docHandleComms epAnn $ do
let guardPart = singleLineGuardsDoc guardDocs let guardPart = singleLineGuardsDoc guardDocs
-- the docForceSingleline might seems superflous, but it -- the docForceSingleline might seems superflous, but it
-- helps the alternative resolving impl. -- helps the alternative resolving impl.
@ -515,7 +542,10 @@ layoutPatternBindFinal alignmentToken binderDoc mPatDoc clauses mWhereDocs hasCo
] ]
] ]
++ wherePartMultiLine ++ wherePartMultiLine
-- multiple clauses, each in a separate, single line _ -> return ()
-- func x y
-- | null x, null y = a + b
-- | otherwise = a - b
addAlternative addAlternative
$ docLines $ docLines
$ [ docAddBaseY BrIndentRegular $ [ docAddBaseY BrIndentRegular
@ -523,7 +553,7 @@ layoutPatternBindFinal alignmentToken binderDoc mPatDoc clauses mWhereDocs hasCo
$ docLines $ docLines
$ map docSetBaseY $ map docSetBaseY
$ clauseDocs $ clauseDocs
<&> \(wrapClause, guardDocs, bodyDoc) -> wrapClause $ do -- TODO92 <&> \(epAnn, guardDocs, bodyDoc) -> docHandleComms epAnn $ do
let guardPart = singleLineGuardsDoc guardDocs let guardPart = singleLineGuardsDoc guardDocs
-- the docForceSingleline might seems superflous, but it -- the docForceSingleline might seems superflous, but it
-- helps the alternative resolving impl. -- helps the alternative resolving impl.
@ -541,8 +571,12 @@ layoutPatternBindFinal alignmentToken binderDoc mPatDoc clauses mWhereDocs hasCo
] ]
] ]
++ wherePartMultiLine ++ wherePartMultiLine
-- multiple clauses, each with the guard(s) in a single line, body -- func x y
-- as a paragraph -- | null x, null y = do
-- stmt x
-- stmt y
-- | otherwise -> do
-- abort
addAlternativeCond (not hasComments) addAlternativeCond (not hasComments)
$ docLines $ docLines
$ [ docAddBaseY BrIndentRegular $ [ docAddBaseY BrIndentRegular
@ -550,34 +584,26 @@ layoutPatternBindFinal alignmentToken binderDoc mPatDoc clauses mWhereDocs hasCo
$ docLines $ docLines
$ map docSetBaseY $ map docSetBaseY
$ clauseDocs $ clauseDocs
<&> \(wrapClause, guardDocs, bodyDoc) -> -- TODO92 <&> \(grhsEpAnn, guardDocs, bodyDoc) -> -- TODO92
wrapClause $ docSeq docHandleComms grhsEpAnn $ docSeq
$ (case guardDocs of [ singleLineGuardsDoc guardDocs
[] -> [] , docCols
[g] -> ColOpPrefix
[ docForceSingleline $ docSeq [ appSep $ return binderDoc
[appSep $ docLit $ Text.pack "|", return g] , docAddBaseY BrIndentRegular
] $ docForceParSpacing
gs -> $ return bodyDoc
[ docForceSingleline ]
$ docSeq ]
$ [appSep $ docLit $ Text.pack "|"]
++ List.intersperse docCommaSep (return <$> gs)
]
)
++ [ docSeparator
, docCols
ColOpPrefix
[ appSep $ return binderDoc
, docAddBaseY BrIndentRegular
$ docForceParSpacing
$ return bodyDoc
]
]
] ]
++ wherePartMultiLine ++ wherePartMultiLine
-- multiple clauses, each with the guard(s) in a single line, body -- func x y
-- in a new line as a paragraph -- | null x, null y
-- = do
-- stmt x
-- stmt y
-- | otherwise
-- = abort
addAlternative addAlternative
$ docLines $ docLines
$ [ docAddBaseY BrIndentRegular $ [ docAddBaseY BrIndentRegular
@ -585,31 +611,26 @@ layoutPatternBindFinal alignmentToken binderDoc mPatDoc clauses mWhereDocs hasCo
$ docLines $ docLines
$ map docSetBaseY $ map docSetBaseY
$ clauseDocs $ clauseDocs
>>= \(wrapClause, guardDocs, bodyDoc) -> -- TODO92 >>= \(grhsEpAnn, guardDocs, bodyDoc) -> -- TODO92
(case guardDocs of [ docHandleComms grhsEpAnn $ singleLineGuardsDoc guardDocs
[] -> [wrapClause docEmpty] , docCols
[g] -> ColOpPrefix
[ wrapClause $ docForceSingleline [ appSep $ return binderDoc
$ docSeq [appSep $ docLit $ Text.pack "|", return g] , docAddBaseY BrIndentRegular
] $ docForceParSpacing
gs -> $ return bodyDoc
[ wrapClause $ docForceSingleline ]
$ docSeq ]
$ [appSep $ docLit $ Text.pack "|"]
++ List.intersperse docCommaSep (return <$> gs)
]
)
++ [ docCols
ColOpPrefix
[ appSep $ return binderDoc
, docAddBaseY BrIndentRegular
$ docForceParSpacing
$ return bodyDoc
]
]
] ]
++ wherePartMultiLine ++ wherePartMultiLine
-- conservative approach: everything starts on the left. -- func x y
-- | null x
-- , null y
-- = do
-- stmt x
-- stmt y
-- | otherwise
-- = abort
addAlternative addAlternative
$ docLines $ docLines
$ [ docAddBaseY BrIndentRegular $ [ docAddBaseY BrIndentRegular
@ -617,14 +638,18 @@ layoutPatternBindFinal alignmentToken binderDoc mPatDoc clauses mWhereDocs hasCo
$ docLines $ docLines
$ map docSetBaseY $ map docSetBaseY
$ clauseDocs $ clauseDocs
>>= \(wrapClause, guardDocs, bodyDoc) -> -- TODO92 >>= \(grhsEpAnn, guardDocs, bodyDoc) -> -- TODO92
(case guardDocs of (case guardDocs of
[] -> [wrapClause docEmpty] [] -> [docHandleComms grhsEpAnn docEmpty]
[g] -> [g] ->
[ wrapClause $ docSeq [appSep $ docLit $ Text.pack "|", return g] [ docHandleComms grhsEpAnn
$ docSeq [appSep
$ docLit $ Text.pack "|", return g]
] ]
(g1 : gr) -> (g1 : gr) ->
( (wrapClause $ docSeq [appSep $ docLit $ Text.pack "|", return g1]) ( ( docHandleComms grhsEpAnn
$ docSeq [appSep $ docLit $ Text.pack "|", return g1]
)
: (gr <&> \g -> : (gr <&> \g ->
docSeq [appSep $ docLit $ Text.pack ",", return g] docSeq [appSep $ docLit $ Text.pack ",", return g]
) )

View File

@ -220,7 +220,7 @@ layoutExpr lexpr@(L _ expr) = do
] ]
, docPar e (docSeq [docLit $ Text.pack "@", t]) , docPar e (docSeq [docLit $ Text.pack "@", t])
] ]
OpApp _topEpAnn _expLeft@(L _ OpApp{}) _expOp _expRight -> do OpApp _topEpAnn _expLeft _expOp _expRight -> do
-- let -- let
-- allowPar = case (expOp, expRight) of -- allowPar = case (expOp, expRight) of
-- (L _ (HsVar _ (L _ (Unqual occname))), _) -- (L _ (HsVar _ (L _ (Unqual occname))), _)
@ -235,60 +235,6 @@ layoutExpr lexpr@(L _ expr) = do
treeAndHasComms <- treeAndHasComms <-
layout_gatherOpTreeE layouters False False id Nothing Nothing [] lexpr layout_gatherOpTreeE layouters False False id Nothing Nothing [] lexpr
layout_opTree layouters treeAndHasComms layout_opTree layouters treeAndHasComms
OpApp epAnn expLeft expOp expRight -> docHandleComms epAnn $ do
expDocLeft <- shareDoc $ layoutExpr expLeft
expDocOp <- shareDoc $ layoutExpr expOp
expDocRight <- shareDoc $ layoutExpr expRight
let
allowPar = case (expOp, expRight) of
(L _ (HsVar _ (L _ (Unqual occname))), _)
| occNameString occname == "$" -> True
(_, L _ (HsApp _ _ (L _ HsVar{}))) -> False
_ -> True
let leftIsDoBlock = case expLeft of
L _ HsDo{} -> True
_ -> False
runFilteredAlternative $ do
-- one-line
addAlternative $ docSeq
[ appSep $ docForceSingleline expDocLeft
, appSep $ docForceSingleline expDocOp
, docForceSingleline expDocRight
]
-- -- line + freely indented block for right expression
-- addAlternative
-- $ docSeq
-- [ appSep $ docForceSingleline expDocLeft
-- , appSep $ docForceSingleline expDocOp
-- , docSetBaseY $ docAddBaseY BrIndentRegular expDocRight
-- ]
-- two-line
addAlternative $ do
let expDocOpAndRight = docForceSingleline $ docCols
ColOpPrefix
[appSep $ expDocOp, docSetBaseY expDocRight]
if leftIsDoBlock
then docLines [expDocLeft, expDocOpAndRight]
else docAddBaseY BrIndentRegular
$ docPar expDocLeft expDocOpAndRight
-- TODO: in both cases, we don't force expDocLeft to be
-- single-line, which has certain.. interesting consequences.
-- At least, the "two-line" label is not entirely
-- accurate.
-- one-line + par
addAlternativeCond allowPar $ docSeq
[ appSep $ docForceSingleline expDocLeft
, appSep $ docForceSingleline expDocOp
, docForceParSpacing expDocRight
]
-- more lines
addAlternative $ do
let expDocOpAndRight =
docCols ColOpPrefix [appSep expDocOp, docSetBaseY expDocRight]
if leftIsDoBlock
then docLines [expDocLeft, expDocOpAndRight]
else docAddBaseY BrIndentRegular
$ docPar expDocLeft expDocOpAndRight
NegApp _ op _ -> do NegApp _ op _ -> do
opDoc <- shareDoc $ layoutExpr op opDoc <- shareDoc $ layoutExpr op
docSeq [docLit $ Text.pack "-", opDoc] docSeq [docLit $ Text.pack "-", opDoc]
@ -585,7 +531,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 +539,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 +560,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 +568,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 +606,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
@ -668,10 +618,9 @@ layoutExpr lexpr@(L _ expr) = do
IndentPolicyLeft -> docLines noHangingBinds IndentPolicyLeft -> docLines noHangingBinds
IndentPolicyMultiple -> docLines noHangingBinds IndentPolicyMultiple -> docLines noHangingBinds
IndentPolicyFree -> docLines IndentPolicyFree -> docLines
[ -- 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 "
@ -679,15 +628,15 @@ layoutExpr lexpr@(L _ expr) = do
] ]
] ]
addAlternative $ docLines addAlternative $ docLines
[ -- 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 +645,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

View File

@ -96,7 +96,9 @@ gatherOpTreeT hasParen hasComms commWrap locOpen locClose opExprList = \case
commWrap commWrap
locOpen locOpen
locClose locClose
((docLit $ printRdrNameWithAnns op1, callLayouter layout_type r1) : opExprList) ( (docLit $ printRdrNameWithAnns op1, callLayouter layout_type r1)
: opExprList
)
l1 l1
(L _ (HsParTy epAnn inner)) -> do (L _ (HsParTy epAnn inner)) -> do
let AnnParen _ spanOpen spanClose = anns epAnn let AnnParen _ spanOpen spanClose = anns epAnn
@ -220,7 +222,8 @@ layoutOpTree allowSinglelinePar = \case
-> ToBriDocM BriDocNumbered -> ToBriDocM BriDocNumbered
coreAlternative hasParen locO locC fixity docL sharedOps sharedOpsFlat lastWrap coreAlternative hasParen locO locC fixity docL sharedOps sharedOpsFlat lastWrap
= do = do
let wrapParenIfSl x inner = if x then wrapParenSl inner else inner indentPolicy <- askLayoutConf _lconfig_indentPolicy
let wrapParenIfSl x inner = if x then wrapParenSl inner else docSetParSpacing inner
wrapParenSl inner = docAlt wrapParenSl inner = docAlt
[ docSeq [ docSeq
[ docLit $ Text.pack "(" [ docLit $ Text.pack "("
@ -251,13 +254,18 @@ layoutOpTree allowSinglelinePar = \case
Nothing -> False Nothing -> False
Just (Fixity _ prec _) -> prec > 0 Just (Fixity _ prec _) -> prec > 0
let isSingleOp = length sharedOps == 1 && length sharedOpsFlat == 1
runFilteredAlternative $ do runFilteredAlternative $ do
-- > one + two + three -- > one + two + three
-- or -- or
-- > one + two + case x of -- > one + two + case x of
-- > _ -> three -- > _ -> three
addAlternativeCond allowSinglelinePar $ wrapParenIfSl hasParen $ docSeq addAlternativeCond allowSinglelinePar
([docForceSingleline docL] ++ case splitFirstLast sharedOps of $ wrapParenIfSl hasParen
$ docSetParSpacing
$ docSeq
([docForceSingleline docL] ++ case splitFirstLast sharedOpsFlat of
FirstLastEmpty -> [] FirstLastEmpty -> []
FirstLastSingleton (od, ed) -> FirstLastSingleton (od, ed) ->
[docSeparator, docForceSingleline od, docSeparator, lastWrap ed] [docSeparator, docForceSingleline od, docSeparator, lastWrap ed]
@ -284,11 +292,29 @@ layoutOpTree allowSinglelinePar = \case
) )
-- this case rather leads to some unfortunate layouting than to anything -- this case rather leads to some unfortunate layouting than to anything
-- useful; disabling for now. (it interfers with cols stuff.) -- useful; disabling for now. (it interfers with cols stuff.)
addAlternativeCond (not hasParen) $ docPar -- one
-- + two
-- + three
addAlternativeCond (not hasParen && not isSingleOp) $ docPar
(docHandleComms locO $ docForceSingleline $ docL) (docHandleComms locO $ docForceSingleline $ docL)
(docFlushCommsPost False locC $ docLines $ sharedOps <&> \(od, ed) -> (docFlushCommsPost False locC $ docLines $ sharedOps <&> \(od, ed) ->
docCols ColOpPrefix [appSep od, docForceSingleline ed] docCols ColOpPrefix [appSep od, docForceSingleline ed]
) )
let singlelineUnlessFree = case indentPolicy of
IndentPolicyLeft -> docForceSingleline
IndentPolicyMultiple -> docForceSingleline
IndentPolicyFree -> id
let curIsPrec0 = case fixity of
Nothing -> False
Just (Fixity _ prec _) -> prec == 0
case sharedOps of
[(od, ed)] | curIsPrec0 ->
addAlternativeCond (not hasParen && isSingleOp)
$ docSetParSpacing
$ docPar
(docHandleComms locO $ docForceSingleline $ docL)
(docSeq [od, docSeparator, singlelineUnlessFree ed])
_ -> pure ()
-- > ( one -- > ( one
-- > + two -- > + two
-- > + three -- > + three
@ -297,7 +323,7 @@ layoutOpTree allowSinglelinePar = \case
$ docForceZeroAdd $ docForceZeroAdd
$ wrapParenMl $ wrapParenMl
(docSetBaseY docL) (docSetBaseY docL)
(sharedOpsFlat <&> \(od, ed) -> (sharedOps <&> \(od, ed) ->
docCols ColOpPrefix [appSep od, docSetBaseY ed] docCols ColOpPrefix [appSep od, docSetBaseY ed]
) )
-- > one -- > one
@ -308,6 +334,6 @@ layoutOpTree allowSinglelinePar = \case
hasParen hasParen
-- ((if not hasParen then docAddBaseY BrIndentRegular else id) docL) -- ((if not hasParen then docAddBaseY BrIndentRegular else id) docL)
(if hasParen then docSetBaseY docL else docL) (if hasParen then docSetBaseY docL else docL)
(sharedOpsFlat <&> \(od, ed) -> ((if hasParen then sharedOps else sharedOpsFlat) <&> \(od, ed) ->
docCols ColOpPrefix [appSep od, docSetBaseY ed] docCols ColOpPrefix [appSep od, docSetBaseY ed]
) )

View File

@ -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

View File

@ -37,12 +37,18 @@ splitArrowType ltype@(L _ typ) = case typ of
splitHsForallTypeFromBinders (getBinders hsf) typ1 splitHsForallTypeFromBinders (getBinders hsf) typ1
HsQualTy NoExtField ctxMay typ1 -> do HsQualTy NoExtField ctxMay typ1 -> do
(innerHead, innerBody) <- splitArrowType typ1 (innerHead, innerBody) <- splitArrowType typ1
(wrapCtx, cntxtDocs) <- case ctxMay of
Nothing -> pure (id, [])
Just (L (SrcSpanAnn epAnn _) ctxs) -> do
let wrap = case epAnn of
EpAnn _ (AnnContext (Just (_, loc)) _ _) _ ->
docFlushCommsPost False (Just $ epaLocationRealSrcSpanStart loc)
. docHandleComms epAnn
_ -> docHandleComms epAnn
x <- ctxs `forM` (shareDoc . layoutType)
pure (wrap, x)
pure pure
$ ( do $ ( wrapCtx $ case cntxtDocs of
cntxtDocs <- case ctxMay of
Nothing -> pure []
Just (L _ ctxs) -> ctxs `forM` (shareDoc . layoutType)
case cntxtDocs of
[] -> docLit $ Text.pack "()" [] -> docLit $ Text.pack "()"
[x] -> x [x] -> x
docs -> docAlt docs -> docAlt

View File

@ -202,7 +202,7 @@ data Layouters = Layouters
, layout_grhs , layout_grhs
:: GHC.LGRHS GhcPs (GHC.LHsExpr GhcPs) :: GHC.LGRHS GhcPs (GHC.LHsExpr GhcPs)
-> ToBriDocM -> ToBriDocM
( ToBriDocM BriDocNumbered -> ToBriDocM BriDocNumbered ( Maybe (GHC.EpAnn GHC.GrhsAnn)
, [BriDocNumbered] , [BriDocNumbered]
, BriDocNumbered , BriDocNumbered
) )
@ -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]
) )

View File

@ -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