Add spaces around record braces (single-line) (fixes #126)
parent
ef7b0fcc70
commit
bdee27cb59
|
@ -43,7 +43,7 @@ func = do
|
||||||
}
|
}
|
||||||
|
|
||||||
#test record construction 1
|
#test record construction 1
|
||||||
func = Foo {_lstate_indent = _lstate_indent state}
|
func = Foo { _lstate_indent = _lstate_indent state }
|
||||||
|
|
||||||
#test record construction 2
|
#test record construction 2
|
||||||
func = Foo
|
func = Foo
|
||||||
|
@ -478,17 +478,17 @@ foo =
|
||||||
#test issue 52 a
|
#test issue 52 a
|
||||||
|
|
||||||
{-# LANGUAGE RecordWildCards #-}
|
{-# LANGUAGE RecordWildCards #-}
|
||||||
v = A {a = 1, ..} where b = 2
|
v = A { a = 1, .. } where b = 2
|
||||||
|
|
||||||
#test issue 52 b
|
#test issue 52 b
|
||||||
|
|
||||||
{-# LANGUAGE RecordWildCards #-}
|
{-# LANGUAGE RecordWildCards #-}
|
||||||
v = A {..} where b = 2
|
v = A { .. } where b = 2
|
||||||
|
|
||||||
#test issue 52 c
|
#test issue 52 c
|
||||||
|
|
||||||
{-# LANGUAGE RecordWildCards #-}
|
{-# LANGUAGE RecordWildCards #-}
|
||||||
v = A {a = 1, b = 2, c = 3}
|
v = A { a = 1, b = 2, c = 3 }
|
||||||
|
|
||||||
#test issue 63 a
|
#test issue 63 a
|
||||||
#pending fix does not work on 8.0.2
|
#pending fix does not work on 8.0.2
|
||||||
|
|
|
@ -931,7 +931,7 @@ func = do
|
||||||
}
|
}
|
||||||
|
|
||||||
#test record construction 1
|
#test record construction 1
|
||||||
func = Foo {_lstate_indent = _lstate_indent state}
|
func = Foo { _lstate_indent = _lstate_indent state }
|
||||||
|
|
||||||
#test record construction 2
|
#test record construction 2
|
||||||
func = Foo
|
func = Foo
|
||||||
|
|
|
@ -749,8 +749,8 @@ layoutExpr lexpr@(L _ expr) = do
|
||||||
then return Nothing
|
then return Nothing
|
||||||
else Just <$> docSharedWrapper layoutExpr fExpr
|
else Just <$> docSharedWrapper layoutExpr fExpr
|
||||||
return (fieldl, lrdrNameToText lnameF, fExpDoc)
|
return (fieldl, lrdrNameToText lnameF, fExpDoc)
|
||||||
let line1 appender wrapper =
|
let line1 wrapper =
|
||||||
[ appender $ docLit $ Text.pack "{"
|
[ appSep $ docLit $ Text.pack "{"
|
||||||
, docWrapNodePrior fd1l $ appSep $ docLit fd1n
|
, docWrapNodePrior fd1l $ appSep $ docLit fd1n
|
||||||
, case fd1e of
|
, case fd1e of
|
||||||
Just x -> docSeq
|
Just x -> docSeq
|
||||||
|
@ -776,8 +776,9 @@ layoutExpr lexpr@(L _ expr) = do
|
||||||
docAlt
|
docAlt
|
||||||
[ docSeq
|
[ docSeq
|
||||||
$ [docNodeAnnKW lexpr Nothing nameDoc, docSeparator]
|
$ [docNodeAnnKW lexpr Nothing nameDoc, docSeparator]
|
||||||
++ line1 id docForceSingleline
|
++ line1 docForceSingleline
|
||||||
++ join (lineR docForceSingleline)
|
++ join (lineR docForceSingleline)
|
||||||
|
++ [docSeparator]
|
||||||
++ lineN
|
++ lineN
|
||||||
, docSetParSpacing
|
, docSetParSpacing
|
||||||
$ docAddBaseY BrIndentRegular
|
$ docAddBaseY BrIndentRegular
|
||||||
|
@ -785,14 +786,14 @@ layoutExpr lexpr@(L _ expr) = do
|
||||||
(docNodeAnnKW lexpr Nothing nameDoc)
|
(docNodeAnnKW lexpr Nothing nameDoc)
|
||||||
( docNonBottomSpacing
|
( docNonBottomSpacing
|
||||||
$ docLines
|
$ docLines
|
||||||
$ [docCols ColRecUpdate $ line1 appSep (docAddBaseY BrIndentRegular)]
|
$ [docCols ColRecUpdate $ line1 (docAddBaseY BrIndentRegular)]
|
||||||
++ (docCols ColRecUpdate <$> lineR (docAddBaseY BrIndentRegular))
|
++ (docCols ColRecUpdate <$> lineR (docAddBaseY BrIndentRegular))
|
||||||
++ [docSeq lineN]
|
++ [docSeq lineN]
|
||||||
)
|
)
|
||||||
]
|
]
|
||||||
RecordCon lname _ _ (HsRecFields [] (Just 0)) -> do
|
RecordCon lname _ _ (HsRecFields [] (Just 0)) -> do
|
||||||
let t = lrdrNameToText lname
|
let t = lrdrNameToText lname
|
||||||
docWrapNode lname $ docLit $ t <> Text.pack " {..}"
|
docWrapNode lname $ docLit $ t <> Text.pack " { .. }"
|
||||||
RecordCon lname _ _ (HsRecFields fs@(_:_) (Just dotdoti)) | dotdoti == length fs -> do
|
RecordCon lname _ _ (HsRecFields fs@(_:_) (Just dotdoti)) | dotdoti == length fs -> do
|
||||||
let nameDoc = docWrapNode lname $ docLit $ lrdrNameToText lname
|
let nameDoc = docWrapNode lname $ docLit $ lrdrNameToText lname
|
||||||
((fd1l, fd1n, fd1e):fdr) <- fs `forM` \fieldl@(L _ (HsRecField (L _ (FieldOcc lnameF _)) fExpr pun)) -> do
|
((fd1l, fd1n, fd1e):fdr) <- fs `forM` \fieldl@(L _ (HsRecField (L _ (FieldOcc lnameF _)) fExpr pun)) -> do
|
||||||
|
@ -800,8 +801,8 @@ layoutExpr lexpr@(L _ expr) = do
|
||||||
then return Nothing
|
then return Nothing
|
||||||
else Just <$> docSharedWrapper layoutExpr fExpr
|
else Just <$> docSharedWrapper layoutExpr fExpr
|
||||||
return (fieldl, lrdrNameToText lnameF, fExpDoc)
|
return (fieldl, lrdrNameToText lnameF, fExpDoc)
|
||||||
let line1 appender wrapper =
|
let line1 wrapper =
|
||||||
[ appender $ docLit $ Text.pack "{"
|
[ appSep $ docLit $ Text.pack "{"
|
||||||
, docWrapNodePrior fd1l $ appSep $ docLit fd1n
|
, docWrapNodePrior fd1l $ appSep $ docLit fd1n
|
||||||
, case fd1e of
|
, case fd1e of
|
||||||
Just x -> docSeq
|
Just x -> docSeq
|
||||||
|
@ -831,9 +832,10 @@ layoutExpr lexpr@(L _ expr) = do
|
||||||
docAlt
|
docAlt
|
||||||
[ docSeq
|
[ docSeq
|
||||||
$ [docNodeAnnKW lexpr Nothing nameDoc, docSeparator]
|
$ [docNodeAnnKW lexpr Nothing nameDoc, docSeparator]
|
||||||
++ line1 id docForceSingleline
|
++ line1 docForceSingleline
|
||||||
++ join (lineR docForceSingleline)
|
++ join (lineR docForceSingleline)
|
||||||
++ lineDot
|
++ lineDot
|
||||||
|
++ [docSeparator]
|
||||||
++ lineN
|
++ lineN
|
||||||
, docSetParSpacing
|
, docSetParSpacing
|
||||||
$ docAddBaseY BrIndentRegular
|
$ docAddBaseY BrIndentRegular
|
||||||
|
@ -841,7 +843,7 @@ layoutExpr lexpr@(L _ expr) = do
|
||||||
(docNodeAnnKW lexpr Nothing nameDoc)
|
(docNodeAnnKW lexpr Nothing nameDoc)
|
||||||
( docNonBottomSpacing
|
( docNonBottomSpacing
|
||||||
$ docLines
|
$ docLines
|
||||||
$ [docCols ColRecUpdate $ line1 appSep (docAddBaseY BrIndentRegular)]
|
$ [docCols ColRecUpdate $ line1 (docAddBaseY BrIndentRegular)]
|
||||||
++ (docCols ColRecUpdate <$> lineR (docAddBaseY BrIndentRegular))
|
++ (docCols ColRecUpdate <$> lineR (docAddBaseY BrIndentRegular))
|
||||||
++ [docSeq lineDot, docSeq lineN]
|
++ [docSeq lineDot, docSeq lineN]
|
||||||
)
|
)
|
||||||
|
|
Loading…
Reference in New Issue