Skip to content

Commit

Permalink
Merge pull request #589 from bittide/lucas/bump-clash
Browse files Browse the repository at this point in the history
Bump clash
  • Loading branch information
martijnbastiaan authored Aug 6, 2024
2 parents 26e40ed + b7eeb1a commit 3248f3c
Show file tree
Hide file tree
Showing 21 changed files with 89 additions and 80 deletions.
2 changes: 1 addition & 1 deletion .github/scripts/cache.py
Original file line number Diff line number Diff line change
Expand Up @@ -52,7 +52,7 @@
CLEAR_AFTER=f"{CLEAR_AFTER_DAYS}d00h00m00s"
TOUCH_AFTER=datetime.timedelta(days=1)

GLOBAL_CACHE_BUST = 2
GLOBAL_CACHE_BUST = 3

CARGO_CACHE_BUST = 2
CARGO_KEY_PREFIX = f"cargo-g{GLOBAL_CACHE_BUST}-l{CARGO_CACHE_BUST}-"
Expand Down
40 changes: 22 additions & 18 deletions .github/workflows/ci.yml
Original file line number Diff line number Diff line change
Expand Up @@ -45,7 +45,7 @@ jobs:
run:
shell: git-nix-shell {0} --option connect-timeout 360 --pure --keep "GITHUB_SHA" --keep "S3_PASSWORD"
container:
image: ghcr.io/clash-lang/nixos-bittide-hardware:2024-07-30
image: ghcr.io/clash-lang/nixos-bittide-hardware:2024-08-06
options: --memory=11g
steps:
- name: Checkout
Expand Down Expand Up @@ -80,7 +80,7 @@ jobs:
shell: git-nix-shell {0} --option connect-timeout 360

container:
image: ghcr.io/clash-lang/nixos-bittide-hardware:2024-07-30
image: ghcr.io/clash-lang/nixos-bittide-hardware:2024-08-06
options: --memory=11g

steps:
Expand Down Expand Up @@ -114,6 +114,10 @@ jobs:
.github/scripts/cabal-gild.sh check
git diff --exit-code
- name: Check that we don't introduce accidental infinite loops in type checkers
run: |
! grep --include=*.hs -E -r '\-fconstraint-solver-iterations *= *0'
build:
name: Build dependencies
runs-on: [self-hosted, compute]
Expand All @@ -122,7 +126,7 @@ jobs:
shell: git-nix-shell {0} --option connect-timeout 360 --pure --keep "GITHUB_SHA" --keep "S3_PASSWORD"

container:
image: ghcr.io/clash-lang/nixos-bittide-hardware:2024-07-30
image: ghcr.io/clash-lang/nixos-bittide-hardware:2024-08-06
options: --memory=11g

steps:
Expand Down Expand Up @@ -162,7 +166,7 @@ jobs:
shell: git-nix-shell {0} --option connect-timeout 360 --pure --keep "GITHUB_OUTPUT"

container:
image: ghcr.io/clash-lang/nixos-bittide-hardware:2024-07-30
image: ghcr.io/clash-lang/nixos-bittide-hardware:2024-08-06
options: --memory=11g

steps:
Expand Down Expand Up @@ -202,7 +206,7 @@ jobs:
fail-fast: false

container:
image: ghcr.io/clash-lang/nixos-bittide-hardware:2024-07-30
image: ghcr.io/clash-lang/nixos-bittide-hardware:2024-08-06
options: --memory=11g

steps:
Expand Down Expand Up @@ -252,7 +256,7 @@ jobs:
needs: [build, lint, cc-sim-topologies-matrix, cc-sim-topologies, bittide-instances-hardware-in-the-loop]

container:
image: ghcr.io/clash-lang/nixos-bittide-hardware:2024-07-30
image: ghcr.io/clash-lang/nixos-bittide-hardware:2024-08-06
options: --memory=11g

steps:
Expand Down Expand Up @@ -325,7 +329,7 @@ jobs:
needs: [build, lint]

container:
image: ghcr.io/clash-lang/nixos-bittide-hardware:2024-07-30
image: ghcr.io/clash-lang/nixos-bittide-hardware:2024-08-06
options: --memory=11g

