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

Safe HaskellNone
LanguageHaskell2010

Language.KansasLava.Fabric

Description

The Fabric module is used for generating a top-level VHDL entity for a Lava circuit, with inputs and outputs.

Synopsis

Documentation

data Fabric a Source #

The Fabric structure, which is also a monad.

fabric_example :: Fabric ()
fabric_example = do
       i0 <- inStdLogic "i0"
       i1 <- inStdLogic "i1"
       let (c,s) = halfAdder i0 i1
       outStdLogic "carry" c
       outStdLogic "sum" s
 where
         halfAdder :: Seq Bool -> Seq Bool -> (Seq Bool,Seq Bool)
         halfAdder a b = (carry,sum_)
               where carry = and2 a b
                     sum_  = xor2 a b

A Fabric consists of a list of input ports, and yields a list of output ports and generics.

Constructors

Fabric 

Fields

Instances

Monad Fabric Source # 

Methods

(>>=) :: Fabric a -> (a -> Fabric b) -> Fabric b #

(>>) :: Fabric a -> Fabric b -> Fabric b #

return :: a -> Fabric a #

fail :: String -> Fabric a #

Functor Fabric Source # 

Methods

fmap :: (a -> b) -> Fabric a -> Fabric b #

(<$) :: a -> Fabric b -> Fabric a #

MonadFix Fabric Source # 

Methods

mfix :: (a -> Fabric a) -> Fabric a #

Applicative Fabric Source # 

Methods

pure :: a -> Fabric a #

(<*>) :: Fabric (a -> b) -> Fabric a -> Fabric b #

liftA2 :: (a -> b -> c) -> Fabric a -> Fabric b -> Fabric c #

(*>) :: Fabric a -> Fabric b -> Fabric b #

(<*) :: Fabric a -> Fabric b -> Fabric a #

data Pad Source #

A Pad represents the type of a top-level input/output port.

Instances

Show Pad Source # 

Methods

showsPrec :: Int -> Pad -> ShowS #

show :: Pad -> String #

showList :: [Pad] -> ShowS #

runFabric :: Fabric a -> [(String, Pad)] -> (a, [(String, Pad)]) Source #

Reify a fabric, returning the output ports and the result of the Fabric monad.

inStdLogic :: (Rep a, Show a, W a ~ X1) => String -> Fabric (Seq a) Source #

Generate a named std_logic input port.

inStdLogicVector :: forall a. (Rep a, Show a, Size (W a)) => String -> Fabric (Seq a) Source #

Generate a named std_logic_vector port input.

inGeneric :: String -> Fabric Integer Source #

Generate a named generic.

outStdLogic :: (Rep a, Show a, W a ~ X1) => String -> Seq a -> Fabric () Source #

Generate a named std_logic output port, given a Lava circuit.

outStdLogicVector :: forall a. (Rep a, Show a, Size (W a)) => String -> Seq a -> Fabric () Source #

Generate a named std_logic_vector output port, given a Lava circuit.

padStdLogicType :: Pad -> StdLogicType Source #

Get the type of a pad.

theClk :: String -> Fabric () Source #

theClk gives the external name for the clock.

theRst :: String -> Fabric () Source #

theRst gives the external name for the reset signal [default = low].

theClkEn :: String -> Fabric () Source #

theClkEn gives the external name for the clock enable signal [default = high].

reifyFabric :: Fabric () -> IO KLEG Source #

reifyFabric does reification of a 'Fabric ()' into a KLEG.

runFabricWithResult :: Fabric a -> [(String, Pad)] -> a Source #

runFabric runs a Fabric a with arguments, and gives a value result. must have no (monadic) outputs.

runFabricWithDriver :: Fabric () -> Fabric a -> a Source #

runFabricWithDriver runs a Fabric () using a driver Fabric.