1111
1212import Build ( buildLibrary
1313 , buildProgram
14+ , buildWithScript
1415 )
1516import Control.Monad.Extra ( concatMapM )
16- import Data.List (isSuffixOf , find , nub )
17+ import Data.List ( isSuffixOf
18+ , find
19+ , nub
20+ )
1721import qualified Data.Map as Map
1822import qualified Data.Text.IO as TIO
1923import Development.Shake ( FilePattern
@@ -79,7 +83,7 @@ data AppSettings = AppSettings {
7983 , appSettingsDevDependencies :: (Map. Map String Version )
8084}
8185
82- data Library = Library { librarySourceDir :: String }
86+ data Library = Library { librarySourceDir :: String , libraryBuildScript :: Maybe String }
8387
8488data Executable = Executable {
8589 executableSourceDir :: String
@@ -102,6 +106,7 @@ data DependencyTree = Dependency {
102106 dependencyName :: String
103107 , dependencyPath :: FilePath
104108 , dependencySourcePath :: FilePath
109+ , dependencyBuildScript :: Maybe String
105110 , dependencyDependencies :: [DependencyTree ]
106111}
107112
@@ -117,8 +122,8 @@ start args = do
117122
118123app :: Arguments -> AppSettings -> IO ()
119124app args settings = case command' args of
120- Build -> build settings
121- Run whichOne -> do
125+ Build -> build settings
126+ Run whichOne -> do
122127 build settings
123128 let buildPrefix = appSettingsBuildPrefix settings
124129 let
@@ -133,13 +138,15 @@ app args settings = case command' args of
133138 case canonicalExecutables of
134139 [] -> putStrLn " No Executables Found"
135140 _ -> case whichOne of
136- " " -> mapM_ system (map (++ " " ++ commandArguments args) canonicalExecutables)
141+ " " -> mapM_
142+ system
143+ (map (++ " " ++ commandArguments args) canonicalExecutables)
137144 name -> do
138- case find (name `isSuffixOf` ) canonicalExecutables of
139- Nothing -> putStrLn " Executable Not Found"
140- Just specified -> do
141- system (specified ++ " " ++ (commandArguments args))
142- return ()
145+ case find (name `isSuffixOf` ) canonicalExecutables of
146+ Nothing -> putStrLn " Executable Not Found"
147+ Just specified -> do
148+ system (specified ++ " " ++ (commandArguments args))
149+ return ()
143150 Test whichOne -> do
144151 build settings
145152 let buildPrefix = appSettingsBuildPrefix settings
@@ -155,13 +162,15 @@ app args settings = case command' args of
155162 case canonicalExecutables of
156163 [] -> putStrLn " No Tests Found"
157164 _ -> case whichOne of
158- " " -> mapM_ system (map (++ " " ++ commandArguments args) canonicalExecutables)
165+ " " -> mapM_
166+ system
167+ (map (++ " " ++ commandArguments args) canonicalExecutables)
159168 name -> do
160- case find (name `isSuffixOf` ) canonicalExecutables of
161- Nothing -> putStrLn " Test Not Found"
162- Just specified -> do
163- system (specified ++ " " ++ (commandArguments args))
164- return ()
169+ case find (name `isSuffixOf` ) canonicalExecutables of
170+ Nothing -> putStrLn " Test Not Found"
171+ Just specified -> do
172+ system (specified ++ " " ++ (commandArguments args))
173+ return ()
165174
166175build :: AppSettings -> IO ()
167176build settings = do
@@ -183,15 +192,24 @@ build settings = do
183192 { dependencyName = projectName
184193 , dependencyPath = " ."
185194 , dependencySourcePath = librarySourceDir'
195+ , dependencyBuildScript = libraryBuildScript librarySettings
186196 , dependencyDependencies = mainDependencyTrees
187197 }
188- thisArchive <- buildLibrary librarySourceDir'
189- [" .f90" , " .f" , " .F" , " .F90" , " .f95" , " .f03" ]
190- (buildPrefix </> projectName)
191- compiler
192- flags
193- projectName
194- (map fst builtDependencies)
198+ thisArchive <- case libraryBuildScript librarySettings of
199+ Just script -> buildWithScript script
200+ " ."
201+ (buildPrefix </> projectName)
202+ compiler
203+ flags
204+ projectName
205+ (map fst builtDependencies)
206+ Nothing -> buildLibrary librarySourceDir'
207+ [" .f90" , " .f" , " .F" , " .F90" , " .f95" , " .f03" ]
208+ (buildPrefix </> projectName)
209+ compiler
210+ flags
211+ projectName
212+ (map fst builtDependencies)
195213 return
196214 $ ( (buildPrefix </> projectName, thisArchive) : builtDependencies
197215 , Just thisDependencyTree
@@ -263,13 +281,18 @@ arguments =
263281 (info buildArguments (progDesc " Build the executable" ))
264282 )
265283 <*> switch (long " release" <> help " Build in release mode" )
266- <*> strOption (long " args" <> metavar " ARGS" <> value " " <> help " Arguments to pass to executables/tests" )
284+ <*> strOption
285+ (long " args" <> metavar " ARGS" <> value " " <> help
286+ " Arguments to pass to executables/tests"
287+ )
267288
268289runArguments :: Parser Command
269- runArguments = Run <$> strArgument (metavar " EXE" <> value " " <> help " Which executable to run" )
290+ runArguments = Run <$> strArgument
291+ (metavar " EXE" <> value " " <> help " Which executable to run" )
270292
271293testArguments :: Parser Command
272- testArguments = Test <$> strArgument (metavar " TEST" <> value " " <> help " Which test to run" )
294+ testArguments =
295+ Test <$> strArgument (metavar " TEST" <> value " " <> help " Which test to run" )
273296
274297buildArguments :: Parser Command
275298buildArguments = pure Build
@@ -297,7 +320,12 @@ settingsCodec =
297320 .= tomlSettingsDevDependencies
298321
299322libraryCodec :: TomlCodec Library
300- libraryCodec = Library <$> Toml. string " source-dir" .= librarySourceDir
323+ libraryCodec =
324+ Library
325+ <$> Toml. string " source-dir"
326+ .= librarySourceDir
327+ <*> Toml. dioptional (Toml. string " build-script" )
328+ .= libraryBuildScript
301329
302330executableCodec :: TomlCodec Executable
303331executableCodec =
@@ -419,7 +447,10 @@ getLibrarySettings maybeSettings = case maybeSettings of
419447 Nothing -> do
420448 defaultExists <- doesDirectoryExist " src"
421449 if defaultExists
422- then return (Just (Library { librarySourceDir = " src" }))
450+ then return
451+ (Just
452+ (Library { librarySourceDir = " src" , libraryBuildScript = Nothing })
453+ )
423454 else return Nothing
424455
425456getExecutableSettings :: [Executable ] -> String -> IO [Executable ]
@@ -490,6 +521,7 @@ fetchDependencies dependencies = do
490521 { dependencyName = name
491522 , dependencyPath = path
492523 , dependencySourcePath = path </> (librarySourceDir librarySettings)
524+ , dependencyBuildScript = libraryBuildScript librarySettings
493525 , dependencyDependencies = newDependencies
494526 }
495527 Nothing -> do
@@ -500,7 +532,7 @@ fetchExecutableDependencies
500532 :: (Maybe DependencyTree ) -> Map. Map String Version -> IO [DependencyTree ]
501533fetchExecutableDependencies maybeProjectTree dependencies =
502534 case maybeProjectTree of
503- Just projectTree@ (Dependency name _ _ _) ->
535+ Just projectTree@ (Dependency name _ _ _ _ ) ->
504536 if name `Map.member` dependencies {- map contains this project-}
505537 then fmap (projectTree : )
506538 (fetchDependencies (Map. delete name dependencies)) {- fetch the other dependencies and include the project tree in the result -}
@@ -524,6 +556,7 @@ fetchExecutableDependencies maybeProjectTree dependencies =
524556 { dependencyName = name
525557 , dependencyPath = path
526558 , dependencySourcePath = path </> (librarySourceDir librarySettings)
559+ , dependencyBuildScript = libraryBuildScript librarySettings
527560 , dependencyDependencies = newDependencies
528561 }
529562 Nothing -> do
@@ -573,18 +606,26 @@ buildDependencies buildPrefix compiler flags dependencies = do
573606
574607buildDependency
575608 :: String -> String -> [String ] -> DependencyTree -> IO [(FilePath , FilePath )]
576- buildDependency buildPrefix compiler flags (Dependency name path sourcePath dependencies)
609+ buildDependency buildPrefix compiler flags (Dependency name path sourcePath mBuildScript dependencies)
577610 = do
578611 transitiveDependencies <- buildDependencies buildPrefix
579612 compiler
580613 flags
581614 dependencies
582615 let buildPath = buildPrefix </> name
583- thisArchive <- buildLibrary sourcePath
584- [" .f90" , " .f" , " .F" , " .F90" , " .f95" , " .f03" ]
585- buildPath
586- compiler
587- flags
588- name
589- (map fst transitiveDependencies)
616+ thisArchive <- case mBuildScript of
617+ Just script -> buildWithScript script
618+ path
619+ buildPath
620+ compiler
621+ flags
622+ name
623+ (map fst transitiveDependencies)
624+ Nothing -> buildLibrary sourcePath
625+ [" .f90" , " .f" , " .F" , " .F90" , " .f95" , " .f03" ]
626+ buildPath
627+ compiler
628+ flags
629+ name
630+ (map fst transitiveDependencies)
590631 return $ (buildPath, thisArchive) : transitiveDependencies
0 commit comments