steps:
Expand All @@ -352,7 +356,7 @@ jobs:
needs: [build, lint]

container:
image: ghcr.io/clash-lang/nixos-bittide-hardware:2024-07-30
image: ghcr.io/clash-lang/nixos-bittide-hardware:2024-08-06
options: --memory=11g

steps:
Expand Down Expand Up @@ -393,7 +397,7 @@ jobs:
run:
shell: git-nix-shell {0} --option connect-timeout 360 --pure --keep "GITHUB_SHA" --keep "S3_PASSWORD"
container:
image: ghcr.io/clash-lang/nixos-bittide-hardware:2024-07-30
image: ghcr.io/clash-lang/nixos-bittide-hardware:2024-08-06
options: --memory=11g
needs: [build]

Expand All @@ -418,7 +422,7 @@ jobs:
run:
shell: git-nix-shell {0} --option connect-timeout 360 --pure --keep "GITHUB_SHA" --keep "S3_PASSWORD"
container:
image: ghcr.io/clash-lang/nixos-bittide-hardware:2024-07-30
image: ghcr.io/clash-lang/nixos-bittide-hardware:2024-08-06
options: --memory=11g
needs: [build]

Expand Down Expand Up @@ -446,7 +450,7 @@ jobs:
run:
shell: git-nix-shell {0} --option connect-timeout 360 --pure --keep "GITHUB_SHA" --keep "S3_PASSWORD"
container:
image: ghcr.io/clash-lang/nixos-bittide-hardware:2024-07-30
image: ghcr.io/clash-lang/nixos-bittide-hardware:2024-08-06
options: --memory=11g
needs: [build]

Expand All @@ -472,7 +476,7 @@ jobs:
run:
shell: git-nix-shell {0} --option connect-timeout 360 --pure --keep "GITHUB_SHA" --keep "S3_PASSWORD"
container:
image: ghcr.io/clash-lang/nixos-bittide-hardware:2024-07-30
image: ghcr.io/clash-lang/nixos-bittide-hardware:2024-08-06
options: --memory=11g
needs: [build]

Expand Down Expand Up @@ -505,7 +509,7 @@ jobs:
needs: [build, lint]

container:
image: ghcr.io/clash-lang/nixos-bittide-hardware:2024-07-30
image: ghcr.io/clash-lang/nixos-bittide-hardware:2024-08-06
options: --memory=11g

steps:
Expand All @@ -532,7 +536,7 @@ jobs:
needs: [build, lint]

container:
image: ghcr.io/clash-lang/nixos-bittide-hardware:2024-07-30
image: ghcr.io/clash-lang/nixos-bittide-hardware:2024-08-06
options: --memory=11g

steps:
Expand All @@ -558,7 +562,7 @@ jobs:
shell: git-nix-shell {0} --option connect-timeout 360 --pure --keep "GITHUB_OUTPUT"

container:
image: ghcr.io/clash-lang/nixos-bittide-hardware:2024-07-30
image: ghcr.io/clash-lang/nixos-bittide-hardware:2024-08-06
options: --memory=11g

steps:
Expand Down Expand Up @@ -591,7 +595,7 @@ jobs:
shell: git-nix-shell {0} --option connect-timeout 360 --pure --keep "GITHUB_OUTPUT"

container:
image: ghcr.io/clash-lang/nixos-bittide-hardware:2024-07-30
image: ghcr.io/clash-lang/nixos-bittide-hardware:2024-08-06
options: --memory=11g

steps:
Expand Down Expand Up @@ -634,7 +638,7 @@ jobs:
fail-fast: false

container:
image: ghcr.io/clash-lang/nixos-bittide-hardware:2024-07-30
image: ghcr.io/clash-lang/nixos-bittide-hardware:2024-08-06
volumes:
- /opt/tools:/opt/tools
options: --init --mac-address="6c:5a:b0:6c:13:0b" --memory=11g
Expand Down Expand Up @@ -714,7 +718,7 @@ jobs:
fail-fast: false

