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
(hackTransform $ Text.unpack inputText)
case parseResult of
Left err -> throwE $ [ErrorInput err]
Right x -> pure $ x
Left err -> throwE [ErrorInput err]
Right x -> pure x
(errsWarns, outputTextL) <- do
let omitCheck =
config

View File

@ -119,7 +119,7 @@ processDefault x = do
-- the module (header). This would remove the need for this hack!
case str of
"\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
-- at insertion position (meant to point out to the user that this node is
@ -174,7 +174,7 @@ briDocByExactInlineOnly infoStr ast = do
False
t
let errorAction = do
mTell $ [ErrorUnknownNode infoStr ast]
mTell [ErrorUnknownNode infoStr ast]
docLit
$ Text.pack "{- BRITTANY ERROR UNHANDLED SYNTACTICAL CONSTRUCT -}"
case (fallbackMode, Text.lines exactPrinted) of
@ -589,7 +589,7 @@ instance DocWrapable a => DocWrapable [a] where
docWrapNode ast bdsm = do
bds <- bdsm
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' <- docWrapNode ast (return bd)
return [bd']
@ -601,23 +601,23 @@ instance DocWrapable a => DocWrapable [a] where
docWrapNodePrior ast bdsm = do
bds <- bdsm
case bds of
[] -> return $ []
[] -> return []
(bd1:bdR) -> do
bd1' <- docWrapNodePrior ast (return bd1)
return $ (bd1':bdR)
return (bd1':bdR)
docWrapNodeRest ast bdsm = do
bds <- bdsm
case reverse bds of
[] -> return $ []
[] -> return []
(bdN:bdR) -> do
bdN' <- docWrapNodeRest ast (return bdN)
return $ reverse $ (bdN':bdR)
return $ reverse (bdN':bdR)
instance DocWrapable a => DocWrapable (Seq a) where
docWrapNode ast bdsm = do
bds <- bdsm
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
Seq.EmptyR -> do
bd1' <- docWrapNode ast (return bd1)
@ -629,14 +629,14 @@ instance DocWrapable a => DocWrapable (Seq a) where
docWrapNodePrior ast bdsm = do
bds <- bdsm
case Seq.viewl bds of
Seq.EmptyL -> return $ Seq.empty
Seq.EmptyL -> return Seq.empty
bd1 Seq.:< bdR -> do
bd1' <- docWrapNodePrior ast (return bd1)
return $ bd1' Seq.<| bdR
docWrapNodeRest ast bdsm = do
bds <- bdsm
case Seq.viewr bds of
Seq.EmptyR -> return $ Seq.empty
Seq.EmptyR -> return Seq.empty
bdR Seq.:> bdN -> do
bdN' <- docWrapNodeRest ast (return bdN)
return $ bdR Seq.|> bdN'
@ -647,19 +647,19 @@ instance DocWrapable ([BriDocNumbered], BriDocNumbered, a) where
if null bds
then do
bd' <- docWrapNode ast (return bd)
return $ (bds, bd', x)
return (bds, bd', x)
else do
bds' <- docWrapNodePrior ast (return bds)
bd' <- docWrapNodeRest ast (return bd)
return $ (bds', bd', x)
return (bds', bd', x)
docWrapNodePrior ast stuffM = do
(bds, bd, x) <- stuffM
bds' <- docWrapNodePrior ast (return bds)
return $ (bds', bd, x)
return (bds', bd, x)
docWrapNodeRest ast stuffM = do
(bds, bd, x) <- stuffM
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
:: Data.Data.Data ast => String -> ast -> ToBriDocM BriDocNumbered
unknownNodeError infoStr ast = do
mTell $ [ErrorUnknownNode infoStr ast]
mTell [ErrorUnknownNode infoStr ast]
docLit $ Text.pack "{- BRITTANY ERROR UNHANDLED SYNTACTICAL CONSTRUCT -}"
spacifyDocs :: [ToBriDocM BriDocNumbered] -> [ToBriDocM BriDocNumbered]

View File

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

View File

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