From 339efd6e4c371366f4541676644b624af51f8097 Mon Sep 17 00:00:00 2001 From: Brad Richardson Date: Tue, 27 Oct 2020 17:20:01 -0500 Subject: Change bootstrap command line to be more like the Fortran version --- bootstrap/src/Fpm.hs | 186 ++++++++++++++++++++++++++++++++----------------- bootstrap/test/Spec.hs | 60 ++++++++-------- 2 files changed, 152 insertions(+), 94 deletions(-) (limited to 'bootstrap') diff --git a/bootstrap/src/Fpm.hs b/bootstrap/src/Fpm.hs index 115b63e..cee04af 100644 --- a/bootstrap/src/Fpm.hs +++ b/bootstrap/src/Fpm.hs @@ -3,7 +3,6 @@ module Fpm ( Arguments(..) - , Command(..) , getArguments , start ) @@ -43,6 +42,7 @@ import Options.Applicative ( Parser , info , long , metavar + , optional , progDesc , strArgument , strOption @@ -67,7 +67,25 @@ import Toml ( TomlCodec ) import qualified Toml -data Arguments = Arguments { command' :: Command, release :: Bool, commandArguments :: String } +data Arguments = + New + { newName :: String + , newWithExecutable :: Bool + , newWithTest :: Bool + , newWithLib :: Bool + } + | Build + { buildRelease :: Bool } + | Run + { runRelease :: Bool + , runTarget :: Maybe String + , runArgs :: Maybe String + } + | Test + { testRelease :: Bool + , testTarget :: Maybe String + , testArgs :: Maybe String + } data TomlSettings = TomlSettings { tomlSettingsProjectName :: String @@ -107,8 +125,6 @@ data GitRef = Tag String | Branch String | Commit String deriving Show data PathVersionSpec = PathVersionSpec { pathVersionSpecPath :: String } deriving Show -data Command = Run String | Test String | Build | New String Bool Bool - data DependencyTree = Dependency { dependencyName :: String , dependencyPath :: FilePath @@ -118,22 +134,22 @@ data DependencyTree = Dependency { } start :: Arguments -> IO () -start args = case command' args of - New projectName withExecutable withTest -> - createNewProject projectName withExecutable withTest +start args = case args of + New { newName = name, newWithExecutable = withExecutable, newWithTest = withTest, newWithLib = withLib } + -> createNewProject name withExecutable withTest withLib _ -> do fpmContents <- TIO.readFile "fpm.toml" let tomlSettings = Toml.decode settingsCodec fpmContents case tomlSettings of Left err -> print err Right tomlSettings' -> do - appSettings <- toml2AppSettings tomlSettings' (release args) + appSettings <- toml2AppSettings tomlSettings' args app args appSettings app :: Arguments -> AppSettings -> IO () -app args settings = case command' args of - Build -> build settings - Run whichOne -> do +app args settings = case args of + Build{} -> build settings + Run { runTarget = whichOne, runArgs = runArgs } -> do build settings let buildPrefix = appSettingsBuildPrefix settings let @@ -148,10 +164,16 @@ app args settings = case command' args of case canonicalExecutables of [] -> putStrLn "No Executables Found" _ -> case whichOne of - "" -> do + Nothing -> do exitCodes <- mapM system - (map (++ " " ++ commandArguments args) canonicalExecutables) + (map + (++ case runArgs of + Nothing -> "" + Just theArgs -> " " ++ theArgs + ) + canonicalExecutables + ) forM_ exitCodes (\exitCode -> when @@ -161,13 +183,15 @@ app args settings = case command' args of ) (exitWith exitCode) ) - name -> do + Just name -> do case find (name `isSuffixOf`) canonicalExecutables of Nothing -> putStrLn "Executable Not Found" Just specified -> do - exitCode <- system (specified ++ " " ++ (commandArguments args)) + exitCode <- case runArgs of + Nothing -> system specified + Just theArgs -> system (specified ++ " " ++ theArgs) exitWith exitCode - Test whichOne -> do + Test { testTarget = whichOne, testArgs = testArgs } -> do build settings let buildPrefix = appSettingsBuildPrefix settings let @@ -182,10 +206,16 @@ app args settings = case command' args of case canonicalExecutables of [] -> putStrLn "No Tests Found" _ -> case whichOne of - "" -> do + Nothing -> do exitCodes <- mapM system - (map (++ " " ++ commandArguments args) canonicalExecutables) + (map + (++ case testArgs of + Nothing -> "" + Just theArgs -> " " ++ theArgs + ) + canonicalExecutables + ) forM_ exitCodes (\exitCode -> when @@ -195,12 +225,15 @@ app args settings = case command' args of ) (exitWith exitCode) ) - name -> do + Just name -> do case find (name `isSuffixOf`) canonicalExecutables of Nothing -> putStrLn "Test Not Found" Just specified -> do - exitCode <- system (specified ++ " " ++ (commandArguments args)) + exitCode <- case testArgs of + Nothing -> system specified + Just theArgs -> system (specified ++ " " ++ theArgs) exitWith exitCode + _ -> putStrLn "Shouldn't be able to get here" build :: AppSettings -> IO () build settings = do @@ -302,42 +335,61 @@ getArguments = execParser ) arguments :: Parser Arguments -arguments = - Arguments - <$> subparser - ( command "run" (info runArguments (progDesc "Run the executable")) - <> command "test" (info testArguments (progDesc "Run the tests")) - <> command "build" - (info buildArguments (progDesc "Build the executable")) - <> command - "new" - (info newArguments - (progDesc "Create a new project in a new directory") - ) +arguments = subparser + ( command + "new" + (info (newArguments <**> helper) + (progDesc "Create a new project in a new directory") + ) + <> command + "build" + (info (buildArguments <**> helper) (progDesc "Build the project")) + <> command + "run" + (info (runArguments <**> helper) (progDesc "Run the executable(s)")) + <> command "test" + (info (testArguments <**> helper) (progDesc "Run the test(s)")) + ) + +newArguments :: Parser Arguments +newArguments = + New + <$> strArgument + ( metavar "NAME" + <> help "Name of new project (must be a valid Fortran identifier)" ) - <*> switch (long "release" <> help "Build in release mode") - <*> strOption - (long "args" <> metavar "ARGS" <> value "" <> help - "Arguments to pass to executables/tests" + <*> switch (long "app" <> help "Include an executable") + <*> switch (long "test" <> help "Include a test") + <*> switch (long "lib" <> help "Include a library") + +buildArguments :: Parser Arguments +buildArguments = Build <$> switch + (long "release" <> help "Build with optimizations instead of debugging") + +runArguments :: Parser Arguments +runArguments = + Run + <$> switch + ( long "release" + <> help "Build with optimizations instead of debugging" ) + <*> optional + (strArgument + (metavar "TARGET" <> help "Name of the executable to run") + ) + <*> optional + (strArgument (metavar "ARGS" <> help "Arguments to the executable")) -runArguments :: Parser Command -runArguments = Run <$> strArgument - (metavar "EXE" <> value "" <> help "Which executable to run") - -testArguments :: Parser Command +testArguments :: Parser Arguments testArguments = - Test <$> strArgument (metavar "TEST" <> value "" <> help "Which test to run") - -buildArguments :: Parser Command -buildArguments = pure Build - -newArguments :: Parser Command -newArguments = - New - <$> strArgument (metavar "NAME" <> help "Name of new project") - <*> switch (long "with-executable" <> help "Include an executable") - <*> switch (long "with-test" <> help "Include a test") + Test + <$> switch + ( long "release" + <> help "Build with optimizations instead of debugging" + ) + <*> optional + (strArgument (metavar "TARGET" <> help "Name of the test to run")) + <*> optional (strArgument (metavar "ARGS" <> help "Arguments to the test")) getDirectoriesFiles :: [FilePath] -> [FilePattern] -> IO [FilePath] getDirectoriesFiles dirs exts = getDirectoryFilesIO "" newPatterns @@ -437,8 +489,12 @@ pathVersionCodec :: Toml.TomlCodec PathVersionSpec pathVersionCodec = PathVersionSpec <$> Toml.string "path" .= pathVersionSpecPath -toml2AppSettings :: TomlSettings -> Bool -> IO AppSettings -toml2AppSettings tomlSettings release = do +toml2AppSettings :: TomlSettings -> Arguments -> IO AppSettings +toml2AppSettings tomlSettings args = do + let release = case args of + Build { buildRelease = r } -> r + Run { runRelease = r } -> r + Test { testRelease = r } -> r let projectName = tomlSettingsProjectName tomlSettings let compiler = "gfortran" librarySettings <- getLibrarySettings $ tomlSettingsLibrary tomlSettings @@ -682,19 +738,20 @@ buildDependency buildPrefix compiler flags (Dependency name path sourcePath mBui (map fst transitiveDependencies) return $ (buildPath, thisArchive) : transitiveDependencies -createNewProject :: String -> Bool -> Bool -> IO () -createNewProject projectName withExecutable withTest = do +createNewProject :: String -> Bool -> Bool -> Bool -> IO () +createNewProject projectName withExecutable withTest withLib = do createDirectory projectName writeFile (projectName "fpm.toml") (templateFpmToml projectName) writeFile (projectName "README.md") (templateReadme projectName) writeFile (projectName ".gitignore") "build/*\n" - createDirectory (projectName "src") - writeFile (projectName "src" projectName <.> "f90") - (templateModule projectName) + when withLib $ do + createDirectory (projectName "src") + writeFile (projectName "src" projectName <.> "f90") + (templateModule projectName) when withExecutable $ do createDirectory (projectName "app") writeFile (projectName "app" "main.f90") - (templateProgram projectName) + (templateProgram projectName withLib) when withTest $ do createDirectory (projectName "test") writeFile (projectName "test" "main.f90") templateTest @@ -736,12 +793,11 @@ templateReadme :: String -> String templateReadme projectName = "# " ++ projectName ++ "\n" ++ "\n" ++ "My cool new project!\n" -templateProgram :: String -> String -templateProgram projectName = +templateProgram :: String -> Bool -> String +templateProgram projectName withLib = "program main\n" - ++ " use " - ++ projectName - ++ ", only: say_hello\n" + ++ (if withLib then " use " ++ projectName ++ ", only: say_hello\n" else "" + ) ++ "\n" ++ " implicit none\n" ++ "\n" diff --git a/bootstrap/test/Spec.hs b/bootstrap/test/Spec.hs index 4e660e7..c1f7108 100644 --- a/bootstrap/test/Spec.hs +++ b/bootstrap/test/Spec.hs @@ -1,6 +1,5 @@ import Development.Shake.FilePath ( () ) import Fpm ( Arguments(..) - , Command(..) , start ) import System.Directory ( withCurrentDirectory ) @@ -19,49 +18,52 @@ main = do testHelloWorld :: IO () testHelloWorld = - withCurrentDirectory (example_path "hello_world") $ start $ Arguments - (Run "") - False - "" + withCurrentDirectory (example_path "hello_world") $ start $ Run + { runRelease = False + , runTarget = Nothing + , runArgs = Nothing + } testHelloComplex :: IO () testHelloComplex = - withCurrentDirectory (example_path "hello_complex") $ start $ Arguments - (Test "") - False - "" + withCurrentDirectory (example_path "hello_complex") $ start $ Test + { testRelease = False + , testTarget = Nothing + , testArgs = Nothing + } testHelloFpm :: IO () testHelloFpm = - withCurrentDirectory (example_path "hello_fpm") $ start $ Arguments - (Run "") - False - "" + withCurrentDirectory (example_path "hello_fpm") $ start $ Run + { runRelease = False + , runTarget = Nothing + , runArgs = Nothing + } testCircular :: IO () testCircular = - withCurrentDirectory (example_path "circular_example") $ start $ Arguments - (Test "") - False - "" + withCurrentDirectory (example_path "circular_example") $ start $ Test + { testRelease = False + , testTarget = Nothing + , testArgs = Nothing + } testWithMakefile :: IO () testWithMakefile = - withCurrentDirectory (example_path "with_makefile") $ start $ Arguments - (Build) - False - "" + withCurrentDirectory (example_path "with_makefile") $ start $ Build + { buildRelease = False + } testMakefileComplex :: IO () testMakefileComplex = - withCurrentDirectory (example_path "makefile_complex") $ start $ Arguments - (Run "") - False - "" + withCurrentDirectory (example_path "makefile_complex") $ start $ Run + { runRelease = False + , runTarget = Nothing + , runArgs = Nothing + } testSubmodule :: IO () testSubmodule = - withCurrentDirectory (example_path "submodules") $ start $ Arguments - (Build) - False - "" + withCurrentDirectory (example_path "submodules") $ start $ Build + { buildRelease = False + } -- cgit v1.2.3 From 55f9d0539bc30e198796e4f60ae3e011513afb69 Mon Sep 17 00:00:00 2001 From: Brad Richardson Date: Wed, 28 Oct 2020 09:39:22 -0500 Subject: Use compiler version and flags to construct build folder name --- bootstrap/package.yaml | 1 + bootstrap/src/Fpm.hs | 63 ++++++++++++++++++++++++++++---------------------- 2 files changed, 36 insertions(+), 28 deletions(-) (limited to 'bootstrap') diff --git a/bootstrap/package.yaml b/bootstrap/package.yaml index 26a7f74..1f5d0fd 100644 --- a/bootstrap/package.yaml +++ b/bootstrap/package.yaml @@ -25,6 +25,7 @@ dependencies: - directory - extra - filepath +- hashable - MissingH - optparse-applicative - process diff --git a/bootstrap/src/Fpm.hs b/bootstrap/src/Fpm.hs index cee04af..0c2af57 100644 --- a/bootstrap/src/Fpm.hs +++ b/bootstrap/src/Fpm.hs @@ -16,6 +16,7 @@ import Control.Monad.Extra ( concatMapM , forM_ , when ) +import Data.Hashable (hash) import Data.List ( isSuffixOf , find , nub @@ -29,6 +30,7 @@ import Development.Shake ( FilePattern import Development.Shake.FilePath ( () , (<.>) , exe + , splitDirectories ) import Options.Applicative ( Parser , (<**>) @@ -59,7 +61,7 @@ import System.Directory ( createDirectory import System.Exit ( ExitCode(..) , exitWith ) -import System.Process ( runCommand +import System.Process ( readProcess , system ) import Toml ( TomlCodec @@ -502,36 +504,37 @@ toml2AppSettings tomlSettings args = do (tomlSettingsExecutables tomlSettings) projectName testSettings <- getTestSettings $ tomlSettingsTests tomlSettings - buildPrefix <- makeBuildPrefix compiler release + let flags = 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" + ] + buildPrefix <- makeBuildPrefix compiler flags 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" - ] + , appSettingsFlags = flags , appSettingsLibrary = librarySettings , appSettingsExecutables = executableSettings , appSettingsTests = testSettings @@ -587,11 +590,15 @@ getTestSettings [] = do else return [] getTestSettings tests = return tests -makeBuildPrefix :: String -> Bool -> IO String -makeBuildPrefix compiler release = +makeBuildPrefix :: FilePath -> [String] -> IO FilePath +makeBuildPrefix compiler flags = do -- TODO Figure out what other info should be part of this -- Probably version, and make sure to not include path to the compiler - return $ "build" compiler ++ "_" ++ if release then "release" else "debug" + versionInfo <- readProcess compiler ["--version"] [] + let compilerName = last (splitDirectories compiler) + let versionHash = hash versionInfo + let flagsHash = hash flags + return $ "build" compilerName ++ "_" ++ show versionHash ++ "_" ++ show flagsHash {- Fetching the dependencies is done on a sort of breadth first approach. All -- cgit v1.2.3 From 7b191a773d3a1f91131943a4ed84b285839bdf35 Mon Sep 17 00:00:00 2001 From: Brad Richardson Date: Wed, 28 Oct 2020 12:33:07 -0500 Subject: Add command line options to specify the compiler --- bootstrap/src/Fpm.hs | 127 ++++++++++++++++++++++++++++++++----------------- bootstrap/test/Spec.hs | 7 +++ 2 files changed, 91 insertions(+), 43 deletions(-) (limited to 'bootstrap') diff --git a/bootstrap/src/Fpm.hs b/bootstrap/src/Fpm.hs index 0c2af57..49c7ee8 100644 --- a/bootstrap/src/Fpm.hs +++ b/bootstrap/src/Fpm.hs @@ -16,7 +16,7 @@ import Control.Monad.Extra ( concatMapM , forM_ , when ) -import Data.Hashable (hash) +import Data.Hashable ( hash ) import Data.List ( isSuffixOf , find , nub @@ -46,6 +46,8 @@ import Options.Applicative ( Parser , metavar , optional , progDesc + , short + , showDefault , strArgument , strOption , subparser @@ -77,14 +79,18 @@ data Arguments = , newWithLib :: Bool } | Build - { buildRelease :: Bool } + { buildRelease :: Bool + , buildCompiler :: FilePath + } | Run { runRelease :: Bool + , runCompiler :: FilePath , runTarget :: Maybe String , runArgs :: Maybe String } | Test { testRelease :: Bool + , testCompiler :: FilePath , testTarget :: Maybe String , testArgs :: Maybe String } @@ -365,8 +371,19 @@ newArguments = <*> switch (long "lib" <> help "Include a library") buildArguments :: Parser Arguments -buildArguments = Build <$> switch - (long "release" <> help "Build with optimizations instead of debugging") +buildArguments = + Build + <$> switch + ( long "release" + <> help "Build with optimizations instead of debugging" + ) + <*> strOption + ( long "compiler" + <> metavar "COMPILER" + <> value "gfortran" + <> help "specify the compiler to use" + <> showDefault + ) runArguments :: Parser Arguments runArguments = @@ -375,6 +392,13 @@ runArguments = ( long "release" <> help "Build with optimizations instead of debugging" ) + <*> strOption + ( long "compiler" + <> metavar "COMPILER" + <> value "gfortran" + <> help "specify the compiler to use" + <> showDefault + ) <*> optional (strArgument (metavar "TARGET" <> help "Name of the executable to run") @@ -389,6 +413,13 @@ testArguments = ( long "release" <> help "Build with optimizations instead of debugging" ) + <*> strOption + ( long "compiler" + <> metavar "COMPILER" + <> value "gfortran" + <> help "specify the compiler to use" + <> showDefault + ) <*> optional (strArgument (metavar "TARGET" <> help "Name of the test to run")) <*> optional (strArgument (metavar "ARGS" <> help "Arguments to the test")) @@ -498,49 +529,53 @@ toml2AppSettings tomlSettings args = do Run { runRelease = r } -> r Test { testRelease = r } -> r let projectName = tomlSettingsProjectName tomlSettings - let compiler = "gfortran" + let compiler = case args of + Build { buildCompiler = c } -> c + Run { runCompiler = c } -> c + Test { testCompiler = c } -> c librarySettings <- getLibrarySettings $ tomlSettingsLibrary tomlSettings executableSettings <- getExecutableSettings (tomlSettingsExecutables tomlSettings) projectName testSettings <- getTestSettings $ tomlSettingsTests tomlSettings - let flags = 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" - ] - buildPrefix <- makeBuildPrefix compiler flags + let flags = if compiler == "gfortran" + then 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" + ] + else [] + buildPrefix <- makeBuildPrefix compiler flags let dependencies = tomlSettingsDependencies tomlSettings let devDependencies = tomlSettingsDevDependencies tomlSettings - return AppSettings - { appSettingsCompiler = compiler - , appSettingsProjectName = projectName - , appSettingsBuildPrefix = buildPrefix - , appSettingsFlags = flags - , appSettingsLibrary = librarySettings - , appSettingsExecutables = executableSettings - , appSettingsTests = testSettings - , appSettingsDependencies = dependencies - , appSettingsDevDependencies = devDependencies - } + return AppSettings { appSettingsCompiler = compiler + , appSettingsProjectName = projectName + , appSettingsBuildPrefix = buildPrefix + , appSettingsFlags = flags + , appSettingsLibrary = librarySettings + , appSettingsExecutables = executableSettings + , appSettingsTests = testSettings + , appSettingsDependencies = dependencies + , appSettingsDevDependencies = devDependencies + } getLibrarySettings :: Maybe Library -> IO (Maybe Library) getLibrarySettings maybeSettings = case maybeSettings of @@ -596,9 +631,15 @@ makeBuildPrefix compiler flags = do -- Probably version, and make sure to not include path to the compiler versionInfo <- readProcess compiler ["--version"] [] let compilerName = last (splitDirectories compiler) - let versionHash = hash versionInfo - let flagsHash = hash flags - return $ "build" compilerName ++ "_" ++ show versionHash ++ "_" ++ show flagsHash + let versionHash = hash versionInfo + let flagsHash = hash flags + return + $ "build" + compilerName + ++ "_" + ++ show versionHash + ++ "_" + ++ show flagsHash {- Fetching the dependencies is done on a sort of breadth first approach. All diff --git a/bootstrap/test/Spec.hs b/bootstrap/test/Spec.hs index c1f7108..ac72b07 100644 --- a/bootstrap/test/Spec.hs +++ b/bootstrap/test/Spec.hs @@ -20,6 +20,7 @@ testHelloWorld :: IO () testHelloWorld = withCurrentDirectory (example_path "hello_world") $ start $ Run { runRelease = False + , runCompiler = "gfortran" , runTarget = Nothing , runArgs = Nothing } @@ -28,6 +29,7 @@ testHelloComplex :: IO () testHelloComplex = withCurrentDirectory (example_path "hello_complex") $ start $ Test { testRelease = False + , testCompiler = "gfortran" , testTarget = Nothing , testArgs = Nothing } @@ -36,6 +38,7 @@ testHelloFpm :: IO () testHelloFpm = withCurrentDirectory (example_path "hello_fpm") $ start $ Run { runRelease = False + , runCompiler = "gfortran" , runTarget = Nothing , runArgs = Nothing } @@ -44,6 +47,7 @@ testCircular :: IO () testCircular = withCurrentDirectory (example_path "circular_example") $ start $ Test { testRelease = False + , testCompiler = "gfortran" , testTarget = Nothing , testArgs = Nothing } @@ -52,12 +56,14 @@ testWithMakefile :: IO () testWithMakefile = withCurrentDirectory (example_path "with_makefile") $ start $ Build { buildRelease = False + , buildCompiler = "gfortran" } testMakefileComplex :: IO () testMakefileComplex = withCurrentDirectory (example_path "makefile_complex") $ start $ Run { runRelease = False + , runCompiler = "gfortran" , runTarget = Nothing , runArgs = Nothing } @@ -66,4 +72,5 @@ testSubmodule :: IO () testSubmodule = withCurrentDirectory (example_path "submodules") $ start $ Build { buildRelease = False + , buildCompiler = "gfortran" } -- cgit v1.2.3 From 5d122c2854dbec1470a660bf80cd0544a8806a78 Mon Sep 17 00:00:00 2001 From: Brad Richardson Date: Wed, 28 Oct 2020 12:49:26 -0500 Subject: Add command line options to specify compiler flags --- bootstrap/src/Fpm.hs | 86 +++++++++++++++++++++++++++++++++++--------------- bootstrap/test/Spec.hs | 7 ++++ 2 files changed, 67 insertions(+), 26 deletions(-) (limited to 'bootstrap') diff --git a/bootstrap/src/Fpm.hs b/bootstrap/src/Fpm.hs index 49c7ee8..cfb67df 100644 --- a/bootstrap/src/Fpm.hs +++ b/bootstrap/src/Fpm.hs @@ -43,6 +43,7 @@ import Options.Applicative ( Parser , helper , info , long + , many , metavar , optional , progDesc @@ -81,16 +82,19 @@ data Arguments = | Build { buildRelease :: Bool , buildCompiler :: FilePath + , buildFlags :: [String] } | Run { runRelease :: Bool , runCompiler :: FilePath + , runFlags :: [String] , runTarget :: Maybe String , runArgs :: Maybe String } | Test { testRelease :: Bool , testCompiler :: FilePath + , testFlags :: [String] , testTarget :: Maybe String , testArgs :: Maybe String } @@ -384,6 +388,14 @@ buildArguments = <> help "specify the compiler to use" <> showDefault ) + <*> many + (strOption + ( long "flag" + <> metavar "FLAG" + <> help + "specify an addional argument to pass to the compiler (can appear multiple times)" + ) + ) runArguments :: Parser Arguments runArguments = @@ -399,6 +411,14 @@ runArguments = <> help "specify the compiler to use" <> showDefault ) + <*> many + (strOption + ( long "flag" + <> metavar "FLAG" + <> help + "specify an addional argument to pass to the compiler (can appear multiple times)" + ) + ) <*> optional (strArgument (metavar "TARGET" <> help "Name of the executable to run") @@ -420,6 +440,14 @@ testArguments = <> help "specify the compiler to use" <> showDefault ) + <*> many + (strOption + ( long "flag" + <> metavar "FLAG" + <> help + "specify an addional argument to pass to the compiler (can appear multiple times)" + ) + ) <*> optional (strArgument (metavar "TARGET" <> help "Name of the test to run")) <*> optional (strArgument (metavar "ARGS" <> help "Arguments to the test")) @@ -531,38 +559,44 @@ toml2AppSettings tomlSettings args = do let projectName = tomlSettingsProjectName tomlSettings let compiler = case args of Build { buildCompiler = c } -> c - Run { runCompiler = c } -> c - Test { testCompiler = c } -> c + Run { runCompiler = c } -> c + Test { testCompiler = c } -> c + let specifiedFlags = case args of + Build { buildFlags = f } -> f + Run { runFlags = f } -> f + Test { testFlags = f } -> f librarySettings <- getLibrarySettings $ tomlSettingsLibrary tomlSettings executableSettings <- getExecutableSettings (tomlSettingsExecutables tomlSettings) projectName testSettings <- getTestSettings $ tomlSettingsTests tomlSettings let flags = if compiler == "gfortran" - then 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" - ] - else [] + then case specifiedFlags of + [] -> 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" + ] + flags -> flags + else specifiedFlags buildPrefix <- makeBuildPrefix compiler flags let dependencies = tomlSettingsDependencies tomlSettings let devDependencies = tomlSettingsDevDependencies tomlSettings diff --git a/bootstrap/test/Spec.hs b/bootstrap/test/Spec.hs index ac72b07..dfa73df 100644 --- a/bootstrap/test/Spec.hs +++ b/bootstrap/test/Spec.hs @@ -21,6 +21,7 @@ testHelloWorld = withCurrentDirectory (example_path "hello_world") $ start $ Run { runRelease = False , runCompiler = "gfortran" + , runFlags = [] , runTarget = Nothing , runArgs = Nothing } @@ -30,6 +31,7 @@ testHelloComplex = withCurrentDirectory (example_path "hello_complex") $ start $ Test { testRelease = False , testCompiler = "gfortran" + , testFlags = [] , testTarget = Nothing , testArgs = Nothing } @@ -39,6 +41,7 @@ testHelloFpm = withCurrentDirectory (example_path "hello_fpm") $ start $ Run { runRelease = False , runCompiler = "gfortran" + , runFlags = [] , runTarget = Nothing , runArgs = Nothing } @@ -48,6 +51,7 @@ testCircular = withCurrentDirectory (example_path "circular_example") $ start $ Test { testRelease = False , testCompiler = "gfortran" + , testFlags = [] , testTarget = Nothing , testArgs = Nothing } @@ -57,6 +61,7 @@ testWithMakefile = withCurrentDirectory (example_path "with_makefile") $ start $ Build { buildRelease = False , buildCompiler = "gfortran" + , buildFlags = [] } testMakefileComplex :: IO () @@ -64,6 +69,7 @@ testMakefileComplex = withCurrentDirectory (example_path "makefile_complex") $ start $ Run { runRelease = False , runCompiler = "gfortran" + , runFlags = [] , runTarget = Nothing , runArgs = Nothing } @@ -73,4 +79,5 @@ testSubmodule = withCurrentDirectory (example_path "submodules") $ start $ Build { buildRelease = False , buildCompiler = "gfortran" + , buildFlags = [] } -- cgit v1.2.3 From fa04b1f441b18cc50af403a0a58c38681c2e66d7 Mon Sep 17 00:00:00 2001 From: Brad Richardson Date: Wed, 28 Oct 2020 16:19:04 -0500 Subject: Switch test or executable target to option - this allows the '--' to signify that all remaining arguments are to the test/executable --- bootstrap/src/Fpm.hs | 44 ++++++++++++++++++++++++++++++-------------- 1 file changed, 30 insertions(+), 14 deletions(-) (limited to 'bootstrap') diff --git a/bootstrap/src/Fpm.hs b/bootstrap/src/Fpm.hs index cfb67df..c23263e 100644 --- a/bootstrap/src/Fpm.hs +++ b/bootstrap/src/Fpm.hs @@ -17,7 +17,8 @@ import Control.Monad.Extra ( concatMapM , when ) import Data.Hashable ( hash ) -import Data.List ( isSuffixOf +import Data.List ( intercalate + , isSuffixOf , find , nub ) @@ -35,6 +36,7 @@ import Development.Shake.FilePath ( () import Options.Applicative ( Parser , (<**>) , (<|>) + , auto , command , execParser , fullDesc @@ -45,6 +47,7 @@ import Options.Applicative ( Parser , long , many , metavar + , option , optional , progDesc , short @@ -89,14 +92,14 @@ data Arguments = , runCompiler :: FilePath , runFlags :: [String] , runTarget :: Maybe String - , runArgs :: Maybe String + , runArgs :: Maybe [String] } | Test { testRelease :: Bool , testCompiler :: FilePath , testFlags :: [String] , testTarget :: Maybe String - , testArgs :: Maybe String + , testArgs :: Maybe [String] } data TomlSettings = TomlSettings { @@ -182,7 +185,7 @@ app args settings = case args of (map (++ case runArgs of Nothing -> "" - Just theArgs -> " " ++ theArgs + Just theArgs -> " " ++ (intercalate " " theArgs) ) canonicalExecutables ) @@ -200,8 +203,9 @@ app args settings = case args of Nothing -> putStrLn "Executable Not Found" Just specified -> do exitCode <- case runArgs of - Nothing -> system specified - Just theArgs -> system (specified ++ " " ++ theArgs) + Nothing -> system specified + Just theArgs -> + system (specified ++ " " ++ (intercalate " " theArgs)) exitWith exitCode Test { testTarget = whichOne, testArgs = testArgs } -> do build settings @@ -224,7 +228,7 @@ app args settings = case args of (map (++ case testArgs of Nothing -> "" - Just theArgs -> " " ++ theArgs + Just theArgs -> " " ++ (intercalate " " theArgs) ) canonicalExecutables ) @@ -242,8 +246,9 @@ app args settings = case args of Nothing -> putStrLn "Test Not Found" Just specified -> do exitCode <- case testArgs of - Nothing -> system specified - Just theArgs -> system (specified ++ " " ++ theArgs) + Nothing -> system specified + Just theArgs -> + system (specified ++ " " ++ (intercalate " " theArgs)) exitWith exitCode _ -> putStrLn "Shouldn't be able to get here" @@ -420,11 +425,17 @@ runArguments = ) ) <*> optional - (strArgument - (metavar "TARGET" <> help "Name of the executable to run") + (strOption + (long "target" <> metavar "TARGET" <> help + "Name of the executable to run" + ) ) <*> optional - (strArgument (metavar "ARGS" <> help "Arguments to the executable")) + (many + (strArgument + (metavar "ARGS" <> help "Arguments to the executable(s) (should follow '--')") + ) + ) testArguments :: Parser Arguments testArguments = @@ -449,8 +460,13 @@ testArguments = ) ) <*> optional - (strArgument (metavar "TARGET" <> help "Name of the test to run")) - <*> optional (strArgument (metavar "ARGS" <> help "Arguments to the test")) + (strOption (long "target" <> metavar "TARGET" <> help "Name of the test to run")) + <*> optional + (many + (strArgument + (metavar "ARGS" <> help "Arguments to the test(s) (should follow '--')") + ) + ) getDirectoriesFiles :: [FilePath] -> [FilePattern] -> IO [FilePath] getDirectoriesFiles dirs exts = getDirectoryFilesIO "" newPatterns -- cgit v1.2.3 From a07bf3fb3fc07a2c3bf13f8c36a158108a38cefa Mon Sep 17 00:00:00 2001 From: Brad Richardson Date: Thu, 29 Oct 2020 11:56:15 -0500 Subject: Change build directory hashes to hex format --- bootstrap/src/Fpm.hs | 9 +++++---- 1 file changed, 5 insertions(+), 4 deletions(-) (limited to 'bootstrap') diff --git a/bootstrap/src/Fpm.hs b/bootstrap/src/Fpm.hs index c23263e..18831d8 100644 --- a/bootstrap/src/Fpm.hs +++ b/bootstrap/src/Fpm.hs @@ -33,6 +33,7 @@ import Development.Shake.FilePath ( () , exe , splitDirectories ) +import Numeric (showHex) import Options.Applicative ( Parser , (<**>) , (<|>) @@ -681,15 +682,15 @@ makeBuildPrefix compiler flags = do -- Probably version, and make sure to not include path to the compiler versionInfo <- readProcess compiler ["--version"] [] let compilerName = last (splitDirectories compiler) - let versionHash = hash versionInfo - let flagsHash = hash flags + let versionHash = abs (hash versionInfo) + let flagsHash = abs (hash flags) return $ "build" compilerName ++ "_" - ++ show versionHash + ++ showHex versionHash "" ++ "_" - ++ show flagsHash + ++ showHex flagsHash "" {- Fetching the dependencies is done on a sort of breadth first approach. All -- cgit v1.2.3 From b38b29f1189d8f5c2dda4980e85b4f0b2b413689 Mon Sep 17 00:00:00 2001 From: Brad Richardson Date: Mon, 9 Nov 2020 16:18:43 -0600 Subject: Add check for if user supplied `--release` and `--flag`. --- bootstrap/src/Fpm.hs | 3 +++ 1 file changed, 3 insertions(+) (limited to 'bootstrap') diff --git a/bootstrap/src/Fpm.hs b/bootstrap/src/Fpm.hs index 18831d8..de4eafb 100644 --- a/bootstrap/src/Fpm.hs +++ b/bootstrap/src/Fpm.hs @@ -582,6 +582,9 @@ toml2AppSettings tomlSettings args = do Build { buildFlags = f } -> f Run { runFlags = f } -> f Test { testFlags = f } -> f + when (release && (length specifiedFlags > 0)) $ do + putStrLn "--release and --flag are mutually exclusive" + exitWith (ExitFailure 1) librarySettings <- getLibrarySettings $ tomlSettingsLibrary tomlSettings executableSettings <- getExecutableSettings (tomlSettingsExecutables tomlSettings) -- cgit v1.2.3 From 3c6440b42b754ca2a14a746012e3592e26ca7782 Mon Sep 17 00:00:00 2001 From: Brad Richardson Date: Mon, 9 Nov 2020 16:40:59 -0600 Subject: Refactor flag definition for easier support of other compilers --- bootstrap/src/Fpm.hs | 38 +++++++++++--------------------------- 1 file changed, 11 insertions(+), 27 deletions(-) (limited to 'bootstrap') diff --git a/bootstrap/src/Fpm.hs b/bootstrap/src/Fpm.hs index de4eafb..db79f5e 100644 --- a/bootstrap/src/Fpm.hs +++ b/bootstrap/src/Fpm.hs @@ -18,6 +18,7 @@ import Control.Monad.Extra ( concatMapM ) import Data.Hashable ( hash ) import Data.List ( intercalate + , isInfixOf , isSuffixOf , find , nub @@ -590,33 +591,7 @@ toml2AppSettings tomlSettings args = do (tomlSettingsExecutables tomlSettings) projectName testSettings <- getTestSettings $ tomlSettingsTests tomlSettings - let flags = if compiler == "gfortran" - then case specifiedFlags of - [] -> 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" - ] - flags -> flags - else specifiedFlags + flags <- defineFlags specifiedFlags compiler release buildPrefix <- makeBuildPrefix compiler flags let dependencies = tomlSettingsDependencies tomlSettings let devDependencies = tomlSettingsDevDependencies tomlSettings @@ -631,6 +606,15 @@ toml2AppSettings tomlSettings args = do , appSettingsDevDependencies = devDependencies } +defineFlags :: [String] -> FilePath -> Bool -> IO [String] +defineFlags [] compiler release + | "gfortran" `isInfixOf` compiler = return $ 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"] + | "caf" `isInfixOf` compiler = return $ 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"] + | otherwise = do + putStrLn $ "Sorry, compiler is currently unsupported: " ++ compiler + exitWith (ExitFailure 1) +defineFlags specifiedFlags _ _ = return specifiedFlags + getLibrarySettings :: Maybe Library -> IO (Maybe Library) getLibrarySettings maybeSettings = case maybeSettings of Just settings -> return maybeSettings -- cgit v1.2.3 From ed3f9c6cf742620a873eb794896ef232d606a614 Mon Sep 17 00:00:00 2001 From: Brad Richardson Date: Mon, 9 Nov 2020 16:42:18 -0600 Subject: Fix formatting --- bootstrap/src/Fpm.hs | 71 ++++++++++++++++++++++++++++++++++++++++++++-------- 1 file changed, 61 insertions(+), 10 deletions(-) (limited to 'bootstrap') diff --git a/bootstrap/src/Fpm.hs b/bootstrap/src/Fpm.hs index db79f5e..b076459 100644 --- a/bootstrap/src/Fpm.hs +++ b/bootstrap/src/Fpm.hs @@ -34,7 +34,7 @@ import Development.Shake.FilePath ( () , exe , splitDirectories ) -import Numeric (showHex) +import Numeric ( showHex ) import Options.Applicative ( Parser , (<**>) , (<|>) @@ -435,7 +435,9 @@ runArguments = <*> optional (many (strArgument - (metavar "ARGS" <> help "Arguments to the executable(s) (should follow '--')") + ( metavar "ARGS" + <> help "Arguments to the executable(s) (should follow '--')" + ) ) ) @@ -462,11 +464,16 @@ testArguments = ) ) <*> optional - (strOption (long "target" <> metavar "TARGET" <> help "Name of the test to run")) + (strOption + (long "target" <> metavar "TARGET" <> help "Name of the test to run" + ) + ) <*> optional (many (strArgument - (metavar "ARGS" <> help "Arguments to the test(s) (should follow '--')") + ( metavar "ARGS" + <> help "Arguments to the test(s) (should follow '--')" + ) ) ) @@ -591,8 +598,8 @@ toml2AppSettings tomlSettings args = do (tomlSettingsExecutables tomlSettings) projectName testSettings <- getTestSettings $ tomlSettingsTests tomlSettings - flags <- defineFlags specifiedFlags compiler release - buildPrefix <- makeBuildPrefix compiler flags + flags <- defineFlags specifiedFlags compiler release + buildPrefix <- makeBuildPrefix compiler flags let dependencies = tomlSettingsDependencies tomlSettings let devDependencies = tomlSettingsDevDependencies tomlSettings return AppSettings { appSettingsCompiler = compiler @@ -608,11 +615,55 @@ toml2AppSettings tomlSettings args = do defineFlags :: [String] -> FilePath -> Bool -> IO [String] defineFlags [] compiler release - | "gfortran" `isInfixOf` compiler = return $ 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"] - | "caf" `isInfixOf` compiler = return $ 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"] + | "gfortran" `isInfixOf` compiler = return $ 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" + ] + | "caf" `isInfixOf` compiler = return $ 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" + ] | otherwise = do - putStrLn $ "Sorry, compiler is currently unsupported: " ++ compiler - exitWith (ExitFailure 1) + putStrLn $ "Sorry, compiler is currently unsupported: " ++ compiler + exitWith (ExitFailure 1) defineFlags specifiedFlags _ _ = return specifiedFlags getLibrarySettings :: Maybe Library -> IO (Maybe Library) -- cgit v1.2.3 From 5ae9d75cbe87590baddf6b233286b6221b74657e Mon Sep 17 00:00:00 2001 From: Brad Richardson Date: Mon, 9 Nov 2020 17:42:07 -0600 Subject: Refactor to make supporting more compilers more straightforward --- bootstrap/src/Build.hs | 41 ++++++----- bootstrap/src/Fpm.hs | 186 +++++++++++++++++++++++++------------------------ 2 files changed, 119 insertions(+), 108 deletions(-) (limited to 'bootstrap') diff --git a/bootstrap/src/Build.hs b/bootstrap/src/Build.hs index 083e646..0d22112 100644 --- a/bootstrap/src/Build.hs +++ b/bootstrap/src/Build.hs @@ -1,6 +1,7 @@ {-# LANGUAGE MultiWayIf #-} module Build - ( buildLibrary + ( CompilerSettings(..) + , buildLibrary , buildProgram , buildWithScript ) @@ -50,22 +51,28 @@ import System.Directory ( createDirectoryIfMissing , withCurrentDirectory ) +data CompilerSettings = CompilerSettings { + compilerSettingsCompiler :: FilePath + , compilerSettingsFlags :: [String] + , compilerSettingsModuleFlag :: String + , compilerSettingsIncludeFlag :: String +} + buildProgram :: FilePath -> [FilePath] -> [FilePattern] -> FilePath - -> FilePath - -> [String] + -> CompilerSettings -> String -> FilePath -> [FilePath] -> IO () -buildProgram programDirectory' libraryDirectories sourceExtensions buildDirectory' compiler flags programName programSource archives +buildProgram programDirectory' libraryDirectories sourceExtensions buildDirectory' (CompilerSettings { compilerSettingsCompiler = compiler, compilerSettingsFlags = flags, compilerSettingsModuleFlag = moduleFlag, compilerSettingsIncludeFlag = includeFlag }) programName programSource archives = do let programDirectory = foldl1 () (splitDirectories programDirectory') - let buildDirectory = foldl1 () (splitDirectories buildDirectory') - let includeFlags = map ("-I" ++) libraryDirectories + let buildDirectory = foldl1 () (splitDirectories buildDirectory') + let includeFlags = map (includeFlag ++) libraryDirectories sourceFiles <- getDirectoriesFiles [programDirectory] sourceExtensions rawSources <- mapM sourceFileToRawSource sourceFiles let sources' = map processRawSource rawSources @@ -98,7 +105,7 @@ buildProgram programDirectory' libraryDirectories sourceExtensions buildDirector in fileMatcher &?> \(objectFile : _) -> do need (sourceFile : directDependencies) cmd compiler - ["-c", "-J" ++ buildDirectory] + ["-c", moduleFlag ++ buildDirectory] includeFlags flags ["-o", objectFile, sourceFile] @@ -112,14 +119,13 @@ buildLibrary :: FilePath -> [FilePattern] -> FilePath - -> FilePath - -> [String] + -> CompilerSettings -> String -> [FilePath] -> IO (FilePath) -buildLibrary libraryDirectory sourceExtensions buildDirectory compiler flags libraryName otherLibraryDirectories +buildLibrary libraryDirectory sourceExtensions buildDirectory (CompilerSettings { compilerSettingsCompiler = compiler, compilerSettingsFlags = flags, compilerSettingsModuleFlag = moduleFlag, compilerSettingsIncludeFlag = includeFlag }) libraryName otherLibraryDirectories = do - let includeFlags = map ("-I" ++) otherLibraryDirectories + let includeFlags = map (includeFlag ++) otherLibraryDirectories sourceFiles <- getDirectoriesFiles [libraryDirectory] sourceExtensions rawSources <- mapM sourceFileToRawSource sourceFiles let sources = map processRawSource rawSources @@ -149,7 +155,7 @@ buildLibrary libraryDirectory sourceExtensions buildDirectory compiler flags lib in fileMatcher &?> \(objectFile : _) -> do need (sourceFile : directDependencies) cmd compiler - ["-c", "-J" ++ buildDirectory] + ["-c", moduleFlag ++ buildDirectory] includeFlags flags ["-o", objectFile, sourceFile] @@ -164,18 +170,19 @@ buildWithScript :: String -> FilePath -> FilePath - -> FilePath - -> [String] + -> CompilerSettings -> String -> [FilePath] -> IO (FilePath) -buildWithScript script projectDirectory buildDirectory compiler flags libraryName otherLibraryDirectories +buildWithScript script projectDirectory buildDirectory (CompilerSettings { compilerSettingsCompiler = compiler, compilerSettingsFlags = flags, compilerSettingsModuleFlag = moduleFlag, compilerSettingsIncludeFlag = includeFlag }) libraryName otherLibraryDirectories = do absoluteBuildDirectory <- makeAbsolute buildDirectory createDirectoryIfMissing True absoluteBuildDirectory absoluteLibraryDirectories <- mapM makeAbsolute otherLibraryDirectories - setEnv "FC" compiler - setEnv "FFLAGS" (intercalate " " flags) + setEnv "FC" compiler + setEnv "FFLAGS" (intercalate " " flags) + setEnv "FINCLUDEFLAG" includeFlag + setEnv "FMODUELFLAG" moduleFlag setEnv "BUILD_DIR" $ unWindowsPath absoluteBuildDirectory setEnv "INCLUDE_DIRS" (intercalate " " (map unWindowsPath absoluteLibraryDirectories)) diff --git a/bootstrap/src/Fpm.hs b/bootstrap/src/Fpm.hs index b076459..256f8e1 100644 --- a/bootstrap/src/Fpm.hs +++ b/bootstrap/src/Fpm.hs @@ -8,7 +8,8 @@ module Fpm ) where -import Build ( buildLibrary +import Build ( CompilerSettings(..) + , buildLibrary , buildProgram , buildWithScript ) @@ -114,10 +115,9 @@ data TomlSettings = TomlSettings { } data AppSettings = AppSettings { - appSettingsCompiler :: String + appSettingsCompiler :: CompilerSettings , appSettingsProjectName :: String , appSettingsBuildPrefix :: String - , appSettingsFlags :: [String] , appSettingsLibrary :: (Maybe Library) , appSettingsExecutables :: [Executable] , appSettingsTests :: [Executable] @@ -256,16 +256,14 @@ app args settings = case args of build :: AppSettings -> IO () build settings = do - let compiler = appSettingsCompiler settings - let projectName = appSettingsProjectName settings - let buildPrefix = appSettingsBuildPrefix settings - let flags = appSettingsFlags settings - let executables = appSettingsExecutables settings - let tests = appSettingsTests settings + let compilerSettings = appSettingsCompiler settings + let projectName = appSettingsProjectName settings + let buildPrefix = appSettingsBuildPrefix settings + let executables = appSettingsExecutables settings + let tests = appSettingsTests settings mainDependencyTrees <- fetchDependencies (appSettingsDependencies settings) builtDependencies <- buildDependencies buildPrefix - compiler - flags + compilerSettings mainDependencyTrees (executableDepends, maybeTree) <- case appSettingsLibrary settings of Just librarySettings -> do @@ -281,15 +279,13 @@ build settings = do Just script -> buildWithScript script "." (buildPrefix projectName) - compiler - flags + compilerSettings projectName (map fst builtDependencies) Nothing -> buildLibrary librarySourceDir' [".f90", ".f", ".F", ".F90", ".f95", ".f03"] (buildPrefix projectName) - compiler - flags + compilerSettings projectName (map fst builtDependencies) return @@ -303,14 +299,13 @@ build settings = do do localDependencies <- fetchExecutableDependencies maybeTree dependencies - >>= buildDependencies buildPrefix compiler flags + >>= buildDependencies buildPrefix compilerSettings buildProgram sourceDir ((map fst executableDepends) ++ (map fst localDependencies)) [".f90", ".f", ".F", ".F90", ".f95", ".f03"] (buildPrefix sourceDir) - compiler - flags + compilerSettings name mainFile ((map snd executableDepends) ++ (map snd localDependencies)) @@ -318,13 +313,13 @@ build settings = do executables devDependencies <- fetchExecutableDependencies maybeTree (appSettingsDevDependencies settings) - >>= buildDependencies buildPrefix compiler flags + >>= buildDependencies buildPrefix compilerSettings mapM_ (\Executable { executableSourceDir = sourceDir, executableMainFile = mainFile, executableName = name, executableDependencies = dependencies } -> do localDependencies <- fetchExecutableDependencies maybeTree dependencies - >>= buildDependencies buildPrefix compiler flags + >>= buildDependencies buildPrefix compilerSettings buildProgram sourceDir ( (map fst executableDepends) @@ -333,8 +328,7 @@ build settings = do ) [".f90", ".f", ".F", ".F90", ".f95", ".f03"] (buildPrefix sourceDir) - compiler - flags + compilerSettings name mainFile ( (map snd executableDepends) @@ -598,14 +592,14 @@ toml2AppSettings tomlSettings args = do (tomlSettingsExecutables tomlSettings) projectName testSettings <- getTestSettings $ tomlSettingsTests tomlSettings - flags <- defineFlags specifiedFlags compiler release - buildPrefix <- makeBuildPrefix compiler flags + compilerSettings <- defineCompilerSettings specifiedFlags compiler release + buildPrefix <- makeBuildPrefix (compilerSettingsCompiler compilerSettings) + (compilerSettingsFlags compilerSettings) let dependencies = tomlSettingsDependencies tomlSettings let devDependencies = tomlSettingsDevDependencies tomlSettings - return AppSettings { appSettingsCompiler = compiler + return AppSettings { appSettingsCompiler = compilerSettings , appSettingsProjectName = projectName , appSettingsBuildPrefix = buildPrefix - , appSettingsFlags = flags , appSettingsLibrary = librarySettings , appSettingsExecutables = executableSettings , appSettingsTests = testSettings @@ -613,58 +607,74 @@ toml2AppSettings tomlSettings args = do , appSettingsDevDependencies = devDependencies } -defineFlags :: [String] -> FilePath -> Bool -> IO [String] -defineFlags [] compiler release - | "gfortran" `isInfixOf` compiler = return $ 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" - ] - | "caf" `isInfixOf` compiler = return $ 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" - ] - | otherwise = do +defineCompilerSettings :: [String] -> FilePath -> Bool -> IO CompilerSettings +defineCompilerSettings specifiedFlags compiler release + | "gfortran" `isInfixOf` compiler + = let flags = case specifiedFlags of + [] -> 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" + ] + fs -> fs + in return $ CompilerSettings { compilerSettingsCompiler = compiler + , compilerSettingsFlags = flags + , compilerSettingsModuleFlag = "-J" + , compilerSettingsIncludeFlag = "-I" + } + | "caf" `isInfixOf` compiler + = let flags = case specifiedFlags of + [] -> 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" + ] + fs -> fs + in return $ CompilerSettings { compilerSettingsCompiler = compiler + , compilerSettingsFlags = flags + , compilerSettingsModuleFlag = "-J" + , compilerSettingsIncludeFlag = "-I" + } + | otherwise + = do putStrLn $ "Sorry, compiler is currently unsupported: " ++ compiler exitWith (ExitFailure 1) -defineFlags specifiedFlags _ _ = return specifiedFlags getLibrarySettings :: Maybe Library -> IO (Maybe Library) getLibrarySettings maybeSettings = case maybeSettings of @@ -840,37 +850,31 @@ fetchDependency name version = do the transitive dependencies have been built before trying to build this one -} buildDependencies - :: String - -> String - -> [String] - -> [DependencyTree] - -> IO [(FilePath, FilePath)] -buildDependencies buildPrefix compiler flags dependencies = do - built <- concatMapM (buildDependency buildPrefix compiler flags) dependencies + :: String -> CompilerSettings -> [DependencyTree] -> IO [(FilePath, FilePath)] +buildDependencies buildPrefix compilerSettings dependencies = do + built <- concatMapM (buildDependency buildPrefix compilerSettings) + dependencies return $ reverse (nub (reverse built)) buildDependency - :: String -> String -> [String] -> DependencyTree -> IO [(FilePath, FilePath)] -buildDependency buildPrefix compiler flags (Dependency name path sourcePath mBuildScript dependencies) + :: String -> CompilerSettings -> DependencyTree -> IO [(FilePath, FilePath)] +buildDependency buildPrefix compilerSettings (Dependency name path sourcePath mBuildScript dependencies) = do transitiveDependencies <- buildDependencies buildPrefix - compiler - flags + compilerSettings dependencies let buildPath = buildPrefix name thisArchive <- case mBuildScript of Just script -> buildWithScript script path buildPath - compiler - flags + compilerSettings name (map fst transitiveDependencies) Nothing -> buildLibrary sourcePath [".f90", ".f", ".F", ".F90", ".f95", ".f03"] buildPath - compiler - flags + compilerSettings name (map fst transitiveDependencies) return $ (buildPath, thisArchive) : transitiveDependencies -- cgit v1.2.3