1
1
mirror of https://github.com/google/ormolu.git synced 2024-07-14 19:20:33 +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: |
nix-build --keep-going --no-out-link --argstr ormoluCompiler ghc8103
timeout: 100
- wait
- label: Check formatting
command: |
./format.sh
git diff --exit-code --color=always
# - wait
# - label: Check formatting
# command: |
# ./format.sh
# git diff --exit-code --color=always

View File

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

View File

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

View File

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

View File

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

View File

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

View File

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

View File

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

View File

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

View File

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

View File

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

View File

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

View File

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

View File

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

View File

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

View File

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

View File

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

View File

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

View File

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

View File

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

View File

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

View File

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

View File

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

View File

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

View File

@ -4,16 +4,16 @@ foo x = proc a -> a -< x
bar f x =
proc
( y,
z,
w
( y
, z
, w
)
->
f -- The value
-<
( x, -- Foo
w, -- Bar
z -- Baz
( x -- Foo
, w -- Bar
, z -- Baz
)
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 =
proc a -> case a of
Left
( (a, b),
(c, d)
( (a, b)
, (c, d)
) -> f (a <> c) -< b <> d
Right
(Left a) ->

View File

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

View File

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

View File

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

View File

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

View File

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

View File

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

View File

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

View File

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

View File

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

View File

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

View File

@ -8,8 +8,8 @@ sort = sortBy ?cmp
sort' ::
( ?cmp ::
a -> a -> Bool,
?foo :: Int
a -> a -> Bool
, ?foo :: Int
) =>
[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 =
[ (a, b, c, d) -- Foo
| a <-
x, -- Bar
b <- y, -- Baz
any even [a, b],
c <-
z
* z ^ 2, -- Bar baz
d <-
w
+ w, -- Baz bar
all
even
[ a,
b,
c,
d
]
| a <-
x -- Bar
, b <- y -- Baz
, any even [a, b]
, c <-
z
* z ^ 2 -- Bar baz
, d <-
w
+ w -- Baz bar
, all
even
[ a
, b
, c
, d
]
]

View File

@ -1,35 +1,35 @@
baz x y z w =
[ ( a,
b,
c,
d,
e,
f,
g,
h,
i,
j
[ ( a
, b
, c
, d
, e
, f
, g
, h
, i
, j
)
| a <- -- Foo 1
x, -- Foo 2
b <- -- Bar 1
y, -- Bar 2
| a <- -- Foo 1
x -- Foo 2
, b <- -- Bar 1
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
`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
+ b, -- Bar bar 2
-- Bar bar 3
j <- -- Bar baz 1
a + b -- Bar baz 2
+ 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 =
runPure $ case (getReader name, getWriter name) of
( Right (TextReader r, rexts),
Right (TextWriter w, wexts)
( Right (TextReader r, rexts)
, Right (TextWriter w, wexts)
) -> undefined
f xs = case xs of
[ a,
b
[ a
, b
] -> a + b
g xs = case xs of

View File

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

View File

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

View File

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

View File

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

View File

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

View File

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

View File

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

View File

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

View File

@ -1,6 +1,6 @@
x :: [Int]
x =
[ 1,
2,
somethingSomething 3
[ 1
, 2
, 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
{ t1
, t2
} =
App "->" [t1, t2]

View File

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

View File

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

View File

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

View File

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

View File

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

View File

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

View File

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

View File

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

View File

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

View File

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

View File

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

View File

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

View File

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

View File

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

View File

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

View File

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

View File

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

View File

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

View File

@ -82,7 +82,7 @@ p_classFundeps fdeps = unless (null fdeps) $ do
breakpoint
txt "|"
space
inci $ sep commaDel (sitcc . located' p_funDep) fdeps
sep commaDel (sitcc . located' p_funDep) fdeps
p_funDep :: FunDep (Located RdrName) -> R ()
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 = \case
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_typeAscription hswc
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.
notImplemented "HsCmdApp"
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 ->
p_case cmdPlacement p_hsCmd e mgroup
HsCmdIf NoExtField _ if' then' else' ->
@ -627,7 +627,7 @@ p_hsExpr' s = \case
space
located e p_hsExpr
HsPar NoExtField e ->
parens s (located e (dontUseBraces . p_hsExpr))
parens s (sitcc $ located e (dontUseBraces . p_hsExpr))
SectionL NoExtField x op -> do
located x p_hsExpr
breakpoint
@ -686,10 +686,9 @@ p_hsExpr' s = \case
(breakpoint >> txt "|" >> space)
p_seqBody
p_seqBody =
sitcc
. sep
commaDel
(located' (sitcc . p_stmt))
sep
commaDel
(located' (sitcc . p_stmt))
stmts = init xs
yield = last xs
lists = foldr (liftAppend . gatherStmt) [] stmts
@ -948,7 +947,7 @@ p_pat = \case
txt "@"
located pat p_pat
ParPat NoExtField pat ->
located pat (parens S . p_pat)
located pat (parens S . sitcc . p_pat)
BangPat NoExtField pat -> do
txt "!"
located pat p_pat

View File

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

View File

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