Remove redundant '$'s

pull/132/head
Sergey Vinokurov 2018-03-30 10:50:44 +01:00
parent 2ed9a13fdb
commit 0dad5051df
No known key found for this signature in database
GPG Key ID: D6CD29530F98D6B8
4 changed files with 57 additions and 57 deletions

View File

@ -93,8 +93,8 @@ parsePrintModule configRaw inputText = runExceptT $ do
cppCheckFunc cppCheckFunc
(hackTransform $ Text.unpack inputText) (hackTransform $ Text.unpack inputText)
case parseResult of case parseResult of
Left err -> throwE $ [ErrorInput err] Left err -> throwE [ErrorInput err]
Right x -> pure $ x Right x -> pure x
(errsWarns, outputTextL) <- do (errsWarns, outputTextL) <- do
let omitCheck = let omitCheck =
config config

View File

@ -119,7 +119,7 @@ processDefault x = do
-- the module (header). This would remove the need for this hack! -- the module (header). This would remove the need for this hack!
case str of case str of
"\n" -> return () "\n" -> return ()
_ -> mTell $ Text.Builder.fromString $ str _ -> mTell $ Text.Builder.fromString str
-- | Use ExactPrint's output for this node; add a newly generated inline comment -- | Use ExactPrint's output for this node; add a newly generated inline comment
-- at insertion position (meant to point out to the user that this node is -- at insertion position (meant to point out to the user that this node is
@ -174,7 +174,7 @@ briDocByExactInlineOnly infoStr ast = do
False False
t t
let errorAction = do let errorAction = do
mTell $ [ErrorUnknownNode infoStr ast] mTell [ErrorUnknownNode infoStr ast]
docLit docLit
$ Text.pack "{- BRITTANY ERROR UNHANDLED SYNTACTICAL CONSTRUCT -}" $ Text.pack "{- BRITTANY ERROR UNHANDLED SYNTACTICAL CONSTRUCT -}"
case (fallbackMode, Text.lines exactPrinted) of case (fallbackMode, Text.lines exactPrinted) of
@ -589,7 +589,7 @@ instance DocWrapable a => DocWrapable [a] where
docWrapNode ast bdsm = do docWrapNode ast bdsm = do
bds <- bdsm bds <- bdsm
case bds of case bds of
[] -> return $ [] -- TODO: this might be bad. maybe. then again, not really. well. [] -> return [] -- TODO: this might be bad. maybe. then again, not really. well.
[bd] -> do [bd] -> do
bd' <- docWrapNode ast (return bd) bd' <- docWrapNode ast (return bd)
return [bd'] return [bd']
@ -601,23 +601,23 @@ instance DocWrapable a => DocWrapable [a] where
docWrapNodePrior ast bdsm = do docWrapNodePrior ast bdsm = do
bds <- bdsm bds <- bdsm
case bds of case bds of
[] -> return $ [] [] -> return []
(bd1:bdR) -> do (bd1:bdR) -> do
bd1' <- docWrapNodePrior ast (return bd1) bd1' <- docWrapNodePrior ast (return bd1)
return $ (bd1':bdR) return (bd1':bdR)
docWrapNodeRest ast bdsm = do docWrapNodeRest ast bdsm = do
bds <- bdsm bds <- bdsm
case reverse bds of case reverse bds of
[] -> return $ [] [] -> return []
(bdN:bdR) -> do (bdN:bdR) -> do
bdN' <- docWrapNodeRest ast (return bdN) bdN' <- docWrapNodeRest ast (return bdN)
return $ reverse $ (bdN':bdR) return $ reverse (bdN':bdR)
instance DocWrapable a => DocWrapable (Seq a) where instance DocWrapable a => DocWrapable (Seq a) where
docWrapNode ast bdsm = do docWrapNode ast bdsm = do
bds <- bdsm bds <- bdsm
case Seq.viewl bds of case Seq.viewl bds of
Seq.EmptyL -> return $ Seq.empty -- TODO: this might be bad. maybe. then again, not really. well. Seq.EmptyL -> return Seq.empty -- TODO: this might be bad. maybe. then again, not really. well.
bd1 Seq.:< rest -> case Seq.viewr rest of bd1 Seq.:< rest -> case Seq.viewr rest of
Seq.EmptyR -> do Seq.EmptyR -> do
bd1' <- docWrapNode ast (return bd1) bd1' <- docWrapNode ast (return bd1)
@ -629,14 +629,14 @@ instance DocWrapable a => DocWrapable (Seq a) where
docWrapNodePrior ast bdsm = do docWrapNodePrior ast bdsm = do
bds <- bdsm bds <- bdsm
case Seq.viewl bds of case Seq.viewl bds of
Seq.EmptyL -> return $ Seq.empty Seq.EmptyL -> return Seq.empty
bd1 Seq.:< bdR -> do bd1 Seq.:< bdR -> do
bd1' <- docWrapNodePrior ast (return bd1) bd1' <- docWrapNodePrior ast (return bd1)
return $ bd1' Seq.<| bdR return $ bd1' Seq.<| bdR
docWrapNodeRest ast bdsm = do docWrapNodeRest ast bdsm = do
bds <- bdsm bds <- bdsm
case Seq.viewr bds of case Seq.viewr bds of
Seq.EmptyR -> return $ Seq.empty Seq.EmptyR -> return Seq.empty
bdR Seq.:> bdN -> do bdR Seq.:> bdN -> do
bdN' <- docWrapNodeRest ast (return bdN) bdN' <- docWrapNodeRest ast (return bdN)
return $ bdR Seq.|> bdN' return $ bdR Seq.|> bdN'
@ -647,19 +647,19 @@ instance DocWrapable ([BriDocNumbered], BriDocNumbered, a) where
if null bds if null bds
then do then do
bd' <- docWrapNode ast (return bd) bd' <- docWrapNode ast (return bd)
return $ (bds, bd', x) return (bds, bd', x)
else do else do
bds' <- docWrapNodePrior ast (return bds) bds' <- docWrapNodePrior ast (return bds)
bd' <- docWrapNodeRest ast (return bd) bd' <- docWrapNodeRest ast (return bd)
return $ (bds', bd', x) return (bds', bd', x)
docWrapNodePrior ast stuffM = do docWrapNodePrior ast stuffM = do
(bds, bd, x) <- stuffM (bds, bd, x) <- stuffM
bds' <- docWrapNodePrior ast (return bds) bds' <- docWrapNodePrior ast (return bds)
return $ (bds', bd, x) return (bds', bd, x)
docWrapNodeRest ast stuffM = do docWrapNodeRest ast stuffM = do
(bds, bd, x) <- stuffM (bds, bd, x) <- stuffM
bd' <- docWrapNodeRest ast (return bd) bd' <- docWrapNodeRest ast (return bd)
return $ (bds, bd', x) return (bds, bd', x)
@ -685,7 +685,7 @@ docEnsureIndent ind mbd = mbd >>= \bd -> allocateNode $ BDFEnsureIndent ind bd
unknownNodeError unknownNodeError
:: Data.Data.Data ast => String -> ast -> ToBriDocM BriDocNumbered :: Data.Data.Data ast => String -> ast -> ToBriDocM BriDocNumbered
unknownNodeError infoStr ast = do unknownNodeError infoStr ast = do
mTell $ [ErrorUnknownNode infoStr ast] mTell [ErrorUnknownNode infoStr ast]
docLit $ Text.pack "{- BRITTANY ERROR UNHANDLED SYNTACTICAL CONSTRUCT -}" docLit $ Text.pack "{- BRITTANY ERROR UNHANDLED SYNTACTICAL CONSTRUCT -}"
spacifyDocs :: [ToBriDocM BriDocNumbered] -> [ToBriDocM BriDocNumbered] spacifyDocs :: [ToBriDocM BriDocNumbered] -> [ToBriDocM BriDocNumbered]

View File

@ -61,7 +61,7 @@ layoutExpr lexpr@(L _ expr) = do
bodyDoc <- docAddBaseY BrIndentRegular <$> docSharedWrapper layoutExpr body bodyDoc <- docAddBaseY BrIndentRegular <$> docSharedWrapper layoutExpr body
let funcPatternPartLine = let funcPatternPartLine =
docCols ColCasePattern docCols ColCasePattern
$ (patDocs <&> (\p -> docSeq [docForceSingleline p, docSeparator])) (patDocs <&> (\p -> docSeq [docForceSingleline p, docSeparator]))
docAlt docAlt
[ -- single line [ -- single line
docSeq docSeq
@ -313,12 +313,12 @@ layoutExpr lexpr@(L _ expr) = do
$ docAddBaseY BrIndentRegular $ docAddBaseY BrIndentRegular
$ docPar $ docPar
expDocLeft expDocLeft
(docCols ColOpPrefix [appSep $ expDocOp, docSetBaseY expDocRight]) (docCols ColOpPrefix [appSep expDocOp, docSetBaseY expDocRight])
NegApp op _ -> do NegApp op _ -> do
opDoc <- docSharedWrapper layoutExpr op opDoc <- docSharedWrapper layoutExpr op
docSeq $ [ docLit $ Text.pack "-" docSeq [ docLit $ Text.pack "-"
, opDoc , opDoc
] ]
HsPar innerExp -> do HsPar innerExp -> do
innerExpDoc <- docSharedWrapper (docWrapNode lexpr . layoutExpr) innerExp innerExpDoc <- docSharedWrapper (docWrapNode lexpr . layoutExpr) innerExp
docAlt docAlt
@ -357,7 +357,7 @@ layoutExpr lexpr@(L _ expr) = do
case splitFirstLast argDocs of case splitFirstLast argDocs of
FirstLastEmpty -> docSeq FirstLastEmpty -> docSeq
[ openLit [ openLit
, docNodeAnnKW lexpr (Just AnnOpenP) $ closeLit , docNodeAnnKW lexpr (Just AnnOpenP) closeLit
] ]
FirstLastSingleton e -> docAlt FirstLastSingleton e -> docAlt
[ docCols ColTuple [ docCols ColTuple
@ -382,12 +382,12 @@ layoutExpr lexpr@(L _ expr) = do
addAlternative $ addAlternative $
let let
start = docCols ColTuples start = docCols ColTuples
[appSep $ openLit, e1] [appSep openLit, e1]
linesM = ems <&> \d -> linesM = ems <&> \d ->
docCols ColTuples [docCommaSep, d] docCols ColTuples [docCommaSep, d]
lineN = docCols ColTuples [docCommaSep, docNodeAnnKW lexpr (Just AnnOpenP) eN] lineN = docCols ColTuples [docCommaSep, docNodeAnnKW lexpr (Just AnnOpenP) eN]
end = closeLit end = closeLit
in docSetBaseY $ docLines $ [start] ++ linesM ++ [lineN] ++ [end] in docSetBaseY $ docLines $ [start] ++ linesM ++ [lineN, end]
HsCase cExp (MG lmatches@(L _ matches) _ _ _) -> do HsCase cExp (MG lmatches@(L _ matches) _ _ _) -> do
cExpDoc <- docSharedWrapper layoutExpr cExp cExpDoc <- docSharedWrapper layoutExpr cExp
binderDoc <- docLit $ Text.pack "->" binderDoc <- docLit $ Text.pack "->"
@ -551,9 +551,9 @@ layoutExpr lexpr@(L _ expr) = do
Just [bindDoc] -> docAlt Just [bindDoc] -> docAlt
[ docSeq [ docSeq
[ appSep $ docLit $ Text.pack "let" [ appSep $ docLit $ Text.pack "let"
, appSep $ docForceSingleline $ bindDoc , appSep $ docForceSingleline bindDoc
, appSep $ docLit $ Text.pack "in" , appSep $ docLit $ Text.pack "in"
, docForceSingleline $ expDoc1 , docForceSingleline expDoc1
] ]
, docLines , docLines
[ docAlt [ docAlt
@ -565,7 +565,7 @@ layoutExpr lexpr@(L _ expr) = do
, docAddBaseY BrIndentRegular , docAddBaseY BrIndentRegular
$ docPar $ docPar
(docLit $ Text.pack "let") (docLit $ Text.pack "let")
(docSetBaseAndIndent $ bindDoc) (docSetBaseAndIndent bindDoc)
] ]
, docAlt , docAlt
[ docSeq [ docSeq
@ -575,7 +575,7 @@ layoutExpr lexpr@(L _ expr) = do
, docAddBaseY BrIndentRegular , docAddBaseY BrIndentRegular
$ docPar $ docPar
(docLit $ Text.pack "in") (docLit $ Text.pack "in")
(docSetBaseY $ expDoc1) (docSetBaseY expDoc1)
] ]
] ]
] ]
@ -598,21 +598,21 @@ layoutExpr lexpr@(L _ expr) = do
[ docAddBaseY BrIndentRegular [ docAddBaseY BrIndentRegular
$ docPar $ docPar
(docLit $ Text.pack "let") (docLit $ Text.pack "let")
(docSetBaseAndIndent $ docLines $ bindDocs) (docSetBaseAndIndent $ docLines bindDocs)
, docSeq , docSeq
[ docLit $ Text.pack "in " [ docLit $ Text.pack "in "
, docAddBaseY BrIndentRegular $ expDoc1 , docAddBaseY BrIndentRegular expDoc1
] ]
] ]
addAlternativeCond (indentPolicy /= IndentPolicyLeft) addAlternativeCond (indentPolicy /= IndentPolicyLeft)
$ docLines $ docLines
[ docSeq [ docSeq
[ appSep $ docLit $ Text.pack "let" [ appSep $ docLit $ Text.pack "let"
, docSetBaseAndIndent $ docLines $ bindDocs , docSetBaseAndIndent $ docLines bindDocs
] ]
, docSeq , docSeq
[ appSep $ docLit $ Text.pack "in " [ appSep $ docLit $ Text.pack "in "
, docSetBaseY $ expDoc1 , docSetBaseY expDoc1
] ]
] ]
addAlternative addAlternative
@ -700,7 +700,7 @@ layoutExpr lexpr@(L _ expr) = do
[ docSeq [ docSeq
[ docLit $ Text.pack "[" [ docLit $ Text.pack "["
, docSeparator , docSeparator
, docSetBaseY $ docNodeAnnKW lexpr (Just AnnOpenS) $ e , docSetBaseY $ docNodeAnnKW lexpr (Just AnnOpenS) e
] ]
, docLit $ Text.pack "]" , docLit $ Text.pack "]"
] ]
@ -739,20 +739,20 @@ layoutExpr lexpr@(L _ expr) = do
fExpDoc <- if pun fExpDoc <- if pun
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 appender wrapper =
[ appender $ docLit $ Text.pack "{" [ appender $ 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
[ appSep $ docLit $ Text.pack "=" [ appSep $ docLit $ Text.pack "="
, docWrapNodeRest fd1l $ wrapper $ x , docWrapNodeRest fd1l $ wrapper x
] ]
Nothing -> docEmpty Nothing -> docEmpty
] ]
let lineR wrapper = fdr <&> \(lfield, fText, fDoc) -> let lineR wrapper = fdr <&> \(lfield, fText, fDoc) ->
[ docCommaSep [ docCommaSep
, appSep $ docLit $ fText , appSep $ docLit fText
, case fDoc of , case fDoc of
Just x -> docWrapNode lfield $ docSeq Just x -> docWrapNode lfield $ docSeq
[ appSep $ docLit $ Text.pack "=" [ appSep $ docLit $ Text.pack "="
@ -766,14 +766,14 @@ layoutExpr lexpr@(L _ expr) = do
] ]
docAlt docAlt
[ docSeq [ docSeq
$ [docNodeAnnKW lexpr Nothing $ nameDoc, docSeparator] $ [docNodeAnnKW lexpr Nothing nameDoc, docSeparator]
++ line1 id docForceSingleline ++ line1 id docForceSingleline
++ join (lineR docForceSingleline) ++ join (lineR docForceSingleline)
++ lineN ++ lineN
, docSetParSpacing , docSetParSpacing
$ docAddBaseY BrIndentRegular $ docAddBaseY BrIndentRegular
$ docPar $ docPar
(docNodeAnnKW lexpr Nothing $ nameDoc) (docNodeAnnKW lexpr Nothing nameDoc)
( docNonBottomSpacing ( docNonBottomSpacing
$ docLines $ docLines
$ [docCols ColRecUpdate $ line1 appSep (docAddBaseY BrIndentRegular)] $ [docCols ColRecUpdate $ line1 appSep (docAddBaseY BrIndentRegular)]
@ -790,20 +790,20 @@ layoutExpr lexpr@(L _ expr) = do
fExpDoc <- if pun fExpDoc <- if pun
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 appender wrapper =
[ appender $ docLit $ Text.pack "{" [ appender $ 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
[ appSep $ docLit $ Text.pack "=" [ appSep $ docLit $ Text.pack "="
, docWrapNodeRest fd1l $ wrapper $ x , docWrapNodeRest fd1l $ wrapper x
] ]
Nothing -> docEmpty Nothing -> docEmpty
] ]
let lineR wrapper = fdr <&> \(lfield, fText, fDoc) -> let lineR wrapper = fdr <&> \(lfield, fText, fDoc) ->
[ docCommaSep [ docCommaSep
, appSep $ docLit $ fText , appSep $ docLit fText
, case fDoc of , case fDoc of
Just x -> docWrapNode lfield $ docSeq Just x -> docWrapNode lfield $ docSeq
[ appSep $ docLit $ Text.pack "=" [ appSep $ docLit $ Text.pack "="
@ -821,7 +821,7 @@ layoutExpr lexpr@(L _ expr) = do
] ]
docAlt docAlt
[ docSeq [ docSeq
$ [docNodeAnnKW lexpr Nothing $ nameDoc, docSeparator] $ [docNodeAnnKW lexpr Nothing nameDoc, docSeparator]
++ line1 id docForceSingleline ++ line1 id docForceSingleline
++ join (lineR docForceSingleline) ++ join (lineR docForceSingleline)
++ lineDot ++ lineDot
@ -829,7 +829,7 @@ layoutExpr lexpr@(L _ expr) = do
, docSetParSpacing , docSetParSpacing
$ docAddBaseY BrIndentRegular $ docAddBaseY BrIndentRegular
$ docPar $ docPar
(docNodeAnnKW lexpr Nothing $ nameDoc) (docNodeAnnKW lexpr Nothing nameDoc)
( docNonBottomSpacing ( docNonBottomSpacing
$ docLines $ docLines
$ [docCols ColRecUpdate $ line1 appSep (docAddBaseY BrIndentRegular)] $ [docCols ColRecUpdate $ line1 appSep (docAddBaseY BrIndentRegular)]
@ -880,7 +880,7 @@ layoutExpr lexpr@(L _ expr) = do
, docSetBaseY $ docLines $ let , docSetBaseY $ docLines $ let
line1 = docCols ColRecUpdate line1 = docCols ColRecUpdate
[ appSep $ docLit $ Text.pack "{" [ appSep $ docLit $ Text.pack "{"
, docWrapNodePrior rF1f $ appSep $ docLit $ rF1n , docWrapNodePrior rF1f $ appSep $ docLit rF1n
, case rF1e of , case rF1e of
Just x -> docWrapNodeRest rF1f $ docSeq Just x -> docWrapNodeRest rF1f $ docSeq
[ appSep $ docLit $ Text.pack "=" [ appSep $ docLit $ Text.pack "="
@ -890,7 +890,7 @@ layoutExpr lexpr@(L _ expr) = do
] ]
lineR = rFr <&> \(lfield, fText, fDoc) -> docWrapNode lfield $ docCols ColRecUpdate lineR = rFr <&> \(lfield, fText, fDoc) -> docWrapNode lfield $ docCols ColRecUpdate
[ docCommaSep [ docCommaSep
, appSep $ docLit $ fText , appSep $ docLit fText
, case fDoc of , case fDoc of
Just x -> docSeq [ appSep $ docLit $ Text.pack "=" Just x -> docSeq [ appSep $ docLit $ Text.pack "="
, docForceSingleline x , docForceSingleline x
@ -913,14 +913,14 @@ layoutExpr lexpr@(L _ expr) = do
$ docSetParSpacing $ docSetParSpacing
$ docAddBaseY BrIndentRegular $ docAddBaseY BrIndentRegular
$ docPar $ docPar
(docNodeAnnKW lexpr Nothing $ rExprDoc) (docNodeAnnKW lexpr Nothing rExprDoc)
(docNonBottomSpacing $ docLines $ let (docNonBottomSpacing $ docLines $ let
expressionWrapper = if indentPolicy == IndentPolicyLeft expressionWrapper = if indentPolicy == IndentPolicyLeft
then docForceParSpacing then docForceParSpacing
else docSetBaseY else docSetBaseY
line1 = docCols ColRecUpdate line1 = docCols ColRecUpdate
[ appSep $ docLit $ Text.pack "{" [ appSep $ docLit $ Text.pack "{"
, docWrapNodePrior rF1f $ appSep $ docLit $ rF1n , docWrapNodePrior rF1f $ appSep $ docLit rF1n
, docWrapNodeRest rF1f $ case rF1e of , docWrapNodeRest rF1f $ case rF1e of
Just x -> docAlt Just x -> docAlt
[ docSeq [ appSep $ docLit $ Text.pack "=" [ docSeq [ appSep $ docLit $ Text.pack "="
@ -934,7 +934,7 @@ layoutExpr lexpr@(L _ expr) = do
lineR = rFr <&> \(lfield, fText, fDoc) -> docWrapNode lfield lineR = rFr <&> \(lfield, fText, fDoc) -> docWrapNode lfield
$ docCols ColRecUpdate $ docCols ColRecUpdate
[ docCommaSep [ docCommaSep
, appSep $ docLit $ fText , appSep $ docLit fText
, case fDoc of , case fDoc of
Just x -> docAlt Just x -> docAlt
[ docSeq [ appSep $ docLit $ Text.pack "=" [ docSeq [ appSep $ docLit $ Text.pack "="

View File

@ -94,14 +94,14 @@ layoutPat lpat@(L _ pat) = docWrapNode lpat $ case pat of
fExpDoc <- if pun fExpDoc <- if pun
then return Nothing then return Nothing
else Just <$> docSharedWrapper layoutPat fPat else Just <$> docSharedWrapper layoutPat fPat
return $ (lrdrNameToText lnameF, fExpDoc) return (lrdrNameToText lnameF, fExpDoc)
fmap Seq.singleton $ docSeq fmap Seq.singleton $ docSeq
[ appSep $ docLit t [ appSep $ docLit t
, appSep $ docLit $ Text.pack "{" , appSep $ docLit $ Text.pack "{"
, docSeq $ List.intersperse docCommaSep , docSeq $ List.intersperse docCommaSep
$ fds <&> \case $ fds <&> \case
(fieldName, Just fieldDoc) -> docSeq (fieldName, Just fieldDoc) -> docSeq
[ appSep $ docLit $ fieldName [ appSep $ docLit fieldName
, appSep $ docLit $ Text.pack "=" , appSep $ docLit $ Text.pack "="
, fieldDoc >>= colsWrapPat , fieldDoc >>= colsWrapPat
] ]
@ -123,13 +123,13 @@ layoutPat lpat@(L _ pat) = docWrapNode lpat $ case pat of
fExpDoc <- if pun fExpDoc <- if pun
then return Nothing then return Nothing
else Just <$> docSharedWrapper layoutPat fPat else Just <$> docSharedWrapper layoutPat fPat
return $ (lrdrNameToText lnameF, fExpDoc) return (lrdrNameToText lnameF, fExpDoc)
fmap Seq.singleton $ docSeq fmap Seq.singleton $ docSeq
[ appSep $ docLit t [ appSep $ docLit t
, appSep $ docLit $ Text.pack "{" , appSep $ docLit $ Text.pack "{"
, docSeq $ fds >>= \case , docSeq $ fds >>= \case
(fieldName, Just fieldDoc) -> (fieldName, Just fieldDoc) ->
[ appSep $ docLit $ fieldName [ appSep $ docLit fieldName
, appSep $ docLit $ Text.pack "=" , appSep $ docLit $ Text.pack "="
, fieldDoc >>= colsWrapPat , fieldDoc >>= colsWrapPat
, docCommaSep , docCommaSep
@ -167,7 +167,7 @@ layoutPat lpat@(L _ pat) = docWrapNode lpat $ case pat of
docAddBaseY BrIndentRegular $ docSeq docAddBaseY BrIndentRegular $ docSeq
[ appSep $ return xN [ appSep $ return xN
, appSep $ docLit $ Text.pack "::" , appSep $ docLit $ Text.pack "::"
, docForceSingleline $ tyDoc , docForceSingleline tyDoc
] ]
return $ xR Seq.|> xN' return $ xR Seq.|> xN'
ListPat elems _ _ -> ListPat elems _ _ ->
@ -205,7 +205,7 @@ wrapPatPrepend
wrapPatPrepend pat prepElem = do wrapPatPrepend pat prepElem = do
patDocs <- layoutPat pat patDocs <- layoutPat pat
case Seq.viewl patDocs of case Seq.viewl patDocs of
Seq.EmptyL -> return $ Seq.empty Seq.EmptyL -> return Seq.empty
x1 Seq.:< xR -> do x1 Seq.:< xR -> do
x1' <- docSeq [prepElem, return x1] x1' <- docSeq [prepElem, return x1]
return $ x1' Seq.<| xR return $ x1' Seq.<| xR