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

Safe HaskellNone
LanguageHaskell2010

Language.KansasLava.Types

Contents

Description

This module contains the key internal types for Kansas Lava, and some basic utilities (like Show instances) for these types.

Synopsis

Types

data Type Source

Type captures HDL-representable types.

Constructors

B

Bit

S Int

Signed vector, with a width.

U Int

Unsigned vector, with a width.

V Int

std_logic_vector, with a width.

ClkTy

Clock Signal

GenericTy

generics in VHDL, argument must be integer

RomTy Int

a constant array of values.

TupleTy [Type]

Tuple, represented as a larger std_logic_vector

MatrixTy Int Type

Matrix, for example a vhdl array.

SampledTy Int Int

Our "floating" values. The first number is the precisionscale (+- N) The second number is the bits used to represent this number

typeWidth :: Type -> Int Source

typeWidth returns the width of a type when represented in VHDL.

isTypeSigned :: Type -> Bool Source

isTypeSigned determines if a type has a signed representation. This is necessary for the implementation of isSigned in the Bits type class.

data StdLogicType Source

StdLogicType is the type for std_logic things, typically input/output arguments to VHDL entities.

Constructors

SL

std_logic

SLV Int

std_logic_vector (n-1 downto 0)

SLVA Int Int

std_logic_vector (n-1 downto 0) (m-1 downto 0)

G

generic (inward) argument

toStdLogicType :: Type -> StdLogicType Source

toStdLogic maps Lava Types to a StdLogicType

fromStdLogicType :: StdLogicType -> Type Source

fromStdLogic maps StdLogicTypes to Lava types.

Id

data Id Source

Id is the name/tag of a block of compuation.

Constructors

Prim String

built in thing

External String

VHDL entity

Function [(RepValue, RepValue)]

anonymous function

ClockId String

An environment box

Comment [String]

An identity; also a multi-line comments

BlackBox (Box Dynamic)

BlackBox can be removed without harm The rule is you can only insert you own types in here (or use newtype). Prelude or other peoples types are not allowed (because typecase becomes ambigious)

Instances

newtype Box a Source

Box wraps a dynamic, so that we can define custom Eq/Ord instances.

Constructors

Box a 

Instances

Eq (Box a) 
Ord (Box a) 

Entity

data Entity s Source

An Entity Entity is our central BOX of computation, round an Id.

Constructors

Entity Id [(String, Type)] [(String, Type, Driver s)] 

Instances

newtype E Source

E is the knot-tyed version of Entity.

Constructors

E (Entity E) 

Instances

Eq E 
Show E 
MuRef E 
type DeRef E = Entity 

entityFind :: Show a => String -> Entity a -> (Type, Driver a) Source

entityFind finds an input in a list, avoiding the need to have ordering.

Driver

data Driver s Source

A Driver is a specific driven wire (signal in VHDL), which types contains a value that changes over time.

Constructors

Port String s

a specific port on the entity

Pad String

an input pad

ClkDom String

the clock domain (the clock enable, resolved via context)

Lit RepValue

A representable Value (including unknowns, aka X in VHDL)

Generic Integer

A generic argument, always fully defined

Lits [RepValue]

A list of values, typically constituting a ROM initialization.

Error String

A call to err, in Datatype format for reification purposes

Instances

newtype D a Source

The D type adds a phantom type to a driver.

Constructors

D 

Fields

unD :: Driver E
 

Instances

Show (D a) 

Ways of intepreting Signal

class Clock clk Source

class Clock is a type that can be be used to represent a clock.

Instances

data CLK Source

genericdefaultboardstandardvanilla clock.

Instances

RepValue

newtype RepValue Source

A RepValue is a value that can be represented using a bit encoding. The least significant bit is at the front of the list.

Constructors

RepValue 

Fields

unRepValue :: [Maybe Bool]
 

appendRepValue :: RepValue -> RepValue -> RepValue Source

appendRepValue joins two RepValue; the least significant value first. TODO: reverse this!

isValidRepValue :: RepValue -> Bool Source

isValidRepValue checks to see is a RepValue is completely valid.

