Improve comments-affecting-layout behaviour for tuples (#231)
parent
85d55c3768
commit
825ec425d4
|
@ -802,3 +802,25 @@ zItazySunefp twgq nlyo lwojjoBiecao =
|
|||
#test module initial comment
|
||||
-- test
|
||||
module MyModule where
|
||||
|
||||
#test issue 231
|
||||
|
||||
foo =
|
||||
[ ("xxx", "xx")
|
||||
, --
|
||||
("xx" , "xx")
|
||||
--
|
||||
, ("xx" , "xxxxx")
|
||||
, ("xx" , "xx")
|
||||
]
|
||||
|
||||
#test issue 231 not
|
||||
|
||||
foo =
|
||||
[ ("xx", "xx")
|
||||
, ( "xx" --
|
||||
, "xx"
|
||||
)
|
||||
, ("xx", "xxxxx")
|
||||
, ("xx", "xx")
|
||||
]
|
||||
|
|
|
@ -66,6 +66,7 @@ module Language.Haskell.Brittany.Internal.LayouterBasics
|
|||
, allocateNode
|
||||
, docSharedWrapper
|
||||
, hasAnyCommentsBelow
|
||||
, hasCommentsBetween
|
||||
, hasAnyCommentsConnected
|
||||
, hasAnyCommentsPrior
|
||||
, hasAnyRegularCommentsConnected
|
||||
|
@ -299,6 +300,25 @@ hasAnyCommentsBelow ast@(L l _) =
|
|||
List.any (\(c, _) -> ExactPrint.commentIdentifier c > l)
|
||||
<$> astConnectedComments ast
|
||||
|
||||
hasCommentsBetween
|
||||
:: Data ast
|
||||
=> GHC.Located ast
|
||||
-> AnnKeywordId
|
||||
-> AnnKeywordId
|
||||
-> ToBriDocM Bool
|
||||
hasCommentsBetween ast leftKey rightKey = do
|
||||
mAnn <- astAnn ast
|
||||
let go1 [] = False
|
||||
go1 ((ExactPrint.G kw, _dp) : rest) | kw == leftKey = go2 rest
|
||||
go1 (_ : rest) = go1 rest
|
||||
go2 [] = False
|
||||
go2 ((ExactPrint.AnnComment _, _dp) : _rest) = True
|
||||
go2 ((ExactPrint.G kw, _dp) : _rest) | kw == rightKey = False
|
||||
go2 (_ : rest) = go2 rest
|
||||
case mAnn of
|
||||
Nothing -> pure False
|
||||
Just ann -> pure $ go1 $ ExactPrint.annsDP ann
|
||||
|
||||
-- | True if there are any comments that are connected to any node below (in AST
|
||||
-- sense) the given node
|
||||
hasAnyCommentsConnected :: Data ast => GHC.Located ast -> ToBriDocM Bool
|
||||
|
|
|
@ -528,7 +528,10 @@ layoutExpr lexpr@(L _ expr) = do
|
|||
argDocs <- forM argExprs
|
||||
$ docSharedWrapper
|
||||
$ \(arg, exprM) -> docWrapNode arg $ maybe docEmpty layoutExpr exprM
|
||||
hasComments <- hasAnyCommentsBelow lexpr
|
||||
hasComments <- orM
|
||||
( hasCommentsBetween lexpr AnnOpenP AnnCloseP
|
||||
: map hasAnyCommentsBelow args
|
||||
)
|
||||
let (openLit, closeLit) = case boxity of
|
||||
Boxed -> (docLit $ Text.pack "(", docLit $ Text.pack ")")
|
||||
Unboxed -> (docParenHashLSep, docParenHashRSep)
|
||||
|
|
Loading…
Reference in New Issue