Skip to content
This repository has been archived by the owner on Sep 7, 2018. It is now read-only.

Commit

Permalink
Add and use snatToNum
Browse files Browse the repository at this point in the history
See #72
  • Loading branch information
christiaanb committed Sep 2, 2016
1 parent 8b49099 commit 60153aa
Show file tree
Hide file tree
Showing 7 changed files with 22 additions and 17 deletions.
4 changes: 2 additions & 2 deletions src/CLaSH/Prelude/BlockRam/File.hs
Original file line number Diff line number Diff line change
Expand Up @@ -98,7 +98,7 @@ import Data.Maybe (listToMaybe)
import GHC.TypeLits (KnownNat)
import Numeric (readInt)

import CLaSH.Promoted.Nat (SNat (..), pow2SNat, snatToInteger)
import CLaSH.Promoted.Nat (SNat (..), pow2SNat, snatToNum)
import CLaSH.Sized.BitVector (BitVector)
import CLaSH.Signal (Signal)
import CLaSH.Signal.Explicit (Signal', SClock, register', systemClock)
Expand Down Expand Up @@ -285,7 +285,7 @@ blockRamFile# :: KnownNat m
-- clock cycle
blockRamFile# clk sz file wr rd en din = register' clk (errorX "blockRamFile#: intial value undefined") dout
where
szI = fromInteger $ snatToInteger sz
szI = snatToNum sz
dout = runST $ do
mem <- unsafeIOToST (initMem file)
arr <- newListArray (0,szI-1) mem
Expand Down
4 changes: 2 additions & 2 deletions src/CLaSH/Prelude/RAM.hs
Original file line number Diff line number Diff line change
Expand Up @@ -43,7 +43,7 @@ import Data.Array.MArray.Safe (newListArray,readArray,writeArray)
import Data.Array.ST.Safe (STArray)
import GHC.TypeLits (KnownNat)

