aboutsummaryrefslogtreecommitdiff
path: root/src
diff options
context:
space:
mode:
Diffstat (limited to 'src')
-rw-r--r--src/Build.hs7
-rw-r--r--src/Fpm.hs266
2 files changed, 175 insertions, 98 deletions
diff --git a/src/Build.hs b/src/Build.hs
index 2e471ec..913e754 100644
--- a/src/Build.hs
+++ b/src/Build.hs
@@ -69,8 +69,9 @@ buildProgram
-> [String]
-> String
-> FilePath
+ -> [FilePath]
-> IO ()
-buildProgram programDirectory libraryDirectories sourceExtensions buildDirectory compiler flags programName programSource
+buildProgram programDirectory libraryDirectories sourceExtensions buildDirectory compiler flags programName programSource archives
= do
sourceFiles <- getDirectoriesFiles [programDirectory] sourceExtensions
canonicalProgramSource <- makeAbsolute $ programDirectory </> programSource
@@ -93,7 +94,6 @@ buildProgram programDirectory libraryDirectories sourceExtensions buildDirectory
let allModuleMaps =
moduleLookupMap `Map.union` foldl Map.union Map.empty otherModuleMaps
let includeFlags = map ("-I" ++) libraryDirectories
- archives <- getDirectoriesFiles libraryDirectories [".a"]
shake shakeOptions { shakeFiles = buildDirectory
, shakeChange = ChangeModtimeAndDigest
, shakeColor = True
@@ -151,7 +151,7 @@ buildLibrary
-> [String]
-> String
-> [FilePath]
- -> IO ()
+ -> IO (FilePath)
buildLibrary libraryDirectory sourceExtensions buildDirectory compiler flags libraryName otherLibraryDirectories
= do
sourceFiles <- getDirectoriesFiles [libraryDirectory] sourceExtensions
@@ -193,6 +193,7 @@ buildLibrary libraryDirectory sourceExtensions buildDirectory compiler flags lib
need objectFiles
cmd "ar" ["rs"] a objectFiles
want [archiveFile]
+ return archiveFile
-- A little wrapper around getDirectoryFiles so we can get files from multiple directories
getDirectoriesFiles :: [FilePath] -> [FilePattern] -> IO [FilePath]
diff --git a/src/Fpm.hs b/src/Fpm.hs
index 253bc85..3903e5e 100644
--- a/src/Fpm.hs
+++ b/src/Fpm.hs
@@ -60,6 +60,7 @@ data TomlSettings = TomlSettings {
, tomlSettingsExecutables :: [Executable]
, tomlSettingsTests :: [Executable]
, tomlSettingsDependencies :: (Map.Map String Version)
+ , tomlSettingsDevDependencies :: (Map.Map String Version)
}
data AppSettings = AppSettings {
@@ -71,6 +72,7 @@ data AppSettings = AppSettings {
, appSettingsExecutables :: [Executable]
, appSettingsTests :: [Executable]
, appSettingsDependencies :: (Map.Map String Version)
+ , appSettingsDevDependencies :: (Map.Map String Version)
}
data Library = Library { librarySourceDir :: String }
@@ -79,15 +81,16 @@ data Executable = Executable {
executableSourceDir :: String
, executableMainFile :: String
, executableName :: String
-}
+ , executableDependencies :: (Map.Map String Version)
+} deriving Show
-data Version = SimpleVersion String | GitVersion GitVersionSpec | PathVersion PathVersionSpec
+data Version = SimpleVersion String | GitVersion GitVersionSpec | PathVersion PathVersionSpec deriving Show
-data GitVersionSpec = GitVersionSpec { gitVersionSpecUrl :: String, gitVersionSpecRef :: Maybe GitRef }
+data GitVersionSpec = GitVersionSpec { gitVersionSpecUrl :: String, gitVersionSpecRef :: Maybe GitRef } deriving Show
-data GitRef = Tag String | Branch String | Commit String
+data GitRef = Tag String | Branch String | Commit String deriving Show
-data PathVersionSpec = PathVersionSpec { pathVersionSpecPath :: String }
+data PathVersionSpec = PathVersionSpec { pathVersionSpecPath :: String } deriving Show
data Command = Run | Test | Build
@@ -125,7 +128,7 @@ app args settings = case command' args of
canonicalExecutables <- mapM makeAbsolute executables
case canonicalExecutables of
[] -> putStrLn "No Executables Found"
- _ -> mapM_ runCommand canonicalExecutables
+ _ -> mapM_ system canonicalExecutables
Test -> do
build settings
let buildPrefix = appSettingsBuildPrefix settings
@@ -140,7 +143,7 @@ app args settings = case command' args of
canonicalExecutables <- mapM makeAbsolute executables
case canonicalExecutables of
[] -> putStrLn "No Tests Found"
- _ -> mapM_ runCommand canonicalExecutables
+ _ -> mapM_ system canonicalExecutables
build :: AppSettings -> IO ()
build settings = do
@@ -150,46 +153,76 @@ build settings = do
let flags = appSettingsFlags settings
let executables = appSettingsExecutables settings
let tests = appSettingsTests settings
- builtDependencies <-
- fetchDependencies [projectName] (appSettingsDependencies settings)
- >>= buildDependencies buildPrefix compiler flags
- executableDepends <- case appSettingsLibrary settings of
+ mainDependencyTrees <- fetchDependencies (appSettingsDependencies settings)
+ builtDependencies <- buildDependencies buildPrefix
+ compiler
+ flags
+ mainDependencyTrees
+ (executableDepends, maybeTree) <- case appSettingsLibrary settings of
Just librarySettings -> do
let librarySourceDir' = librarySourceDir librarySettings
- buildLibrary librarySourceDir'
- [".f90", ".f", ".F", ".F90", ".f95", ".f03"]
- (buildPrefix </> projectName)
- compiler
- flags
- projectName
- builtDependencies
- return $ (buildPrefix </> projectName) : builtDependencies
+ let thisDependencyTree = Dependency
+ { dependencyName = projectName
+ , dependencyPath = "."
+ , dependencySourcePath = librarySourceDir'
+ , dependencyDependencies = mainDependencyTrees
+ }
+ thisArchive <- buildLibrary librarySourceDir'
+ [".f90", ".f", ".F", ".F90", ".f95", ".f03"]
+ (buildPrefix </> projectName)
+ compiler
+ flags
+ projectName
+ (map fst builtDependencies)
+ return
+ $ ( (buildPrefix </> projectName, thisArchive) : builtDependencies
+ , Just thisDependencyTree
+ )
Nothing -> do
- return builtDependencies
+ return (builtDependencies, Nothing)
mapM_
- (\Executable { executableSourceDir = sourceDir, executableMainFile = mainFile, executableName = name } ->
+ (\Executable { executableSourceDir = sourceDir, executableMainFile = mainFile, executableName = name, executableDependencies = dependencies } ->
do
- buildProgram sourceDir
- executableDepends
- [".f90", ".f", ".F", ".F90", ".f95", ".f03"]
- (buildPrefix </> sourceDir)
- compiler
- flags
- name
- mainFile
+ localDependencies <-
+ fetchExecutableDependencies maybeTree dependencies
+ >>= buildDependencies buildPrefix compiler flags
+ buildProgram
+ sourceDir
+ ((map fst executableDepends) ++ (map fst localDependencies))
+ [".f90", ".f", ".F", ".F90", ".f95", ".f03"]
+ (buildPrefix </> sourceDir)
+ compiler
+ flags
+ name
+ mainFile
+ ((map snd executableDepends) ++ (map snd localDependencies))
)
executables
+ devDependencies <-
+ fetchExecutableDependencies maybeTree (appSettingsDevDependencies settings)
+ >>= buildDependencies buildPrefix compiler flags
mapM_
- (\Executable { executableSourceDir = sourceDir, executableMainFile = mainFile, executableName = name } ->
+ (\Executable { executableSourceDir = sourceDir, executableMainFile = mainFile, executableName = name, executableDependencies = dependencies } ->
do
- buildProgram sourceDir
- executableDepends
- [".f90", ".f", ".F", ".F90", ".f95", ".f03"]
- (buildPrefix </> sourceDir)
- compiler
- flags
- name
- mainFile
+ localDependencies <-
+ fetchExecutableDependencies maybeTree dependencies
+ >>= buildDependencies buildPrefix compiler flags
+ buildProgram
+ sourceDir
+ ( (map fst executableDepends)
+ ++ (map fst devDependencies)
+ ++ (map fst localDependencies)
+ )
+ [".f90", ".f", ".F", ".F90", ".f95", ".f03"]
+ (buildPrefix </> sourceDir)
+ compiler
+ flags
+ name
+ mainFile
+ ( (map snd executableDepends)
+ ++ (map snd devDependencies)
+ ++ (map snd localDependencies)
+ )
)
tests
@@ -241,6 +274,8 @@ settingsCodec =
.= tomlSettingsTests
<*> Toml.tableMap Toml._KeyString versionCodec "dependencies"
.= tomlSettingsDependencies
+ <*> Toml.tableMap Toml._KeyString versionCodec "dev-dependencies"
+ .= tomlSettingsDevDependencies
libraryCodec :: TomlCodec Library
libraryCodec = Library <$> Toml.string "source-dir" .= librarySourceDir
@@ -254,6 +289,8 @@ executableCodec =
.= executableMainFile
<*> Toml.string "name"
.= executableName
+ <*> Toml.tableMap Toml._KeyString versionCodec "dependencies"
+ .= executableDependencies
matchSimpleVersion :: Version -> Maybe String
matchSimpleVersion = \case
@@ -289,7 +326,9 @@ versionCodec :: Toml.Key -> Toml.TomlCodec Version
versionCodec key =
Toml.dimatch matchSimpleVersion SimpleVersion (Toml.string key)
<|> Toml.dimatch matchGitVersion GitVersion (Toml.table gitVersionCodec key)
- <|> Toml.dimatch matchPathVersion PathVersion (Toml.table pathVersionCodec key)
+ <|> Toml.dimatch matchPathVersion
+ PathVersion
+ (Toml.table pathVersionCodec key)
gitVersionCodec :: Toml.TomlCodec GitVersionSpec
gitVersionCodec =
@@ -307,7 +346,7 @@ gitRefCodec =
pathVersionCodec :: Toml.TomlCodec PathVersionSpec
pathVersionCodec =
- PathVersionSpec <$> Toml.string "path" .= pathVersionSpecPath
+ PathVersionSpec <$> Toml.string "path" .= pathVersionSpecPath
toml2AppSettings :: TomlSettings -> Bool -> IO AppSettings
toml2AppSettings tomlSettings release = do
@@ -319,38 +358,40 @@ toml2AppSettings tomlSettings release = do
projectName
testSettings <- getTestSettings $ tomlSettingsTests tomlSettings
buildPrefix <- makeBuildPrefix compiler release
- let dependencies = tomlSettingsDependencies tomlSettings
+ let dependencies = tomlSettingsDependencies tomlSettings
+ let devDependencies = tomlSettingsDevDependencies tomlSettings
return AppSettings
- { appSettingsCompiler = compiler
- , appSettingsProjectName = projectName
- , appSettingsBuildPrefix = buildPrefix
- , appSettingsFlags = if release
- then
- [ "-Wall"
- , "-Wextra"
- , "-Wimplicit-interface"
- , "-fPIC"
- , "-fmax-errors=1"
- , "-O3"
- , "-march=native"
- , "-ffast-math"
- , "-funroll-loops"
- ]
- else
- [ "-Wall"
- , "-Wextra"
- , "-Wimplicit-interface"
- , "-fPIC"
- , "-fmax-errors=1"
- , "-g"
- , "-fbounds-check"
- , "-fcheck-array-temporaries"
- , "-fbacktrace"
- ]
- , appSettingsLibrary = librarySettings
- , appSettingsExecutables = executableSettings
- , appSettingsTests = testSettings
- , appSettingsDependencies = dependencies
+ { appSettingsCompiler = compiler
+ , appSettingsProjectName = projectName
+ , appSettingsBuildPrefix = buildPrefix
+ , appSettingsFlags = if release
+ then
+ [ "-Wall"
+ , "-Wextra"
+ , "-Wimplicit-interface"
+ , "-fPIC"
+ , "-fmax-errors=1"
+ , "-O3"
+ , "-march=native"
+ , "-ffast-math"
+ , "-funroll-loops"
+ ]
+ else
+ [ "-Wall"
+ , "-Wextra"
+ , "-Wimplicit-interface"
+ , "-fPIC"
+ , "-fmax-errors=1"
+ , "-g"
+ , "-fbounds-check"
+ , "-fcheck-array-temporaries"
+ , "-fbacktrace"
+ ]
+ , appSettingsLibrary = librarySettings
+ , appSettingsExecutables = executableSettings
+ , appSettingsTests = testSettings
+ , appSettingsDependencies = dependencies
+ , appSettingsDevDependencies = devDependencies
}
getLibrarySettings :: Maybe Library -> IO (Maybe Library)
@@ -370,9 +411,10 @@ getExecutableSettings [] projectName = do
defaultMainExists <- doesFileExist ("app" </> "main.f90")
if defaultMainExists
then return
- [ Executable { executableSourceDir = "app"
- , executableMainFile = "main.f90"
- , executableName = projectName
+ [ Executable { executableSourceDir = "app"
+ , executableMainFile = "main.f90"
+ , executableName = projectName
+ , executableDependencies = Map.empty
}
]
else return []
@@ -387,9 +429,10 @@ getTestSettings [] = do
defaultMainExists <- doesFileExist ("test" </> "main.f90")
if defaultMainExists
then return
- [ Executable { executableSourceDir = "test"
- , executableMainFile = "main.f90"
- , executableName = "runTests"
+ [ Executable { executableSourceDir = "test"
+ , executableMainFile = "main.f90"
+ , executableName = "runTests"
+ , executableDependencies = Map.empty
}
]
else return []
@@ -410,13 +453,9 @@ makeBuildPrefix compiler release =
dealing with half fetched, or adding dependencies.
TODO check for version compatibility issues
-}
-fetchDependencies :: [String] -> Map.Map String Version -> IO [DependencyTree]
-fetchDependencies knownPackages dependencies = do
- theseDependencies <- mapM
- (uncurry fetchDependency)
- (filter (\(name, _) -> not (name `elem` knownPackages))
- (Map.toList dependencies)
- )
+fetchDependencies :: Map.Map String Version -> IO [DependencyTree]
+fetchDependencies dependencies = do
+ theseDependencies <- mapM (uncurry fetchDependency) (Map.toList dependencies)
mapM fetchTransitiveDependencies theseDependencies
where
fetchTransitiveDependencies :: (String, FilePath) -> IO DependencyTree
@@ -427,7 +466,40 @@ fetchDependencies knownPackages dependencies = do
case librarySettingsM of
Just librarySettings -> do
newDependencies <- fetchDependencies
- (name : knownPackages)
+ (tomlSettingsDependencies tomlSettings)
+ return $ Dependency
+ { dependencyName = name
+ , dependencyPath = path
+ , dependencySourcePath = path </> (librarySourceDir librarySettings)
+ , dependencyDependencies = newDependencies
+ }
+ Nothing -> do
+ putStrLn $ "No library found in " ++ name
+ undefined
+
+fetchExecutableDependencies
+ :: (Maybe DependencyTree) -> Map.Map String Version -> IO [DependencyTree]
+fetchExecutableDependencies maybeProjectTree dependencies =
+ case maybeProjectTree of
+ Just projectTree@(Dependency name _ _ _) ->
+ if name `Map.member` dependencies {- map contains this project-}
+ then fmap (projectTree :)
+ (fetchDependencies (Map.delete name dependencies)) {- fetch the other dependencies and include the project tree in the result -}
+ else do {- fetch all the dependencies, passing the project tree on down -}
+ theseDependencies <- mapM (uncurry fetchDependency)
+ (Map.toList dependencies)
+ mapM fetchTransitiveDependencies theseDependencies
+ Nothing -> fetchDependencies dependencies
+ where
+ fetchTransitiveDependencies :: (String, FilePath) -> IO DependencyTree
+ fetchTransitiveDependencies (name, path) = do
+ tomlSettings <- Toml.decodeFile settingsCodec (path </> "fpm.toml")
+ librarySettingsM <- withCurrentDirectory path
+ $ getLibrarySettings (tomlSettingsLibrary tomlSettings)
+ case librarySettingsM of
+ Just librarySettings -> do
+ newDependencies <- fetchExecutableDependencies
+ maybeProjectTree
(tomlSettingsDependencies tomlSettings)
return $ Dependency
{ dependencyName = name
@@ -471,13 +543,17 @@ fetchDependency name version = do
the transitive dependencies have been built before trying to build this one
-}
buildDependencies
- :: String -> String -> [String] -> [DependencyTree] -> IO [FilePath]
+ :: String
+ -> String
+ -> [String]
+ -> [DependencyTree]
+ -> IO [(FilePath, FilePath)]
buildDependencies buildPrefix compiler flags dependencies = do
built <- concatMapM (buildDependency buildPrefix compiler flags) dependencies
return $ nub built
buildDependency
- :: String -> String -> [String] -> DependencyTree -> IO [FilePath]
+ :: String -> String -> [String] -> DependencyTree -> IO [(FilePath, FilePath)]
buildDependency buildPrefix compiler flags (Dependency name path sourcePath dependencies)
= do
transitiveDependencies <- buildDependencies buildPrefix
@@ -485,11 +561,11 @@ buildDependency buildPrefix compiler flags (Dependency name path sourcePath depe
flags
dependencies
let buildPath = buildPrefix </> name
- buildLibrary sourcePath
- [".f90", ".f", ".F", ".F90", ".f95", ".f03"]
- buildPath
- compiler
- flags
- name
- transitiveDependencies
- return $ buildPath : transitiveDependencies
+ thisArchive <- buildLibrary sourcePath
+ [".f90", ".f", ".F", ".F90", ".f95", ".f03"]
+ buildPath
+ compiler
+ flags
+ name
+ (map fst transitiveDependencies)
+ return $ (buildPath, thisArchive) : transitiveDependencies