kansas-lava-0.2.4.5: Kansas Lava is a hardware simulator and VHDL generator.

Safe HaskellNone
LanguageHaskell2010

Language.KansasLava.RTL

Description

The RTL module provides a small DSL that's useful for control-oriented -- stateful -- computations.

Synopsis

Documentation

data RTL s c a where Source #

RTL Monad; s == the runST state; c is governing clock, and a is the result

Constructors

RTL :: (Pred c -> STRef s Int -> ST s (a, [Int])) -> RTL s c a 
(:=) :: forall c b s. Rep b => Reg s c b -> Signal c b -> RTL s c () infixr 0 
CASE :: [Cond s c] -> RTL s c () 
WHEN :: Signal c Bool -> RTL s c () -> RTL s c () 
DEBUG :: forall c b s. Rep b => String -> Reg s c b -> RTL s c () 

Instances

Monad (RTL s c) Source # 

Methods

(>>=) :: RTL s c a -> (a -> RTL s c b) -> RTL s c b #

(>>) :: RTL s c a -> RTL s c b -> RTL s c b #

return :: a -> RTL s c a #

fail :: String -> RTL s c a #

Functor (RTL s c) Source # 

Methods

fmap :: (a -> b) -> RTL s c a -> RTL s c b #

(<$) :: a -> RTL s c b -> RTL s c a #

Applicative (RTL s c) Source # 

Methods

pure :: a -> RTL s c a #

(<*>) :: RTL s c (a -> b) -> RTL s c a -> RTL s c b #

liftA2 :: (a -> b -> c) -> RTL s c a -> RTL s c b -> RTL s c c #

(*>) :: RTL s c a -> RTL s c b -> RTL s c b #

(<*) :: RTL s c a -> RTL s c b -> RTL s c a #

data Reg s c a Source #

A register is used internally to represent a register or memory element.

data Cond s c Source #

A conditional statement.

Constructors

IF (Signal c Bool) (RTL s c ()) 
OTHERWISE (RTL s c ()) 

runRTL :: forall c a. Clock c => (forall s. RTL s c a) -> a Source #

Run the RTL monad.

reg :: Reg s c a -> Signal c a Source #

reg is the value of a register, as set by the start of the cycle.

var :: Reg s c a -> Signal c a Source #

var is the value of a register, as will be set in the next cycle, so intra-cycle changes are observed. The is simular to a *variable* in VHDL.

newReg :: forall a c s. (Clock c, Rep a) => a -> RTL s c (Reg s c a) Source #

Declare a new register.

newArr :: forall a c ix s. (Size ix, Clock c, Rep a, Num ix, Rep ix) => Witness ix -> RTL s c (Signal c ix -> Reg s c a) Source #

Declare an array. Arrays support partual updates.

match :: Rep a => Signal c (Enabled a) -> (Signal c a -> RTL s c ()) -> Cond s c Source #

match checks for a enabled value, and if so, executes the given RTL in context, by constructing the correct Cond-itional.