Compare commits
No commits in common. "628ab81bc944f0cb0dca90049c9b928389202bd8" and "7bbbea728d5744b9a5341f235ac1925fc3c4bcce" have entirely different histories.
628ab81bc9
...
7bbbea728d
|
@ -21,10 +21,3 @@ foo =
|
|||
, 4
|
||||
, 5
|
||||
]
|
||||
|
||||
#test set-base-y for multiple line elements
|
||||
foo =
|
||||
[ aaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaa
|
||||
, bbbbbbbbbbbbbbbbbb
|
||||
$ cccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccc
|
||||
]
|
||||
|
|
|
@ -241,9 +241,3 @@ func = do
|
|||
**~ cccccccccccccccccccccccccccccccccccccccccccccccccc
|
||||
)
|
||||
== 13
|
||||
|
||||
#test allow lambdacase parspacing after operator
|
||||
foo = do
|
||||
abc `forM_` \case
|
||||
True -> 1
|
||||
False -> 0
|
||||
|
|
|
@ -1090,14 +1090,3 @@ func = do
|
|||
)
|
||||
nogcVassuVvbFiew
|
||||
kyxson = vzahxEooRecOriqdp apneZejuzTfuQkuJosqoa
|
||||
|
||||
#test base level for operands
|
||||
func = do
|
||||
pure
|
||||
$!! otherFunc
|
||||
(SomeLargeRecord { aaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaa = 1
|
||||
, bbbbbbbbbbbbbbbbbbbbbbbbbbbbbbbbbb = 2
|
||||
, cccccccccccccccccccccccccccccccccc = 3
|
||||
}
|
||||
)
|
||||
anotherArgument
|
||||
|
|
|
@ -45,7 +45,7 @@ displayOpTree = \case
|
|||
++ ")"
|
||||
++ join [ (showOp op ++ "(" ++ displayOpTree t ++ ")") | (op, t) <- ops ]
|
||||
)
|
||||
OpLeaf _ (x, _) -> show x
|
||||
OpLeaf (x, _) -> show x
|
||||
where
|
||||
showOp :: BriDocNumbered -> String
|
||||
showOp = \case
|
||||
|
@ -185,7 +185,7 @@ addAllParens topLevelParen = \case
|
|||
remSuperfluousParens :: Int -> OpTree -> OpTree
|
||||
remSuperfluousParens outerFixity = \case
|
||||
x@OpLeaf{} -> x
|
||||
OpUnknown _ locO locC c@(OpLeaf _ doc) [] | isLit doc ->
|
||||
OpUnknown _ locO locC c@(OpLeaf doc) [] | isLit doc ->
|
||||
OpUnknown NoParen locO locC c []
|
||||
OpUnknown _ locO locC c@(OpUnknown ParenWithSpace _ _ _ _) [] ->
|
||||
OpUnknown NoParen locO locC (remSuperfluousParens 11 c) []
|
||||
|
|
|
@ -736,15 +736,15 @@ layoutExpr lexpr@(L _ expr) = do
|
|||
, docForceSingleline eN
|
||||
, closeDoc]
|
||||
addAlternative
|
||||
$ let start = docCols ColList [appSep $ openDoc, docSetBaseY e1]
|
||||
$ let start = docCols ColList [appSep $ openDoc, e1]
|
||||
linesM = ems <&> \(p, ast, d) ->
|
||||
docCols
|
||||
ColList
|
||||
[ docHandleComms p docCommaSep
|
||||
, docSetBaseY $ docFlushCommsPost True ast $ d
|
||||
, docFlushCommsPost True ast $ d
|
||||
]
|
||||
lineN = docCols ColList
|
||||
[docHandleComms finalCommaPos $ docCommaSep, docSetBaseY eN]
|
||||
[docHandleComms finalCommaPos $ docCommaSep, eN]
|
||||
in docSetBaseY
|
||||
$ docLines
|
||||
$ [start]
|
||||
|
|
|
@ -7,7 +7,6 @@ import GHC ( GenLocated(L) )
|
|||
import GHC.Hs
|
||||
import GHC.Types.Fixity ( Fixity(Fixity) )
|
||||
import qualified GHC.Types.SrcLoc as GHC
|
||||
import qualified GHC.OldList as List
|
||||
|
||||
import Language.Haskell.Brittany.Internal.Components.BriDoc
|
||||
import Language.Haskell.Brittany.Internal.Components.OpTree
|
||||
|
@ -18,13 +17,6 @@ import Language.Haskell.Brittany.Internal.Types
|
|||
import Language.Haskell.Brittany.Internal.Utils
|
||||
|
||||
|
||||
allowAsOpPar :: LHsExpr GhcPs -> Bool
|
||||
allowAsOpPar = \case
|
||||
L _ HsLam{} -> True
|
||||
L _ HsLamCase{} -> True
|
||||
L _ HsDo{} -> True
|
||||
_ -> False
|
||||
|
||||
gatherOpTreeE
|
||||
:: OpParenMode
|
||||
-> Bool
|
||||
|
@ -47,7 +39,7 @@ gatherOpTreeE hasParen hasComms commWrap locOpen locClose opExprList = \case
|
|||
locOpen
|
||||
locClose
|
||||
( ( docHandleComms epAnn $ callLayouter layout_expr op1
|
||||
, OpLeaf (allowAsOpPar r1) inner
|
||||
, OpLeaf inner
|
||||
)
|
||||
: opExprList
|
||||
)
|
||||
|
@ -80,7 +72,9 @@ gatherOpTreeE hasParen hasComms commWrap locOpen locClose opExprList = \case
|
|||
-- if null opExprList
|
||||
-- then pure (innerTree, innerHasComms)
|
||||
-- else do
|
||||
numberedRights <- opExprList `forM` \(x, y) -> do
|
||||
numberedRights <-
|
||||
opExprList
|
||||
`forM` \(x, y) -> do
|
||||
x' <- x
|
||||
pure (x', y)
|
||||
pure
|
||||
|
@ -89,10 +83,12 @@ gatherOpTreeE hasParen hasComms commWrap locOpen locClose opExprList = \case
|
|||
)
|
||||
final | hasParen == NoParen && null opExprList -> do
|
||||
tree <- commWrap $ callLayouter layout_expr final
|
||||
pure (OpLeaf (allowAsOpPar final) tree, hasComms)
|
||||
pure (OpLeaf tree, hasComms)
|
||||
final@(L _ inner) -> do
|
||||
numberedLeft <- commWrap $ callLayouter layout_expr final
|
||||
numberedRights <- opExprList `forM` \(x, y) -> do
|
||||
numberedRights <-
|
||||
opExprList
|
||||
`forM` \(x, y) -> do
|
||||
x' <- x
|
||||
pure (x', y)
|
||||
pure
|
||||
|
@ -104,7 +100,7 @@ gatherOpTreeE hasParen hasComms commWrap locOpen locClose opExprList = \case
|
|||
)
|
||||
locOpen
|
||||
locClose
|
||||
(OpLeaf (allowAsOpPar final) numberedLeft)
|
||||
(OpLeaf $ numberedLeft)
|
||||
numberedRights
|
||||
, hasComms
|
||||
)
|
||||
|
@ -130,11 +126,15 @@ gatherOpTreeT hasParen hasComms commWrap locOpen locClose opExprList = \case
|
|||
commWrap
|
||||
locOpen
|
||||
locClose
|
||||
((docLit $ printRdrNameWithAnns op1, OpLeaf False inner) : opExprList)
|
||||
( (docLit $ printRdrNameWithAnns op1, OpLeaf inner)
|
||||
: opExprList
|
||||
)
|
||||
l1
|
||||
final@(L _ inner) -> do
|
||||
numberedLeft <- commWrap $ callLayouter2 layout_type False final
|
||||
numberedRights <- opExprList `forM` \(x, y) -> do
|
||||
numberedRights <-
|
||||
opExprList
|
||||
`forM` \(x, y) -> do
|
||||
x' <- x
|
||||
pure (x', y)
|
||||
pure
|
||||
|
@ -146,7 +146,7 @@ gatherOpTreeT hasParen hasComms commWrap locOpen locClose opExprList = \case
|
|||
)
|
||||
locOpen
|
||||
locClose
|
||||
(OpLeaf False numberedLeft)
|
||||
(OpLeaf $ numberedLeft)
|
||||
numberedRights
|
||||
, hasComms
|
||||
)
|
||||
|
@ -238,9 +238,7 @@ layoutOpTree allowSinglelinePar = \case
|
|||
sharedOps <- simpleTransform docOps
|
||||
let lastWrap = if getPrec fixity <= 1
|
||||
then docForceParSpacing
|
||||
else case List.last docOps of
|
||||
(_, OpLeaf True _) -> docForceParSpacing
|
||||
_ -> docForceSingleline
|
||||
else docForceSingleline
|
||||
coreAlternative hasParen
|
||||
locO
|
||||
locC
|
||||
|
@ -249,7 +247,7 @@ layoutOpTree allowSinglelinePar = \case
|
|||
sharedOps
|
||||
sharedOpsFlat
|
||||
lastWrap
|
||||
OpLeaf _ l -> pure l
|
||||
OpLeaf l -> pure l
|
||||
where
|
||||
isPrec0 x = getPrec x == 0
|
||||
getPrec = \case
|
||||
|
@ -425,7 +423,7 @@ layoutOpTree allowSinglelinePar = \case
|
|||
let singlelineUnlessFree = case indentPolicy of
|
||||
IndentPolicyLeft -> docForceSingleline
|
||||
IndentPolicyMultiple -> docForceSingleline
|
||||
IndentPolicyFree -> docSetBaseY
|
||||
IndentPolicyFree -> id
|
||||
let curIsPrec0 = case fixity of
|
||||
Nothing -> False
|
||||
Just (Fixity _ prec _) -> prec == 0
|
||||
|
|
|
@ -75,7 +75,7 @@ splitArrowType ltype@(L _ typ) = case typ of
|
|||
docPar open $ docLines $ list ++ [close]
|
||||
]
|
||||
arrowDoc <- docLitS "=>"
|
||||
pure (OpLeaf False outerHead, (arrowDoc, innerHead) : innerBody)
|
||||
pure (OpLeaf outerHead, (arrowDoc, innerHead) : innerBody)
|
||||
HsFunTy epAnn _ typ1 typ2 -> do
|
||||
(typ1Doc, (innerHead, innerBody)) <- do
|
||||
let
|
||||
|
@ -97,7 +97,7 @@ splitArrowType ltype@(L _ typ) = case typ of
|
|||
typ2Tuple <- splitArrowType typ2
|
||||
pure (typ1Doc, typ2Tuple)
|
||||
arrowDoc <- docLitS "->"
|
||||
pure $ (OpLeaf False typ1Doc, (arrowDoc, innerHead) : innerBody)
|
||||
pure $ (OpLeaf typ1Doc, (arrowDoc, innerHead) : innerBody)
|
||||
HsParTy epAnn inner -> do
|
||||
let AnnParen _ spanOpen spanClose = anns epAnn
|
||||
(headPart, restParts) <- splitArrowType inner
|
||||
|
@ -115,7 +115,7 @@ splitArrowType ltype@(L _ typ) = case typ of
|
|||
pure $ (OpUnknown NoParen Nothing Nothing innerHead innerRest, [])
|
||||
_ -> do
|
||||
inner <- layoutType False ltype
|
||||
pure (OpLeaf False inner, [])
|
||||
pure (OpLeaf inner, [])
|
||||
|
||||
splitOpType :: LHsType GhcPs -> ToBriDocM (OpTree, [(BriDocNumbered, OpTree)])
|
||||
splitOpType = \case
|
||||
|
@ -123,10 +123,10 @@ splitOpType = \case
|
|||
docL <- layoutType False l1
|
||||
docOp <- docHandleComms pos $ docLit $ printRdrNameWithAnns op1
|
||||
(innerHead, innerBody) <- splitOpType r1
|
||||
pure $ (OpLeaf False docL, (docOp, innerHead) : innerBody)
|
||||
pure $ (OpLeaf docL, (docOp, innerHead) : innerBody)
|
||||
ltype -> do
|
||||
inner <- layoutType False ltype
|
||||
pure (OpLeaf False inner, [])
|
||||
pure (OpLeaf inner, [])
|
||||
|
||||
|
||||
splitHsForallTypeFromBinders
|
||||
|
@ -159,7 +159,7 @@ splitHsForallTypeFromBinders binders typ = do
|
|||
)
|
||||
]
|
||||
dotDoc <- docLitS "."
|
||||
pure (OpLeaf False outerHead, (dotDoc, innerHead) : innerBody)
|
||||
pure (OpLeaf outerHead, (dotDoc, innerHead) : innerBody)
|
||||
|
||||
layoutSplitArrowType
|
||||
:: (OpTree, [(BriDocNumbered, OpTree)])
|
||||
|
|
|
@ -178,7 +178,7 @@ data OpTree
|
|||
GHC.Fixity -- only Just after (successful!) lookup phase
|
||||
OpTree
|
||||
[(BriDocNumbered, OpTree)]
|
||||
| OpLeaf Bool BriDocNumbered -- bool determines if parspacing is preferred
|
||||
| OpLeaf BriDocNumbered
|
||||
|
||||
data SortItemsFlag = ShouldSortItems | KeepItemsUnsorted
|
||||
|
||||
|
|
Loading…
Reference in New Issue