From eab76694dfbbd10fce74b8ac59bf523a96cf37fa Mon Sep 17 00:00:00 2001 From: Jasper Van der Jeugt Date: Thu, 8 Oct 2020 13:49:50 +0200 Subject: SimpleAlign: add multi_way_if flag in config --- data/stylish-haskell.yaml | 1 + lib/Language/Haskell/Stylish/Config.hs | 3 ++- lib/Language/Haskell/Stylish/Step/SimpleAlign.hs | 30 +++++++++++----------- .../Haskell/Stylish/Step/SimpleAlign/Tests.hs | 12 +++++++++ 4 files changed, 30 insertions(+), 16 deletions(-) diff --git a/data/stylish-haskell.yaml b/data/stylish-haskell.yaml index e0a739c..9709184 100644 --- a/data/stylish-haskell.yaml +++ b/data/stylish-haskell.yaml @@ -94,6 +94,7 @@ steps: cases: true top_level_patterns: true records: true + multi_way_if: true # Import cleanup - imports: diff --git a/lib/Language/Haskell/Stylish/Config.hs b/lib/Language/Haskell/Stylish/Config.hs index 36688a5..682d7d7 100644 --- a/lib/Language/Haskell/Stylish/Config.hs +++ b/lib/Language/Haskell/Stylish/Config.hs @@ -208,7 +208,8 @@ parseSimpleAlign c o = SimpleAlign.step <*> (SimpleAlign.Config <$> withDef SimpleAlign.cCases "cases" <*> withDef SimpleAlign.cTopLevelPatterns "top_level_patterns" - <*> withDef SimpleAlign.cRecords "records") + <*> withDef SimpleAlign.cRecords "records" + <*> withDef SimpleAlign.cMultiWayIf "multi_way_if") where withDef f k = fromMaybe (f SimpleAlign.defaultConfig) <$> (o A..:? k) diff --git a/lib/Language/Haskell/Stylish/Step/SimpleAlign.hs b/lib/Language/Haskell/Stylish/Step/SimpleAlign.hs index e03f665..523a6fb 100644 --- a/lib/Language/Haskell/Stylish/Step/SimpleAlign.hs +++ b/lib/Language/Haskell/Stylish/Step/SimpleAlign.hs @@ -1,5 +1,6 @@ -------------------------------------------------------------------------------- -{-# LANGUAGE TypeFamilies #-} +{-# LANGUAGE RecordWildCards #-} +{-# LANGUAGE TypeFamilies #-} module Language.Haskell.Stylish.Step.SimpleAlign ( Config (..) , defaultConfig @@ -28,6 +29,7 @@ data Config = Config { cCases :: !Bool , cTopLevelPatterns :: !Bool , cRecords :: !Bool + , cMultiWayIf :: !Bool } deriving (Show) @@ -37,6 +39,7 @@ defaultConfig = Config { cCases = True , cTopLevelPatterns = True , cRecords = True + , cMultiWayIf = True } @@ -136,21 +139,18 @@ matchToAlignable _conf (S.L _ (Hs.Match _ _ _ _)) = Nothing -------------------------------------------------------------------------------- multiWayIfToAlignable - :: Config - -> Hs.LHsExpr Hs.GhcPs + :: Hs.LHsExpr Hs.GhcPs -> [Alignable S.RealSrcSpan] -multiWayIfToAlignable conf (S.L _ (Hs.HsMultiIf _ grhss)) = - fromMaybe [] $ traverse (grhsToAlignable conf) grhss -multiWayIfToAlignable _conf _ = [] +multiWayIfToAlignable (S.L _ (Hs.HsMultiIf _ grhss)) = + fromMaybe [] $ traverse grhsToAlignable grhss +multiWayIfToAlignable _ = [] -------------------------------------------------------------------------------- grhsToAlignable - :: Config - -> S.Located (Hs.GRHS Hs.GhcPs (Hs.LHsExpr Hs.GhcPs)) + :: S.Located (Hs.GRHS Hs.GhcPs (Hs.LHsExpr Hs.GhcPs)) -> Maybe (Alignable S.RealSrcSpan) -grhsToAlignable conf (S.L grhsloc (Hs.GRHS _ guards@(_ : _) body)) = do - guard $ cCases conf +grhsToAlignable (S.L grhsloc (Hs.GRHS _ guards@(_ : _) body)) = do let guardsLocs = map S.getLoc guards bodyLoc = S.getLoc body left = foldl1' S.combineSrcSpans guardsLocs @@ -163,13 +163,13 @@ grhsToAlignable conf (S.L grhsloc (Hs.GRHS _ guards@(_ : _) body)) = do , aRight = bodyPos , aRightLead = length "-> " } -grhsToAlignable _conf (S.L _ (Hs.XGRHS x)) = Hs.noExtCon x -grhsToAlignable _conf (S.L _ _) = Nothing +grhsToAlignable (S.L _ (Hs.XGRHS x)) = Hs.noExtCon x +grhsToAlignable (S.L _ _) = Nothing -------------------------------------------------------------------------------- step :: Maybe Int -> Config -> Step -step maxColumns config = makeStep "Cases" $ \ls module' -> +step maxColumns config@(Config {..}) = makeStep "Cases" $ \ls module' -> let changes :: (S.Located (Hs.HsModule Hs.GhcPs) -> [a]) -> (a -> [Alignable S.RealSrcSpan]) @@ -179,7 +179,7 @@ step maxColumns config = makeStep "Cases" $ \ls module' -> configured :: [Change String] configured = concat $ - [changes records recordToAlignable | cRecords config] ++ + [changes records recordToAlignable | cRecords ] ++ [changes everything (matchGroupToAlignable config)] ++ - [changes everything (multiWayIfToAlignable config)] in + [changes everything multiWayIfToAlignable | cMultiWayIf] in applyChanges configured ls diff --git a/tests/Language/Haskell/Stylish/Step/SimpleAlign/Tests.hs b/tests/Language/Haskell/Stylish/Step/SimpleAlign/Tests.hs index 5b502d1..827022c 100644 --- a/tests/Language/Haskell/Stylish/Step/SimpleAlign/Tests.hs +++ b/tests/Language/Haskell/Stylish/Step/SimpleAlign/Tests.hs @@ -32,6 +32,7 @@ tests = testGroup "Language.Haskell.Stylish.Step.SimpleAlign.Tests" , testCase "case 11" case11 , testCase "case 12" case12 , testCase "case 13" case13 + , testCase "case 13b" case13b ] @@ -213,3 +214,14 @@ case13 = assertSnippet (step Nothing defaultConfig) , " | n < 10, x <- 1 -> x" , " | otherwise -> 2" ] + +case13b :: Assertion +case13b = assertSnippet (step Nothing defaultConfig {cMultiWayIf = False}) + [ "cond n = if" + , " | n < 10, x <- 1 -> x" + , " | otherwise -> 2" + ] + [ "cond n = if" + , " | n < 10, x <- 1 -> x" + , " | otherwise -> 2" + ] -- cgit v1.2.3