11--------------------------------------------------------------------------------
2- {-# LANGUAGE TypeFamilies #-}
2+ {-# LANGUAGE RecordWildCards #-}
3+ {-# LANGUAGE TypeFamilies #-}
34module 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--------------------------------------------------------------------------------
138141multiWayIfToAlignable
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--------------------------------------------------------------------------------
148150grhsToAlignable
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--------------------------------------------------------------------------------
171171step :: 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
0 commit comments