diff options
-rw-r--r-- | .gitignore | 1 | ||||
-rw-r--r-- | app/Main.hs | 294 | ||||
-rw-r--r-- | example_fpm.toml | 25 | ||||
-rw-r--r-- | example_project/app/main.f90 | 7 | ||||
-rw-r--r-- | example_project/fpm.toml | 8 | ||||
-rw-r--r-- | example_project/src/Hello_m.f90 | 12 | ||||
-rw-r--r-- | example_project/test/main.f90 | 3 | ||||
-rw-r--r-- | hello_complex/.gitignore | 1 | ||||
-rw-r--r-- | hello_complex/apps/say_goodbye/say_goodbye.f90 | 7 | ||||
-rw-r--r-- | hello_complex/apps/say_hello/say_hello.f90 | 7 | ||||
-rw-r--r-- | hello_complex/fpm.toml | 25 | ||||
-rw-r--r-- | hello_complex/source/farewell_m.f90 | 13 | ||||
-rw-r--r-- | hello_complex/source/greet_m.f90 | 13 | ||||
-rw-r--r-- | hello_complex/tests/farewell/farewell_test.f90 | 18 | ||||
-rw-r--r-- | hello_complex/tests/greet/greet_test.f90 | 18 | ||||
-rw-r--r-- | hello_world/.gitignore | 1 | ||||
-rw-r--r-- | hello_world/app/main.f90 | 3 | ||||
-rw-r--r-- | hello_world/fpm.toml | 2 | ||||
-rw-r--r-- | src/Build.hs | 11 | ||||
-rw-r--r-- | src/Fpm.hs | 309 | ||||
-rw-r--r-- | src/Lib.hs | 21 | ||||
-rw-r--r-- | test/Spec.hs | 19 | ||||
-rw-r--r-- | test/test1.f90 | 8 |
23 files changed, 445 insertions, 381 deletions
@@ -1,4 +1,3 @@ .stack-work/ fpm.cabal *~ -example_project/build/* diff --git a/app/Main.hs b/app/Main.hs index 38ba8f1..4897901 100644 --- a/app/Main.hs +++ b/app/Main.hs @@ -1,296 +1,8 @@ -{-# LANGUAGE OverloadedStrings #-} - module Main where -import Build ( buildLibrary - , buildProgram - ) -import qualified Data.Text.IO as TIO -import Development.Shake ( FilePattern - , (<//>) - , getDirectoryFilesIO - ) -import Development.Shake.FilePath ( (</>) ) -import Options.Applicative ( Parser - , (<**>) - , command - , execParser - , fullDesc - , header - , help - , helper - , info - , long - , progDesc - , subparser - , switch - ) -import System.Directory ( doesDirectoryExist - , doesFileExist +import Fpm ( getArguments + , start ) -import System.Process ( runCommand ) -import Toml ( TomlCodec - , (.=) - ) -import qualified Toml - -data Arguments = Arguments { command' :: Command, release :: Bool } - -data TomlSettings = TomlSettings { - tomlSettingsCompiler :: String - , tomlSettingsProjectName :: String - , tomlSettingsLibrary :: (Maybe Library) - , tomlSettingsExecutables :: [Executable] - , tomlSettingsTests :: [Executable] -} - -data AppSettings = AppSettings { - appSettingsCompiler :: String - , appSettingsProjectName :: String - , appSettingsBuildPrefix :: String - , appSettingsFlags :: [String] - , appSettingsLibrary :: (Maybe Library) - , appSettingsExecutables :: [Executable] - , appSettingsTests :: [Executable] -} - -data Library = Library { librarySourceDir :: String } - -data Executable = Executable { - executableSourceDir :: String - , executableMainFile :: String - , executableName :: String -} - -data Command = Run | Test | Build main :: IO () -main = do - args <- getArguments - 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) - app args appSettings - -app :: Arguments -> AppSettings -> IO () -app args settings = case command' args of - Build -> build settings - Run -> do - build settings - let buildPrefix = appSettingsBuildPrefix settings - let - executableNames = map - (\Executable { executableSourceDir = sourceDir, executableMainFile = mainFile, executableName = name } -> - sourceDir </> name - ) - (appSettingsExecutables settings) - let executables = map (buildPrefix </>) executableNames - mapM_ runCommand executables - Test -> do - build settings - let buildPrefix = appSettingsBuildPrefix settings - let - executableNames = map - (\Executable { executableSourceDir = sourceDir, executableMainFile = mainFile, executableName = name } -> - sourceDir </> name - ) - (appSettingsTests settings) - let executables = map (buildPrefix </>) executableNames - mapM_ runCommand executables - -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 - executableDepends <- case appSettingsLibrary settings of - Just librarySettings -> do - let librarySourceDir' = librarySourceDir librarySettings - buildLibrary librarySourceDir' - [".f90", ".f", ".F", ".F90", ".f95", ".f03"] - (buildPrefix </> "library") - compiler - flags - projectName - [] - return [buildPrefix </> "library"] - Nothing -> do - return [] - mapM_ - (\Executable { executableSourceDir = sourceDir, executableMainFile = mainFile, executableName = name } -> - do - buildProgram sourceDir - executableDepends - [".f90", ".f", ".F", ".F90", ".f95", ".f03"] - (buildPrefix </> sourceDir) - compiler - flags - name - mainFile - ) - executables - mapM_ - (\Executable { executableSourceDir = sourceDir, executableMainFile = mainFile, executableName = name } -> - do - buildProgram sourceDir - executableDepends - [".f90", ".f", ".F", ".F90", ".f95", ".f03"] - (buildPrefix </> sourceDir) - compiler - flags - name - mainFile - ) - tests - -getArguments :: IO Arguments -getArguments = execParser - (info - (arguments <**> helper) - (fullDesc <> progDesc "Work with Fortran projects" <> header - "fpm - A Fortran package manager and build system" - ) - ) - -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")) - ) - <*> switch (long "release" <> help "Build in release mode") - -runArguments :: Parser Command -runArguments = pure Run - -testArguments :: Parser Command -testArguments = pure Test - -buildArguments :: Parser Command -buildArguments = pure Build - -getDirectoriesFiles :: [FilePath] -> [FilePattern] -> IO [FilePath] -getDirectoriesFiles dirs exts = getDirectoryFilesIO "" newPatterns - where - newPatterns = concatMap appendExts dirs - appendExts dir = map ((dir <//> "*") ++) exts - -settingsCodec :: TomlCodec TomlSettings -settingsCodec = - TomlSettings - <$> Toml.string "compiler" - .= tomlSettingsCompiler - <*> Toml.string "name" - .= tomlSettingsProjectName - <*> Toml.dioptional (Toml.table libraryCodec "library") - .= tomlSettingsLibrary - <*> Toml.list executableCodec "executable" - .= tomlSettingsExecutables - <*> Toml.list executableCodec "test" - .= tomlSettingsTests - -libraryCodec :: TomlCodec Library -libraryCodec = Library <$> Toml.string "source-dir" .= librarySourceDir - -executableCodec :: TomlCodec Executable -executableCodec = - Executable - <$> Toml.string "source-dir" - .= executableSourceDir - <*> Toml.string "main" - .= executableMainFile - <*> Toml.string "name" - .= executableName - -toml2AppSettings :: TomlSettings -> Bool -> IO AppSettings -toml2AppSettings tomlSettings release = do - let projectName = tomlSettingsProjectName tomlSettings - librarySettings <- getLibrarySettings $ tomlSettingsLibrary tomlSettings - executableSettings <- getExecutableSettings - (tomlSettingsExecutables tomlSettings) - projectName - testSettings <- getTestSettings $ tomlSettingsTests tomlSettings - return AppSettings - { appSettingsCompiler = tomlSettingsCompiler tomlSettings - , appSettingsProjectName = projectName - , appSettingsBuildPrefix = "build" - </> if release then "release" else "debug" - , 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" - ] - , appSettingsLibrary = librarySettings - , appSettingsExecutables = executableSettings - , appSettingsTests = testSettings - } - -getLibrarySettings :: Maybe Library -> IO (Maybe Library) -getLibrarySettings maybeSettings = case maybeSettings of - Just settings -> return maybeSettings - Nothing -> do - defaultExists <- doesDirectoryExist "src" - if defaultExists - then return (Just (Library { librarySourceDir = "src" })) - else return Nothing - -getExecutableSettings :: [Executable] -> String -> IO [Executable] -getExecutableSettings [] projectName = do - defaultDirectoryExists <- doesDirectoryExist "app" - if defaultDirectoryExists - then do - defaultMainExists <- doesFileExist ("app" </> "main.f90") - if defaultMainExists - then return - [ Executable { executableSourceDir = "app" - , executableMainFile = "main.f90" - , executableName = projectName - } - ] - else return [] - else return [] -getExecutableSettings executables _ = return executables - -getTestSettings :: [Executable] -> IO [Executable] -getTestSettings [] = do - defaultDirectoryExists <- doesDirectoryExist "test" - if defaultDirectoryExists - then do - defaultMainExists <- doesFileExist ("test" </> "main.f90") - if defaultMainExists - then return - [ Executable { executableSourceDir = "test" - , executableMainFile = "main.f90" - , executableName = "runTests" - } - ] - else return [] - else return [] -getTestSettings tests = return tests +main = getArguments >>= start diff --git a/example_fpm.toml b/example_fpm.toml deleted file mode 100644 index b7a2057..0000000 --- a/example_fpm.toml +++ /dev/null @@ -1,25 +0,0 @@ -name = "package-name" -version = "0.1.0" -license = "BSD3" -author = "Author name here" -maintainer = "example@example.com" -copyright = "2020 Author name here" -dependencies = ["../std-lib.tar.gz"] -compiler = "gfortran" -devel-options = ["-g", "-Wall", "-Wextra", "-Werror", "-pedantic"] -release-options = ["-O3"] - -[library] -source-dirs = "src" - -[executables.executable-name] -main = "Main.f90" -source-dirs = "app" -linker-options = ["-O3"] -dependencies = ["iso_varying_string"] - -[tests.test-name] -main = "Spec.f90" -source-dirs = "test" -linker-options = ["-Og"] -dependencies = ["vegetables >= 1.0 && < 2.0"] diff --git a/example_project/app/main.f90 b/example_project/app/main.f90 deleted file mode 100644 index 7783f8f..0000000 --- a/example_project/app/main.f90 +++ /dev/null @@ -1,7 +0,0 @@ -program example_project - use Hello_m, only: sayHello - - implicit none - - call sayHello("World") -end program example_project diff --git a/example_project/fpm.toml b/example_project/fpm.toml deleted file mode 100644 index 38cc3b7..0000000 --- a/example_project/fpm.toml +++ /dev/null @@ -1,8 +0,0 @@ -name = "example_project" -version = "0.1.0" -license = "BSD3" -author = "Author" -maintainer = "example@example.com" -copyright = "2020 Author" -dependencies = [] -compiler = "gfortran" diff --git a/example_project/src/Hello_m.f90 b/example_project/src/Hello_m.f90 deleted file mode 100644 index 60088a2..0000000 --- a/example_project/src/Hello_m.f90 +++ /dev/null @@ -1,12 +0,0 @@ -module Hello_m - implicit none - private - - public :: sayHello -contains - subroutine sayHello(name) - character(len=*), intent(in) :: name - - print *, "Hello, " // name // "!" - end subroutine sayHello -end module Hello_m diff --git a/example_project/test/main.f90 b/example_project/test/main.f90 deleted file mode 100644 index c3bc1e9..0000000 --- a/example_project/test/main.f90 +++ /dev/null @@ -1,3 +0,0 @@ -program runTests - print *, "Running Tests" -end program runTests diff --git a/hello_complex/.gitignore b/hello_complex/.gitignore new file mode 100644 index 0000000..a007fea --- /dev/null +++ b/hello_complex/.gitignore @@ -0,0 +1 @@ +build/* diff --git a/hello_complex/apps/say_goodbye/say_goodbye.f90 b/hello_complex/apps/say_goodbye/say_goodbye.f90 new file mode 100644 index 0000000..6966e79 --- /dev/null +++ b/hello_complex/apps/say_goodbye/say_goodbye.f90 @@ -0,0 +1,7 @@ +program say_goodbye + use farewell_m, only: make_farewell + + implicit none + + print *, make_farewell("World") +end program say_goodbye diff --git a/hello_complex/apps/say_hello/say_hello.f90 b/hello_complex/apps/say_hello/say_hello.f90 new file mode 100644 index 0000000..cc648f2 --- /dev/null +++ b/hello_complex/apps/say_hello/say_hello.f90 @@ -0,0 +1,7 @@ +program say_hello + use greet_m, only: make_greeting + + implicit none + + print *, make_greeting("World") +end program say_hello diff --git a/hello_complex/fpm.toml b/hello_complex/fpm.toml new file mode 100644 index 0000000..8408d3a --- /dev/null +++ b/hello_complex/fpm.toml @@ -0,0 +1,25 @@ +name = "hello_complex" +compiler = "gfortran" + +[library] +source-dir="source" + +[[executable]] +name="say_hello" +source-dir="apps/say_hello" +main="say_hello.f90" + +[[executable]] +name="say_goodbye" +source-dir="apps/say_goodbye" +main="say_goodbye.f90" + +[[test]] +name="greet_test" +source-dir="tests/greet" +main="greet_test.f90" + +[[test]] +name="farewell_test" +source-dir="tests/farewell" +main="farewell_test.f90" diff --git a/hello_complex/source/farewell_m.f90 b/hello_complex/source/farewell_m.f90 new file mode 100644 index 0000000..9fc75b9 --- /dev/null +++ b/hello_complex/source/farewell_m.f90 @@ -0,0 +1,13 @@ +module farewell_m + implicit none + private + + public :: make_farewell +contains + function make_farewell(name) result(greeting) + character(len=*), intent(in) :: name + character(len=:), allocatable :: greeting + + greeting = "Goodbye, " // name // "!" + end function make_farewell +end module farewell_m diff --git a/hello_complex/source/greet_m.f90 b/hello_complex/source/greet_m.f90 new file mode 100644 index 0000000..2372f9a --- /dev/null +++ b/hello_complex/source/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/hello_complex/tests/farewell/farewell_test.f90 b/hello_complex/tests/farewell/farewell_test.f90 new file mode 100644 index 0000000..0f21b18 --- /dev/null +++ b/hello_complex/tests/farewell/farewell_test.f90 @@ -0,0 +1,18 @@ +program farewell_test + use farewell_m, only: make_farewell + use iso_fortran_env, only: error_unit, output_unit + + implicit none + + character(len=:), allocatable :: farewell + + allocate(character(len=0) :: farewell) + farewell = make_farewell("World") + + if (farewell == "Goodbye, World!") then + write(output_unit, *) "Passed" + else + write(error_unit, *) "Failed" + call exit(1) + end if +end program farewell_test diff --git a/hello_complex/tests/greet/greet_test.f90 b/hello_complex/tests/greet/greet_test.f90 new file mode 100644 index 0000000..41fa508 --- /dev/null +++ b/hello_complex/tests/greet/greet_test.f90 @@ -0,0 +1,18 @@ +program greet_test + use greet_m, only: make_greeting + use iso_fortran_env, only: error_unit, output_unit + + implicit none + + character(len=:), allocatable :: greeting + + allocate(character(len=0) :: greeting) + greeting = make_greeting("World") + + if (greeting == "Hello, World!") then + write(output_unit, *) "Passed" + else + write(error_unit, *) "Failed" + call exit(1) + end if +end program greet_test diff --git a/hello_world/.gitignore b/hello_world/.gitignore new file mode 100644 index 0000000..a007fea --- /dev/null +++ b/hello_world/.gitignore @@ -0,0 +1 @@ +build/* diff --git a/hello_world/app/main.f90 b/hello_world/app/main.f90 new file mode 100644 index 0000000..d16022b --- /dev/null +++ b/hello_world/app/main.f90 @@ -0,0 +1,3 @@ +program hello_world + print *, "Hello, World!" +end program hello_world diff --git a/hello_world/fpm.toml b/hello_world/fpm.toml new file mode 100644 index 0000000..d715850 --- /dev/null +++ b/hello_world/fpm.toml @@ -0,0 +1,2 @@ +name = "hello_world" +compiler = "gfortran" diff --git a/src/Build.hs b/src/Build.hs index 0c692cb..12b6bcd 100644 --- a/src/Build.hs +++ b/src/Build.hs @@ -5,6 +5,7 @@ module Build where import Control.Applicative ( (<|>) ) +import Control.Monad ( filterM ) import Data.Char ( isAsciiLower , isDigit , toLower @@ -41,6 +42,7 @@ import Development.Shake.FilePath ( dropExtension , (<.>) , (-<.>) ) +import System.Directory ( makeAbsolute ) import System.FilePath ( splitDirectories ) import Text.ParserCombinators.ReadP ( ReadP , char @@ -71,8 +73,13 @@ buildProgram buildProgram programDirectory libraryDirectories sourceExtensions buildDirectory compiler flags programName programSource = do sourceFiles <- getDirectoriesFiles [programDirectory] sourceExtensions - let moduleSourceFiles = - filter (/= programDirectory </> programSource) sourceFiles + canonicalProgramSource <- makeAbsolute $ programDirectory </> programSource + moduleSourceFiles <- filterM + (\source -> do + canonicalSource <- makeAbsolute source + return $ canonicalProgramSource /= canonicalSource + ) + sourceFiles let moduleObjectFiles = map (sourceFileToObjectFile buildDirectory programDirectory) moduleSourceFiles diff --git a/src/Fpm.hs b/src/Fpm.hs new file mode 100644 index 0000000..afe9a70 --- /dev/null +++ b/src/Fpm.hs @@ -0,0 +1,309 @@ +{-# LANGUAGE OverloadedStrings #-} + +module Fpm + ( Arguments(..) + , Command(..) + , getArguments + , start + ) +where + +import Build ( buildLibrary + , buildProgram + ) +import qualified Data.Text.IO as TIO +import Development.Shake ( FilePattern + , (<//>) + , getDirectoryFilesIO + ) +import Development.Shake.FilePath ( (</>) + , (<.>) + , exe + ) +import Options.Applicative ( Parser + , (<**>) + , command + , execParser + , fullDesc + , header + , help + , helper + , info + , long + , progDesc + , subparser + , switch + ) +import System.Directory ( doesDirectoryExist + , doesFileExist + , makeAbsolute + ) +import System.Process ( runCommand ) +import Toml ( TomlCodec + , (.=) + ) +import qualified Toml + +data Arguments = Arguments { command' :: Command, release :: Bool } + +data TomlSettings = TomlSettings { + tomlSettingsCompiler :: String + , tomlSettingsProjectName :: String + , tomlSettingsLibrary :: (Maybe Library) + , tomlSettingsExecutables :: [Executable] + , tomlSettingsTests :: [Executable] +} + +data AppSettings = AppSettings { + appSettingsCompiler :: String + , appSettingsProjectName :: String + , appSettingsBuildPrefix :: String + , appSettingsFlags :: [String] + , appSettingsLibrary :: (Maybe Library) + , appSettingsExecutables :: [Executable] + , appSettingsTests :: [Executable] +} + +data Library = Library { librarySourceDir :: String } + +data Executable = Executable { + executableSourceDir :: String + , executableMainFile :: String + , executableName :: String +} + +data Command = Run | Test | Build + +start :: Arguments -> IO () +start args = 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) + app args appSettings + +app :: Arguments -> AppSettings -> IO () +app args settings = case command' args of + Build -> build settings + Run -> do + build settings + let buildPrefix = appSettingsBuildPrefix settings + let + executableNames = map + (\Executable { executableSourceDir = sourceDir, executableMainFile = mainFile, executableName = name } -> + sourceDir </> name + ) + (appSettingsExecutables settings) + let executables = + map (buildPrefix </>) $ map (flip (<.>) exe) executableNames + canonicalExecutables <- mapM makeAbsolute executables + mapM_ runCommand canonicalExecutables + Test -> do + build settings + let buildPrefix = appSettingsBuildPrefix settings + let + executableNames = map + (\Executable { executableSourceDir = sourceDir, executableMainFile = mainFile, executableName = name } -> + sourceDir </> name + ) + (appSettingsTests settings) + let executables = + map (buildPrefix </>) $ map (flip (<.>) exe) executableNames + canonicalExecutables <- mapM makeAbsolute executables + mapM_ runCommand canonicalExecutables + +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 + executableDepends <- case appSettingsLibrary settings of + Just librarySettings -> do + let librarySourceDir' = librarySourceDir librarySettings + buildLibrary librarySourceDir' + [".f90", ".f", ".F", ".F90", ".f95", ".f03"] + (buildPrefix </> "library") + compiler + flags + projectName + [] + return [buildPrefix </> "library"] + Nothing -> do + return [] + mapM_ + (\Executable { executableSourceDir = sourceDir, executableMainFile = mainFile, executableName = name } -> + do + buildProgram sourceDir + executableDepends + [".f90", ".f", ".F", ".F90", ".f95", ".f03"] + (buildPrefix </> sourceDir) + compiler + flags + name + mainFile + ) + executables + mapM_ + (\Executable { executableSourceDir = sourceDir, executableMainFile = mainFile, executableName = name } -> + do + buildProgram sourceDir + executableDepends + [".f90", ".f", ".F", ".F90", ".f95", ".f03"] + (buildPrefix </> sourceDir) + compiler + flags + name + mainFile + ) + tests + +getArguments :: IO Arguments +getArguments = execParser + (info + (arguments <**> helper) + (fullDesc <> progDesc "Work with Fortran projects" <> header + "fpm - A Fortran package manager and build system" + ) + ) + +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")) + ) + <*> switch (long "release" <> help "Build in release mode") + +runArguments :: Parser Command +runArguments = pure Run + +testArguments :: Parser Command +testArguments = pure Test + +buildArguments :: Parser Command +buildArguments = pure Build + +getDirectoriesFiles :: [FilePath] -> [FilePattern] -> IO [FilePath] +getDirectoriesFiles dirs exts = getDirectoryFilesIO "" newPatterns + where + newPatterns = concatMap appendExts dirs + appendExts dir = map ((dir <//> "*") ++) exts + +settingsCodec :: TomlCodec TomlSettings +settingsCodec = + TomlSettings + <$> Toml.string "compiler" + .= tomlSettingsCompiler + <*> Toml.string "name" + .= tomlSettingsProjectName + <*> Toml.dioptional (Toml.table libraryCodec "library") + .= tomlSettingsLibrary + <*> Toml.list executableCodec "executable" + .= tomlSettingsExecutables + <*> Toml.list executableCodec "test" + .= tomlSettingsTests + +libraryCodec :: TomlCodec Library +libraryCodec = Library <$> Toml.string "source-dir" .= librarySourceDir + +executableCodec :: TomlCodec Executable +executableCodec = + Executable + <$> Toml.string "source-dir" + .= executableSourceDir + <*> Toml.string "main" + .= executableMainFile + <*> Toml.string "name" + .= executableName + +toml2AppSettings :: TomlSettings -> Bool -> IO AppSettings +toml2AppSettings tomlSettings release = do + let projectName = tomlSettingsProjectName tomlSettings + librarySettings <- getLibrarySettings $ tomlSettingsLibrary tomlSettings + executableSettings <- getExecutableSettings + (tomlSettingsExecutables tomlSettings) + projectName + testSettings <- getTestSettings $ tomlSettingsTests tomlSettings + return AppSettings + { appSettingsCompiler = tomlSettingsCompiler tomlSettings + , appSettingsProjectName = projectName + , appSettingsBuildPrefix = "build" + </> if release then "release" else "debug" + , 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" + ] + , appSettingsLibrary = librarySettings + , appSettingsExecutables = executableSettings + , appSettingsTests = testSettings + } + +getLibrarySettings :: Maybe Library -> IO (Maybe Library) +getLibrarySettings maybeSettings = case maybeSettings of + Just settings -> return maybeSettings + Nothing -> do + defaultExists <- doesDirectoryExist "src" + if defaultExists + then return (Just (Library { librarySourceDir = "src" })) + else return Nothing + +getExecutableSettings :: [Executable] -> String -> IO [Executable] +getExecutableSettings [] projectName = do + defaultDirectoryExists <- doesDirectoryExist "app" + if defaultDirectoryExists + then do + defaultMainExists <- doesFileExist ("app" </> "main.f90") + if defaultMainExists + then return + [ Executable { executableSourceDir = "app" + , executableMainFile = "main.f90" + , executableName = projectName + } + ] + else return [] + else return [] +getExecutableSettings executables _ = return executables + +getTestSettings :: [Executable] -> IO [Executable] +getTestSettings [] = do + defaultDirectoryExists <- doesDirectoryExist "test" + if defaultDirectoryExists + then do + defaultMainExists <- doesFileExist ("test" </> "main.f90") + if defaultMainExists + then return + [ Executable { executableSourceDir = "test" + , executableMainFile = "main.f90" + , executableName = "runTests" + } + ] + else return [] + else return [] +getTestSettings tests = return tests diff --git a/src/Lib.hs b/src/Lib.hs deleted file mode 100644 index 3d4aede..0000000 --- a/src/Lib.hs +++ /dev/null @@ -1,21 +0,0 @@ -module Lib - ( someFunc, - someFunc2 - ) where - -import Development.Shake.FilePath ((</>)) -import System.Process (callCommand) - - -someFunc :: IO () -someFunc = do - putStrLn "someFunc" - a <- callCommand "gfortran test/test1.f90 -o test1" - a <- callCommand $ "." </> "test1" - return () - -someFunc2 :: IO () -someFunc2 = do - putStrLn "example" - a <- callCommand "cd example_project && stack run -- build" - return () diff --git a/test/Spec.hs b/test/Spec.hs index 1c9fc48..cd10913 100644 --- a/test/Spec.hs +++ b/test/Spec.hs @@ -1,6 +1,19 @@ -import Lib (someFunc, someFunc2) +import Development.Shake.FilePath ( (</>) ) +import Fpm ( Arguments(..) + , Command(..) + , start + ) +import System.Directory ( withCurrentDirectory ) main :: IO () main = do - someFunc - someFunc2 + testHelloWorld + testHelloComplex + +testHelloWorld :: IO () +testHelloWorld = + withCurrentDirectory "hello_world" $ start $ Arguments Run False + +testHelloComplex :: IO () +testHelloComplex = + withCurrentDirectory "hello_complex" $ start $ Arguments Test False diff --git a/test/test1.f90 b/test/test1.f90 deleted file mode 100644 index f577b58..0000000 --- a/test/test1.f90 +++ /dev/null @@ -1,8 +0,0 @@ -program test1 -implicit none -integer :: i -i = 5+5 -print *, i -print *, "Fortran test code executed" -print *, "TESTS PASSED" -end program |