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

Safe HaskellNone
LanguageHaskell2010

Language.KansasLava

Contents

Description

A top-level module that re-exports the relevent parts of the library's internal modules.

Synopsis

Basic types in Kansas Lava

Generating KLEG netlists

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.

reifyFabric :: Fabric () -> IO KLEG Source

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

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.

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].

The CSeq and Seq types

data Signal c a Source

These are sequences of values over time. We assume edge triggered logic (checked at (typically) rising edge of clock) This clock is assumed known, based on who is consuming the list. Right now, it is global, but we think we can support multiple clocks with a bit of work.

Instances

(Bounded a, Rep a) => Bounded (Signal i a) 
(Rep a, Enum a) => Enum (Signal i a) 
(Rep a, Eq a) => Eq (Signal c a) 
(Eq a, Show a, Fractional a, Rep a) => Fractional (Signal i a) 
(Rep a, Integral a) => Integral (Signal i a) 
(Num a, Rep a) => Num (Signal i a) 
(Ord a, Rep a) => Ord (Signal i a) 
(Rep a, Real a) => Real (Signal i a) 
Rep a => Show (Signal c a) 
(Show a, Bits a, Rep a) => Bits (Signal i a) 
Dual (Signal c a) 

type Seq a = Signal CLK a Source

Signal in some implicit clock domain.

toS :: (Clock c, Rep a) => [a] -> Signal c a Source

Convert a list of values into a Signal. The shallow portion of the resulting Signal will begin with the input list, then an infinite stream of X unknowns.

toS' :: (Clock c, Rep a) => [Maybe a] -> Signal c a Source

Convert a list of values into a Signal. The input list is wrapped with a Maybe, and any Nothing elements are mapped to X's unknowns.

undefinedS :: forall a sig clk. (Rep a, sig ~ Signal clk) => sig a Source

Create a Signal with undefined for both the deep and shallow elements.

fromS :: Rep a => Signal c a -> [Maybe a] Source

Convert a Signal of values into a list of Maybe values.

takeS :: (Rep a, Clock c) => Int -> Signal c a -> Signal c a Source

take the first n elements of a Signal; the rest is undefined.

pureS :: Rep a => a -> Signal i a Source

A pure Signal.

witnessS :: Rep a => Witness a -> Signal i a -> Signal i a Source

A Signal witness identity function. Useful when typing things.

commentS :: forall a sig clk. (Rep a, sig ~ Signal clk) => String -> sig a -> sig a Source

Attach a comment to a Signal.

pack :: Pack clk a => Unpacked clk a -> Signal clk a Source

Push the sign type *into* the compound data type.

unpack :: Pack clk a => Signal clk a -> Unpacked clk a Source

packMatrix :: (Rep a, Size x, sig ~ Signal clk) => Matrix x (sig a) -> sig (Matrix x a) Source

unpackMatrix :: (Rep a, Size x, sig ~ Signal clk) => sig (Matrix x a) -> Matrix x (sig a) Source

register :: forall a clk. (Rep a, Clock clk) => a -> Signal clk a -> Signal clk a Source

A register is a state element with a reset. The reset is supplied by the clock domain in the Signal.

registers :: forall a clk. (Rep a, Clock clk) => Int -> a -> Signal clk a -> Signal clk a Source

registers generates a serial sequence of n registers, all with the same initial value.

delay :: forall a clk. (Rep a, Clock clk) => Signal clk a -> Signal clk a Source

a delay is a register with no defined default / initial value.

delays :: forall a clk. (Rep a, Clock clk) => Int -> Signal clk a -> Signal clk a Source

delays generates a serial sequence of n delays.

Rendering KLEG as a Graph

writeDotCircuit Source

Arguments

:: FilePath

Name of output dot file, can be relative or absolute path.

-> KLEG

The reified Lava circuit.

-> IO () 

The writeDotCircuit function converts a Lava circuit into a graphviz output.

Optimizing KLEG

data OptimizationOpts Source

Data structure for passing optimization parameters.

Constructors

OptimizationOpts 

Fields

optDebugLevel :: Int
 

optimizeCircuit :: OptimizationOpts -> KLEG -> IO KLEG Source

Basic optimizations, and assumes reaching a fixpoint. Cleans things up, but does not work too hard, because the VHDL compiler get many of the combinatorial optimizations anyway.

Outputing VHDL

writeVhdlCircuit :: String -> FilePath -> KLEG -> IO () Source

The vhdlCircuit function converts a Lava KLEG into a VHDL entity/architecture pair.

writeVhdlPrelude :: FilePath -> IO () Source

Write the Lava Prelude into this file. For example:

writeVhdlPrelude "Lava.vhd" 

RTL sub-DSL

Probes

Protocols

Rep

Kansas Lava User-level Utils

Version Change Dump

data VCD Source

VCD is a primary bit-wise record of an interactive session with some circuit Map from module/name to stream.

Instances

writeVCDFile Source

Arguments

:: Bool

Whether to include the clock signal in the list of signals

-> Integer

Timescale in nanoseconds

-> FilePath

name of VCD file

-> VCD 
-> IO () 

Convert a VCD to a VCD file.

readVCDFile :: FilePath -> Signature -> IO VCD Source

Convert a VCD file to a VCD object.