aboutsummaryrefslogtreecommitdiff
path: root/bootstrap/unit_test/ProgramSourceConstructionTest.hs
blob: 63699650d9f8f5381955268a9ba9044e5f157088 (plain)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
module ProgramSourceConstructionTest
  ( test
  )
where

import           BuildModel                     ( RawSource(..)
                                                , Source(..)
                                                , processRawSource
                                                )
import           Hedge                          ( Result
                                                , Test
                                                , assertEquals
                                                , assertThat
                                                , fail'
                                                , givenInput
                                                , then'
                                                , whenTransformed
                                                )
import           System.FilePath                ( (</>) )

test :: IO (Test ())
test = return $ givenInput
  "a program"
  exampleProgram
  [ whenTransformed
      "processed to a source"
      processRawSource
      [ 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
      , then' "it knows what modules it uses directly" checkProgramModulesUsed
      ]
  ]

exampleProgram :: RawSource
exampleProgram = RawSource programSourceFileName' $ unlines
  [ "program some_program"
  , "  use module1"
  , "  USE MODULE2"
  , "  implicit none"
  , "  print *, \"Hello, World!\""
  , "end program"
  ]

programSourceFileName' :: String
programSourceFileName' = "some" </> "file" </> "somewhere.f90"

checkIsProgram :: Source -> Result
checkIsProgram Program{} = assertThat True
checkIsProgram _         = assertThat False

checkProgramSourceFileName :: Source -> Result
checkProgramSourceFileName p@(Program{}) =
  assertEquals programSourceFileName' $ programSourceFileName p
checkProgramSourceFileName _ = fail' "wasn't a Program"

checkProgramObjectFileName :: Source -> Result
checkProgramObjectFileName p@(Program{}) =
  assertEquals ("." </> "some_file_somewhere.f90.o")
    $ (programObjectFileName p) "."
checkProgramObjectFileName _ = fail' "wasn't a Program"

checkProgramModulesUsed :: Source -> Result
checkProgramModulesUsed p@(Program{}) =
  assertEquals ["module1", "module2"] $ programModulesUsed p
checkProgramModulesUsed _ = fail' "wasn't a Program"