2
2
module CabalHelperSpec where
3
3
4
4
import Haskell.Ide.Engine.Cradle
5
+ import HIE.Bios.Types (runCradle , cradleOptsProg , Cradle , CradleLoadResult (.. ))
5
6
import Test.Hspec
6
7
import System.FilePath
7
8
import System.Directory (getCurrentDirectory , removeFile )
@@ -25,91 +26,130 @@ simpleCabalPath cwd = rootPath cwd </> "simple-cabal"
25
26
simpleStackPath :: FilePath -> FilePath
26
27
simpleStackPath cwd = rootPath cwd </> " simple-stack"
27
28
29
+ multiSourceDirsPath :: FilePath -> FilePath
30
+ multiSourceDirsPath cwd = rootPath cwd </> " multi-source-dirs"
31
+
28
32
spec :: Spec
29
33
spec = beforeAll_ setupStackFiles $ do
30
34
describe " cabal-helper spec" $ do
31
- describe " find cabal entry point spec " findCabalHelperEntryPointSpec
32
- describe " cradle discovery" cabalHelperCradleSpec
35
+ describe " find entry point" findCabalHelperEntryPointSpec
36
+ describe " cradle discovery and loading " cabalHelperCradleSpec
33
37
34
38
cabalHelperCradleSpec :: Spec
35
39
cabalHelperCradleSpec = do
36
40
cwd <- runIO getCurrentDirectory
37
41
describe " dummy filepath, finds none-cradle" $ do
38
- it " implicit exe, dummy filepath " $ do
42
+ it " implicit exe" $ do
39
43
crdl <- cabalHelperCradle (implicitExePath cwd </> " File.hs" )
40
44
crdl `shouldSatisfy` isCabalCradle
41
- it " mono repo, dummy filepath " $ do
45
+ it " mono repo" $ do
42
46
crdl <- cabalHelperCradle (monoRepoPath cwd </> " File.hs" )
43
47
crdl `shouldSatisfy` isCabalCradle
44
- it " stack repo, dummy filepath " $ do
48
+ it " stack repo" $ do
45
49
crdl <- cabalHelperCradle (simpleStackPath cwd </> " File.hs" )
46
50
crdl `shouldSatisfy` isStackCradle
47
- it " cabal repo, dummy filepath " $
51
+ it " cabal repo" $
48
52
pendingWith " Can not work because of global `cabal.project`"
49
53
-- crdl <- cabalHelperCradle (simpleCabalPath cwd </> "File.hs")
50
54
-- crdl `shouldSatisfy` isCabalCradle
51
- it " sub package, dummy filepath " $ do
55
+ it " sub package" $ do
52
56
crdl <- cabalHelperCradle (subPackagePath cwd </> " File.hs" )
53
57
crdl `shouldSatisfy` isStackCradle
58
+ it " multi-source-dirs" $ do
59
+ crdl <- cabalHelperCradle (multiSourceDirsPath cwd </> " File.hs" )
60
+ crdl `shouldSatisfy` isStackCradle
54
61
55
- describe " Existing projects" $ do
62
+ describe " existing projects" $ do
56
63
it " implicit exe" $ do
57
- crdl <- cabalHelperCradle ( implicitExePath cwd </> " src" </> " Exe.hs" )
58
- crdl `shouldSatisfy` isCabalCradle
64
+ let fp = implicitExePath cwd </> " src" </> " Exe.hs"
65
+ componentTest fp isCabalCradle
59
66
it " mono repo" $ do
60
- crdl <- cabalHelperCradle ( monoRepoPath cwd </> " A" </> " Main.hs" )
61
- crdl `shouldSatisfy` isCabalCradle
67
+ let fp = monoRepoPath cwd </> " A" </> " Main.hs"
68
+ componentTest fp isCabalCradle
62
69
it " stack repo" $ do
63
- crdl <- cabalHelperCradle ( simpleStackPath cwd </> " MyLib.hs" )
64
- crdl `shouldSatisfy` isStackCradle
70
+ let fp = simpleStackPath cwd </> " MyLib.hs"
71
+ componentTest fp isStackCradle
65
72
it " cabal repo" $
66
73
pendingWith " Can not work because of global `cabal.project`"
67
- -- crdl <- cabalHelperCradle (simpleCabalPath cwd </> "MyLib.hs")
68
- -- crdl `shouldSatisfy` isCabalCradle
74
+ -- let fp = (simpleCabalPath cwd </> "MyLib.hs")
75
+ -- componentTest fp isStackCradle
69
76
it " sub package" $ do
70
- crdl <- cabalHelperCradle (subPackagePath cwd </> " plugins-api" </> " PluginLib.hs" )
71
- crdl `shouldSatisfy` isStackCradle
77
+ let fp = subPackagePath cwd </> " plugins-api" </> " PluginLib.hs"
78
+ componentTest fp isStackCradle
79
+ it " multi-source-dirs, nested dir" $ do
80
+ let fp = multiSourceDirsPath cwd </> " src" </> " input" </> " Lib.hs"
81
+ componentTest fp isStackCradle
82
+ it " multi-source-dirs" $ do
83
+ let fp = multiSourceDirsPath cwd </> " src" </> " BetterLib.hs"
84
+ componentTest fp isStackCradle
85
+
86
+ componentTest :: FilePath -> (Cradle -> Bool ) -> Expectation
87
+ componentTest fp testCradleType = do
88
+ crdl <- cabalHelperCradle fp
89
+ crdl `shouldSatisfy` testCradleType
90
+ loadComponent crdl fp
91
+
92
+ loadComponent :: Cradle -> FilePath -> Expectation
93
+ loadComponent crdl fp = do
94
+ result <- runCradle (cradleOptsProg crdl) (\ _ -> return () ) fp
95
+ case result of
96
+ CradleFail err -> expectationFailure $ " Loading should not have failed: " ++ show err
97
+ _ -> return ()
98
+ return ()
72
99
73
100
findCabalHelperEntryPointSpec :: Spec
74
101
findCabalHelperEntryPointSpec = do
75
102
cwd <- runIO getCurrentDirectory
76
103
describe " implicit exe" $ do
77
- it " Find project root with dummy filepath" $ do
104
+ it " dummy filepath" $ do
78
105
let dummyFile = implicitExePath cwd </> " File.hs"
79
106
cabalTest dummyFile
80
- it " Find project root from source component" $ do
107
+ it " source component" $ do
81
108
let libFile = implicitExePath cwd </> " src" </> " Lib.hs"
82
109
cabalTest libFile
83
- it " Find project root from executable component" $ do
110
+ it " executable component" $ do
84
111
let mainFile = implicitExePath cwd </> " src" </> " Exe.hs"
85
112
cabalTest mainFile
86
113
87
114
describe " mono repo" $ do
88
- it " Find project root with dummy filepath" $ do
115
+ it " dummy filepath" $ do
89
116
let dummyFile = monoRepoPath cwd </> " File.hs"
90
117
cabalTest dummyFile
91
- it " Find project root with existing executable" $ do
118
+ it " existing executable" $ do
92
119
let mainFile = monoRepoPath cwd </> " A" </> " Main.hs"
93
120
cabalTest mainFile
94
121
95
122
describe " sub package repo" $ do
96
- it " Find project root with dummy filepath" $ do
123
+ it " dummy filepath" $ do
97
124
let dummyFile = subPackagePath cwd </> " File.hs"
98
125
stackTest dummyFile
99
- it " Find project root with existing executable" $ do
126
+ it " existing executable" $ do
100
127
let mainFile = subPackagePath cwd </> " plugins-api" </> " PluginLib.hs"
101
128
stackTest mainFile
102
129
103
130
describe " stack repo" $ do
104
- it " Find project root with dummy filepath" $ do
131
+ it " dummy filepath" $ do
105
132
let dummyFile = simpleStackPath cwd </> " File.hs"
106
133
stackTest dummyFile
107
- it " Find project root with real filepath" $ do
134
+ it " real filepath" $ do
108
135
let dummyFile = simpleStackPath cwd </> " MyLib.hs"
109
136
stackTest dummyFile
110
137
138
+ describe " multi-source-dirs" $ do
139
+ it " dummy filepath" $ do
140
+ let dummyFile = multiSourceDirsPath cwd </> " File.hs"
141
+ stackTest dummyFile
142
+
143
+ it " real filepath" $ do
144
+ let dummyFile = multiSourceDirsPath cwd </> " src" </> " BetterLib.hs"
145
+ stackTest dummyFile
146
+
147
+ it " nested filpath" $ do
148
+ let dummyFile = multiSourceDirsPath cwd </> " src" </> " input" </> " Lib.hs"
149
+ stackTest dummyFile
150
+
111
151
describe " simple cabal repo" $
112
- it " Find porject root with dummy filepath" $
152
+ it " Find project root with dummy filepath" $
113
153
pendingWith " Change test-setup, we will always find `cabal.project` in root dir"
114
154
115
155
-- -------------------------------------------------------------
@@ -133,20 +173,23 @@ stackTest fp = do
133
173
setupStackFiles :: IO ()
134
174
setupStackFiles = do
135
175
resolver <- readResolver
136
- cwd <- getCurrentDirectory
176
+ cwd <- getCurrentDirectory
137
177
writeFile (implicitExePath cwd </> " stack.yaml" ) (standardStackYaml resolver)
138
- writeFile (monoRepoPath cwd </> " stack.yaml" ) (monoRepoStackYaml resolver)
139
- writeFile (subPackagePath cwd </> " stack.yaml" ) (subPackageStackYaml resolver)
178
+ writeFile (monoRepoPath cwd </> " stack.yaml" ) (monoRepoStackYaml resolver)
179
+ writeFile (subPackagePath cwd </> " stack.yaml" ) (subPackageStackYaml resolver)
140
180
writeFile (simpleStackPath cwd </> " stack.yaml" ) (standardStackYaml resolver)
181
+ writeFile (multiSourceDirsPath cwd </> " stack.yaml" )
182
+ (standardStackYaml resolver)
141
183
142
184
143
185
cleanupStackFiles :: IO ()
144
186
cleanupStackFiles = do
145
- cwd <- getCurrentDirectory
187
+ cwd <- getCurrentDirectory
146
188
removeFile (implicitExePath cwd </> " stack.yaml" )
147
- removeFile (monoRepoPath cwd </> " stack.yaml" )
148
- removeFile (subPackagePath cwd </> " stack.yaml" )
189
+ removeFile (monoRepoPath cwd </> " stack.yaml" )
190
+ removeFile (subPackagePath cwd </> " stack.yaml" )
149
191
removeFile (simpleStackPath cwd </> " stack.yaml" )
192
+ removeFile (multiSourceDirsPath cwd </> " stack.yaml" )
150
193
151
194
-- -------------------------------------------------------------
152
195
0 commit comments