getValidRepValue :: RepValue -> Maybe [Bool] Source

getValidRepValue Returns a binary rep, or Nothing is *any* bits are X.

chooseRepValue :: RepValue -> RepValue Source

chooseRepValue turns a RepValue with (optional) unknow values, and chooses a representation for the RepValue.

cmpRepValue :: RepValue -> RepValue -> Bool Source

cmpRepValue compares a golden value with another value, returning the bits that are different. The first value may contain X, in which case *any* value in that bit location will match. This means that cmpRepValue is not commutative.

BitPat

data BitPat w Source

Constructors

BitPat 

Instances

Size w => Enum (BitPat w) 
Eq (BitPat w) 
Size w => Integral (BitPat w) 
Size w => Num (BitPat w) 
Ord (BitPat w) 
Size w => Real (BitPat w) 
Show (BitPat w) 
IsString (BitPat w) 

(&) :: (Size w1, Size w2, Size w, w ~ ADD w1 w2, w1 ~ SUB w w2, w2 ~ SUB w w1) => BitPat w1 -> BitPat w2 -> BitPat w infixl 6 Source

& is a sized append for BitPat.

every :: forall w. Size w => [BitPat w] Source

KLEG

data KLEG Source

KLEG (Kansas Lava Entity Graph) is our primary way of representing a graph of entities.

Constructors

KLEG 

Fields

theCircuit :: [(Unique, Entity Unique)]

This the main graph. There is no actual node for the source or sink.

theSrcs :: [(String, Type)]

this is a (convenience) list of the src values.

theSinks :: [(String, Type, Driver Unique)]

these are the sinks; all values are generated from here.

Instances

visitEntities :: KLEG -> (Unique -> Entity Unique -> Maybe a) -> [a] Source

Map a function across all of the entities in a KLEG, accumulating the results in a list.

mapEntities :: KLEG -> (Unique -> Entity Unique -> Maybe (Entity Unique)) -> KLEG Source

Map a function across a KLEG, modifying each Entity for which the function returns a Just. Any entities that the function returns Nothing for will be removed from the resulting KLEG.

allocEntities :: KLEG -> [Unique] Source

Generate a list of Unique ids that are guaranteed not to conflict with any ids already in the KLEG.

data Signature Source

A Signature is the structure-level type of a KLEG.

Constructors

Signature 

Fields

sigInputs :: [(String, Type)]
 
sigOutputs :: [(String, Type)]
 
sigGenerics :: [(String, Integer)]
 

circuitSignature :: KLEG -> Signature Source

Calculate a signature from a KLEG.

Witness

data Witness w Source

Create a type witness, to help resolve some of the type issues. Really, we are using this in a system-F style. (As suggested by an anonymous TFP referee, as a better alternative to using 'error "witness"').

Constructors

Witness 

Dual shallow/deep

class Dual a where Source

Select the shallow embedding from one circuit, and the deep embedding from another.

Methods

dual :: a -> a -> a Source

Take the shallow value from the first argument, and the deep value from the second.

Instances

Dual b => Dual (a -> b) 
(Dual a, Dual b) => Dual (a, b) 
Dual (Signal c a) 
(Dual a, Dual b, Dual c) => Dual (a, b, c) 

Our version of tuples

data a :> b infixr 5 Source

Alternative definition for (,). Constructor is right-associative.

Constructors

a :> b infixr 5 

Instances

(Eq a, Eq b) => Eq ((:>) a b) 
(Ord a, Ord b) => Ord ((:>) a b) 
(Read a, Read b) => Read ((:>) a b) 
(Show a, Show b) => Show ((:>) a b) 
(Rep a, Rep b) => Rep ((:>) a b) 
(Unit a, Unit b) => Unit ((:>) a b) 
type W ((:>) a b) = ADD (W a) (W b) 
data X ((:>) a b) = XCell (X a, X b) 

Synthesis control

data Synthesis Source

How to balance our circuits. Typically use Sweet(spot), but Small has permission to take longer, and Fast has permission use extra gates.

Constructors

Small 
Sweet 
Fast