-
Notifications
You must be signed in to change notification settings - Fork 0
/
Copy pathBuild.hs
71 lines (57 loc) · 2.52 KB
/
Build.hs
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
70
71
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
import Development.Shake
import Development.Shake.FilePath
import Development.Shake.Classes
import Distribution.Simple.GHC (ghcPlatformAndVersionString)
import Distribution.System (Platform (Platform), buildArch, buildOS)
import Distribution.Types.Version (mkVersion)
import Clash.Driver.Types (Manifest (fileNames))
import Data.List.Split (splitOn)
-- A string like "8.10.2"
newtype GhcVersion = GhcVersion ()
deriving (Show, Typeable, Eq, Hashable, Binary, NFData)
type instance RuleResult GhcVersion = String
topModule = "Euphrates"
topEntity = "euphrates"
main :: IO ()
main = shakeArgs shakeOptions{shakeFiles="_build"} $ do
want ["_build/euphrates.bit"]
getGhcVersion <- addOracle $ \(GhcVersion _) ->
fromStdout <$> cmd "ghc --numeric-version" :: Action String
"_build/euphrates.bit" %> \out -> do
need ["_build/ulx3s_out.config"]
cmd_ "ecppack" "_build/ulx3s_out.config" out
"_build/ulx3s_out.config" %> \out -> do
need ["_build/euphrates.json", "ulx3s_v20.lpf"]
cmd_ "nextpnr-ecp5" $ unwords
[ "--85k"
, "--json _build/euphrates.json"
, "--lpf ulx3s_v20.lpf"
, "--textcfg", out
]
"_build/euphrates.json" %> \_ -> do
need ["_build/euphrates.ys"]
cmd_ "yosys _build/euphrates.ys"
"_build/euphrates.ys" %> \out -> do
let manifestDir = "_build/verilog" </> topModule </> topEntity
manifest <- read <$> readFile' (manifestDir </> topEntity <.> "manifest") :: Action Manifest
let verilogSources = map (manifestDir </>) (filter (".v" `isExtensionOf`) (fileNames manifest))
writeFileLines out
[ "read_verilog " <> unwords verilogSources
, "synth_ecp5 -top euphrates -noccu2 -nomux -nodram -json _build/euphrates.json"
]
"_build/verilog/Euphrates/euphrates/euphrates.manifest" %> \_ -> do
versionString <- getGhcVersion $ GhcVersion ()
let version = mkVersion $ map read $ splitOn "." versionString
let platform = Platform buildArch buildOS
need [".ghc.environment" <.> ghcPlatformAndVersionString platform version]
cmd_ "cabal run clash -- -fclash-hdldir _build --verilog Euphrates.Top"
-- FIXME Doesn't really work, this ought to depend on all the sources
".ghc.environment.*" %> \_ -> do
need ["euphrates.cabal"]
cmd_ "cabal build --write-ghc-environment-files=always"
phony "clean" $ do
putInfo "Cleaning files in _build and GHC environment file(s)"
liftIO $ removeFiles "." [".ghc.environment.*"]
removeFilesAfter "_build" ["//*"]