{-# LANGUAGE DataKinds #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE MagicHash #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE Unsafe #-}
{-# OPTIONS_HADDOCK show-extensions #-}
module Clash.Explicit.ROM.File
(
romFile
, romFilePow2
, romFile#
)
where
import Data.Array (listArray,(!))
import GHC.TypeLits (KnownNat)
import System.IO.Unsafe (unsafePerformIO)
import Clash.Explicit.BlockRam.File (initMem)
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 (Undefined(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 = \clk :: Clock dom
clk en :: 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 = \clk :: Clock dom
clk en :: Enable dom
en sz :: SNat n
sz file :: FilePath
file rd :: 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 :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Signal dom addr
rd)
{-# INLINE romFile #-}
romFile#
:: (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# clk :: Clock dom
clk en :: Enable dom
en sz :: SNat n
sz file :: FilePath
file rd :: Signal dom Int
rd =
Clock dom
-> Enable dom
-> BitVector m
-> Signal dom (BitVector m)
-> Signal dom (BitVector m)
forall (dom :: Domain) a.
(KnownDomain dom, Undefined a) =>
Clock dom -> Enable dom -> a -> Signal dom a -> Signal dom a
delay Clock dom
clk Enable dom
en (FilePath -> BitVector m
forall a. (Undefined a, HasCallStack) => FilePath -> a
deepErrorX "First value of romFile is undefined") ((Array Int (BitVector m)
content Array Int (BitVector m) -> Int -> BitVector m
forall i e. Ix i => Array i e -> i -> e
!) (Int -> BitVector m) -> Signal dom Int -> Signal dom (BitVector m)
forall (f :: * -> *) 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 (0,Int
szIInt -> Int -> Int
forall a. Num a => a -> a -> a
-1) [BitVector m]
mem
szI :: Int
szI = SNat n -> Int
forall a (n :: Nat). Num a => SNat n -> a
snatToNum SNat n
sz
{-# NOINLINE romFile# #-}