Skip to content

Commit 9d0b00a

Browse files
fourmolu (#60)
1 parent 1e1e1b4 commit 9d0b00a

File tree

24 files changed

+300
-221
lines changed

24 files changed

+300
-221
lines changed

.github/workflows/haskell-ci.yml

Lines changed: 12 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -23,6 +23,18 @@ concurrency:
2323
cancel-in-progress: true
2424

2525
jobs:
26+
check-formatting:
27+
name: Check formatting
28+
runs-on: ubuntu-latest
29+
steps:
30+
- uses: actions/checkout@v4
31+
- name: install fourmolu
32+
run: |
33+
wget https://github.com/fourmolu/fourmolu/releases/download/v0.17.0.0/fourmolu-0.17.0.0-linux-x86_64
34+
chmod +x fourmolu-0.17.0.0-linux-x86_64
35+
mv fourmolu-0.17.0.0-linux-x86_64 fourmolu
36+
- run: ./fourmolu -c .
37+
2638
test-with-cabal:
2739
name: Haskell-CI - Linux - ${{ matrix.ghc-version }}
2840

bench/Constrained/Bench.hs

Lines changed: 3 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -10,11 +10,10 @@
1010
module Constrained.Bench where
1111

1212
import Constrained.API
13-
import Constrained.Generation
14-
import Constrained.Examples.Set
15-
import Constrained.Examples.Map
1613
import Constrained.Examples.Basic
17-
14+
import Constrained.Examples.Map
15+
import Constrained.Examples.Set
16+
import Constrained.Generation
1817
import Control.DeepSeq
1918
import Criterion
2019
import Data.Map (Map)

examples/Constrained/Examples/Basic.hs

Lines changed: 12 additions & 11 deletions
Original file line numberDiff line numberDiff line change
@@ -346,23 +346,24 @@ manyInconsistentTrans = constrained' $ \ [var| a |] [var| b |] c d e [var| f |]
346346

347347
complicatedEither :: Specification (Either Int Int, (Either Int Int, Int, Int))
348348
complicatedEither = constrained' $ \ [var| i |] [var| t |] ->
349-
[ caseOn i
350-
(branch $ \ a -> a `elem_` lit [1..10])
351-
(branch $ \ b -> b `elem_` lit [1..10])
349+
[ caseOn
350+
i
351+
(branch $ \a -> a `elem_` lit [1 .. 10])
352+
(branch $ \b -> b `elem_` lit [1 .. 10])
352353
, match t $ \ [var| k |] _ _ ->
353-
[ k ==. i
354-
, not_ $ k `elem_` lit [ Left j | j <- [1..9] ]
355-
]
354+
[ k ==. i
355+
, not_ $ k `elem_` lit [Left j | j <- [1 .. 9]]
356+
]
356357
]
357358

358359
pairCant :: Specification (Int, (Int, Int))
359360
pairCant = constrained' $ \ [var| i |] [var| p |] ->
360-
[ assert $ i `elem_` lit [1..10]
361+
[ assert $ i `elem_` lit [1 .. 10]
361362
, match p $ \ [var| k |] _ ->
362-
[ k ==. i
363-
, not_ $ k `elem_` lit [1..9]
364-
]
363+
[ k ==. i
364+
, not_ $ k `elem_` lit [1 .. 9]
365+
]
365366
]
366367

367368
signumPositive :: Specification Rational
368-
signumPositive = constrained $ \ x -> signum (x * 30) >=. 1
369+
signumPositive = constrained $ \x -> signum (x * 30) >=. 1

examples/Constrained/Examples/Fold.hs

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -36,10 +36,10 @@ evenSpec = explainSpec ["even via (x+x)"] $
3636
(\ [var|somey|] -> [assert $ evenx ==. somey + somey])
3737

3838
composeEvenSpec :: Specification Int
39-
composeEvenSpec = constrained $ \ x -> [satisfies x evenSpec, assert $ x >. 10]
39+
composeEvenSpec = constrained $ \x -> [satisfies x evenSpec, assert $ x >. 10]
4040

4141
composeOddSpec :: Specification Int
42-
composeOddSpec = constrained $ \ x -> [satisfies x oddSpec, assert $ x >. 10]
42+
composeOddSpec = constrained $ \x -> [satisfies x oddSpec, assert $ x >. 10]
4343

4444
sum3WithLength :: Integer -> Specification ([Int], Int, Int, Int)
4545
sum3WithLength n =

examples/Constrained/Examples/Map.hs

Lines changed: 20 additions & 17 deletions
Original file line numberDiff line numberDiff line change
@@ -128,24 +128,27 @@ mapIsJust = constrained' $ \ [var| x |] [var| y |] ->
128128

129129
eitherKeys :: Specification ([Int], [Int], Map (Either Int Int) Int)
130130
eitherKeys = constrained' $ \ [var| as |] [var| bs |] [var| m |] ->
131-
[
132-
forAll' m $ \ [var| k |] _v ->
133-
[ caseOn k
134-
(branch $ \ a -> a `elem_` as)
135-
(branch $ \ b -> b `elem_` bs)
136-
, reify as (map Left) $ \ ls ->
137-
reify bs (map Right) $ \ rs ->
138-
k `elem_` ls ++. rs
131+
[ forAll' m $ \ [var| k |] _v ->
132+
[ caseOn
133+
k
134+
(branch $ \a -> a `elem_` as)
135+
(branch $ \b -> b `elem_` bs)
136+
, reify as (map Left) $ \ls ->
137+
reify bs (map Right) $ \rs ->
138+
k `elem_` ls ++. rs
139139
]
140140
]
141141

142142
keysExample :: Specification (Either Int Int)
143-
keysExample = constrained $ \ k ->
144-
[ caseOn k
145-
(branch $ \ a -> a `elem_` as)
146-
(branch $ \ b -> b `elem_` bs)
147-
, reify as (map Left) $ \ ls ->
148-
reify bs (map Right) $ \ rs ->
149-
k `elem_` ls ++. rs
150-
] where as = lit [ 1 .. 10]
151-
bs = lit [ 11 .. 20 ]
143+
keysExample = constrained $ \k ->
144+
[ caseOn
145+
k
146+
(branch $ \a -> a `elem_` as)
147+
(branch $ \b -> b `elem_` bs)
148+
, reify as (map Left) $ \ls ->
149+
reify bs (map Right) $ \rs ->
150+
k `elem_` ls ++. rs
151+
]
152+
where
153+
as = lit [1 .. 10]
154+
bs = lit [11 .. 20]

fourmolu.yaml

Lines changed: 16 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,16 @@
1+
indentation: 2
2+
function-arrows: trailing
3+
comma-style: leading
4+
import-export-style: diff-friendly
5+
indent-wheres: true
6+
record-brace-space: true
7+
newlines-between-decls: 1
8+
haddock-style: single-line
9+
haddock-style-module:
10+
let-style: auto
11+
in-style: right-align
12+
unicode: never
13+
respectful: false
14+
fixities: []
15+
single-constraint-parens: never
16+
column-limit: 100

scripts/fourmolize.sh

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1 @@
1+
fourmolu -i .

src/Constrained/Base.hs

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -32,7 +32,7 @@ module Constrained.Base (
3232
pattern (:<:),
3333
pattern (:>:),
3434
pattern Unary,
35-
Ctx(..),
35+
Ctx (..),
3636
toCtx,
3737
flipCtx,
3838
fromListCtx,
@@ -675,7 +675,7 @@ instance Show (BaseW d r) where
675675
show ToGenericW = "toSimpleRep"
676676
show FromGenericW = "fromSimpleRep"
677677

678-
instance Syntax BaseW where
678+
instance Syntax BaseW
679679

680680
instance Semantics BaseW where
681681
semantics FromGenericW = fromSimpleRep

src/Constrained/Conformance.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -31,9 +31,9 @@ import Constrained.Syntax
3131
import Data.List (intersect, nub)
3232
import Data.List.NonEmpty qualified as NE
3333
import Data.Maybe
34+
import Data.Semigroup (sconcat)
3435
import Data.Set (Set)
3536
import Data.Set qualified as Set
36-
import Data.Semigroup (sconcat)
3737
import Prettyprinter hiding (cat)
3838
import Test.QuickCheck (Property, Testable, property)
3939

src/Constrained/Env.hs

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -1,9 +1,9 @@
11
{-# LANGUAGE DerivingVia #-}
2-
{-# LANGUAGE ImpredicativeTypes #-}
32
{-# LANGUAGE ExistentialQuantification #-}
43
{-# LANGUAGE GADTs #-}
54
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
65
{-# LANGUAGE ImportQualifiedPost #-}
6+
{-# LANGUAGE ImpredicativeTypes #-}
77
{-# LANGUAGE OverloadedStrings #-}
88
{-# LANGUAGE StandaloneDeriving #-}
99

@@ -76,7 +76,7 @@ find env var = do
7676
-- | Filter the keys in an env, useful for removing irrelevant variables in
7777
-- error messages
7878
filterKeys :: Env -> (forall a. Typeable a => Var a -> Bool) -> Env
79-
filterKeys (Env m) f = Env $ Map.filterWithKey (\ (EnvKey k) _ -> f k) m
79+
filterKeys (Env m) f = Env $ Map.filterWithKey (\(EnvKey k) _ -> f k) m
8080

8181
instance Pretty EnvValue where
8282
pretty (EnvValue x) = viaShow x

0 commit comments

Comments
 (0)