aboutsummaryrefslogtreecommitdiff
path: root/app
diff options
context:
space:
mode:
authorBrad Richardson <everythingfunctional@protonmail.com>2020-04-12 21:47:52 -0500
committerGitHub <noreply@github.com>2020-04-12 21:47:52 -0500
commit3a5e426e3103dae2f71732e2a830bd38ffe2c96b (patch)
tree5fbc47c5058d28142c4c26440cc6e7119a1bd308 /app
parentae3ab0973aab3d443c937bf4edab25933e0df931 (diff)
parentba4f284b66b23ba00bb7086203af1e9d7630a177 (diff)
downloadfpm-3a5e426e3103dae2f71732e2a830bd38ffe2c96b.tar.gz
fpm-3a5e426e3103dae2f71732e2a830bd38ffe2c96b.zip
Merge pull request #52 from everythingfunctional/projectSettings
Finish simple project settings
Diffstat (limited to 'app')
-rw-r--r--app/Main.hs127
1 files changed, 87 insertions, 40 deletions
diff --git a/app/Main.hs b/app/Main.hs
index 9e3f264..9438eb2 100644
--- a/app/Main.hs
+++ b/app/Main.hs
@@ -5,9 +5,6 @@ module Main where
import Build ( buildLibrary
, buildProgram
)
-import Data.Text ( Text
- , unpack
- )
import qualified Data.Text.IO as TIO
import Development.Shake ( FilePattern
, (<//>)
@@ -28,7 +25,9 @@ import Options.Applicative ( Parser
, subparser
, switch
)
-import System.Directory ( doesDirectoryExist )
+import System.Directory ( doesDirectoryExist
+ , doesFileExist
+ )
import Toml ( TomlCodec
, (.=)
)
@@ -37,17 +36,28 @@ import qualified Toml
data Arguments = Arguments { command' :: Command, release :: Bool }
data TomlSettings = TomlSettings {
- tomlSettingsCompiler :: !Text
- , tomlSettingsProjectName :: !Text
- , tomlSettingsLibrary :: !(Maybe Library) }
+ tomlSettingsCompiler :: String
+ , tomlSettingsProjectName :: String
+ , tomlSettingsLibrary :: (Maybe Library)
+ , tomlSettingsExecutables :: [Executable]
+}
data AppSettings = AppSettings {
- appSettingsCompiler :: !Text
- , appSettingsProjectName :: !Text
- , appSettingsFlags :: ![Text]
- , appSettingsLibrary :: !(Maybe Library) }
-
-data Library = Library { librarySourceDir :: !Text }
+ appSettingsCompiler :: String
+ , appSettingsProjectName :: String
+ , appSettingsBuildPrefix :: String
+ , appSettingsFlags :: [String]
+ , appSettingsLibrary :: (Maybe Library)
+ , appSettingsExecutables :: [Executable]
+}
+
+data Library = Library { librarySourceDir :: String }
+
+data Executable = Executable {
+ executableSourceDir :: String
+ , executableMainFile :: String
+ , executableName :: String
+}
data Command = Run | Test | Build
@@ -71,36 +81,37 @@ app args settings = case command' args of
build :: AppSettings -> IO ()
build settings = do
putStrLn "Building"
- let compiler = unpack $ appSettingsCompiler settings
- let projectName = unpack $ appSettingsProjectName settings
- let flags = map unpack $ appSettingsFlags settings
- case appSettingsLibrary settings of
+ let compiler = appSettingsCompiler settings
+ let projectName = appSettingsProjectName settings
+ let buildPrefix = appSettingsBuildPrefix settings
+ let flags = appSettingsFlags settings
+ let executables = appSettingsExecutables settings
+ executableDepends <- case appSettingsLibrary settings of
Just librarySettings -> do
- let librarySourceDir' = unpack $ librarySourceDir librarySettings
+ let librarySourceDir' = librarySourceDir librarySettings
buildLibrary librarySourceDir'
[".f90", ".f", ".F", ".F90", ".f95", ".f03"]
- ("build" </> "library")
+ (buildPrefix </> "library")
compiler
flags
projectName
[]
- buildProgram "app"
- ["build" </> "library"]
- [".f90", ".f", ".F", ".F90", ".f95", ".f03"]
- ("build" </> "app")
- compiler
- flags
- projectName
- "main.f90"
+ return [buildPrefix </> "library"]
Nothing -> do
- buildProgram "app"
- []
- [".f90", ".f", ".F", ".F90", ".f95", ".f03"]
- ("build" </> "app")
- compiler
- flags
- projectName
- "main.f90"
+ 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
getArguments :: IO Arguments
getArguments = execParser
@@ -140,22 +151,40 @@ getDirectoriesFiles dirs exts = getDirectoryFilesIO "" newPatterns
settingsCodec :: TomlCodec TomlSettings
settingsCodec =
TomlSettings
- <$> Toml.text "compiler"
+ <$> Toml.string "compiler"
.= tomlSettingsCompiler
- <*> Toml.text "name"
+ <*> Toml.string "name"
.= tomlSettingsProjectName
<*> Toml.dioptional (Toml.table libraryCodec "library")
.= tomlSettingsLibrary
+ <*> Toml.list executableCodec "executable"
+ .= tomlSettingsExecutables
libraryCodec :: TomlCodec Library
-libraryCodec = Library <$> Toml.text "source-dir" .= librarySourceDir
+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
- librarySettings <- getLibrarySettings $ tomlSettingsLibrary tomlSettings
+ let projectName = tomlSettingsProjectName tomlSettings
+ librarySettings <- getLibrarySettings $ tomlSettingsLibrary tomlSettings
+ executableSettings <- getExecutableSettings
+ (tomlSettingsExecutables tomlSettings)
+ projectName
return AppSettings
{ appSettingsCompiler = tomlSettingsCompiler tomlSettings
- , appSettingsProjectName = tomlSettingsProjectName tomlSettings
+ , appSettingsProjectName = projectName
+ , appSettingsBuildPrefix = "build"
+ </> if release then "release" else "debug"
, appSettingsFlags = if release
then
[ "-Wall"
@@ -182,6 +211,7 @@ toml2AppSettings tomlSettings release = do
, "-fbacktrace"
]
, appSettingsLibrary = librarySettings
+ , appSettingsExecutables = executableSettings
}
getLibrarySettings :: Maybe Library -> IO (Maybe Library)
@@ -192,3 +222,20 @@ getLibrarySettings maybeSettings = case maybeSettings of
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