Filter binders with docSetBaseAndIndent.

pull/66/head
Evan Rutledge Borden 2017-11-25 20:50:17 -05:00 committed by Lennart Spitzner
parent de0851f975
commit e9a2de7a85
3 changed files with 63 additions and 48 deletions

View File

@ -532,7 +532,8 @@ func = do
#test let #test let
func = do func = do
let x = 13 let
x = 13
stmt x stmt x
@ -1021,7 +1022,8 @@ layoutPatternBindFinal alignmentToken binderDoc mPatDoc clauseDocs = do
] ]
| not hasComments | not hasComments
, [(guards, body, _bodyRaw)] <- [clauseDocs] , [(guards, body, _bodyRaw)] <- [clauseDocs]
, let guardPart = singleLineGuardsDoc guards , let
guardPart = singleLineGuardsDoc guards
, wherePart <- case mWhereDocs of , wherePart <- case mWhereDocs of
Nothing -> return @[] $ docEmpty Nothing -> return @[] $ docEmpty
Just [w] -> return @[] $ docSeq Just [w] -> return @[] $ docSeq
@ -1042,7 +1044,8 @@ layoutPatternBindFinal alignmentToken binderDoc mPatDoc clauseDocs = do
] ]
++ wherePartMultiLine ++ wherePartMultiLine
| [(guards, body, _bodyRaw)] <- [clauseDocs] | [(guards, body, _bodyRaw)] <- [clauseDocs]
, let guardPart = singleLineGuardsDoc guards , let
guardPart = singleLineGuardsDoc guards
, Data.Maybe.isJust mWhereDocs , Data.Maybe.isJust mWhereDocs
] ]
++ -- two-line solution + where in next line(s) ++ -- two-line solution + where in next line(s)
@ -1054,18 +1057,20 @@ layoutPatternBindFinal alignmentToken binderDoc mPatDoc clauseDocs = do
] ]
++ wherePartMultiLine ++ wherePartMultiLine
| [(guards, body, _bodyRaw)] <- [clauseDocs] | [(guards, body, _bodyRaw)] <- [clauseDocs]
, let guardPart = singleLineGuardsDoc guards , let
guardPart = singleLineGuardsDoc guards
] ]
#test comment-testcase-17 #test comment-testcase-17
{-# LANGUAGE MultiWayIf #-} {-# LANGUAGE MultiWayIf #-}
func = do func = do
let foo = if let
| Constuctoooooooooooooooooooooooooooooooooooor `elem` artics -- TODO foo = if
-> max | Constuctoooooooooooooooooooooooooooooooooooor `elem` artics -- TODO
(defLen - 0.2) -- TODO -> max
(defLen * 0.8) (defLen - 0.2) -- TODO
| otherwise -> max (defLen - 0.05) (defLen * 0.95) -- TODO (defLen * 0.8)
| otherwise -> max (defLen - 0.05) (defLen * 0.95) -- TODO
return True return True
#test issue 49 #test issue 49
@ -1109,7 +1114,7 @@ foo =
## from the input; i cannot really express this yet with the current ## from the input; i cannot really express this yet with the current
## test-suite. ## test-suite.
## #test ayaz ## #test ayaz
## ##
## myManageHook = ## myManageHook =
## composeOne [isFullscreen -?> doFullFloat, isDialog -?> doFloat, transience] ## composeOne [isFullscreen -?> doFullFloat, isDialog -?> doFloat, transience]
## <+> composeAll ## <+> composeAll

View File

@ -539,33 +539,39 @@ layoutExpr lexpr@(L _ expr) = do
-- if "let" is moved horizontally as part of the transformation, as the -- if "let" is moved horizontally as part of the transformation, as the
-- comments before the first let item are moved horizontally with it. -- comments before the first let item are moved horizontally with it.
docSetIndentLevel $ case mBindDocs of docSetIndentLevel $ case mBindDocs of
Just [bindDoc] -> docAlt Just [bindDoc] -> docAltFilter
[ docSeq [ ( indentPolicy /= IndentPolicyLeft
[ appSep $ docLit $ Text.pack "let"
, appSep $ docForceSingleline $ return bindDoc
, appSep $ docLit $ Text.pack "in"
, docForceSingleline $ expDoc1
]
, docLines
[ docSeq
[ appSep $ docLit $ Text.pack "let"
, docSetBaseAndIndent $ return bindDoc
]
, docSeq , docSeq
[ appSep $ docLit $ Text.pack "in " [ appSep $ docLit $ Text.pack "let"
, docSetBaseY $ expDoc1 , appSep $ docForceSingleline $ return bindDoc
, appSep $ docLit $ Text.pack "in"
, docForceSingleline $ expDoc1
] ]
] )
, docLines , ( indentPolicy /= IndentPolicyLeft
[ docAddBaseY BrIndentRegular , docLines
$ docPar [ docSeq
(appSep $ docLit $ Text.pack "let") [ appSep $ docLit $ Text.pack "let"
(docSetBaseAndIndent $ return bindDoc) , docSetBaseAndIndent $ return bindDoc
, docAddBaseY BrIndentRegular ]
$ docPar , docSeq
(appSep $ docLit $ Text.pack "in") [ appSep $ docLit $ Text.pack "in "
(docSetBaseY $ expDoc1) , docSetBaseY $ expDoc1
] ]
]
)
, ( True
, docLines
[ docAddBaseY BrIndentRegular
$ docPar
(appSep $ docLit $ Text.pack "let")
(docSetBaseAndIndent $ return bindDoc)
, docAddBaseY BrIndentRegular
$ docPar
(appSep $ docLit $ Text.pack "in")
(docSetBaseY $ expDoc1)
]
)
] ]
Just bindDocs@(_:_) -> docAltFilter Just bindDocs@(_:_) -> docAltFilter
--either --either

View File

@ -50,19 +50,23 @@ layoutStmt lstmt@(L _ stmt) = do
] ]
LetStmt binds -> layoutLocalBinds binds >>= \case LetStmt binds -> layoutLocalBinds binds >>= \case
Nothing -> docLit $ Text.pack "let" -- i just tested Nothing -> docLit $ Text.pack "let" -- i just tested
-- it, and it is -- it, and it is
-- indeed allowed. -- indeed allowed.
-- heh. -- heh.
Just [] -> docLit $ Text.pack "let" -- this probably never happens Just [] -> docLit $ Text.pack "let" -- this probably never happens
Just [bindDoc] -> docAlt Just [bindDoc] -> docAltFilter
[ docCols [ ( indentPolicy /= IndentPolicyLeft
ColDoLet , docCols
[ appSep $ docLit $ Text.pack "let" ColDoLet
, docSetBaseAndIndent $ return bindDoc [ appSep $ docLit $ Text.pack "let"
] , docSetBaseAndIndent $ return bindDoc
, docAddBaseY BrIndentRegular $ docPar ]
(docLit $ Text.pack "let") )
(docSetBaseAndIndent $ return bindDoc) , ( True
, docAddBaseY BrIndentRegular $ docPar
(docLit $ Text.pack "let")
(docSetBaseAndIndent $ return bindDoc)
)
] ]
Just bindDocs -> docAltFilter Just bindDocs -> docAltFilter
[ ( indentPolicy /= IndentPolicyLeft [ ( indentPolicy /= IndentPolicyLeft