aboutsummaryrefslogtreecommitdiff
path: root/bootstrap/src/BuildModel.hs
blob: b8bc122e8b057baaef37f11449594b5160274664 (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
module BuildModel where

import           Data.List                      ( intercalate )
import           System.FilePath                ( (</>)
                                                , (<.>)
                                                , splitDirectories
                                                )

data RawSource = RawSource {
    rawSourceFilename :: FilePath
  , rawSourceContents :: String
}

data Source = Program {
    programSourceFileName :: FilePath
  , programObjectFileName :: FilePath -> FilePath
}

processRawSource :: RawSource -> Source
processRawSource rawSource =
  let sourceFileName = rawSourceFilename rawSource
  in  Program
        { programSourceFileName = sourceFileName
        , programObjectFileName = \buildDirectory ->
                                    buildDirectory
                                      </> (pathSeparatorsToUnderscores
                                            sourceFileName
                                          )
                                      <.> "o"
        }

pathSeparatorsToUnderscores :: FilePath -> FilePath
pathSeparatorsToUnderscores fileName =
  intercalate "_" (splitDirectories fileName)