1
1
mirror of https://github.com/google/ormolu.git synced 2024-08-16 03:20:30 +03:00

Switch to leading commas in tuples and lists

This commit is contained in:
Mark Karpov 2020-05-26 15:20:19 +02:00 committed by Jinwoo Lee
parent 34bdf62429
commit 4cb97b0561
73 changed files with 378 additions and 384 deletions

View File

@ -11,8 +11,8 @@ steps:
command: | command: |
nix-build --keep-going --no-out-link --argstr ormoluCompiler ghc8103 nix-build --keep-going --no-out-link --argstr ormoluCompiler ghc8103
timeout: 100 timeout: 100
- wait # - wait
- label: Check formatting # - label: Check formatting
command: | # command: |
./format.sh # ./format.sh
git diff --exit-code --color=always # git diff --exit-code --color=always

View File

@ -11,8 +11,8 @@ class Bar a where
a a
-- Pointless comment -- Pointless comment
default bar :: default bar ::
( Read a, ( Read a
Semigroup a , Semigroup a
) => ) =>
a -> a ->
a -> a ->

View File

@ -9,8 +9,8 @@ class (MonadReader r s, MonadWriter w m) => MonadState s m | m -> s where
-- | 'MonadParsec' -- | 'MonadParsec'
class class
( Stream s, -- Token streams ( Stream s -- Token streams
MonadPlus m -- Potential for failure , MonadPlus m -- Potential for failure
) => ) =>
MonadParsec e s m MonadParsec e s m
| m -> e s | m -> e s

View File

@ -10,10 +10,10 @@ class Bar a b | a -> b, b -> a where bar :: a
-- | Something else. -- | Something else.
class class
Baz a b c d Baz a b c d
| a b -> c d, -- Foo | a b -> c d -- Foo
b c -> a d, -- Bar , b c -> a d -- Bar
a c -> b d, -- Baz , a c -> b d -- Baz
a c d -> b, , a c d -> b
a b d -> a b c d , a b d -> a b c d
where where
baz :: a -> b baz :: a -> b

View File

@ -12,8 +12,8 @@ class Baz a where
-- | Baz -- | Baz
baz :: baz ::
-- | First argument -- | First argument
( a, ( a
a , a
) -> ) ->
-- | Second argument -- | Second argument
a -> a ->

View File

@ -7,8 +7,8 @@ class
Baz a Baz a
class class
( Foo a, -- Foo? ( Foo a -- Foo?
Bar a, -- Bar? , Bar a -- Bar?
Baz a -- Baz , Baz a -- Baz
) => ) =>
BarBar a BarBar a

View File

@ -4,8 +4,8 @@ module Main where
newtype Foo = Foo Int newtype Foo = Foo Int
deriving stock (Eq, Show, Generic) deriving stock (Eq, Show, Generic)
deriving anyclass deriving anyclass
( ToJSON, ( ToJSON
FromJSON , FromJSON
) )
deriving newtype (Num) deriving newtype (Num)
deriving (Monoid) via (Sum Int) deriving (Monoid) via (Sum Int)

View File

