{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE Unsafe #-}
{-# OPTIONS_HADDOCK show-extensions #-}
module Clash.Explicit.ROM.File
(
romFile
, romFilePow2
, memFile
, romFile#
)
where
import Data.Array (listArray)
import Data.Array.Base (unsafeAt)
import GHC.TypeLits (KnownNat)
import System.IO.Unsafe (unsafePerformIO)
import Clash.Annotations.Primitive (hasBlackBox)
import Clash.Explicit.BlockRam.File (initMem, memFile)
import Clash.Promoted.Nat (SNat (..), pow2SNat, snatToNum)
import Clash.Sized.BitVector (BitVector)
import Clash.Explicit.Signal (Clock, Enable, Signal, KnownDomain, delay)
import Clash.Sized.Unsigned (Unsigned)
import Clash.XException (NFDataX(deepErrorX))
romFilePow2
:: forall dom n m
. (KnownNat m, KnownNat n, KnownDomain dom)
=> Clock dom
-> Enable dom
-> FilePath
-> Signal dom (Unsigned n)
-> Signal dom (BitVector m)
romFilePow2 :: Clock dom
-> Enable dom
-> FilePath
-> Signal dom (Unsigned n)
-> Signal dom (BitVector m)
romFilePow2 = \Clock dom
clk Enable dom
en -> Clock dom
-> Enable dom
-> SNat (2 ^ n)
-> FilePath
-> Signal dom (Unsigned n)
-> Signal dom (BitVector m)
forall (m :: Nat) addr (dom :: Domain) (n :: Nat).
(KnownNat m, Enum addr, KnownDomain dom) =>
Clock dom
-> Enable dom
-> SNat n
-> FilePath
-> Signal dom addr
-> Signal dom (BitVector m)
romFile Clock dom
clk Enable dom
en (SNat n -> SNat (2 ^ n)
forall (a :: Nat). SNat a -> SNat (2 ^ a)
pow2SNat (KnownNat n => SNat n
forall (n :: Nat). KnownNat n => SNat n
SNat @n))
{-# INLINE romFilePow2 #-}
romFile
:: (KnownNat m, Enum addr, KnownDomain dom)
=> Clock dom
-> Enable dom
-> SNat n
-> FilePath
-> Signal dom addr
-> Signal dom (BitVector m)
romFile :: Clock dom
-> Enable dom
-> SNat n
-> FilePath
-> Signal dom addr
-> Signal dom (BitVector m)
romFile = \Clock dom
clk Enable dom
en SNat n
sz FilePath
file Signal dom addr
rd -> Clock dom
-> Enable dom
-> SNat n
-> FilePath
-> Signal dom Int
-> Signal dom (BitVector m)
forall (m :: Nat) (dom :: Domain) (n :: Nat).
(KnownNat m, KnownDomain dom) =>
Clock dom
-> Enable dom
-> SNat n
-> FilePath
-> Signal dom Int
-> Signal dom (BitVector m)
romFile# Clock dom
clk Enable dom
en SNat n
sz FilePath
file (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 romFile #-}
romFile#
:: forall m dom n
. (KnownNat m, KnownDomain dom)
=> Clock dom
-> Enable dom
-> SNat n
-> FilePath
-> Signal dom Int
-> Signal dom (BitVector m)
romFile# :: Clock dom
-> Enable dom
-> SNat n
-> FilePath
-> Signal dom Int
-> Signal dom (BitVector m)
romFile# Clock dom
clk Enable dom
en SNat n
sz FilePath
file Signal dom Int
rd =
Clock dom
-> Enable dom
-> BitVector m
-> Signal dom (BitVector m)
-> Signal dom (BitVector m)
forall (dom :: Domain) a.
(KnownDomain dom, NFDataX a) =>
Clock dom -> Enable dom -> a -> Signal dom a -> Signal dom a
delay Clock dom
clk Enable dom
en (FilePath -> BitVector m
forall a. (NFDataX a, HasCallStack) => FilePath -> a
deepErrorX FilePath
"First value of romFile is undefined")
(Int -> BitVector m
safeAt (Int -> BitVector m) -> Signal dom Int -> Signal dom (BitVector m)
forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
<$> Signal dom Int
rd)
where
mem :: [BitVector m]
mem = IO [BitVector m] -> [BitVector m]
forall a. IO a -> a
unsafePerformIO (FilePath -> IO [BitVector m]
forall (n :: Nat). KnownNat n => FilePath -> IO [BitVector n]
initMem FilePath
file)
content :: Array Int (BitVector m)
content = (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]
mem
szI :: Int
szI = SNat n -> Int
forall a (n :: Nat). Num a => SNat n -> a
snatToNum SNat n
sz
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)
content Int
i
else
FilePath -> BitVector m
forall a. (NFDataX a, HasCallStack) => FilePath -> a
deepErrorX (FilePath
"romFile: address " FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ Int -> FilePath
forall a. Show a => a -> FilePath
show Int
i FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++
FilePath
" not in range [0.." FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ Int -> FilePath
forall a. Show a => a -> FilePath
show Int
szI FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
")")
{-# INLINE safeAt #-}
{-# NOINLINE romFile# #-}
{-# ANN romFile# hasBlackBox #-}