container:
image: ghcr.io/clash-lang/nixos-bittide-hardware:2024-07-30
image: ghcr.io/clash-lang/nixos-bittide-hardware:2024-08-06
volumes:
- /opt/tools:/opt/tools
- /dev:/dev
Expand Down
2 changes: 1 addition & 1 deletion bittide-instances/src/Bittide/Instances/Domains.hs
Original file line number Diff line number Diff line change
Expand Up @@ -6,7 +6,7 @@

module Bittide.Instances.Domains where

import Clash.Explicit.Prelude
import Clash.Explicit.Prelude hiding (PeriodToCycles)

import Bittide.ClockControl
import Bittide.Arithmetic.Time
Expand Down
1 change: 0 additions & 1 deletion bittide-instances/src/Bittide/Instances/Hitl/FincFdec.hs
Original file line number Diff line number Diff line change
Expand Up @@ -15,7 +15,6 @@ import Clash.Explicit.Prelude
import Clash.Prelude (withClockResetEnable)
import Clash.Xilinx.ClockGen (clockWizardDifferential)

import Bittide.Arithmetic.Time
import Bittide.Counter (domainDiffCounter)
import Bittide.ClockControl (SpeedChange(NoChange, SlowDown, SpeedUp), speedChangeToFincFdec)
import Bittide.ClockControl.Si539xSpi (si539xSpi, ConfigState(Finished))
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -33,7 +33,7 @@ module Bittide.Instances.Hitl.FullMeshHwCc
) where

import Clash.Prelude (withClockResetEnable)
import Clash.Explicit.Prelude
import Clash.Explicit.Prelude hiding (PeriodToCycles)
import qualified Clash.Explicit.Prelude as E

