diff options
-rw-r--r-- | circular_example/.gitignore | 1 | ||||
-rw-r--r-- | circular_example/fpm.toml | 8 | ||||
-rw-r--r-- | circular_example/src/greet_m.f90 | 13 | ||||
-rw-r--r-- | circular_example/tests/main.f90 | 7 | ||||
-rw-r--r-- | circular_test/.gitignore | 1 | ||||
-rw-r--r-- | circular_test/fpm.toml | 4 | ||||
-rw-r--r-- | circular_test/src/hello_test.f90 | 12 | ||||
-rw-r--r-- | src/Build.hs | 7 | ||||
-rw-r--r-- | src/Fpm.hs | 185 | ||||
-rw-r--r-- | test/Spec.hs | 5 |
10 files changed, 178 insertions, 65 deletions
diff --git a/circular_example/.gitignore b/circular_example/.gitignore new file mode 100644 index 0000000..a007fea --- /dev/null +++ b/circular_example/.gitignore @@ -0,0 +1 @@ +build/* diff --git a/circular_example/fpm.toml b/circular_example/fpm.toml new file mode 100644 index 0000000..034ec57 --- /dev/null +++ b/circular_example/fpm.toml @@ -0,0 +1,8 @@ +name = "circular_example" + +[[test]] + name = "test" + source-dir = "tests" + main = "main.f90" + [test.dependencies] + circular_test = { path = "../circular_test" } diff --git a/circular_example/src/greet_m.f90 b/circular_example/src/greet_m.f90 new file mode 100644 index 0000000..2372f9a --- /dev/null +++ b/circular_example/src/greet_m.f90 @@ -0,0 +1,13 @@ +module greet_m + implicit none + private + + public :: make_greeting +contains + function make_greeting(name) result(greeting) + character(len=*), intent(in) :: name + character(len=:), allocatable :: greeting + + greeting = "Hello, " // name // "!" + end function make_greeting +end module greet_m diff --git a/circular_example/tests/main.f90 b/circular_example/tests/main.f90 new file mode 100644 index 0000000..5b7d803 --- /dev/null +++ b/circular_example/tests/main.f90 @@ -0,0 +1,7 @@ +program run_tests + use hello_test, only: run_test + + implicit none + + call run_test +end program run_tests diff --git a/circular_test/.gitignore b/circular_test/.gitignore new file mode 100644 index 0000000..a007fea --- /dev/null +++ b/circular_test/.gitignore @@ -0,0 +1 @@ +build/* diff --git a/circular_test/fpm.toml b/circular_test/fpm.toml new file mode 100644 index 0000000..56cfa2e --- /dev/null +++ b/circular_test/fpm.toml @@ -0,0 +1,4 @@ +name = "circular_test" + +[dependencies] +circular_example = { path = "../circular_example"} diff --git a/circular_test/src/hello_test.f90 b/circular_test/src/hello_test.f90 new file mode 100644 index 0000000..5a591c6 --- /dev/null +++ b/circular_test/src/hello_test.f90 @@ -0,0 +1,12 @@ +module hello_test + use greet_m, only: make_greeting + + implicit none + private + + public :: run_test +contains + subroutine run_test + print *, make_greeting("from test") + end subroutine run_test +end module hello_test 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] @@ -79,15 +79,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 @@ -150,46 +151,67 @@ 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 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)) ) tests @@ -254,6 +276,8 @@ executableCodec = .= executableMainFile <*> Toml.string "name" .= executableName + <*> Toml.tableMap Toml._KeyString versionCodec "dependencies" + .= executableDependencies matchSimpleVersion :: Version -> Maybe String matchSimpleVersion = \case @@ -289,7 +313,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 +333,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 @@ -370,9 +396,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 +414,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 +438,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 +451,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 +528,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 +546,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 diff --git a/test/Spec.hs b/test/Spec.hs index dfa70d6..2808af9 100644 --- a/test/Spec.hs +++ b/test/Spec.hs @@ -10,6 +10,7 @@ main = do testHelloWorld testHelloComplex testHelloFpm + testCircular testHelloWorld :: IO () testHelloWorld = @@ -22,3 +23,7 @@ testHelloComplex = testHelloFpm :: IO () testHelloFpm = withCurrentDirectory "hello_fpm" $ start $ Arguments Run False + +testCircular :: IO () +testCircular = + withCurrentDirectory "circular_example" $ start $ Arguments Test False |