Skip to content

Commit

Permalink
Add Shake build system
Browse files Browse the repository at this point in the history
  • Loading branch information
acairncross committed Dec 11, 2020
1 parent 3f95569 commit 1f5556e
Show file tree
Hide file tree
Showing 4 changed files with 551 additions and 0 deletions.
70 changes: 70 additions & 0 deletions Build.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,70 @@
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}

import Development.Shake
import Development.Shake.FilePath
import Development.Shake.Classes

import Distribution.Simple.GHC (ghcPlatformAndVersionString)
import Distribution.System (Platform (..), buildArch, buildOS)
import Distribution.Types.Version (mkVersion)

import Clash.Driver.Types (Manifest (..))
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"

".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" ["//*"]
7 changes: 7 additions & 0 deletions README.md
Original file line number Diff line number Diff line change
Expand Up @@ -13,3 +13,10 @@ Clash to use, then run Clash:
cabal build --write-ghc-environment-files=always euphrates
cabal run clash -- Euphrates.Top --verilog
```

Or run the Shake based build system to run Clash and synthesize a bitstream for
the ULX3S:

```sh
cabal run shake
```
12 changes: 12 additions & 0 deletions euphrates.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -44,6 +44,18 @@ library
mtl,
reflection,

executable shake
main-is: Build.hs
default-language: Haskell2010
build-depends:
base <5,
Cabal,
clash-lib,
deepseq,
euphrates,
shake,
split,

executable serial
main-is: bin/Serial.hs
default-language: Haskell2010
Expand Down
Loading

0 comments on commit 1f5556e

Please sign in to comment.