Skip to content
Permalink
Browse files
Switch to leading commas in tuples and lists
  • Loading branch information
mrkkrp authored and jinwoo committed Jul 8, 2020
1 parent 913a927 commit 5a36b8b
Show file tree
Hide file tree
Showing 73 changed files with 378 additions and 384 deletions.
@@ -11,8 +11,8 @@ steps:
command: |
nix-build --keep-going --no-out-link --argstr ormoluCompiler ghc8101
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
@@ -11,8 +11,8 @@ class Bar a where
a
-- Pointless comment
default bar ::
( Read a,
Semigroup a
( Read a
, Semigroup a
) =>
a ->
a ->
@@ -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
@@ -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
@@ -12,8 +12,8 @@ class Baz a where
-- | Baz
baz ::
-- | First argument
( a,
a
( a
, a
) ->
-- | Second argument
a ->
@@ -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
@@ -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)
@@ -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
@@ -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
@@ -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
@@ -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)
@@ -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)
@@ -1,7 +1,7 @@
default (Int, Foo, Bar)

default
( Int,
Foo,
Bar
( Int
, Foo
, Bar
)
@@ -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
@@ -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 ""
@@ -7,11 +7,11 @@ data instance
Foo
[Int]
= IntListFoo
( Int,
Int
( Int
, Int
)
( Double,
Double
( Double
, Double
)

data instance Bar Double a
@@ -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
)
@@ -3,8 +3,8 @@
{-# COMPLETE A, B #-}

{-# COMPLETE
A,
B,
C ::
A
, B
, C ::
Foo
#-}
@@ -4,8 +4,8 @@ class Foo a where
{-# MINIMAL
a
| ( b, c, d
| e,
f
| e
, f
)
| g
#-}
@@ -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
@@ -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
@@ -1,7 +1,7 @@
functionName ::
( C1,
C2,
C3
( C1
, C2
, C3
) =>
a ->
b ->
@@ -7,9 +7,9 @@ a = 1
b = 2
c = 3

foo,
bar,
baz ::
foo
, bar
, baz ::
Int
bar = 2
baz = 3
@@ -4,13 +4,13 @@ foo' = [0 .. 5]

bar x =
[ 0
.. x
.. x
]

baz x =
[ 1,
3
.. x
[ 1
, 3
.. x
]

barbaz x = [0, 1 ..]

0 comments on commit 5a36b8b

Please sign in to comment.