import CLaSH.Promoted.Nat (SNat (..), snatToInteger, pow2SNat)
import CLaSH.Promoted.Nat (SNat (..), snatToNum, pow2SNat)
import CLaSH.Signal (Signal)
import CLaSH.Signal.Bundle (bundle)
import CLaSH.Signal.Explicit (Signal', SClock, systemClock, unsafeSynchronizer)
Expand Down Expand Up @@ -146,7 +146,7 @@ asyncRam# :: SClock wclk -- ^ 'Clock' to which to synchronise the write
-> Signal' rclk a -- ^ Value of the @RAM@ at address @r@
asyncRam# wclk rclk sz wr rd en din = unsafeSynchronizer wclk rclk dout
where
szI = fromInteger $ snatToInteger sz
szI = snatToNum sz
rd' = unsafeSynchronizer rclk wclk rd
dout = runST $ do
arr <- newListArray (0,szI-1) (replicate szI (errorX "asyncRam#: initial value undefined"))
Expand Down
10 changes: 5 additions & 5 deletions src/CLaSH/Prelude/ROM/File.hs
Original file line number Diff line number Diff line change
Expand Up @@ -93,7 +93,7 @@ import GHC.TypeLits (KnownNat)
import System.IO.Unsafe (unsafePerformIO)

import CLaSH.Prelude.BlockRam.File (initMem)
import CLaSH.Promoted.Nat (SNat (..), pow2SNat, snatToInteger)
import CLaSH.Promoted.Nat (SNat (..), pow2SNat, snatToNum)
import CLaSH.Sized.BitVector (BitVector)
import CLaSH.Signal (Signal)
import CLaSH.Signal.Explicit (Signal', SClock, register', systemClock)
Expand Down Expand Up @@ -166,15 +166,15 @@ asyncRomFile sz file = asyncRomFile# sz file . fromEnum
-- > where
-- > mem = unsafePerformIO (initMem file)
-- > content = listArray (0,szI-1) mem
-- > szI = fromInteger (snatToInteger sz)
-- > szI = snatToNum sz
--
-- We write:
--
-- > asyncRomFile# sz file = (content !)
-- > where
-- > mem = unsafePerformIO (initMem file)
-- > content = listArray (0,szI-1) mem
-- > szI = fromInteger (snatToInteger sz)
-- > szI = snatToNum sz
--
-- Where instead of returning the BitVector defined by @(content ! rd)@, we
-- return the function (thunk) @(content !)@.
Expand Down Expand Up @@ -232,7 +232,7 @@ asyncRomFile# sz file = (content !) -- Leave "(content !)" eta-reduced, see
where -- Note [Eta-reduction and unsafePerformIO initMem]
mem = unsafePerformIO (initMem file)
content = listArray (0,szI-1) mem
szI = fromInteger (snatToInteger sz)
szI = snatToNum sz

{-# INLINE romFile #-}
-- | A ROM with a synchronous read port, with space for @n@ elements
Expand Down Expand Up @@ -379,4 +379,4 @@ romFile# clk sz file rd = register' clk (errorX "romFile#: initial value undefin
where
mem = unsafePerformIO (initMem file)
content = listArray (0,szI-1) mem
szI = fromInteger (snatToInteger sz)
szI = snatToNum sz
7 changes: 6 additions & 1 deletion src/CLaSH/Promoted/Nat.hs
Original file line number Diff line number Diff line change
Expand Up @@ -24,7 +24,7 @@ module CLaSH.Promoted.Nat
, withSNat
, snat
-- ** Conversion
, snatToInteger
, snatToInteger, snatToNum
-- ** Arithmetic
, addSNat, mulSNat, powSNat
-- *** Partial
Expand Down Expand Up @@ -104,6 +104,11 @@ withSNat f = f SNat
snatToInteger :: SNat n -> Integer
snatToInteger p@SNat = natVal p

-- | Reify the type-level 'Nat' @n@ to it's term-level 'Num'ber.
snatToNum :: Num a => SNat n -> a
snatToNum p@SNat = fromInteger (natVal p)
{-# INLINE snatToNum #-}

-- | Unary representation of a type-level natural
--
-- __NB__: Not synthesisable
Expand Down
6 changes: 3 additions & 3 deletions src/CLaSH/Signal/Explicit.hs
Original file line number Diff line number Diff line change
Expand Up @@ -37,7 +37,7 @@ where
import Data.Maybe (isJust, fromJust)
import GHC.TypeLits (KnownNat, KnownSymbol)

import CLaSH.Promoted.Nat (SNat (..), snatToInteger)
import CLaSH.Promoted.Nat (SNat (..), snatToNum)
import CLaSH.Promoted.Symbol (SSymbol (..))
import CLaSH.Signal.Internal (Signal' (..), Clock (..), SClock (..), register#,
regEn#)
Expand Down Expand Up @@ -243,8 +243,8 @@ unsafeSynchronizer :: SClock clk1 -- ^ 'Clock' of the incoming signal
-> Signal' clk2 a
unsafeSynchronizer (SClock _ period1) (SClock _ period2) s = s'
where
t1 = fromInteger (snatToInteger period1)
t2 = fromInteger (snatToInteger period2)
t1 = snatToNum period1
t2 = snatToNum period2
s' | t1 < t2 = compress t2 t1 s
| t1 > t2 = oversample t1 t2 s
| otherwise = same s
Expand Down
4 changes: 2 additions & 2 deletions src/CLaSH/Sized/Internal/BitVector.hs
Original file line number Diff line number Diff line change
Expand Up @@ -122,7 +122,7 @@ import Test.QuickCheck.Arbitrary (Arbitrary (..), CoArbitrary (..),
import CLaSH.Class.Num (ExtendingNum (..), SaturatingNum (..),
SaturationMode (..))
import CLaSH.Class.Resize (Resize (..))
import CLaSH.Promoted.Nat (SNat, snatToInteger)
import CLaSH.Promoted.Nat (SNat, snatToInteger, snatToNum)
import CLaSH.XException (ShowX (..), showsPrecXWith)

import {-# SOURCE #-} qualified CLaSH.Sized.Vector as V
Expand Down Expand Up @@ -452,7 +452,7 @@ slice# :: BitVector (m + 1 + i) -> SNat m -> SNat n -> BitVector (m + 1 - n)
slice# (BV i) m n = BV (shiftR (i .&. mask) n')
where
m' = snatToInteger m
n' = fromInteger (snatToInteger n)
n' = snatToNum n

mask = 2 ^ (m' + 1) - 1

Expand Down
4 changes: 2 additions & 2 deletions src/CLaSH/Sized/RTree.hs
Original file line number Diff line number Diff line change
Expand Up @@ -68,7 +68,7 @@ import Prelude hiding ((++), (!!))
import Test.QuickCheck (Arbitrary (..), CoArbitrary (..))

import CLaSH.Class.BitPack (BitPack (..))
import CLaSH.Promoted.Nat (SNat (..), UNat (..), pow2SNat, snatToInteger,
import CLaSH.Promoted.Nat (SNat (..), UNat (..), pow2SNat, snatToNum,
subSNat, toUNat)
import CLaSH.Promoted.Nat.Literals (d1)
import CLaSH.Sized.Index (Index)
Expand Down Expand Up @@ -371,7 +371,7 @@ tmap f = tdfold (Proxy @(MapTree b)) (LR . f) (\_ l r -> BR l r)
tindices :: forall d . KnownNat d => RTree d (Index (2^d))
tindices =
tdfold (Proxy @(MapTree (Index (2^d)))) LR
(\s@SNat l r -> BR l (tmap (+(fromInteger (snatToInteger (pow2SNat s)))) r))
(\s@SNat l r -> BR l (tmap (+(snatToNum (pow2SNat s))) r))
(treplicate SNat 0)

data V2TTree (a :: *) (f :: TyFun Nat *) :: *
Expand Down

0 comments on commit 60153aa

Please sign in to comment.