aboutsummaryrefslogtreecommitdiff
path: root/bootstrap
diff options
context:
space:
mode:
authorBrad Richardson <everythingfunctional@protonmail.com>2020-10-14 12:51:29 -0500
committerBrad Richardson <everythingfunctional@protonmail.com>2020-10-14 12:51:29 -0500
commit29356ac6da1a94dbcc0c50c157e8dcb353213793 (patch)
treee7f307adb296de89b13f7d592a81354304fb2571 /bootstrap
parented529804fc47d64f78bdbd3b4e366ff9f632c8d3 (diff)
downloadfpm-29356ac6da1a94dbcc0c50c157e8dcb353213793.tar.gz
fpm-29356ac6da1a94dbcc0c50c157e8dcb353213793.zip
Add test for program object file name
Diffstat (limited to 'bootstrap')
-rw-r--r--bootstrap/src/BuildModel.hs27
-rw-r--r--bootstrap/unit_test/SourceConstructionTest.hs14
2 files changed, 37 insertions, 4 deletions
diff --git a/bootstrap/src/BuildModel.hs b/bootstrap/src/BuildModel.hs
index 711f977..b8bc122 100644
--- a/bootstrap/src/BuildModel.hs
+++ b/bootstrap/src/BuildModel.hs
@@ -1,11 +1,34 @@
module BuildModel where
+import Data.List ( intercalate )
+import System.FilePath ( (</>)
+ , (<.>)
+ , splitDirectories
+ )
+
data RawSource = RawSource {
rawSourceFilename :: FilePath
, rawSourceContents :: String
}
-data Source = Program { programSourceFileName :: String}
+data Source = Program {
+ programSourceFileName :: FilePath
+ , programObjectFileName :: FilePath -> FilePath
+}
processRawSource :: RawSource -> Source
-processRawSource rawSource = Program $ rawSourceFilename rawSource
+processRawSource rawSource =
+ let sourceFileName = rawSourceFilename rawSource
+ in Program
+ { programSourceFileName = sourceFileName
+ , programObjectFileName = \buildDirectory ->
+ buildDirectory
+ </> (pathSeparatorsToUnderscores
+ sourceFileName
+ )
+ <.> "o"
+ }
+
+pathSeparatorsToUnderscores :: FilePath -> FilePath
+pathSeparatorsToUnderscores fileName =
+ intercalate "_" (splitDirectories fileName)
diff --git a/bootstrap/unit_test/SourceConstructionTest.hs b/bootstrap/unit_test/SourceConstructionTest.hs
index 18a66de..2cee008 100644
--- a/bootstrap/unit_test/SourceConstructionTest.hs
+++ b/bootstrap/unit_test/SourceConstructionTest.hs
@@ -7,6 +7,7 @@ import BuildModel ( RawSource(..)
, Source(..)
, processRawSource
)
+import System.FilePath ( (</>) )
import Hedge ( Result
, Test
, assertEquals
@@ -27,6 +28,9 @@ test = return $ givenInput
[ then' "it is a Program" checkIsProgram
, then' "its source file name is the same as the original"
checkProgramSourceFileName
+ , then'
+ "its object file name is the 'flattened' path of the source file with '.o' appended"
+ checkProgramObjectFileName
]
]
@@ -39,15 +43,21 @@ exampleProgram = RawSource programSourceFileName' $ unlines
]
programSourceFileName' :: String
-programSourceFileName' = "some/file/somewhere.f90"
+programSourceFileName' = "some" </> "file" </> "somewhere.f90"
checkIsProgram :: Source -> Result
checkIsProgram s = assertThat $ case s of
Program{} -> True
- _ -> False
+ _ -> False
checkProgramSourceFileName :: Source -> Result
checkProgramSourceFileName s = case s of
p@(Program{}) ->
assertEquals programSourceFileName' $ programSourceFileName p
_ -> fail' "wasn't a Program"
+
+checkProgramObjectFileName :: Source -> Result
+checkProgramObjectFileName s = case s of
+ p@(Program{}) -> assertEquals ("." </> "some_file_somewhere.f90.o")
+ $ (programObjectFileName p) "."
+ _ -> fail' "wasn't a Program"