diff options
Diffstat (limited to 'bootstrap/src')
-rw-r--r-- | bootstrap/src/Build.hs | 8 | ||||
-rw-r--r-- | bootstrap/src/Fpm.hs | 271 |
2 files changed, 268 insertions, 11 deletions
diff --git a/bootstrap/src/Build.hs b/bootstrap/src/Build.hs index 32d1979..724a1c6 100644 --- a/bootstrap/src/Build.hs +++ b/bootstrap/src/Build.hs @@ -75,7 +75,7 @@ buildProgram programDirectory' libraryDirectories sourceExtensions buildDirector libraryModules <- findAvailableModules libraryDirectories let programDirectory = foldl1 (</>) (splitDirectories programDirectory') let buildDirectory = foldl1 (</>) (splitDirectories buildDirectory') - let includeFlags = map (includeFlag ++) libraryDirectories + let includeFlags = (includeFlag ++ buildDirectory) : map (includeFlag ++) libraryDirectories sourceFiles <- getDirectoriesFiles [programDirectory] sourceExtensions rawSources <- mapM sourceFileToRawSource sourceFiles let sources' = map processRawSource rawSources @@ -108,7 +108,7 @@ buildProgram programDirectory' libraryDirectories sourceExtensions buildDirector in fileMatcher &?> \(objectFile : _) -> do need (sourceFile : directDependencies) cmd compiler - ["-c", moduleFlag ++ buildDirectory] + ["-c", moduleFlag, buildDirectory] includeFlags flags ["-o", objectFile, sourceFile] @@ -130,7 +130,7 @@ buildLibrary buildLibrary libraryDirectory sourceExtensions buildDirectory (CompilerSettings { compilerSettingsCompiler = compiler, compilerSettingsFlags = flags, compilerSettingsModuleFlag = moduleFlag, compilerSettingsIncludeFlag = includeFlag }) libraryName otherLibraryDirectories = do otherModules <- findAvailableModules otherLibraryDirectories - let includeFlags = map (includeFlag ++) otherLibraryDirectories + let includeFlags = (includeFlag ++ buildDirectory) : map (includeFlag ++) otherLibraryDirectories sourceFiles <- getDirectoriesFiles [libraryDirectory] sourceExtensions rawSources <- mapM sourceFileToRawSource sourceFiles let sources = map processRawSource rawSources @@ -160,7 +160,7 @@ buildLibrary libraryDirectory sourceExtensions buildDirectory (CompilerSettings in fileMatcher &?> \(objectFile : _) -> do need (sourceFile : directDependencies) cmd compiler - ["-c", moduleFlag ++ buildDirectory] + ["-c", moduleFlag, buildDirectory] includeFlags flags ["-o", objectFile, sourceFile] diff --git a/bootstrap/src/Fpm.hs b/bootstrap/src/Fpm.hs index 9fc1c91..10e14fe 100644 --- a/bootstrap/src/Fpm.hs +++ b/bootstrap/src/Fpm.hs @@ -71,6 +71,7 @@ import System.Exit ( ExitCode(..) , exitWith ) import System.Process ( readProcess + , readProcessWithExitCode , system ) import Toml ( TomlCodec @@ -92,6 +93,7 @@ data Arguments = } | Run { runRelease :: Bool + , runExample :: Bool , runCompiler :: FilePath , runFlags :: [String] , runRunner :: Maybe String @@ -111,6 +113,7 @@ data TomlSettings = TomlSettings { tomlSettingsProjectName :: String , tomlSettingsLibrary :: (Maybe Library) , tomlSettingsExecutables :: [Executable] + , tomlSettingsExamples :: [Executable] , tomlSettingsTests :: [Executable] , tomlSettingsDependencies :: (Map.Map String Version) , tomlSettingsDevDependencies :: (Map.Map String Version) @@ -122,6 +125,7 @@ data AppSettings = AppSettings { , appSettingsBuildPrefix :: String , appSettingsLibrary :: (Maybe Library) , appSettingsExecutables :: [Executable] + , appSettingsExamples :: [Executable] , appSettingsTests :: [Executable] , appSettingsDependencies :: (Map.Map String Version) , appSettingsDevDependencies :: (Map.Map String Version) @@ -168,15 +172,23 @@ start args = case args of app :: Arguments -> AppSettings -> IO () app args settings = case args of Build{} -> build settings - Run { runTarget = whichOne, runArgs = runArgs, runRunner = runner } -> do + Run { runTarget = whichOne, runArgs = runArgs, runRunner = runner, runExample = runExample } -> do build settings let buildPrefix = appSettingsBuildPrefix settings let - executableNames = map - (\Executable { executableSourceDir = sourceDir, executableMainFile = mainFile, executableName = name } -> - sourceDir </> name - ) - (appSettingsExecutables settings) + executableNames = if runExample + then + map + (\Executable { executableSourceDir = sourceDir, executableMainFile = mainFile, executableName = name } -> + sourceDir </> name + ) + (appSettingsExamples settings) + else + map + (\Executable { executableSourceDir = sourceDir, executableMainFile = mainFile, executableName = name } -> + sourceDir </> name + ) + (appSettingsExecutables settings) let executables = map (buildPrefix </>) $ map (flip (<.>) exe) executableNames canonicalExecutables <- mapM makeAbsolute executables @@ -265,6 +277,7 @@ build settings = do let projectName = appSettingsProjectName settings let buildPrefix = appSettingsBuildPrefix settings let executables = appSettingsExecutables settings + let examples = appSettingsExamples settings let tests = appSettingsTests settings mainDependencyTrees <- fetchDependencies (appSettingsDependencies settings) builtDependencies <- buildDependencies buildPrefix @@ -341,6 +354,29 @@ build settings = do ++ (map snd localDependencies) ) ) + examples + mapM_ + (\Executable { executableSourceDir = sourceDir, executableMainFile = mainFile, executableName = name, executableDependencies = dependencies } -> + do + localDependencies <- + fetchExecutableDependencies maybeTree dependencies + >>= buildDependencies buildPrefix compilerSettings + buildProgram + sourceDir + ( (map fst executableDepends) + ++ (map fst devDependencies) + ++ (map fst localDependencies) + ) + [".f90", ".f", ".F", ".F90", ".f95", ".f03"] + (buildPrefix </> sourceDir) + compilerSettings + name + mainFile + ( (map snd executableDepends) + ++ (map snd devDependencies) + ++ (map snd localDependencies) + ) + ) tests getArguments :: IO Arguments @@ -410,6 +446,10 @@ runArguments = ( long "release" <> help "Build with optimizations instead of debugging" ) + <*> switch + ( long "example" + <> help "Run example programs instead of applications" + ) <*> strOption ( long "compiler" <> metavar "COMPILER" @@ -503,6 +543,8 @@ settingsCodec = .= tomlSettingsLibrary <*> Toml.list executableCodec "executable" .= tomlSettingsExecutables + <*> Toml.list executableCodec "example" + .= tomlSettingsExamples <*> Toml.list executableCodec "test" .= tomlSettingsTests <*> Toml.tableMap Toml._KeyString versionCodec "dependencies" @@ -608,6 +650,7 @@ toml2AppSettings tomlSettings args = do executableSettings <- getExecutableSettings (tomlSettingsExecutables tomlSettings) projectName + exampleSettings <- getExampleSettings $ tomlSettingsExamples tomlSettings testSettings <- getTestSettings $ tomlSettingsTests tomlSettings compilerSettings <- defineCompilerSettings specifiedFlags compiler release buildPrefix <- makeBuildPrefix (compilerSettingsCompiler compilerSettings) @@ -619,6 +662,7 @@ toml2AppSettings tomlSettings args = do , appSettingsBuildPrefix = buildPrefix , appSettingsLibrary = librarySettings , appSettingsExecutables = executableSettings + , appSettingsExamples = exampleSettings , appSettingsTests = testSettings , appSettingsDependencies = dependencies , appSettingsDevDependencies = devDependencies @@ -690,6 +734,185 @@ defineCompilerSettings specifiedFlags compiler release , compilerSettingsModuleFlag = "-J" , compilerSettingsIncludeFlag = "-I" } + | "f95" `isInfixOf` compiler + = let flags = case specifiedFlags of + [] -> if release + then + [ "-O3" + , "-Wimplicit-interface" + , "-fPIC" + , "-fmax-errors=1" + , "-ffast-math" + , "-funroll-loops" + ] + else + [ "-Wall" + , "-Wextra" + , "-Wimplicit-interface" + , "-fPIC" + , "-fmax-errors=1" + , "-g" + , "-fbounds-check" + , "-fcheck-array-temporaries" + , "-Wno-maybe-uninitialized" + , "-Wno-uninitialized" + , "-fbacktrace" + ] + fs -> fs + in return $ CompilerSettings { compilerSettingsCompiler = compiler + , compilerSettingsFlags = flags + , compilerSettingsModuleFlag = "-J" + , compilerSettingsIncludeFlag = "-I" + } + | "nvfortran" `isInfixOf` compiler + = let flags = case specifiedFlags of + [] -> if release + then + [ "-Mbackslash" + ] + else + [ "-Minform=inform" + , "-Mbackslash" + , "-g" + , "-Mbounds" + , "-Mchkptr" + , "-Mchkstk" + , "-traceback" + ] + fs -> fs + in return $ CompilerSettings { compilerSettingsCompiler = compiler + , compilerSettingsFlags = flags + , compilerSettingsModuleFlag = "-module" + , compilerSettingsIncludeFlag = "-I" + } + | "ifort" `isInfixOf` compiler + = let flags = case specifiedFlags of + [] -> if release + then + [ "-fp-model", "precise" + , "-pc", "64" + , "-align", "all" + , "-error-limit", "1" + , "-reentrancy", "threaded" + , "-nogen-interfaces" + , "-assume", "byterecl" + , "-assume", "nounderscore" + ] + else + [ "-warn", "all" + , "-check:all:noarg_temp_created" + , "-error-limit", "1" + , "-O0" + , "-g" + , "-assume", "byterecl" + , "-traceback" + ] + fs -> fs + in return $ CompilerSettings { compilerSettingsCompiler = compiler + , compilerSettingsFlags = flags + , compilerSettingsModuleFlag = "-module" + , compilerSettingsIncludeFlag = "-I" + } + | "ifx" `isInfixOf` compiler + = let flags = case specifiedFlags of + [] -> if release + then + [] + else + [] + fs -> fs + in return $ CompilerSettings { compilerSettingsCompiler = compiler + , compilerSettingsFlags = flags + , compilerSettingsModuleFlag = "-module" + , compilerSettingsIncludeFlag = "-I" + } + | "pgfortran" `isInfixOf` compiler || "pgf90" `isInfixOf` compiler || "pgf95" `isInfixOf` compiler + = let flags = case specifiedFlags of + [] -> if release + then + [] + else + [] + fs -> fs + in return $ CompilerSettings { compilerSettingsCompiler = compiler + , compilerSettingsFlags = flags + , compilerSettingsModuleFlag = "-module" + , compilerSettingsIncludeFlag = "-I" + } + | "flang" `isInfixOf` compiler + = let flags = case specifiedFlags of + [] -> if release + then + [] + else + [] + fs -> fs + in return $ CompilerSettings { compilerSettingsCompiler = compiler + , compilerSettingsFlags = flags + , compilerSettingsModuleFlag = "-module" + , compilerSettingsIncludeFlag = "-I" + } + | "lfc" `isInfixOf` compiler + = let flags = case specifiedFlags of + [] -> if release + then + [] + else + [] + fs -> fs + in return $ CompilerSettings { compilerSettingsCompiler = compiler + , compilerSettingsFlags = flags + , compilerSettingsModuleFlag = "-M" + , compilerSettingsIncludeFlag = "-I" + } + | "nagfor" `isInfixOf` compiler + = let flags = case specifiedFlags of + [] -> if release + then + [ "-O4" + , "-coarray=single" + , "-PIC" + ] + else + [ "-g" + , "-C=all" + , "-O0" + , "-gline" + , "-coarray=single" + , "-PIC" + ] + fs -> fs + in return $ CompilerSettings { compilerSettingsCompiler = compiler + , compilerSettingsFlags = flags + , compilerSettingsModuleFlag = "-mdir" + , compilerSettingsIncludeFlag = "-I" + } + | "crayftn" `isInfixOf` compiler + = let flags = case specifiedFlags of + [] -> if release + then + [] + else + [] + fs -> fs + in return $ CompilerSettings { compilerSettingsCompiler = compiler + , compilerSettingsFlags = flags + , compilerSettingsModuleFlag = "-J" + , compilerSettingsIncludeFlag = "-I" + } + | "xlf90" `isInfixOf` compiler + = let flags = case specifiedFlags of + [] -> if release + then + [] + else + [] + fs -> fs + in return $ CompilerSettings { compilerSettingsCompiler = compiler + , compilerSettingsFlags = flags + , compilerSettingsModuleFlag = "-qmoddir" + , compilerSettingsIncludeFlag = "-I" + } | otherwise = do putStrLn $ "Sorry, compiler is currently unsupported: " ++ compiler @@ -725,6 +948,24 @@ getExecutableSettings [] projectName = do else return [] getExecutableSettings executables _ = return executables +getExampleSettings :: [Executable] -> IO [Executable] +getExampleSettings [] = do + defaultDirectoryExists <- doesDirectoryExist "example" + if defaultDirectoryExists + then do + defaultMainExists <- doesFileExist ("example" </> "main.f90") + if defaultMainExists + then return + [ Executable { executableSourceDir = "example" + , executableMainFile = "main.f90" + , executableName = "demo" + , executableDependencies = Map.empty + } + ] + else return [] + else return [] +getExampleSettings examples = return examples + getTestSettings :: [Executable] -> IO [Executable] getTestSettings [] = do defaultDirectoryExists <- doesDirectoryExist "test" @@ -747,7 +988,23 @@ 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 - versionInfo <- readProcess compiler ["--version"] [] + versionInfo <- do + (exitCode, stdout, stderr) <- readProcessWithExitCode compiler + ["--version"] + [] + case exitCode of + ExitSuccess -> case stdout of + "" -> return stderr -- Guess this compiler outputs version info to stderr instead? + _ -> return stdout + _ -> do -- guess this compiler doesn't support the --version option. let's try -version + (exitCode, stdout, stderr) <- readProcessWithExitCode compiler + ["-version"] + [] + case exitCode of + ExitSuccess -> case stdout of + "" -> return stderr -- Guess this compiler outputs version info to stderr instead? + _ -> return stdout + _ -> return "" -- Don't know how to get version info, we'll let defineCompilerSettings report it as unsupported let compilerName = last (splitDirectories compiler) let versionHash = abs (hash versionInfo) let flagsHash = abs (hash flags) |