aboutsummaryrefslogtreecommitdiff
diff options
context:
space:
mode:
-rw-r--r--bootstrap/src/Fpm.hs127
-rw-r--r--bootstrap/test/Spec.hs7
2 files changed, 91 insertions, 43 deletions
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"
}