Skip to content

Commit

Permalink
Add Counter a => Counter (Vec n a) instance #2787
Browse files Browse the repository at this point in the history
  • Loading branch information
gergoerdi committed Aug 28, 2024
1 parent 96f741d commit ec242f6
Showing 1 changed file with 27 additions and 0 deletions.
27 changes: 27 additions & 0 deletions clash-prelude/src/Clash/Class/Counter/Internal.hs
Original file line number Diff line number Diff line change
Expand Up @@ -14,6 +14,7 @@ import Clash.Sized.BitVector (BitVector, Bit)
import Clash.Sized.Index (Index)
import Clash.Sized.Signed (Signed)
import Clash.Sized.Unsigned (Unsigned)
import Clash.Sized.Vector as Vec (Vec, repeat, mapAccumR)

import Data.Bifunctor (bimap)
import Data.Functor.Identity (Identity(..))
Expand All @@ -22,11 +23,14 @@ import Data.Word (Word8, Word16, Word32, Word64)
import GHC.TypeLits (KnownNat, type (<=))

-- $setup
-- >>> :m -Prelude
-- >>> import Clash.Prelude
-- >>> import Clash.Class.Counter
-- >>> import Clash.Sized.BitVector (BitVector)
-- >>> import Clash.Sized.Index (Index)
-- >>> import Clash.Sized.Signed (Signed)
-- >>> import Clash.Sized.Unsigned (Unsigned)
-- >>> import Clash.Sized.Vector (Vec(..), iterate)

-- | t'Clash.Class.Counter.Counter' is a class that composes multiple counters
-- into a single one. It is similar to odometers found in olds cars,
Expand Down Expand Up @@ -193,3 +197,26 @@ instance (Counter a0, Counter a1) => Counter (a0, a1) where
(overflowA, a1) = countPredOverflow a0

genTupleInstances maxTupleSize

rippleR :: (a -> (Bool, a)) -> Vec n a -> (Bool, Vec n a)
rippleR f = mapAccumR step True
where
step carry x = if carry then f x else (False, x)

-- | Counters on vectors increment from right to left.
--
-- >>> type T = Vec 2 (Index 10)
-- >>> countSucc @T (0 :> 0 :> Nil)
-- 0 :> 1 :> Nil
-- >>> countSucc @T (0 :> 1 :> Nil)
-- 0 :> 2 :> Nil
-- >>> countSucc @T (0 :> 9 :> Nil)
-- 1 :> 0 :> Nil
-- >>> iterate (SNat @5) (countSucc @T) (9 :> 8 :> Nil)
-- (9 :> 8 :> Nil) :> (9 :> 9 :> Nil) :> (0 :> 0 :> Nil) :> (0 :> 1 :> Nil) :> (0 :> 2 :> Nil) :> Nil
instance (Counter a, KnownNat n, 1 <= n) => Counter (Vec n a) where
countMin = Vec.repeat countMin
countMax = Vec.repeat countMax

countSuccOverflow = rippleR countSuccOverflow
countPredOverflow = rippleR countPredOverflow

0 comments on commit ec242f6

Please sign in to comment.