import Data.Maybe (fromMaybe)
Expand Down
7 changes: 4 additions & 3 deletions bittide-instances/src/Bittide/Instances/Hitl/FullMeshSwCc.hs
Original file line number Diff line number Diff line change
@@ -1,11 +1,12 @@
-- SPDX-FileCopyrightText: 2023-2024 Google LLC
--
-- SPDX-License-Identifier: Apache-2.0
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE NumericUnderscores #-}
{-# LANGUAGE OverloadedRecordDot #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE OverloadedRecordDot #-}
{-# LANGUAGE NamedFieldPuns #-}

{-# OPTIONS_GHC -fplugin=Protocols.Plugin #-}
{-# OPTIONS_GHC -fconstraint-solver-iterations=20 #-}
Expand Down Expand Up @@ -33,7 +34,7 @@ module Bittide.Instances.Hitl.FullMeshSwCc

import qualified Prelude as P
import Clash.Prelude (withClockResetEnable)
import Clash.Explicit.Prelude
import Clash.Explicit.Prelude hiding (PeriodToCycles)
import qualified Clash.Explicit.Prelude as E

import Data.Maybe (fromMaybe)
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -34,7 +34,7 @@ module Bittide.Instances.Hitl.HwCcTopologies
) where

import Clash.Prelude (withClockResetEnable)
import Clash.Explicit.Prelude
import Clash.Explicit.Prelude hiding (PeriodToCycles)
import qualified Clash.Explicit.Prelude as E

import Data.Bifunctor (bimap)
Expand Down
4 changes: 2 additions & 2 deletions bittide-instances/src/Bittide/Instances/Hitl/IlaPlot.hs
Original file line number Diff line number Diff line change
Expand Up @@ -47,11 +47,11 @@ module Bittide.Instances.Hitl.IlaPlot

import GHC.Stack (HasCallStack)

import Clash.Explicit.Prelude
import Clash.Explicit.Prelude hiding (PeriodToCycles)
import Clash.Explicit.Signal.Extra
import Clash.Sized.Extra (concatUnsigneds)

import Bittide.Arithmetic.Time (Seconds, Milliseconds, PeriodToCycles, trueFor)
import Bittide.Arithmetic.Time (PeriodToCycles, trueFor)
import Bittide.ClockControl (SpeedChange(..), RelDataCount, ClockControlConfig)
import Bittide.ClockControl.Callisto
(CallistoResult(..), ReframingState(..), callistoClockControl)
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -62,7 +62,7 @@
--
module Bittide.Instances.Hitl.SyncInSyncOut where

import Clash.Explicit.Prelude
import Clash.Explicit.Prelude hiding (PeriodToCycles)

import Bittide.Arithmetic.Time
import Bittide.Hitl (HitlTests, allFpgas, hitlVioBool, noConfigTest)
Expand Down
1 change: 0 additions & 1 deletion bittide-instances/src/Bittide/Instances/Pnr/Si539xSpi.hs
Original file line number Diff line number Diff line change
Expand Up @@ -11,7 +11,6 @@ import Clash.Prelude

import Clash.Annotations.TH (makeTopEntity)

import Bittide.Arithmetic.Time
import Bittide.ClockControl
import Bittide.ClockControl.Callisto
import Bittide.ClockControl.Si5395J
Expand Down
47 changes: 27 additions & 20 deletions bittide/src/Bittide/Arithmetic/Time.hs
Original file line number Diff line number Diff line change
Expand Up @@ -2,44 +2,51 @@
--
-- SPDX-License-Identifier: Apache-2.0
{-# LANGUAGE FlexibleInstances,MultiParamTypeClasses,TemplateHaskell #-}
{-# LANGUAGE NumericUnderscores #-}
{-# OPTIONS_GHC -Wno-orphans #-}
module Bittide.Arithmetic.Time where

import GHC.Stack (HasCallStack)
import Clash.Explicit.Prelude hiding (natVal)
import Clash.Explicit.Prelude hiding (natVal, PeriodToCycles)

import Clash.Class.Counter (countSucc, Counter)
import Clash.Signal.Internal (Femtoseconds (Femtoseconds), mapFemtoseconds)
import Data.Data (Proxy(Proxy))
import Data.Data (Proxy(..))
import Data.Int (Int64)
import Data.Kind (Type)

import GHC.TypeNats (natVal)
import GHC.TypeLits.KnownNat (KnownNat1 (..),SNatKn(..), nameToSymbol)

-- | Gets time in 'Picoseconds' from time in 'Seconds'.
type Seconds (s :: Nat) = Milliseconds (1000 * s)
-- | Gets time in 'Picoseconds' from time in 'Milliseconds'.
type Milliseconds (ms :: Nat) = Microseconds (1000 * ms)
-- | Gets time in 'Picoseconds' from time in 'Microseconds'.
type Microseconds (us :: Nat) = Nanoseconds (1000 * us)
-- | Gets time in 'Picoseconds' from time in 'Nanoseconds'.
type Nanoseconds (ns :: Nat) = Picoseconds (1000 * ns)
-- | Gets time in 'Picoseconds' from time in 'Picoseconds', essentially 'id'.
type Picoseconds (ps :: Nat) = ps

-- Make ghc-typelits-knownnat look through the Picoseconds type alias
-- | XXX: We currently retain this in favor of @clash-prelude@s 'PeriodToCycles'
-- until @1 <= DomainPeriod dom@ is trivially true. Related issue:
-- https://github.com/clash-lang/ghc-typelits-extra/issues/56
--
--Number of clock cycles required at the clock frequency of @dom@ before a minimum @period@ has passed.
-- Is always at least one.
type PeriodToCycles dom period = Max 1 (DivRU period (Max 1 (DomainPeriod dom)))

-- Make ghc-typelits-knownnat look through time related type aliases.
-- https://github.com/clash-lang/ghc-typelits-knownnat/issues/53
instance (KnownNat ps) => KnownNat1 $(nameToSymbol ''Picoseconds) ps where
natSing1 = SNatKn (natVal (Proxy @ps))
{-# NOINLINE natSing1 #-}

-- | Number of clock cycles required at the clock frequency of @dom@ before a minimum @period@ has passed.
-- Is always at least one.
type PeriodToCycles dom period = Max 1 (DivRU period (Max 1 (DomainPeriod dom)))
instance (KnownNat ps) => KnownNat1 $(nameToSymbol ''Nanoseconds) ps where
natSing1 = SNatKn (natVal (Proxy @(1_000 * ps)))
{-# NOINLINE natSing1 #-}

instance (KnownNat ps) => KnownNat1 $(nameToSymbol ''Microseconds) ps where
natSing1 = SNatKn (natVal (Proxy @(1_000_000 * ps)))
{-# NOINLINE natSing1 #-}

-- | The domain's clock frequency in Hertz, calculated based on the period stored in ps.
-- This might lead to rounding errors.
type DomainFrequency dom = Div (Seconds 1) (DomainPeriod dom)
instance (KnownNat ps) => KnownNat1 $(nameToSymbol ''Milliseconds) ps where
natSing1 = SNatKn (natVal (Proxy @(1_000_000_000 * ps)))
{-# NOINLINE natSing1 #-}

instance (KnownNat ps) => KnownNat1 $(nameToSymbol ''Seconds) ps where
natSing1 = SNatKn (natVal (Proxy @(1_000_000_000_000 * ps)))
{-# NOINLINE natSing1 #-}

-- | 'Index' with its 'maxBound' corresponding to the number of cycles needed to
-- wait for /n/ milliseconds.
Expand Down
4 changes: 2 additions & 2 deletions bittide/src/Bittide/ClockControl.hs
Original file line number Diff line number Diff line change
Expand Up @@ -22,7 +22,7 @@ module Bittide.ClockControl
)
where

import Clash.Explicit.Prelude
import Clash.Explicit.Prelude hiding (PeriodToCycles)
import Clash.Signal.Internal (Femtoseconds(..))
import Data.Aeson (ToJSON(toJSON))
import Data.Proxy (Proxy(..))
Expand All @@ -32,7 +32,7 @@ import Foreign.Storable (Storable(..))
import GHC.Stack (HasCallStack)

import Bittide.Arithmetic.Ppm
import Bittide.Arithmetic.Time (PeriodToCycles, Nanoseconds, Microseconds, microseconds)
import Bittide.Arithmetic.Time (PeriodToCycles, microseconds)
import Bittide.ClockControl.Foreign.Sizes

import Data.Csv
Expand Down
2 changes: 1 addition & 1 deletion bittide/src/Bittide/ClockControl/Si539xSpi.hs
Original file line number Diff line number Diff line change
Expand Up @@ -11,7 +11,7 @@

module Bittide.ClockControl.Si539xSpi where

import Clash.Prelude
import Clash.Prelude hiding (PeriodToCycles)
import Clash.Cores.SPI

import Data.Maybe
Expand Down
2 changes: 1 addition & 1 deletion bittide/src/Bittide/Transceiver.hs
Original file line number Diff line number Diff line change
Expand Up @@ -89,7 +89,7 @@ module Bittide.Transceiver where

import Clash.Explicit.Prelude

import Bittide.Arithmetic.Time (Milliseconds, trueForSteps)
import Bittide.Arithmetic.Time (trueForSteps)
import Bittide.ElasticBuffer (sticky)
import Clash.Cores.Xilinx.GTH (GthCore)
import Clash.Cores.Xilinx.Ila (IlaConfig(advancedTriggers, depth, stages), ilaConfig, ila, Depth(D1024))
Expand Down
3 changes: 1 addition & 2 deletions bittide/src/Bittide/Wishbone.hs
Original file line number Diff line number Diff line change
Expand Up @@ -11,7 +11,6 @@ module Bittide.Wishbone where

import Clash.Prelude

import Bittide.Arithmetic.Time(DomainFrequency)
import Bittide.DoubleBufferedRam
import Bittide.SharedTypes

Expand Down Expand Up @@ -467,7 +466,7 @@ timeWb = Circuit $ \(wbM2S, _) -> (mealy goMealy (0,0) wbM2S, ())
where
goMealy (frozen, count :: Unsigned 64) wbM2S = ((nextFrozen, succ count), wbS2M)
where
freq = natToNum @(DomainFrequency dom) :: Unsigned 64
freq = natToNum @(DomainToHz dom) :: Unsigned 64
nextFrozen = if isJust (head writes) then count else frozen
RegisterBank (splitAtI -> (frozenMsbs, frozenLsbs)) = getRegsBe @8 frozen
RegisterBank (splitAtI -> (freqMsbs, freqLsbs)) = getRegsBe @8 freq
Expand Down
Loading

0 comments on commit 3248f3c

Please sign in to comment.