mirror of
https://github.com/google/ormolu.git
synced 2024-12-03 18:52:19 +03:00
Support transform list comprehensions
This commit is contained in:
parent
069ae69a5b
commit
9e880c5299
@ -0,0 +1,58 @@
|
|||||||
|
{-# LANGUAGE TransformListComp #-}
|
||||||
|
|
||||||
|
foo xs ys = [(x, y) | x <- xs, y <- ys, then reverse]
|
||||||
|
|
||||||
|
foo' xs ys =
|
||||||
|
[ ( x
|
||||||
|
, y
|
||||||
|
)
|
||||||
|
| x <- xs
|
||||||
|
, y <- ys
|
||||||
|
, -- First comment
|
||||||
|
then reverse -- Second comment
|
||||||
|
]
|
||||||
|
|
||||||
|
bar xs ys = [(x, y) | x <- xs, y <- ys, then sortWith by (x + y)]
|
||||||
|
|
||||||
|
bar' xs ys =
|
||||||
|
[ ( x
|
||||||
|
, y
|
||||||
|
)
|
||||||
|
| x <- xs
|
||||||
|
, y <- ys
|
||||||
|
, -- First comment
|
||||||
|
then sortWith
|
||||||
|
by
|
||||||
|
( x +
|
||||||
|
y -- Second comment
|
||||||
|
)
|
||||||
|
]
|
||||||
|
|
||||||
|
baz xs ys = [(x, y) | x <- xs, y <- ys, then group using permutations]
|
||||||
|
|
||||||
|
baz' xs ys =
|
||||||
|
[ ( x
|
||||||
|
, y
|
||||||
|
)
|
||||||
|
| x <- xs
|
||||||
|
, y <- ys
|
||||||
|
, -- First comment
|
||||||
|
then group using permutations -- Second comment
|
||||||
|
]
|
||||||
|
|
||||||
|
quux xs ys = [(x, y) | x <- xs, y <- ys, then group by (x + y) using groupWith]
|
||||||
|
|
||||||
|
quux' xs ys =
|
||||||
|
[ ( x
|
||||||
|
, y
|
||||||
|
)
|
||||||
|
| x <- xs
|
||||||
|
, y <- ys
|
||||||
|
, -- First comment
|
||||||
|
then group by
|
||||||
|
( x +
|
||||||
|
y
|
||||||
|
)
|
||||||
|
-- Second comment
|
||||||
|
using groupWith -- Third comment
|
||||||
|
]
|
@ -0,0 +1,55 @@
|
|||||||
|
{-# LANGUAGE TransformListComp #-}
|
||||||
|
|
||||||
|
foo xs ys = [(x, y) | x <- xs, y <- ys, then reverse]
|
||||||
|
|
||||||
|
foo' xs ys = [
|
||||||
|
(x,
|
||||||
|
y) |
|
||||||
|
x <- xs,
|
||||||
|
y <- ys,
|
||||||
|
then -- First comment
|
||||||
|
reverse -- Second comment
|
||||||
|
]
|
||||||
|
|
||||||
|
bar xs ys = [(x, y) | x <- xs, y <- ys, then sortWith by (x + y)]
|
||||||
|
|
||||||
|
bar' xs ys = [
|
||||||
|
(x,
|
||||||
|
y) |
|
||||||
|
x <- xs,
|
||||||
|
y <- ys,
|
||||||
|
then -- First comment
|
||||||
|
sortWith
|
||||||
|
by
|
||||||
|
(x
|
||||||
|
+ y) -- Second comment
|
||||||
|
]
|
||||||
|
|
||||||
|
baz xs ys = [(x, y) | x <- xs, y <- ys, then group using permutations]
|
||||||
|
|
||||||
|
baz' xs ys = [
|
||||||
|
(x,
|
||||||
|
y) |
|
||||||
|
x <- xs,
|
||||||
|
y <- ys,
|
||||||
|
then
|
||||||
|
group
|
||||||
|
using -- First comment
|
||||||
|
permutations -- Second comment
|
||||||
|
]
|
||||||
|
|
||||||
|
quux xs ys = [(x, y) | x <- xs, y <- ys, then group by (x + y) using groupWith]
|
||||||
|
|
||||||
|
quux' xs ys = [
|
||||||
|
(x,
|
||||||
|
y) |
|
||||||
|
x <- xs,
|
||||||
|
y <- ys,
|
||||||
|
then
|
||||||
|
group
|
||||||
|
by -- First comment
|
||||||
|
(x
|
||||||
|
+ y)
|
||||||
|
using -- Second comment
|
||||||
|
groupWith -- Third comment
|
||||||
|
]
|
@ -308,20 +308,60 @@ p_stmt' pretty = \case
|
|||||||
LetStmt NoExt binds -> do
|
LetStmt NoExt binds -> do
|
||||||
txt "let "
|
txt "let "
|
||||||
sitcc $ located binds p_hsLocalBinds
|
sitcc $ located binds p_hsLocalBinds
|
||||||
ParStmt NoExt stmts _ _ ->
|
ParStmt {} ->
|
||||||
sequence_ $ intersperse breakpoint $
|
-- NOTE 'ParStmt' should always be eliminated in 'gatherStmt' already,
|
||||||
withSep (txt "| ") p_parStmtBlock stmts
|
-- such that it never occurs in 'p_stmt''. Consequently, handling it
|
||||||
TransStmt {} -> notImplemented "TransStmt"
|
-- here would be redundant.
|
||||||
|
notImplemented "ParStmt"
|
||||||
|
TransStmt {..} -> do
|
||||||
|
-- NOTE 'TransStmt' only needs to account for pretty printing itself,
|
||||||
|
-- since pretty printing of relevant statements (e.g., in 'trS_stmts')
|
||||||
|
-- is handled through 'gatherStmt'.
|
||||||
|
case (trS_form, trS_by) of
|
||||||
|
(ThenForm, Nothing) -> located trS_using $ \x -> do
|
||||||
|
txt "then"
|
||||||
|
breakpoint
|
||||||
|
inci (p_hsExpr x)
|
||||||
|
(ThenForm, Just e) -> do
|
||||||
|
located trS_using $ \x -> do
|
||||||
|
txt "then"
|
||||||
|
breakpoint
|
||||||
|
inci (p_hsExpr x)
|
||||||
|
breakpoint
|
||||||
|
located e $ \x -> do
|
||||||
|
txt "by"
|
||||||
|
breakpoint
|
||||||
|
inci (p_hsExpr x)
|
||||||
|
(GroupForm, Nothing) -> located trS_using $ \x -> do
|
||||||
|
txt "then group using"
|
||||||
|
breakpoint
|
||||||
|
inci (p_hsExpr x)
|
||||||
|
(GroupForm, Just e) -> do
|
||||||
|
located e $ \x -> do
|
||||||
|
txt "then group by"
|
||||||
|
breakpoint
|
||||||
|
inci (p_hsExpr x)
|
||||||
|
breakpoint
|
||||||
|
located trS_using $ \x -> do
|
||||||
|
txt "using"
|
||||||
|
breakpoint
|
||||||
|
inci (p_hsExpr x)
|
||||||
RecStmt {..} -> do
|
RecStmt {..} -> do
|
||||||
txt "rec "
|
txt "rec "
|
||||||
sitcc $ newlineSep (located' (p_stmt' pretty)) recS_stmts
|
sitcc $ newlineSep (located' (p_stmt' pretty)) recS_stmts
|
||||||
XStmtLR {} -> notImplemented "XStmtLR"
|
XStmtLR {} -> notImplemented "XStmtLR"
|
||||||
|
|
||||||
p_parStmtBlock :: ParStmtBlock GhcPs GhcPs -> R ()
|
gatherStmt :: ExprLStmt GhcPs -> [[ExprLStmt GhcPs]]
|
||||||
p_parStmtBlock = \case
|
gatherStmt (L _ (ParStmt NoExt block _ _)) =
|
||||||
ParStmtBlock NoExt stmts _ _ ->
|
foldr ((<>) . gatherStmtBlock) [] block
|
||||||
velt $ withSep comma (located' (sitcc . p_stmt)) stmts
|
gatherStmt (L s stmt@TransStmt {..}) =
|
||||||
XParStmtBlock {} -> notImplemented "XParStmtBlock"
|
foldr liftAppend [] ((gatherStmt <$> trS_stmts) <> pure [[L s stmt]])
|
||||||
|
gatherStmt stmt = [[stmt]]
|
||||||
|
|
||||||
|
gatherStmtBlock :: ParStmtBlock GhcPs GhcPs -> [[ExprLStmt GhcPs]]
|
||||||
|
gatherStmtBlock (ParStmtBlock _ stmts _ _) =
|
||||||
|
foldr (liftAppend . gatherStmt) [] stmts
|
||||||
|
gatherStmtBlock XParStmtBlock {} = notImplemented "XParStmtBlock"
|
||||||
|
|
||||||
p_hsLocalBinds :: HsLocalBindsLR GhcPs GhcPs -> R ()
|
p_hsLocalBinds :: HsLocalBindsLR GhcPs GhcPs -> R ()
|
||||||
p_hsLocalBinds = \case
|
p_hsLocalBinds = \case
|
||||||
@ -468,14 +508,21 @@ p_hsExpr = \case
|
|||||||
newline
|
newline
|
||||||
inci $ located es (newlineSep (located' (sitcc . p_stmt)))
|
inci $ located es (newlineSep (located' (sitcc . p_stmt)))
|
||||||
compBody = brackets $ located es $ \xs -> do
|
compBody = brackets $ located es $ \xs -> do
|
||||||
let stmts = init xs
|
let p_parBody =
|
||||||
|
sequence_ .
|
||||||
|
intersperse breakpoint .
|
||||||
|
withSep (txt "| ") p_seqBody
|
||||||
|
p_seqBody =
|
||||||
|
sequence_ .
|
||||||
|
intersperse (vlayout (pure ()) newline) .
|
||||||
|
withSep comma (located' (sitcc . p_stmt))
|
||||||
|
stmts = init xs
|
||||||
yield = last xs
|
yield = last xs
|
||||||
|
lists = foldr (liftAppend . gatherStmt) [] stmts
|
||||||
located yield p_stmt
|
located yield p_stmt
|
||||||
breakpoint
|
breakpoint
|
||||||
txt "| "
|
txt "| "
|
||||||
case stmts of
|
p_parBody lists
|
||||||
[stmt] | ParStmt {} <- unLoc stmt -> located stmt p_stmt
|
|
||||||
_ -> velt $ withSep comma (located' (sitcc . p_stmt)) stmts
|
|
||||||
case ctx of
|
case ctx of
|
||||||
DoExpr -> doBody "do"
|
DoExpr -> doBody "do"
|
||||||
MDoExpr -> doBody "mdo"
|
MDoExpr -> doBody "mdo"
|
||||||
@ -757,6 +804,15 @@ p_hsBracket = \case
|
|||||||
----------------------------------------------------------------------------
|
----------------------------------------------------------------------------
|
||||||
-- Helpers
|
-- Helpers
|
||||||
|
|
||||||
|
-- | Append each element in both lists with semigroups. If one list is shorter
|
||||||
|
-- than the other, return the rest of the longer list unchanged.
|
||||||
|
|
||||||
|
liftAppend :: Semigroup a => [a] -> [a] -> [a]
|
||||||
|
liftAppend [] [] = []
|
||||||
|
liftAppend [] (y : ys) = y : ys
|
||||||
|
liftAppend (x : xs) [] = x : xs
|
||||||
|
liftAppend (x : xs) (y : ys) = x <> y : liftAppend xs ys
|
||||||
|
|
||||||
getGRHSSpan :: GRHS GhcPs (Located body) -> SrcSpan
|
getGRHSSpan :: GRHS GhcPs (Located body) -> SrcSpan
|
||||||
getGRHSSpan (GRHS NoExt _ body) = getLoc body
|
getGRHSSpan (GRHS NoExt _ body) = getLoc body
|
||||||
getGRHSSpan (XGRHS NoExt) = notImplemented "XGRHS"
|
getGRHSSpan (XGRHS NoExt) = notImplemented "XGRHS"
|
||||||
|
Loading…
Reference in New Issue
Block a user