1+ {-# LANGUAGE RecordWildCards #-}
12module Language.Haskell.Stylish.Config.Tests
23 ( tests
34 ) where
@@ -11,7 +12,7 @@ import qualified Data.YAML.Aeson as Yaml
1112import System.Directory
1213import Test.Framework (Test , testGroup )
1314import Test.Framework.Providers.HUnit (testCase )
14- import Test.HUnit (Assertion , assert , (@?=) )
15+ import Test.HUnit (Assertion , (@?=) )
1516
1617
1718--------------------------------------------------------------------------------
@@ -28,6 +29,10 @@ tests = testGroup "Language.Haskell.Stylish.Config"
2829 testExtensionsFromDotStylish
2930 , testCase " Extensions extracted correctly from .stylish-haskell.yaml and .cabal files"
3031 testExtensionsFromBoth
32+ , testCase " NoXyz extensions from .stylish-haskell.yaml file"
33+ testStylishNoXyz
34+ , testCase " NoXyz extensions from .cabal file"
35+ testCabalNoXyz
3136 , testCase " Correctly read .stylish-haskell.yaml file with default max column number"
3237 testDefaultColumns
3338 , testCase " Correctly read .stylish-haskell.yaml file with specified max column number"
@@ -39,75 +44,105 @@ tests = testGroup "Language.Haskell.Stylish.Config"
3944 ]
4045
4146
47+
48+ --------------------------------------------------------------------------------
49+ type ExtensionName = String
50+
51+ data ConfigFile = ConfigFile
52+ { fileName :: FilePath
53+ , contents :: String
54+ , extensions :: [ExtensionName ]
55+ }
56+
57+ stylishCfg :: ([ExtensionName ] -> String ) -> [ExtensionName ] -> ConfigFile
58+ stylishCfg template exts = ConfigFile
59+ { fileName = " .stylish-haskell.yaml"
60+ , contents = template exts
61+ , extensions = exts
62+ }
63+
64+ cabalCfg :: ([ExtensionName ] -> [ExtensionName ] -> String ) ->
65+ [ExtensionName ] -> [ExtensionName ] -> ConfigFile
66+ cabalCfg template exts1 exts2 = ConfigFile
67+ { fileName = " test.cabal"
68+ , contents = template exts1 exts2
69+ , extensions = exts1 ++ exts2
70+ }
71+
72+
73+ --------------------------------------------------------------------------------
74+ testExtensions :: [ConfigFile ] -> Assertion
75+ testExtensions cfgFiles = do
76+ cfg' <- createFilesAndGetConfig cfgFiles
77+ let expected = Set. fromList (concatMap extensions cfgFiles)
78+ actual = Set. fromList (configLanguageExtensions cfg')
79+ actual @?= expected
80+
81+ testColumns :: Maybe Int -> [ConfigFile ] -> Assertion
82+ testColumns expected cfgFiles = do
83+ cfg' <- createFilesAndGetConfig cfgFiles
84+ let actual = configColumns cfg'
85+ actual @?= expected
86+
87+
4288--------------------------------------------------------------------------------
4389-- | Put an example config files (.cabal/.stylish-haskell.yaml/both)
4490-- into the current directory and extract extensions from it.
45- createFilesAndGetConfig :: [( FilePath , String ) ] -> IO Config
91+ createFilesAndGetConfig :: [ConfigFile ] -> IO Config
4692createFilesAndGetConfig files = withTestDirTree $ do
47- mapM_ (\ (k, v) -> writeFile k v ) files
93+ mapM_ (\ ConfigFile { .. } -> writeFile fileName contents ) files
4894 -- create an empty directory and change into it
4995 createDirectory " src"
5096 setCurrentDirectory " src"
5197 -- from that directory read the config file and extract extensions
5298 -- to make sure the search for .cabal file works
53- config <- loadConfig (const (pure () )) Nothing
54- pure config
99+ loadConfig (const (pure () )) Nothing
55100
56101
57102--------------------------------------------------------------------------------
58103testExtensionsFromDotCabal :: Assertion
59- testExtensionsFromDotCabal =
60- assert $ (expected == ) . Set. fromList . configLanguageExtensions <$>
61- createFilesAndGetConfig [(" test.cabal" , dotCabal True )]
62- where
63- expected = Set. fromList [" ScopedTypeVariables" , " DataKinds" ]
64-
104+ testExtensionsFromDotCabal = testExtensions
105+ [ cabalCfg dotCabal [" ScopedTypeVariables" ] [" DataKinds" ] ]
65106
66107--------------------------------------------------------------------------------
67108testExtensionsFromDotStylish :: Assertion
68- testExtensionsFromDotStylish =
69- assert $ (expected == ) . Set. fromList . configLanguageExtensions <$>
70- createFilesAndGetConfig [(" .stylish-haskell.yaml" , dotStylish)]
71- where
72- expected = Set. fromList [" TemplateHaskell" , " QuasiQuotes" ]
73-
109+ testExtensionsFromDotStylish = testExtensions
110+ [ stylishCfg dotStylish [" TemplateHaskell" , " QuasiQuotes" ] ]
74111
75112--------------------------------------------------------------------------------
76113testExtensionsFromBoth :: Assertion
77- testExtensionsFromBoth =
78- assert $ (expected == ) . Set. fromList . configLanguageExtensions <$>
79- createFilesAndGetConfig [ (" test.cabal" , dotCabal True )
80- , (" .stylish-haskell.yaml" , dotStylish)]
81- where
82- expected = Set. fromList
83- [" ScopedTypeVariables" , " DataKinds" , " TemplateHaskell" , " QuasiQuotes" ]
114+ testExtensionsFromBoth = testExtensions
115+ [ cabalCfg dotCabal [" ScopedTypeVariables" ] [" DataKinds" ]
116+ , stylishCfg dotStylish [" TemplateHaskell" , " QuasiQuotes" ]
117+ ]
118+
119+ --------------------------------------------------------------------------------
120+ testStylishNoXyz :: Assertion
121+ testStylishNoXyz = testExtensions
122+ [ stylishCfg dotStylish [" NoStarIsType" , " NoTypeOperators" ] ]
123+
124+ --------------------------------------------------------------------------------
125+ testCabalNoXyz :: Assertion
126+ testCabalNoXyz = testExtensions
127+ [ cabalCfg dotCabal [" NoStarIsType" ] [" NoTypeOperators" ] ]
84128
85129
86130--------------------------------------------------------------------------------
87131testSpecifiedColumns :: Assertion
88- testSpecifiedColumns =
89- assert $ (expected == ) . configColumns <$>
90- createFilesAndGetConfig [(" .stylish-haskell.yaml" , dotStylish)]
91- where
92- expected = Just 110
132+ testSpecifiedColumns = testColumns (Just 110 )
133+ [ stylishCfg dotStylish [] ]
93134
94135
95136--------------------------------------------------------------------------------
96137testDefaultColumns :: Assertion
97- testDefaultColumns =
98- assert $ (expected == ) . configColumns <$>
99- createFilesAndGetConfig [(" .stylish-haskell.yaml" , dotStylish2)]
100- where
101- expected = Just 80
138+ testDefaultColumns = testColumns (Just 80 )
139+ [ stylishCfg dotStylish2 [" DataKinds" ] ]
102140
103141
104142--------------------------------------------------------------------------------
105143testNoColumns :: Assertion
106- testNoColumns =
107- assert $ (expected == ) . configColumns <$>
108- createFilesAndGetConfig [(" .stylish-haskell.yaml" , dotStylish3)]
109- where
110- expected = Nothing
144+ testNoColumns = testColumns Nothing
145+ [ stylishCfg dotStylish3 [" DataKinds" ] ]
111146
112147
113148--------------------------------------------------------------------------------
@@ -129,8 +164,8 @@ testBoolSimpleAlign = do
129164-- | Example cabal file borrowed from
130165-- https://www.haskell.org/cabal/users-guide/developing-packages.html
131166-- with some default-extensions added
132- dotCabal :: Bool -> String
133- dotCabal includeExtensions = unlines $
167+ dotCabal :: [ ExtensionName ] -> [ ExtensionName ] -> String
168+ dotCabal exts1 exts2 = unlines $
134169 [ " name: TestPackage"
135170 , " version: 0.0"
136171 , " synopsis: Package with library and two programs"
@@ -142,22 +177,22 @@ dotCabal includeExtensions = unlines $
142177 , " library"
143178 , " build-depends: HUnit"
144179 , " exposed-modules: A, B, C"
180+ , " default-extensions:"
145181 ] ++
146- [if includeExtensions then " default-extensions: ScopedTypeVariables"
147- else " " ]
182+ map (" " ++ ) exts1
148183 ++
149184 [ " "
150185 , " executable program1"
151186 , " main-is: Main.hs"
152187 , " hs-source-dirs: prog1"
153188 , " other-modules: A, B"
189+ , " default-extensions:"
154190 ] ++
155- [if includeExtensions then " default-extensions: DataKinds"
156- else " " ]
191+ map (" " ++ ) exts2
157192
158193-- | Example .stylish-haskell.yaml
159- dotStylish :: String
160- dotStylish = unlines $
194+ dotStylish :: [ ExtensionName ] -> String
195+ dotStylish exts = unlines $
161196 [ " steps:"
162197 , " - imports:"
163198 , " align: none"
@@ -177,13 +212,12 @@ dotStylish = unlines $
177212 , " via: \" indent 2\" "
178213 , " columns: 110"
179214 , " language_extensions:"
180- , " - TemplateHaskell"
181- , " - QuasiQuotes"
182- ]
215+ ] ++
216+ map (" - " ++ ) exts
183217
184218-- | Example .stylish-haskell.yaml
185- dotStylish2 :: String
186- dotStylish2 = unlines $
219+ dotStylish2 :: [ ExtensionName ] -> String
220+ dotStylish2 exts = unlines $
187221 [ " steps:"
188222 , " - imports:"
189223 , " align: none"
@@ -196,13 +230,13 @@ dotStylish2 = unlines $
196230 , " remove_redundant: true"
197231 , " - trailing_whitespace: {}"
198232 , " language_extensions:"
199- , " - TemplateHaskell "
200- , " - QuasiQuotes "
201- ]
233+ ] ++
234+ map ( " - " ++ ) exts
235+
202236
203237-- | Example .stylish-haskell.yaml
204- dotStylish3 :: String
205- dotStylish3 = unlines $
238+ dotStylish3 :: [ ExtensionName ] -> String
239+ dotStylish3 exts = unlines $
206240 [ " steps:"
207241 , " - imports:"
208242 , " align: none"
@@ -216,6 +250,5 @@ dotStylish3 = unlines $
216250 , " - trailing_whitespace: {}"
217251 , " columns: null"
218252 , " language_extensions:"
219- , " - TemplateHaskell"
220- , " - QuasiQuotes"
221- ]
253+ ] ++
254+ map (" - " ++ ) exts
0 commit comments