Skip to content

Commit

Permalink
Clean Cabal cache before calling it
Browse files Browse the repository at this point in the history
Cabal/GHC doesn't know about files produced by cargo, and will therefore
fail to invalidate caches. While there are ways to tell Cabal/GHC to
depend on these files, they are known to be broken in our tool versions.

See: haskell/cabal#4746

Note that we don't use `cabal clean`, as it will also remove any sources
it downloaded (specified in `cabal.project`).
  • Loading branch information
martijnbastiaan committed Aug 18, 2023
1 parent 97ca442 commit 686a4f1
Showing 1 changed file with 24 additions and 2 deletions.
26 changes: 24 additions & 2 deletions bittide-shake/bin/Shake.hs
Original file line number Diff line number Diff line change
Expand Up @@ -10,15 +10,17 @@ module Main where
import Prelude

import Control.Applicative (liftA2)
import Control.Monad (forM_, unless)
import Control.Monad.Extra (ifM, unlessM, when)
import Data.Char(isSpace)
import Data.Foldable (for_)
import Data.List (dropWhileEnd)
import Data.List (dropWhileEnd, isPrefixOf)
import Development.Shake
import GHC.Stack (HasCallStack)
import System.Console.ANSI (setSGR)
import System.Directory
import System.FilePath
import System.FilePath.Glob (glob)
import System.Process (readProcess, callProcess)

import Paths_bittide_shake
Expand Down Expand Up @@ -201,7 +203,7 @@ shakeOpts :: ShakeOptions
shakeOpts = shakeOptions
{ shakeFiles = buildDir
, shakeChange = ChangeDigest
, shakeVersion = "9"
, shakeVersion = "10"
}

-- | Run Vivado on given TCL script
Expand Down Expand Up @@ -334,6 +336,26 @@ main = do
-- build bittide-instance because we have instances that includes a binaries.
command_ [Cwd "firmware-binaries"] "cargo" ["build", "--release"]

-- XXX: Cabal/GHC doesn't know about files produced by cargo, and
-- will therefore fail to invalidate caches. While there are
-- ways to tell Cabal/GHC to depend on these files, they are
-- known to be broken in our tool versions. This workaround
-- removes all build artifacts _except_ for "bittide-shake".
--
-- See: https://github.com/haskell/cabal/issues/4746
--
-- We need to manually remove build artifacts, because Cabal
-- does not support per package/component cleans:
--
-- See: https://github.com/haskell/cabal/issues/7506
--
buildDirs <- liftIO (glob "dist-newstyle/build/*/ghc-*/*")
forM_ buildDirs $ \dir -> do
let fileName = takeFileName dir
unless ("bittide-shake" `isPrefixOf` fileName) $
command_ [] "rm" ["-rf", dir]

-- Generate RTL
let
(buildTool, buildToolArgs) =
defaultClashCmd clashBuildDir targetName
Expand Down

0 comments on commit 686a4f1

Please sign in to comment.