aboutsummaryrefslogtreecommitdiff
diff options
context:
space:
mode:
authorBrad Richardson <brichardson@structint.com>2020-03-24 16:11:18 -0500
committerBrad Richardson <brichardson@structint.com>2020-03-24 16:11:18 -0500
commit97a21c32b70440ab2017208063db1638ff35e1f9 (patch)
tree3f305dc61063cdc7f4b89d4340de0b090c615ba3
parentf4c1f60ecbd2c075e846a33480bd4ade0b8c9e2a (diff)
downloadfpm-97a21c32b70440ab2017208063db1638ff35e1f9.tar.gz
fpm-97a21c32b70440ab2017208063db1638ff35e1f9.zip
Put together simplest example of reading settings from fpm.toml
- determine compiler based on fpm.toml
-rw-r--r--app/Main.hs37
-rw-r--r--package.yaml1
2 files changed, 29 insertions, 9 deletions
diff --git a/app/Main.hs b/app/Main.hs
index 5b1f864..eceb260 100644
--- a/app/Main.hs
+++ b/app/Main.hs
@@ -1,8 +1,14 @@
+{-# LANGUAGE OverloadedStrings #-}
+
module Main where
import Build ( buildLibrary
, buildPrograms
)
+import Data.Text ( Text
+ , unpack
+ )
+import qualified Data.Text.IO as TIO
import Development.Shake ( FilePattern
, (<//>)
, getDirectoryFilesIO
@@ -19,29 +25,39 @@ import Options.Applicative ( Parser
, progDesc
, subparser
)
+import Toml ( TomlCodec
+ , (.=)
+ )
+import qualified Toml
newtype Arguments = Arguments { command' :: Command }
+data Settings = Settings { compiler :: !Text }
+
data Command = Run | Test | Build
main :: IO ()
main = do
- args <- getArguments
- app args
+ args <- getArguments
+ fpmContents <- TIO.readFile "fpm.toml"
+ let settings = Toml.decode settingsCodec fpmContents
+ case settings of
+ Left err -> print err
+ Right settings -> app args settings
-app :: Arguments -> IO ()
-app args = case command' args of
+app :: Arguments -> Settings -> IO ()
+app args settings = case command' args of
Run -> putStrLn "Run"
Test -> putStrLn "Test"
- Build -> build
+ Build -> build settings
-build :: IO ()
-build = do
+build :: Settings -> IO ()
+build settings = do
putStrLn "Building"
buildLibrary "src"
[".f90", ".f", ".F", ".F90", ".f95", ".f03"]
("build" </> "library")
- "gfortran"
+ (unpack $ compiler settings)
["-g", "-Wall", "-Wextra", "-Werror", "-pedantic"]
"library"
[]
@@ -49,7 +65,7 @@ build = do
["build" </> "library"]
[".f90", ".f", ".F", ".F90", ".f95", ".f03"]
("build" </> "app")
- "gfortran"
+ (unpack $ compiler settings)
["-g", "-Wall", "-Wextra", "-Werror", "-pedantic"]
getArguments :: IO Arguments
@@ -82,3 +98,6 @@ getDirectoriesFiles dirs exts = getDirectoryFilesIO "" newPatterns
where
newPatterns = concatMap appendExts dirs
appendExts dir = map ((dir <//> "*") ++) exts
+
+settingsCodec :: TomlCodec Settings
+settingsCodec = Settings <$> Toml.text "compiler" .= compiler
diff --git a/package.yaml b/package.yaml
index cf6c69f..c46000a 100644
--- a/package.yaml
+++ b/package.yaml
@@ -28,6 +28,7 @@ dependencies:
- process
- shake
- split
+- text
- tomland >= 1.0