diff options
-rw-r--r-- | app/Main.hs | 54 | ||||
-rw-r--r-- | example_project/app/main.f90 (renamed from example_project/app/Hello_world.f90) | 4 | ||||
-rw-r--r-- | example_project/fpm.toml | 11 | ||||
-rw-r--r-- | src/Build.hs | 76 |
4 files changed, 99 insertions, 46 deletions
diff --git a/app/Main.hs b/app/Main.hs index eceb260..a6f3ea2 100644 --- a/app/Main.hs +++ b/app/Main.hs @@ -3,7 +3,7 @@ module Main where import Build ( buildLibrary - , buildPrograms + , buildProgram ) import Data.Text ( Text , unpack @@ -32,7 +32,13 @@ import qualified Toml newtype Arguments = Arguments { command' :: Command } -data Settings = Settings { compiler :: !Text } +data Settings = Settings { + settingsCompiler :: !Text + , settingsProjectName :: !Text + , settingsDebugOptions :: ![Text] + , settingsLibrary :: !Library } + +data Library = Library { librarySourceDir :: !Text } data Command = Run | Test | Build @@ -43,7 +49,8 @@ main = do let settings = Toml.decode settingsCodec fpmContents case settings of Left err -> print err - Right settings -> app args settings + Right settings -> do + app args settings app :: Arguments -> Settings -> IO () app args settings = case command' args of @@ -54,19 +61,26 @@ app args settings = case command' args of build :: Settings -> IO () build settings = do putStrLn "Building" - buildLibrary "src" + let compiler = unpack $ settingsCompiler settings + let projectName = unpack $ settingsProjectName settings + let flags = map unpack $ settingsDebugOptions settings + let librarySettings = settingsLibrary settings + let librarySourceDir' = unpack $ librarySourceDir librarySettings + buildLibrary librarySourceDir' [".f90", ".f", ".F", ".F90", ".f95", ".f03"] ("build" </> "library") - (unpack $ compiler settings) - ["-g", "-Wall", "-Wextra", "-Werror", "-pedantic"] - "library" + compiler + flags + projectName [] - buildPrograms "app" - ["build" </> "library"] - [".f90", ".f", ".F", ".F90", ".f95", ".f03"] - ("build" </> "app") - (unpack $ compiler settings) - ["-g", "-Wall", "-Wextra", "-Werror", "-pedantic"] + buildProgram "app" + ["build" </> "library"] + [".f90", ".f", ".F", ".F90", ".f95", ".f03"] + ("build" </> "app") + compiler + flags + projectName + "main.f90" getArguments :: IO Arguments getArguments = execParser @@ -100,4 +114,16 @@ getDirectoriesFiles dirs exts = getDirectoryFilesIO "" newPatterns appendExts dir = map ((dir <//> "*") ++) exts settingsCodec :: TomlCodec Settings -settingsCodec = Settings <$> Toml.text "compiler" .= compiler +settingsCodec = + Settings + <$> Toml.text "compiler" + .= settingsCompiler + <*> Toml.text "name" + .= settingsProjectName + <*> Toml.arrayOf Toml._Text "debug-options" + .= settingsDebugOptions + <*> Toml.table libraryCodec "library" + .= settingsLibrary + +libraryCodec :: TomlCodec Library +libraryCodec = Library <$> Toml.text "source-dir" .= librarySourceDir diff --git a/example_project/app/Hello_world.f90 b/example_project/app/main.f90 index 956a6c2..7783f8f 100644 --- a/example_project/app/Hello_world.f90 +++ b/example_project/app/main.f90 @@ -1,7 +1,7 @@ -program Hello_world +program example_project use Hello_m, only: sayHello implicit none call sayHello("World") -end program Hello_world +end program example_project diff --git a/example_project/fpm.toml b/example_project/fpm.toml index eda6e6b..a8bded7 100644 --- a/example_project/fpm.toml +++ b/example_project/fpm.toml @@ -6,14 +6,13 @@ maintainer = "example@example.com" copyright = "2020 Author" dependencies = [] compiler = "gfortran" -devel-options = ["-g", "-Wall", "-Wextra", "-Werror", "-pedantic"] +debug-options = ["-g", "-Wall", "-Wextra", "-Werror", "-pedantic"] release-options = ["-O3"] [library] -source-dirs = "src" + source-dir = "src" -[executables.Hello_world] -main = "Hello_world.f90" -source-dirs = "app" -linker-options = ["-O3"] +[executables.example_project] +main = "main.f90" +source-dir = "app" dependencies = [] diff --git a/src/Build.hs b/src/Build.hs index e7a43f6..0c692cb 100644 --- a/src/Build.hs +++ b/src/Build.hs @@ -1,6 +1,6 @@ module Build ( buildLibrary - , buildPrograms + , buildProgram ) where @@ -58,26 +58,35 @@ type ModuleName = String data LineContents = ModuleUsed ModuleName | Other -buildPrograms +buildProgram :: FilePath -> [FilePath] -> [FilePattern] -> FilePath -> FilePath -> [String] + -> String + -> FilePath -> IO () -buildPrograms programDirectory libraryDirectories sourceExtensions buildDirectory compiler flags +buildProgram programDirectory libraryDirectories sourceExtensions buildDirectory compiler flags programName programSource = do sourceFiles <- getDirectoriesFiles [programDirectory] sourceExtensions - let sourceFileLookupMap = - createSourceFileLookupMap buildDirectory programDirectory sourceFiles - libraryModuleMaps <- mapM getLibraryModuleMap libraryDirectories - let libraryModuleMap = foldl Map.union Map.empty libraryModuleMaps - let includeFlags = map ("-I" ++) libraryDirectories + let moduleSourceFiles = + filter (/= programDirectory </> programSource) sourceFiles + let moduleObjectFiles = map + (sourceFileToObjectFile buildDirectory programDirectory) + moduleSourceFiles + let sourceFileLookupMap = createSourceFileLookupMap buildDirectory + programDirectory + moduleSourceFiles + let moduleLookupMap = createModuleLookupMap buildDirectory + programDirectory + moduleSourceFiles + otherModuleMaps <- mapM getLibraryModuleMap libraryDirectories + let allModuleMaps = + moduleLookupMap `Map.union` foldl Map.union Map.empty otherModuleMaps + let includeFlags = map ("-I" ++) libraryDirectories archives <- getDirectoriesFiles libraryDirectories [".a"] - let executables = map - (sourceFileToExecutable buildDirectory programDirectory) - sourceFiles shake shakeOptions { shakeFiles = buildDirectory , shakeChange = ChangeModtimeAndDigest , shakeColor = True @@ -85,28 +94,47 @@ buildPrograms programDirectory libraryDirectories sourceExtensions buildDirector , shakeProgress = progressSimple } $ do - buildDirectory </> "*" <.> "o" %> \objectFile -> do + want [buildDirectory </> programName <.> exe] + buildDirectory </> programName <.> exe %> \executable -> do + let objectFile = sourceFileToObjectFile buildDirectory + programDirectory + programSource + let allObjectFiles = objectFile : moduleObjectFiles + need allObjectFiles + need archives + cmd compiler allObjectFiles archives ["-o", executable] flags + buildDirectory </> programSource -<.> "o" %> \objectFile -> do let realObjectFile = foldl (</>) "" $ splitDirectories objectFile - let sourceFile = fromMaybe - undefined - (Map.lookup realObjectFile sourceFileLookupMap) + let sourceFile = programDirectory </> programSource need [sourceFile] modulesUsed <- liftIO $ getModulesUsed sourceFile let moduleFilesNeeded = - mapMaybe (`Map.lookup` libraryModuleMap) modulesUsed + mapMaybe (`Map.lookup` allModuleMaps) modulesUsed + let includeFlags = map ("-I" ++) libraryDirectories need moduleFilesNeeded cmd compiler - ["-c"] + ["-c", "-J" ++ buildDirectory] includeFlags flags ["-o", objectFile, sourceFile] - (\file -> foldl (</>) "" (splitDirectories file) `elem` executables) - ?> \exe -> do - let objectFile = map toLower exe -<.> "o" - need [objectFile] - need archives - cmd compiler objectFile archives ["-o", exe] flags - want executables + map (\ext -> buildDirectory </> "*" <.> ext) ["o", "mod"] + &%> \[objectFile, moduleFile] -> do + let realObjectFile = + foldl (</>) "" $ splitDirectories objectFile + let sourceFile = fromMaybe + undefined + (Map.lookup realObjectFile sourceFileLookupMap) + need [sourceFile] + modulesUsed <- liftIO $ getModulesUsed sourceFile + let moduleFilesNeeded = + mapMaybe (`Map.lookup` allModuleMaps) modulesUsed + let includeFlags = map ("-I" ++) libraryDirectories + need moduleFilesNeeded + cmd compiler + ["-c", "-J" ++ buildDirectory] + includeFlags + flags + ["-o", objectFile, sourceFile] buildLibrary :: FilePath |