{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE Trustworthy #-}
{-# OPTIONS_HADDOCK show-extensions #-}
module Clash.Explicit.ROM.Blob
(
romBlob
, romBlobPow2
, MemBlob
, createMemBlob
, memBlobTH
, unpackMemBlob
, romBlob#
) where
import Data.Array (listArray)
import Data.Array.Base (unsafeAt)
import GHC.Stack (withFrozenCallStack)
import GHC.TypeLits (KnownNat, type (^))
import Clash.Annotations.Primitive (hasBlackBox)
import Clash.Explicit.BlockRam.Blob (createMemBlob, memBlobTH)
import Clash.Explicit.BlockRam.Internal (MemBlob(..), unpackMemBlob)
import Clash.Promoted.Nat (natToNum)
import Clash.Signal.Internal
(Clock (..), KnownDomain, Signal (..), Enable, fromEnable)
import Clash.Sized.Internal.BitVector (BitVector)
import Clash.Sized.Internal.Unsigned (Unsigned)
import Clash.XException (deepErrorX, seqX)
romBlob
:: forall dom addr m n
. ( KnownDomain dom
, Enum addr
)
=> Clock dom
-> Enable dom
-> MemBlob n m
-> Signal dom addr
-> Signal dom (BitVector m)
romBlob :: Clock dom
-> Enable dom
-> MemBlob n m
-> Signal dom addr
-> Signal dom (BitVector m)
romBlob = \Clock dom
clk Enable dom
en MemBlob n m
content Signal dom addr
rd -> Clock dom
-> Enable dom
-> MemBlob n m
-> Signal dom Int
-> Signal dom (BitVector m)
forall (dom :: Domain) (m :: Nat) (n :: Nat).
KnownDomain dom =>
Clock dom
-> Enable dom
-> MemBlob n m
-> Signal dom Int
-> Signal dom (BitVector m)
romBlob# Clock dom
clk Enable dom
en MemBlob n m
content (addr -> Int
forall a. Enum a => a -> Int
fromEnum (addr -> Int) -> Signal dom addr -> Signal dom Int
forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
<$> Signal dom addr
rd)
{-# INLINE romBlob #-}
romBlobPow2
:: forall dom m n
. ( KnownDomain dom
, KnownNat n
)
=> Clock dom
-> Enable dom
-> MemBlob (2^n) m
-> Signal dom (Unsigned n)
-> Signal dom (BitVector m)
romBlobPow2 :: Clock dom
-> Enable dom
-> MemBlob (2 ^ n) m
-> Signal dom (Unsigned n)
-> Signal dom (BitVector m)
romBlobPow2 = Clock dom
-> Enable dom
-> MemBlob (2 ^ n) m
-> Signal dom (Unsigned n)
-> Signal dom (BitVector m)
forall (dom :: Domain) addr (m :: Nat) (n :: Nat).
(KnownDomain dom, Enum addr) =>
Clock dom
-> Enable dom
-> MemBlob n m
-> Signal dom addr
-> Signal dom (BitVector m)
romBlob
{-# INLINE romBlobPow2 #-}
romBlob#
:: forall dom m n
. KnownDomain dom
=> Clock dom
-> Enable dom
-> MemBlob n m
-> Signal dom Int
-> Signal dom (BitVector m)
romBlob# :: Clock dom
-> Enable dom
-> MemBlob n m
-> Signal dom Int
-> Signal dom (BitVector m)
romBlob# !Clock dom
_ Enable dom
en content :: MemBlob n m
content@MemBlob{} =
BitVector m
-> Signal dom Bool -> Signal dom Int -> Signal dom (BitVector m)
forall (dom :: Domain) (dom :: Domain) (dom :: Domain).
BitVector m
-> Signal dom Bool -> Signal dom Int -> Signal dom (BitVector m)
go
((HasCallStack => BitVector m) -> BitVector m
forall a. HasCallStack => (HasCallStack => a) -> a
withFrozenCallStack (String -> BitVector m
forall a. (NFDataX a, HasCallStack) => String -> a
deepErrorX String
"romBlob: initial value undefined"))
(Enable dom -> Signal dom Bool
forall (dom :: Domain). Enable dom -> Signal dom Bool
fromEnable Enable dom
en)
where
szI :: Int
szI = (Num Int, KnownNat n) => Int
forall (n :: Nat) a. (Num a, KnownNat n) => a
natToNum @n @Int
arr :: Array Int (BitVector m)
arr = (Int, Int) -> [BitVector m] -> Array Int (BitVector m)
forall i e. Ix i => (i, i) -> [e] -> Array i e
listArray (Int
0,Int
szIInt -> Int -> Int
forall a. Num a => a -> a -> a
-Int
1) ([BitVector m] -> Array Int (BitVector m))
-> [BitVector m] -> Array Int (BitVector m)
forall a b. (a -> b) -> a -> b
$ MemBlob n m -> [BitVector m]
forall (n :: Nat) (m :: Nat). MemBlob n m -> [BitVector m]
unpackMemBlob MemBlob n m
content
go :: BitVector m
-> Signal dom Bool -> Signal dom Int -> Signal dom (BitVector m)
go BitVector m
o (Bool
e :- Signal dom Bool
es) rd :: Signal dom Int
rd@(~(Int
r :- Signal dom Int
rs)) =
let o1 :: BitVector m
o1 = if Bool
e then Int -> BitVector m
safeAt Int
r else BitVector m
o
in BitVector m
o BitVector m -> Signal dom (BitVector m) -> Signal dom (BitVector m)
forall a b. a -> b -> b
`seqX` BitVector m
o BitVector m -> Signal dom (BitVector m) -> Signal dom (BitVector m)
forall (dom :: Domain) a. a -> Signal dom a -> Signal dom a
:- (Signal dom Int
rd Signal dom Int
-> Signal dom (BitVector m) -> Signal dom (BitVector m)
`seq` BitVector m
-> Signal dom Bool -> Signal dom Int -> Signal dom (BitVector m)
go BitVector m
o1 Signal dom Bool
es Signal dom Int
rs)
safeAt :: Int -> BitVector m
safeAt :: Int -> BitVector m
safeAt Int
i =
if (Int
0 Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<= Int
i) Bool -> Bool -> Bool
&& (Int
i Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
szI) then
Array Int (BitVector m) -> Int -> BitVector m
forall (a :: Type -> Type -> Type) e i.
(IArray a e, Ix i) =>
a i e -> Int -> e
unsafeAt Array Int (BitVector m)
arr Int
i
else
(HasCallStack => BitVector m) -> BitVector m
forall a. HasCallStack => (HasCallStack => a) -> a
withFrozenCallStack
(String -> BitVector m
forall a. (NFDataX a, HasCallStack) => String -> a
deepErrorX (String
"romBlob: address " String -> String -> String
forall a. [a] -> [a] -> [a]
++ Int -> String
forall a. Show a => a -> String
show Int
i String -> String -> String
forall a. [a] -> [a] -> [a]
++
String
" not in range [0.." String -> String -> String
forall a. [a] -> [a] -> [a]
++ Int -> String
forall a. Show a => a -> String
show Int
szI String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
")"))
{-# INLINE safeAt #-}
{-# NOINLINE romBlob# #-}
{-# ANN romBlob# hasBlackBox #-}