Skip to content

Commit eab7669

Browse files
committed
SimpleAlign: add multi_way_if flag in config
1 parent 9638bba commit eab7669

File tree

4 files changed

+30
-16
lines changed

4 files changed

+30
-16
lines changed

data/stylish-haskell.yaml

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -94,6 +94,7 @@ steps:
9494
cases: true
9595
top_level_patterns: true
9696
records: true
97+
multi_way_if: true
9798

9899
# Import cleanup
99100
- imports:

lib/Language/Haskell/Stylish/Config.hs

Lines changed: 2 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -208,7 +208,8 @@ parseSimpleAlign c o = SimpleAlign.step
208208
<*> (SimpleAlign.Config
209209
<$> withDef SimpleAlign.cCases "cases"
210210
<*> withDef SimpleAlign.cTopLevelPatterns "top_level_patterns"
211-
<*> withDef SimpleAlign.cRecords "records")
211+
<*> withDef SimpleAlign.cRecords "records"
212+
<*> withDef SimpleAlign.cMultiWayIf "multi_way_if")
212213
where
213214
withDef f k = fromMaybe (f SimpleAlign.defaultConfig) <$> (o A..:? k)
214215

lib/Language/Haskell/Stylish/Step/SimpleAlign.hs

Lines changed: 15 additions & 15 deletions
Original file line numberDiff line numberDiff line change
@@ -1,5 +1,6 @@
11
--------------------------------------------------------------------------------
2-
{-# LANGUAGE TypeFamilies #-}
2+
{-# LANGUAGE RecordWildCards #-}
3+
{-# LANGUAGE TypeFamilies #-}
34
module Language.Haskell.Stylish.Step.SimpleAlign
45
( Config (..)
56
, defaultConfig
@@ -28,6 +29,7 @@ data Config = Config
2829
{ cCases :: !Bool
2930
, cTopLevelPatterns :: !Bool
3031
, cRecords :: !Bool
32+
, cMultiWayIf :: !Bool
3133
} deriving (Show)
3234

3335

@@ -37,6 +39,7 @@ defaultConfig = Config
3739
{ cCases = True
3840
, cTopLevelPatterns = True
3941
, cRecords = True
42+
, cMultiWayIf = True
4043
}
4144

4245

@@ -136,21 +139,18 @@ matchToAlignable _conf (S.L _ (Hs.Match _ _ _ _)) = Nothing
136139

137140
--------------------------------------------------------------------------------
138141
multiWayIfToAlignable
139-
:: Config
140-
-> Hs.LHsExpr Hs.GhcPs
142+
:: Hs.LHsExpr Hs.GhcPs
141143
-> [Alignable S.RealSrcSpan]
142-
multiWayIfToAlignable conf (S.L _ (Hs.HsMultiIf _ grhss)) =
143-
fromMaybe [] $ traverse (grhsToAlignable conf) grhss
144-
multiWayIfToAlignable _conf _ = []
144+
multiWayIfToAlignable (S.L _ (Hs.HsMultiIf _ grhss)) =
145+
fromMaybe [] $ traverse grhsToAlignable grhss
146+
multiWayIfToAlignable _ = []
145147

146148

147149
--------------------------------------------------------------------------------
148150
grhsToAlignable
149-
:: Config
150-
-> S.Located (Hs.GRHS Hs.GhcPs (Hs.LHsExpr Hs.GhcPs))
151+
:: S.Located (Hs.GRHS Hs.GhcPs (Hs.LHsExpr Hs.GhcPs))
151152
-> Maybe (Alignable S.RealSrcSpan)
152-
grhsToAlignable conf (S.L grhsloc (Hs.GRHS _ guards@(_ : _) body)) = do
153-
guard $ cCases conf
153+
grhsToAlignable (S.L grhsloc (Hs.GRHS _ guards@(_ : _) body)) = do
154154
let guardsLocs = map S.getLoc guards
155155
bodyLoc = S.getLoc body
156156
left = foldl1' S.combineSrcSpans guardsLocs
@@ -163,13 +163,13 @@ grhsToAlignable conf (S.L grhsloc (Hs.GRHS _ guards@(_ : _) body)) = do
163163
, aRight = bodyPos
164164
, aRightLead = length "-> "
165165
}
166-
grhsToAlignable _conf (S.L _ (Hs.XGRHS x)) = Hs.noExtCon x
167-
grhsToAlignable _conf (S.L _ _) = Nothing
166+
grhsToAlignable (S.L _ (Hs.XGRHS x)) = Hs.noExtCon x
167+
grhsToAlignable (S.L _ _) = Nothing
168168

169169

170170
--------------------------------------------------------------------------------
171171
step :: Maybe Int -> Config -> Step
172-
step maxColumns config = makeStep "Cases" $ \ls module' ->
172+
step maxColumns config@(Config {..}) = makeStep "Cases" $ \ls module' ->
173173
let changes
174174
:: (S.Located (Hs.HsModule Hs.GhcPs) -> [a])
175175
-> (a -> [Alignable S.RealSrcSpan])
@@ -179,7 +179,7 @@ step maxColumns config = makeStep "Cases" $ \ls module' ->
179179

180180
configured :: [Change String]
181181
configured = concat $
182-
[changes records recordToAlignable | cRecords config] ++
182+
[changes records recordToAlignable | cRecords ] ++
183183
[changes everything (matchGroupToAlignable config)] ++
184-
[changes everything (multiWayIfToAlignable config)] in
184+
[changes everything multiWayIfToAlignable | cMultiWayIf] in
185185
applyChanges configured ls

tests/Language/Haskell/Stylish/Step/SimpleAlign/Tests.hs

Lines changed: 12 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -32,6 +32,7 @@ tests = testGroup "Language.Haskell.Stylish.Step.SimpleAlign.Tests"
3232
, testCase "case 11" case11
3333
, testCase "case 12" case12
3434
, testCase "case 13" case13
35+
, testCase "case 13b" case13b
3536
]
3637

3738

@@ -213,3 +214,14 @@ case13 = assertSnippet (step Nothing defaultConfig)
213214
, " | n < 10, x <- 1 -> x"
214215
, " | otherwise -> 2"
215216
]
217+
218+
case13b :: Assertion
219+
case13b = assertSnippet (step Nothing defaultConfig {cMultiWayIf = False})
220+
[ "cond n = if"
221+
, " | n < 10, x <- 1 -> x"
222+
, " | otherwise -> 2"
223+
]
224+
[ "cond n = if"
225+
, " | n < 10, x <- 1 -> x"
226+
, " | otherwise -> 2"
227+
]

0 commit comments

Comments
 (0)