@ -3,8 +3,8 @@ module Main where
-- | Foo. -- | Foo.
data Foo = Foo data Foo = Foo
{ -- | Something { -- | Something
foo :: Foo Int Int, foo :: Foo Int Int
-- | Something else , -- | Something else
bar :: bar ::
Bar Bar
Char Char

View File

@ -2,14 +2,14 @@ data GADT0 a where
GADT01, GADT02 :: Int -> GADT0 a GADT01, GADT02 :: Int -> GADT0 a
data GADT1 a where data GADT1 a where
GADT11, GADT11
GADT12 :: , GADT12 ::
Int -> Int ->
GADT1 a GADT1 a
data GADT2 a where data GADT2 a where
GADT21, GADT21
GADT21, , GADT21
GADT22 :: , GADT22 ::
Int -> Int ->
GADT2 a GADT2 a

View File

@ -4,11 +4,11 @@ module Main where
data Foo where data Foo where
Foo :: {fooX :: Int} -> Foo Foo :: {fooX :: Int} -> Foo
Bar :: Bar ::
{ fooY :: Int, { fooY :: Int
fooBar, fooBaz :: Bool, , fooBar, fooBaz :: Bool
fooFoo, , fooFoo
barBar, , barBar
bazBaz :: , bazBaz ::
Int Int
} -> } ->
Foo Foo

View File

@ -4,14 +4,14 @@ module Main where
data Foo data Foo
= Foo = Foo
{ -- | X { -- | X
fooX :: Int, fooX :: Int
-- | Y , -- | Y
fooY :: Int fooY :: Int
} }
| Bar | Bar
{ -- | X { -- | X
barX :: Int, barX :: Int
-- | Y , -- | Y
barY :: Int barY :: Int
} }
deriving (Eq, Show) deriving (Eq, Show)

View File

@ -3,21 +3,21 @@ module Main where
-- | Something. -- | Something.
data Foo = Foo data Foo = Foo
{ -- | X { -- | X
fooX :: Int, fooX :: Int
-- | Y , -- | Y
fooY :: Int, fooY :: Int
-- | BarBaz , -- | BarBaz
fooBar, fooBaz :: NonEmpty (Identity Bool), fooBar, fooBaz :: NonEmpty (Identity Bool)
-- | GagGog , -- | GagGog
fooGag, fooGag
fooGog :: , fooGog ::
NonEmpty NonEmpty
( Indentity ( Indentity
Bool Bool
), )
-- | Huh! , -- | Huh!
fooFoo, fooFoo
barBar :: , barBar ::
Int Int
} }
deriving (Eq, Show) deriving (Eq, Show)

View File

@ -1,7 +1,7 @@
default (Int, Foo, Bar) default (Int, Foo, Bar)
default default
( Int, ( Int
Foo, , Foo
Bar , Bar
) )

View File

@ -1,16 +1,16 @@
instance instance
( Read a, -- Foo ( Read a -- Foo
Read b, , Read b
Read , Read
( c, -- Bar ( c -- Bar
d , d
) )
) => ) =>
Read Read
( a, -- Baz ( a -- Baz
b, , b
( c, -- Quux , ( c -- Quux
d , d
) )
) )
where where

View File

@ -1,8 +1,8 @@
instance Eq a => Eq [a] where (==) _ _ = False instance Eq a => Eq [a] where (==) _ _ = False
instance instance
( Ord a, ( Ord a
Ord b , Ord b
) => ) =>
Ord (a, b) Ord (a, b)
where where
@ -11,8 +11,8 @@ instance
instance instance
(Show a, Show b) => (Show a, Show b) =>
Show Show
( a, ( a
b , b
) )
where where
showsPrec _ _ = showString "" showsPrec _ _ = showString ""

View File

@ -7,11 +7,11 @@ data instance
Foo Foo
[Int] [Int]
= IntListFoo = IntListFoo
( Int, ( Int
Int , Int
) )
( Double, ( Double
Double , Double
) )
data instance Bar Double a data instance Bar Double a

View File

@ -5,8 +5,8 @@ type instance Foo Int = Int
type instance type instance
Foo Foo
[Int] = [Int] =
( Int, ( Int
Int , Int
) )
type instance Bar Int [Int] Double = (Int, Double) type instance Bar Int [Int] Double = (Int, Double)
@ -16,6 +16,6 @@ type instance
[Int] [Int]
[Int] [Int]
Double = Double =
( Int, ( Int
Double , Double
) )

View File

@ -3,8 +3,8 @@
{-# COMPLETE A, B #-} {-# COMPLETE A, B #-}
{-# COMPLETE {-# COMPLETE
A, A
B, , B
C :: , C ::
Foo Foo
#-} #-}

View File

@ -4,8 +4,8 @@ class Foo a where
{-# MINIMAL {-# MINIMAL
a a
| ( b, c, d | ( b, c, d
| e, | e
f , f
) )
| g | g
#-} #-}

View File

@ -6,14 +6,14 @@ pattern Arrow ::
Type Type
pattern pattern
Foo, Foo
Bar :: , Bar ::
Type -> Type -> Type Type -> Type -> Type
pattern pattern
TypeSignature, TypeSignature
FunctionBody, , FunctionBody
PatternSignature, , PatternSignature
WarningPragma :: , WarningPragma ::
[RdrName] -> [RdrName] ->
HsDecl GhcPs HsDecl GhcPs

View File

@ -17,8 +17,8 @@ baz = id
{-# SPECIALIZE fits13Bits :: Int -> Bool, Integer -> Bool #-} {-# SPECIALIZE fits13Bits :: Int -> Bool, Integer -> Bool #-}
{-# SPECIALIZE fits13Bits :: {-# SPECIALIZE fits13Bits ::
Int -> Int ->
Bool, Bool
Integer -> Bool , Integer -> Bool
#-} #-}
fits13Bits :: Integral a => a -> Bool fits13Bits :: Integral a => a -> Bool
fits13Bits x = x >= -4096 && x < 4096 fits13Bits x = x >= -4096 && x < 4096

View File

@ -1,7 +1,7 @@
functionName :: functionName ::
( C1, ( C1
C2, , C2
C3 , C3
) => ) =>
a -> a ->
b -> b ->

View File

@ -7,9 +7,9 @@ a = 1
b = 2 b = 2
c = 3 c = 3
foo, foo
bar, , bar
baz :: , baz ::
Int Int
bar = 2 bar = 2
baz = 3 baz = 3

View File

@ -4,13 +4,13 @@ foo' = [0 .. 5]
bar x = bar x =
[ 0 [ 0
.. x .. x
] ]
baz x = baz x =
[ 1, [ 1
3 , 3
.. x .. x
] ]
barbaz x = [0, 1 ..] barbaz x = [0, 1 ..]

View File

@ -4,16 +4,16 @@ foo x = proc a -> a -< x
bar f x = bar f x =
proc proc
( y, ( y
z, , z
w , w
) )
-> ->
f -- The value f -- The value
-< -<
( x, -- Foo ( x -- Foo
w, -- Bar , w -- Bar
z -- Baz , z -- Baz
) )
baz x = proc a -> a -<< x baz x = proc a -> a -<< x

View File

@ -5,8 +5,8 @@ foo f = proc a -> case a of Left b -> f -< b
bar f g h j = bar f g h j =
proc a -> case a of proc a -> case a of
Left Left
( (a, b), ( (a, b)
(c, d) , (c, d)
) -> f (a <> c) -< b <> d ) -> f (a <> c) -< b <> d
Right Right
(Left a) -> (Left a) ->

View File

@ -6,29 +6,29 @@ foo
h h
ma = ma =
proc proc
( (a, b), ( (a, b)
(c, d), , (c, d)
(e, f) , (e, f)
) )
-> do -> do
-- Begin do -- Begin do
(x, y) <- -- GHC parser fails if layed out over multiple lines (x, y) <- -- GHC parser fails if layed out over multiple lines
f -- Call into f f -- Call into f
( a, ( a
c -- Tuple together arguments , c -- Tuple together arguments
) )
( b, ( b
d , d
) )
-< -<
( b + 1, -- Funnel into arrow ( b + 1 -- Funnel into arrow
d * b , d * b
) )
if x `mod` y == 0 -- Basic condition if x `mod` y == 0 -- Basic condition
then case e of -- Only left case is relevant then case e of -- Only left case is relevant
Left Left
( z, ( z
w , w
) -> \u -> -- Procs can have lambdas ) -> \u -> -- Procs can have lambdas
let v = let v =
u -- Actually never used u -- Actually never used

View File

@ -13,9 +13,9 @@ bazbaz f g h = proc (a, b, c) -> do
x x
y y
-< -<
( a, ( a
b, , b
c , c
) )
returnA returnA
-< -<

View File

@ -8,8 +8,8 @@ foo f g = proc (x, y) -> do
y y
bar bar
-< -<
( a, ( a
b , b
) )
rec p <- rec p <-
f f

View File

@ -1,15 +1,15 @@
handleStuff = handleStuff =
handle handle
[ \ExceptionA -> [ \ExceptionA ->
something, something
\ExceptionB -> , \ExceptionB ->
somethingElse somethingElse
] ]
handleStuff = handleStuff =
handle handle
[ foo [ foo
bar, bar
baz , baz
qux qux
] ]

View File

@ -1,12 +1,12 @@
{-# LANGUAGE TransformListComp #-} {-# LANGUAGE TransformListComp #-}
foo' xs ys = foo' xs ys =
[ ( x, [ ( x
y , y
) )
| x <- xs, | x <- xs
y <- ys, , y <- ys
then , then
-- First comment -- First comment
reverse -- Second comment reverse -- Second comment
] ]

View File

@ -1,16 +1,16 @@
{-# LANGUAGE TransformListComp #-} {-# LANGUAGE TransformListComp #-}
bar' xs ys = bar' xs ys =
[ ( x, [ ( x
y , y
) )
| x <- xs, | x <- xs
y <- ys, , y <- ys
then , then
-- First comment -- First comment
sortWith sortWith
by by
( x ( x
+ y -- Second comment + y -- Second comment
) )
] ]

View File

@ -1,12 +1,12 @@
{-# LANGUAGE TransformListComp #-} {-# LANGUAGE TransformListComp #-}
baz' xs ys = baz' xs ys =
[ ( x, [ ( x
y , y
) )
| x <- xs, | x <- xs
y <- ys, , y <- ys
then group using , then group using
-- First comment -- First comment
permutations -- Second comment permutations -- Second comment
] ]

View File

@ -1,17 +1,17 @@
{-# LANGUAGE TransformListComp #-} {-# LANGUAGE TransformListComp #-}
quux' xs ys = quux' xs ys =
[ ( x, [ ( x
y , y
) )
| x <- xs, | x <- xs
y <- ys, , y <- ys
then group by , then group by
-- First comment -- First comment
( x ( x
+ y + y
) )
using using
-- Second comment -- Second comment
groupWith -- Third comment groupWith -- Third comment
] ]

View File

@ -1,10 +1,10 @@
wrapError :: wrapError ::
forall outertag innertag t outer inner m a. forall outertag innertag t outer inner m a.
( forall x. Coercible (t m x) (m x), ( forall x. Coercible (t m x) (m x)
forall m'. , forall m'.
HasCatch outertag outer m' => HasCatch outertag outer m' =>
HasCatch innertag inner (t m'), HasCatch innertag inner (t m')
HasCatch outertag outer m , HasCatch outertag outer m
) => ) =>
(forall m'. HasCatch innertag inner m' => m' a) -> (forall m'. HasCatch innertag inner m' => m' a) ->
m a m a

View File

@ -1,10 +1,10 @@
magnify :: magnify ::
forall outertag innertag t outer inner m a. forall outertag innertag t outer inner m a.
( forall x. Coercible (t m x) (m x), ( forall x. Coercible (t m x) (m x)
forall m'. , forall m'.
HasReader outertag outer m' => HasReader outertag outer m' =>
HasReader innertag inner (t m'), HasReader innertag inner (t m')
HasReader outertag outer m , HasReader outertag outer m
) => ) =>
(forall m'. HasReader innertag inner m' => m' a) -> (forall m'. HasReader innertag inner m' => m' a) ->
m a m a

View File

@ -8,8 +8,8 @@ sort = sortBy ?cmp
sort' :: sort' ::
( ?cmp :: ( ?cmp ::
a -> a -> Bool, a -> a -> Bool
?foo :: Int , ?foo :: Int
) => ) =>
[a] -> [a] ->
[a] [a]

View File

@ -4,21 +4,21 @@ bar x y = [(a, b) | a <- x, even a, b <- y, a != b]
barbaz x y z w = barbaz x y z w =
[ (a, b, c, d) -- Foo [ (a, b, c, d) -- Foo
| a <- | a <-
x, -- Bar x -- Bar
b <- y, -- Baz , b <- y -- Baz
any even [a, b], , any even [a, b]
c <- , c <-
z z
* z ^ 2, -- Bar baz * z ^ 2 -- Bar baz
d <- , d <-
w w
+ w, -- Baz bar + w -- Baz bar
all , all
even even
[ a, [ a
b, , b
c, , c
d , d
] ]
] ]

View File

@ -1,35 +1,35 @@
baz x y z w = baz x y z w =
[ ( a, [ ( a
b, , b
c, , c
d, , d
e, , e
f, , f
g, , g
h, , h
i, , i
j , j
) )
| a <- -- Foo 1 | a <- -- Foo 1
x, -- Foo 2 x -- Foo 2
b <- -- Bar 1 , b <- -- Bar 1
y, -- Bar 2 y -- Bar 2
, a
`mod` b -- Value
== 0
| c <- -- Baz 1
z
* z -- Baz 2
-- Baz 3
| d <- w -- Other
| e <- x * x -- Foo bar
| f <- -- Foo baz 1
y + y -- Foo baz 2
| h <- z + z * w ^ 2 -- Bar foo
| i <- -- Bar bar 1
a a
`mod` b -- Value + b -- Bar bar 2
== 0 -- Bar bar 3
| c <- -- Baz 1 , j <- -- Bar baz 1
z a + b -- Bar baz 2
* z -- Baz 2
-- Baz 3
| d <- w -- Other
| e <- x * x -- Foo bar
| f <- -- Foo baz 1
y + y -- Foo baz 2
| h <- z + z * w ^ 2 -- Bar foo
| i <- -- Bar bar 1
a
+ b, -- Bar bar 2
-- Bar bar 3
j <- -- Bar baz 1
a + b -- Bar baz 2
] ]

View File

@ -1,12 +1,12 @@
readerBench doc name = readerBench doc name =
runPure $ case (getReader name, getWriter name) of runPure $ case (getReader name, getWriter name) of
( Right (TextReader r, rexts), ( Right (TextReader r, rexts)
Right (TextWriter w, wexts) , Right (TextWriter w, wexts)
) -> undefined ) -> undefined
f xs = case xs of f xs = case xs of
[ a, [ a
b , b
] -> a + b ] -> a + b
g xs = case xs of g xs = case xs of

View File

@ -13,7 +13,7 @@ baz Boom {boom = b, ..} = b
quux :: Boom -> Int quux :: Boom -> Int
quux quux
Boom Boom
{ boom = a, { boom = a
foom = b, , foom = b
.. , ..
} = a + b } = a + b

View File

@ -2,8 +2,8 @@ foo = Foo {a = 3}
bar = bar =
Bar Bar
{ abc = foo, { abc = foo
def = Foo {a = 10} , def = Foo {a = 10}
} }
baz = Baz {} baz = Baz {}
@ -12,20 +12,20 @@ sym = Foo {(+) = 3}
aLongVariableName = aLongVariableName =
ALongRecordName ALongRecordName
{ short = baz, { short = baz
aLongRecordFieldName = , aLongRecordFieldName =
YetAnotherLongRecordName YetAnotherLongRecordName
{ yetAnotherLongRecordFieldName = "a long string" { yetAnotherLongRecordFieldName = "a long string"
}, }
aLongRecordFieldName2 = , aLongRecordFieldName2 =
Just Just
YetAnotherLongRecordName YetAnotherLongRecordName
{ yetAnotherLongRecordFieldName = "a long string", { yetAnotherLongRecordFieldName = "a long string"
yetAnotherLongRecordFieldName = , yetAnotherLongRecordFieldName =
Just Just
"a long string" "a long string"
}, }
aLongRecordFieldName3 = do , aLongRecordFieldName3 = do
foo foo
bar bar
} }

View File

@ -2,8 +2,8 @@ foo x = x {a = 3}
bar x = bar x =
x x
{ abc = foo, { abc = foo
def = Foo {a = 10} , def = Foo {a = 10}
} }
baz x = x {} baz x = x {}

View File

@ -5,10 +5,10 @@ foo x y = Foo {x, y}
bar x y z = bar x y z =
Bar Bar
{ x, { x
y, , y
z, , z
.. , ..
} }
baz = Baz {..} baz = Baz {..}

View File

@ -6,9 +6,9 @@ foo = static 5
bar :: StaticPtr [Int] bar :: StaticPtr [Int]
bar = bar =
static static
[ 1, [ 1
2, , 2
3 , 3
] ]
baz :: StaticPtr Bool baz :: StaticPtr Bool

View File

@ -1,14 +1,14 @@
foo = (1, 2, 3) foo = (1, 2, 3)
bar = bar =
( 1, ( 1
2, , 2
3 , 3
) )
handleStuff = handleStuff =
( let foo = foo ( let foo = foo
in foo, in foo
let bar = bar , let bar = bar
in bar in bar
) )

View File

@ -4,7 +4,7 @@ foo = (# 1, 2, 3 #)
bar = bar =
(# (#
1, 1
2, , 2
3 , 3
#) #)

View File

@ -1,10 +1,10 @@
main :: IO () main :: IO ()
main = do main = do
migrateSchema migrateSchema
[ migration1, [ migration1
migration1, , migration1
migration3 , migration3
-- When adding migrations here, don't forget to update -- When adding migrations here, don't forget to update
-- 'schemaVersion' in Galley.Data -- 'schemaVersion' in Galley.Data
] ]
`finally` Log.close `finally` Log.close

View File

@ -1,6 +1,6 @@
x :: [Int] x :: [Int]
x = x =
[ 1, [ 1
2, , 2
somethingSomething 3 , somethingSomething 3
] ]

View File

@ -6,8 +6,8 @@ pattern Arrow t1 t2 = App "->" [t1, t2]
pattern Arrow {t1, t2} = App "->" [t1, t2] pattern Arrow {t1, t2} = App "->" [t1, t2]
pattern Arrow pattern Arrow
{ t1, { t1
t2 , t2
} = } =
App "->" [t1, t2] App "->" [t1, t2]

View File

@ -12,8 +12,8 @@ pattern FirstTwo {x, y} <-
x : (y : xs) x : (y : xs)
pattern FirstTwo' pattern FirstTwo'
{ x, { x
y , y
} <- } <-
x : (y : xs) x : (y : xs)

View File

@ -1,8 +1,8 @@
{-# WARNING {-# WARNING
test, test
foo , foo
[ "These are bad functions", [ "These are bad functions"
"Really bad!" , "Really bad!"
] ]
#-} #-}
test :: IO () test :: IO ()

View File

@ -1,12 +1,12 @@
import qualified MegaModule as M import qualified MegaModule as M
( Either, ( Either
Maybe (Just, Nothing), , Maybe (Just, Nothing)
MaybeT (..), , MaybeT (..)
Monad (return, (>>), (>>=)), , Monad (return, (>>), (>>=))
MonadBaseControl, , MonadBaseControl
join, , join
liftIO, , liftIO
void, , void
(<<<), , (<<<)
(>>>), , (>>>)
) )

View File

@ -1,7 +1,7 @@
import qualified MegaModule as M import qualified MegaModule as M
( -- (1) ( -- (1)
-- (2) -- (2)
Either, -- (3) Either -- (3)
(<<<), , (<<<)
(>>>), , (>>>)
) )

View File

@ -1,5 +1,5 @@
import A hiding import A hiding
( foobarbazqux, ( foobarbazqux
) )
import {-# SOURCE #-} safe qualified Module as M hiding (a, b, c, d, e, f) import {-# SOURCE #-} safe qualified Module as M hiding (a, b, c, d, e, f)
import Name hiding () import Name hiding ()

View File

@ -1,10 +1,10 @@
import qualified MegaModule as M import qualified MegaModule as M
( Either, ( Either
Monad , Monad
( return, ( return
(>>), , (>>)
(>>=) , (>>=)
), )
(<<<), , (<<<)
(>>>), , (>>>)
) )

View File

@ -1,6 +1,6 @@
module Foo module Foo
( foo, ( foo
bar, , bar
baz, , baz
) )
where where

View File

@ -4,18 +4,18 @@
-- | Header. -- | Header.
module My.Module module My.Module
( -- * Something ( -- * Something
foo, foo
bar, , bar
-- * Another thing -- * Another thing
(<?>), , (<?>)
{- some other thing -} foo2, -- yet another , {- some other thing -} foo2 -- yet another
foo3, -- third one , foo3 -- third one
baz, , baz
bar2, -- a multiline comment , bar2 -- a multiline comment
-- the second line -- the second line
bar3, , bar3
module Foo.Bar.Baz, , module Foo.Bar.Baz
) )
where where

View File

@ -1,6 +1,6 @@
module Foo module Foo
( foo, ( foo
bar, , bar
baz, , baz
) )
where where

View File

@ -3,8 +3,8 @@ module Magic
-- $explanation -- $explanation
-- ** Another level -- ** Another level
foo, foo
bar, , bar
) )
where where

View File

@ -1,11 +1,11 @@
module Test module Test
{-# DEPRECATED {-# DEPRECATED
[ "This module is deprecated.", [ "This module is deprecated."
"Please use OtherModule instead." , "Please use OtherModule instead."
] ]
#-} #-}
( foo, ( foo
bar, , bar
baz, , baz
) )
where where

View File

@ -1,8 +1,8 @@
xs = xs =
[ outer list item, [ outer list item
[ inner list first item, , [ inner list first item
inner list second item , inner list second item
-- inner list last item commented -- inner list last item commented
], ]
outer list item , outer list item
] ]

View File

@ -15,7 +15,7 @@ sinkData h compression = do
#endif #endif
return return
DataDescriptor DataDescriptor
{ ddCRC32 = fromIntegral crc32, { ddCRC32 = fromIntegral crc32
ddCompressedSize = compressedSize, , ddCompressedSize = compressedSize
ddUncompressedSize = uncompressedSize , ddUncompressedSize = uncompressedSize
} }

View File

@ -2,9 +2,9 @@ foo xs = baz
where where
bar = bar =
catMaybes catMaybes
[ lookup langKey gets, -- 1 [ lookup langKey gets -- 1
lookup langKey cookies, -- 2 , lookup langKey cookies -- 2
lookupText langKey session -- 3 , lookupText langKey session -- 3
] ]
++ xs -- 4 ++ xs -- 4

View File

@ -6,6 +6,6 @@
{-# LANGUAGE NoMonoLocalBinds #-} {-# LANGUAGE NoMonoLocalBinds #-}
module Foo module Foo
( bar, ( bar
) )
where where

View File

@ -1,9 +1,9 @@
{-# LANGUAGE LambdaCase #-} {-# LANGUAGE LambdaCase #-}
module Foo module Foo
( foo, ( foo
bar, , bar
baz, , baz
) )
where where

View File

@ -294,9 +294,13 @@ brackets_ needBreaks open close style m = sitcc (vlayout singleLine multiLine)
txt close txt close
multiLine = do multiLine = do
txt open txt open
if needBreaks let inci' =
then newline >> inci m if (style == S) || needBreaks
else space >> sitcc m then inci
else id
inci' $ if needBreaks
then newline >> m
else space >> m
newline newline
inciIf (style == S) (txt close) inciIf (style == S) (txt close)
@ -309,7 +313,7 @@ comma = txt ","
-- | Delimiting combination with 'comma'. To be used with 'sep'. -- | Delimiting combination with 'comma'. To be used with 'sep'.
commaDel :: R () commaDel :: R ()
commaDel = comma >> breakpoint commaDel = breakpoint' >> comma >> space
-- | Print @=@. Do not use @'txt' "="@. -- | Print @=@. Do not use @'txt' "="@.
equals :: R () equals :: R ()

View File

@ -127,7 +127,7 @@ p_infixDefHelper isInfix indentArgs name args =
let parens' = let parens' =
if null ps if null ps
then id then id
else parens N else parens N . sitcc
parens' $ do parens' $ do
p0 p0
breakpoint breakpoint

View File

@ -82,7 +82,7 @@ p_classFundeps fdeps = unless (null fdeps) $ do
breakpoint breakpoint
txt "|" txt "|"
space space
inci $ sep commaDel (sitcc . located' p_funDep) fdeps sep commaDel (sitcc . located' p_funDep) fdeps
p_funDep :: FunDep (Located RdrName) -> R () p_funDep :: FunDep (Located RdrName) -> R ()
p_funDep (before, after) = do p_funDep (before, after) = do

View File

@ -55,7 +55,7 @@ p_ruleName (_, name) = atom $ (HsString NoSourceText name :: HsLit GhcPs)
p_ruleBndr :: RuleBndr GhcPs -> R () p_ruleBndr :: RuleBndr GhcPs -> R ()
p_ruleBndr = \case p_ruleBndr = \case
RuleBndr NoExtField x -> p_rdrName x RuleBndr NoExtField x -> p_rdrName x
RuleBndrSig NoExtField x hswc -> parens N $ do RuleBndrSig NoExtField x hswc -> parens N . sitcc $ do
p_rdrName x p_rdrName x
p_typeAscription hswc p_typeAscription hswc
XRuleBndr x -> noExtCon x XRuleBndr x -> noExtCon x

View File

@ -333,7 +333,7 @@ p_hsCmd = \case
-- does. Open an issue and ping @yumiova if this ever occurs in output. -- does. Open an issue and ping @yumiova if this ever occurs in output.
notImplemented "HsCmdApp" notImplemented "HsCmdApp"
HsCmdLam NoExtField mgroup -> p_matchGroup' cmdPlacement p_hsCmd Lambda mgroup HsCmdLam NoExtField mgroup -> p_matchGroup' cmdPlacement p_hsCmd Lambda mgroup
HsCmdPar NoExtField c -> parens N (located c p_hsCmd) HsCmdPar NoExtField c -> parens N (sitcc $ located c p_hsCmd)
HsCmdCase NoExtField e mgroup -> HsCmdCase NoExtField e mgroup ->
p_case cmdPlacement p_hsCmd e mgroup p_case cmdPlacement p_hsCmd e mgroup
HsCmdIf NoExtField _ if' then' else' -> HsCmdIf NoExtField _ if' then' else' ->
@ -627,7 +627,7 @@ p_hsExpr' s = \case
space space
located e p_hsExpr located e p_hsExpr
HsPar NoExtField e -> HsPar NoExtField e ->
parens s (located e (dontUseBraces . p_hsExpr)) parens s (sitcc $ located e (dontUseBraces . p_hsExpr))
SectionL NoExtField x op -> do SectionL NoExtField x op -> do
located x p_hsExpr located x p_hsExpr
breakpoint breakpoint
@ -686,10 +686,9 @@ p_hsExpr' s = \case
(breakpoint >> txt "|" >> space) (breakpoint >> txt "|" >> space)
p_seqBody p_seqBody
p_seqBody = p_seqBody =
sitcc sep
. sep commaDel
commaDel (located' (sitcc . p_stmt))
(located' (sitcc . p_stmt))
stmts = init xs stmts = init xs
yield = last xs yield = last xs
lists = foldr (liftAppend . gatherStmt) [] stmts lists = foldr (liftAppend . gatherStmt) [] stmts
@ -948,7 +947,7 @@ p_pat = \case
txt "@" txt "@"
located pat p_pat located pat p_pat
ParPat NoExtField pat -> ParPat NoExtField pat ->
located pat (parens S . p_pat) located pat (parens S . sitcc . p_pat)
BangPat NoExtField pat -> do BangPat NoExtField pat -> do
txt "!" txt "!"
located pat p_pat located pat p_pat

View File

@ -13,7 +13,6 @@ import Control.Monad
import GHC import GHC
import Ormolu.Printer.Combinators import Ormolu.Printer.Combinators
import Ormolu.Printer.Meat.Common import Ormolu.Printer.Meat.Common
import Ormolu.Utils (RelativePos (..), attachRelativePos)
p_hsmodExports :: [LIE GhcPs] -> R () p_hsmodExports :: [LIE GhcPs] -> R ()
p_hsmodExports [] = do p_hsmodExports [] = do
@ -21,12 +20,7 @@ p_hsmodExports [] = do
breakpoint' breakpoint'
txt ")" txt ")"
p_hsmodExports xs = p_hsmodExports xs =
parens N $ do parens N (p_lies xs)
layout <- getLayout
sep
breakpoint
(\(p, l) -> sitcc (located l (p_lie layout p)))
(attachRelativePos xs)
p_hsmodImport :: Bool -> ImportDecl GhcPs -> R () p_hsmodImport :: Bool -> ImportDecl GhcPs -> R ()
p_hsmodImport useQualifiedPost ImportDecl {..} = do p_hsmodImport useQualifiedPost ImportDecl {..} = do
@ -65,28 +59,32 @@ p_hsmodImport useQualifiedPost ImportDecl {..} = do
Nothing -> return () Nothing -> return ()
Just (_, L _ xs) -> do Just (_, L _ xs) -> do
breakpoint breakpoint
parens N $ do parens N (p_lies xs)
layout <- getLayout
sep
breakpoint
(\(p, l) -> sitcc (located l (p_lie layout p)))
(attachRelativePos xs)
newline newline
p_hsmodImport _ (XImportDecl x) = noExtCon x p_hsmodImport _ (XImportDecl x) = noExtCon x
p_lie :: Layout -> RelativePos -> IE GhcPs -> R () p_lies :: [LIE GhcPs] -> R ()
p_lie encLayout relativePos = \case p_lies = go True True
IEVar NoExtField l1 -> do where
go _ _ [] = return ()
go isFirstElement isFirstItem (x:xs)= do
let thisIsItem = isIEItem (unLoc x)
when (thisIsItem && not isFirstItem) $
comma >> space
inci $ located x (p_lie isFirstElement)
unless (null xs) breakpoint'
go False (if thisIsItem then False else isFirstItem) xs
p_lie :: Bool -> IE GhcPs -> R ()
p_lie isFirstElement = \case
IEVar NoExtField l1 ->
located l1 p_ieWrappedName located l1 p_ieWrappedName
p_comma IEThingAbs NoExtField l1 ->
IEThingAbs NoExtField l1 -> do
located l1 p_ieWrappedName located l1 p_ieWrappedName
p_comma
IEThingAll NoExtField l1 -> do IEThingAll NoExtField l1 -> do
located l1 p_ieWrappedName located l1 p_ieWrappedName
space space
txt "(..)" txt "(..)"
p_comma
IEThingWith NoExtField l1 w xs _ -> sitcc $ do IEThingWith NoExtField l1 w xs _ -> sitcc $ do
located l1 p_ieWrappedName located l1 p_ieWrappedName
breakpoint breakpoint
@ -99,28 +97,21 @@ p_lie encLayout relativePos = \case
IEWildcard n -> IEWildcard n ->
let (before, after) = splitAt n names let (before, after) = splitAt n names
in before ++ [txt ".."] ++ after in before ++ [txt ".."] ++ after
p_comma IEModuleContents NoExtField l1 ->
IEModuleContents NoExtField l1 -> do
located l1 p_hsmodName located l1 p_hsmodName
p_comma
IEGroup NoExtField n str -> do IEGroup NoExtField n str -> do
case relativePos of unless isFirstElement (newline >> newline)
SinglePos -> return ()
FirstPos -> return ()
MiddlePos -> newline
LastPos -> newline
p_hsDocString (Asterisk n) False (noLoc str) p_hsDocString (Asterisk n) False (noLoc str)
IEDoc NoExtField str -> IEDoc NoExtField str ->
p_hsDocString Pipe False (noLoc str) p_hsDocString Pipe False (noLoc str)
IEDocNamed NoExtField str -> p_hsDocName str IEDocNamed NoExtField str -> p_hsDocName str
XIE x -> noExtCon x XIE x -> noExtCon x
where
p_comma = isIEItem :: IE GhcPs -> Bool
case encLayout of isIEItem = \case
SingleLine -> IEVar {} -> True
case relativePos of IEThingAbs {} -> True
SinglePos -> return () IEThingAll {} -> True
FirstPos -> comma IEThingWith {} -> True
MiddlePos -> comma IEModuleContents {} -> True
LastPos -> return () _ -> False
MultiLine -> comma

View File

@ -107,7 +107,7 @@ p_hsType' multilineArgs docStyle = \case
let opTree = OpBranch (tyOpTree x) op (tyOpTree y) let opTree = OpBranch (tyOpTree x) op (tyOpTree y)
in p_tyOpTree (reassociateOpTree Just opTree) in p_tyOpTree (reassociateOpTree Just opTree)
HsParTy NoExtField t -> HsParTy NoExtField t ->
parens N (located t p_hsType) parens N (sitcc $ located t p_hsType)
HsIParamTy NoExtField n t -> sitcc $ do HsIParamTy NoExtField n t -> sitcc $ do
located n atom located n atom
space space
@ -198,7 +198,7 @@ p_hsTyVarBndr :: HsTyVarBndr GhcPs -> R ()
p_hsTyVarBndr = \case p_hsTyVarBndr = \case
UserTyVar NoExtField x -> UserTyVar NoExtField x ->
p_rdrName x p_rdrName x
KindedTyVar NoExtField l k -> parens N $ do KindedTyVar NoExtField l k -> parens N . sitcc $ do
located l atom located l atom
space space
txt "::" txt "::"