Also handle comments inside ThingWith
parent
21c080572b
commit
3708838b6a
|
@ -765,7 +765,27 @@ import Test ( -- comment
|
||||||
|
|
||||||
#test long-bindings
|
#test long-bindings
|
||||||
import Test ( longbindingNameThatoverflowsColum )
|
import Test ( longbindingNameThatoverflowsColum )
|
||||||
import Test ( Long(List, Of, Things) )
|
import Test ( Long( List
|
||||||
|
, Of
|
||||||
|
, Things
|
||||||
|
) )
|
||||||
|
|
||||||
|
#test things-with-with-comments
|
||||||
|
import Test ( Thing( -- Comments
|
||||||
|
)
|
||||||
|
)
|
||||||
|
import Test ( Thing( Item
|
||||||
|
-- and Comment
|
||||||
|
)
|
||||||
|
)
|
||||||
|
import Test ( Thing( With
|
||||||
|
-- Comments
|
||||||
|
, and
|
||||||
|
-- also
|
||||||
|
, items
|
||||||
|
-- !
|
||||||
|
)
|
||||||
|
)
|
||||||
|
|
||||||
#test preamble full-preamble
|
#test preamble full-preamble
|
||||||
{-# LANGUAGE BangPatterns #-}
|
{-# LANGUAGE BangPatterns #-}
|
||||||
|
|
|
@ -771,6 +771,28 @@ import Test ( -- comment
|
||||||
import Test (longbindingNameThatoverflowsColum)
|
import Test (longbindingNameThatoverflowsColum)
|
||||||
import Test (Long(List, Of, Things))
|
import Test (Long(List, Of, Things))
|
||||||
|
|
||||||
|
#test things-with-with-comments
|
||||||
|
import Test ( Thing( With
|
||||||
|
-- Comments
|
||||||
|
, and
|
||||||
|
-- also
|
||||||
|
, items
|
||||||
|
-- !
|
||||||
|
)
|
||||||
|
)
|
||||||
|
import Test ( Thing( Item
|
||||||
|
-- and Comment
|
||||||
|
)
|
||||||
|
)
|
||||||
|
import Test ( Thing( With
|
||||||
|
-- Comments
|
||||||
|
, and
|
||||||
|
-- also
|
||||||
|
, items
|
||||||
|
-- !
|
||||||
|
)
|
||||||
|
)
|
||||||
|
|
||||||
#test preamble full-preamble
|
#test preamble full-preamble
|
||||||
{-# LANGUAGE BangPatterns #-}
|
{-# LANGUAGE BangPatterns #-}
|
||||||
|
|
||||||
|
|
|
@ -44,14 +44,32 @@ layoutIE lie@(L _ ie) = docWrapNode lie $ case ie of
|
||||||
IEThingAbs _ -> ien
|
IEThingAbs _ -> ien
|
||||||
IEThingAll _ -> docSeq [ien, docLit $ Text.pack "(..)"]
|
IEThingAll _ -> docSeq [ien, docLit $ Text.pack "(..)"]
|
||||||
IEThingWith _ (IEWildcard _) _ _ -> docSeq [ien, docLit $ Text.pack "(..)"]
|
IEThingWith _ (IEWildcard _) _ _ -> docSeq [ien, docLit $ Text.pack "(..)"]
|
||||||
IEThingWith _ _ ns fs ->
|
IEThingWith _ _ ns _ -> do
|
||||||
docSeq
|
hasComments <- hasAnyCommentsBelow lie
|
||||||
$ [ien, docLit $ Text.pack "("]
|
docAltFilter
|
||||||
++ intersperse docCommaSep (map nameDoc ns ++ map prepareFL fs)
|
[(not hasComments, docSeq $ [ien, docLit $ Text.pack "("]
|
||||||
++ [docLit $ Text.pack ")"]
|
++ intersperse docCommaSep (map nameDoc ns)
|
||||||
|
++ [docParenR])
|
||||||
|
,(otherwise, docSeq [ien, layoutItems (splitFirstLast ns)])
|
||||||
|
]
|
||||||
where
|
where
|
||||||
nameDoc = (docLit =<<) . lrdrNameToTextAnn . prepareName
|
nameDoc = (docLit =<<) . lrdrNameToTextAnn . prepareName
|
||||||
prepareFL = docLit . Text.pack . FastString.unpackFS . flLabel . unLoc
|
layoutItem n = docSeq [docCommaSep, docWrapNode n $ nameDoc n]
|
||||||
|
layoutItems FirstLastEmpty =
|
||||||
|
docSetBaseY $
|
||||||
|
docLines [docSeq [docParenLSep, docWrapNodeRest lie docEmpty]
|
||||||
|
,docParenR
|
||||||
|
]
|
||||||
|
layoutItems (FirstLastSingleton n) =
|
||||||
|
docSetBaseY $ docLines
|
||||||
|
[docSeq [docParenLSep, docWrapNodeRest lie $ nameDoc n], docParenR]
|
||||||
|
layoutItems (FirstLast n1 nMs nN) =
|
||||||
|
docSetBaseY $ docLines $
|
||||||
|
[docSeq [docParenLSep, docWrapNode n1 $ nameDoc n1]]
|
||||||
|
++ map layoutItem nMs
|
||||||
|
++ [ docSeq [docCommaSep, docWrapNodeRest lie $ nameDoc nN]
|
||||||
|
, docParenR
|
||||||
|
]
|
||||||
IEModuleContents n -> docSeq
|
IEModuleContents n -> docSeq
|
||||||
[ docLit $ Text.pack "module"
|
[ docLit $ Text.pack "module"
|
||||||
, docSeparator
|
, docSeparator
|
||||||
|
@ -101,7 +119,7 @@ layoutLLIEs llies = do
|
||||||
[] -> docAltFilter
|
[] -> docAltFilter
|
||||||
[ (not hasComments, docLit $ Text.pack "()")
|
[ (not hasComments, docLit $ Text.pack "()")
|
||||||
, (otherwise, docPar (docSeq [docParenLSep, docWrapNode llies docEmpty])
|
, (otherwise, docPar (docSeq [docParenLSep, docWrapNode llies docEmpty])
|
||||||
$ docLines [docParenR])
|
docParenR)
|
||||||
]
|
]
|
||||||
(ieDsH:ieDsT) ->
|
(ieDsH:ieDsT) ->
|
||||||
docAltFilter
|
docAltFilter
|
||||||
|
|
Loading…
Reference in New Issue