kansas-lava-0.2.4.5: 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

Instances

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

Eq Id Source # 

Methods

(==) :: Id -> Id -> Bool #

(/=) :: Id -> Id -> Bool #

Ord Id Source # 

Methods

compare :: Id -> Id -> Ordering #

(<) :: Id -> Id -> Bool #

(<=) :: Id -> Id -> Bool #

(>) :: Id -> Id -> Bool #

(>=) :: Id -> Id -> Bool #

max :: Id -> Id -> Id #

min :: Id -> Id -> Id #

Show Id Source # 

Methods

showsPrec :: Int -> Id -> ShowS #

show :: Id -> String #

showList :: [Id] -> ShowS #

newtype Box a Source #

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

Constructors

Box a 

Instances

Eq (Box a) Source # 

Methods

(==) :: Box a -> Box a -> Bool #

(/=) :: Box a -> Box a -> Bool #

Ord (Box a) Source # 

Methods

compare :: Box a -> Box a -> Ordering #

(<) :: Box a -> Box a -> Bool #

(<=) :: Box a -> Box a -> Bool #

(>) :: Box a -> Box a -> Bool #

(>=) :: Box a -> Box a -> Bool #

max :: Box a -> Box a -> Box a #

min :: Box a -> Box a -> 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

Functor Entity Source # 

Methods

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

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

Foldable Entity Source # 

Methods

fold :: Monoid m => Entity m -> m #

foldMap :: Monoid m => (a -> m) -> Entity a -> m #

foldr :: (a -> b -> b) -> b -> Entity a -> b #

foldr' :: (a -> b -> b) -> b -> Entity a -> b #

foldl :: (b -> a -> b) -> b -> Entity a -> b #

foldl' :: (b -> a -> b) -> b -> Entity a -> b #

foldr1 :: (a -> a -> a) -> Entity a -> a #

foldl1 :: (a -> a -> a) -> Entity a -> a #

toList :: Entity a -> [a] #

null :: Entity a -> Bool #

length :: Entity a -> Int #

elem :: Eq a => a -> Entity a -> Bool #

maximum :: Ord a => Entity a -> a #

minimum :: Ord a => Entity a -> a #

sum :: Num a => Entity a -> a #

product :: Num a => Entity a -> a #

Traversable Entity Source # 

Methods

traverse :: Applicative f => (a -> f b) -> Entity a -> f (Entity b) #

sequenceA :: Applicative f => Entity (f a) -> f (Entity a) #

mapM :: Monad m => (a -> m b) -> Entity a -> m (Entity b) #

sequence :: Monad m => Entity (m a) -> m (Entity a) #

Eq s => Eq (Entity s) Source # 

Methods

(==) :: Entity s -> Entity s -> Bool #

(/=) :: Entity s -> Entity s -> Bool #

Ord s => Ord (Entity s) Source # 

Methods

compare :: Entity s -> Entity s -> Ordering #

(<) :: Entity s -> Entity s -> Bool #

(<=) :: Entity s -> Entity s -> Bool #

(>) :: Entity s -> Entity s -> Bool #

(>=) :: Entity s -> Entity s -> Bool #

max :: Entity s -> Entity s -> Entity s #

min :: Entity s -> Entity s -> Entity s #

Show s => Show (Entity s) Source # 

Methods

showsPrec :: Int -> Entity s -> ShowS #

show :: Entity s -> String #

showList :: [Entity s] -> ShowS #

newtype E Source #

E is the knot-tyed version of Entity.

Constructors

E (Entity E) 

Instances

Eq E Source # 

Methods

(==) :: E -> E -> Bool #

(/=) :: E -> E -> Bool #

Show E Source # 

Methods

showsPrec :: Int -> E -> ShowS #

show :: E -> String #

showList :: [E] -> ShowS #

MuRef E Source # 

Associated Types

type DeRef E :: * -> * #

Methods

mapDeRef :: Applicative f => (forall b. (MuRef b, ((* -> *) ~ DeRef E) (DeRef b)) => b -> f u) -> E -> f (DeRef E u) #

type DeRef E Source # 
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

Functor Driver Source # 

Methods

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

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

Foldable Driver Source # 

Methods

fold :: Monoid m => Driver m -> m #

foldMap :: Monoid m => (a -> m) -> Driver a -> m #

foldr :: (a -> b -> b) -> b -> Driver a -> b #

foldr' :: (a -> b -> b) -> b -> Driver a -> b #

foldl :: (b -> a -> b) -> b -> Driver a -> b #

foldl' :: (b -> a -> b) -> b -> Driver a -> b #

foldr1 :: (a -> a -> a) -> Driver a -> a #

foldl1 :: (a -> a -> a) -> Driver a -> a #

toList :: Driver a -> [a] #

null :: Driver a -> Bool #

length :: Driver a -> Int #

elem :: Eq a => a -> Driver a -> Bool #

maximum :: Ord a => Driver a -> a #

minimum :: Ord a => Driver a -> a #

sum :: Num a => Driver a -> a #

product :: Num a => Driver a -> a #

Traversable Driver Source # 

Methods

traverse :: Applicative f => (a -> f b) -> Driver a -> f (Driver b) #

sequenceA :: Applicative f => Driver (f a) -> f (Driver a) #

mapM :: Monad m => (a -> m b) -> Driver a -> m (Driver b) #

sequence :: Monad m => Driver (m a) -> m (Driver a) #

Eq s => Eq (Driver s) Source # 

Methods

(==) :: Driver s -> Driver s -> Bool #

(/=) :: Driver s -> Driver s -> Bool #

Ord s => Ord (Driver s) Source # 

Methods

compare :: Driver s -> Driver s -> Ordering #

(<) :: Driver s -> Driver s -> Bool #

(<=) :: Driver s -> Driver s -> Bool #

(>) :: Driver s -> Driver s -> Bool #

(>=) :: Driver s -> Driver s -> Bool #

max :: Driver s -> Driver s -> Driver s #

min :: Driver s -> Driver s -> Driver s #

Show i => Show (Driver i) Source # 

Methods

showsPrec :: Int -> Driver i -> ShowS #

show :: Driver i -> String #

showList :: [Driver i] -> ShowS #

newtype D a Source #

The D type adds a phantom type to a driver.

Constructors

D 

Fields

Instances

Show (D a) Source # 

Methods

showsPrec :: Int -> D a -> ShowS #

show :: D a -> String #

showList :: [D a] -> ShowS #

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

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) Source # 

Methods

succ :: BitPat w -> BitPat w #

pred :: BitPat w -> BitPat w #

toEnum :: Int -> BitPat w #

fromEnum :: BitPat w -> Int #

enumFrom :: BitPat w -> [BitPat w] #

enumFromThen :: BitPat w -> BitPat w -> [BitPat w] #

enumFromTo :: BitPat w -> BitPat w -> [BitPat w] #

enumFromThenTo :: BitPat w -> BitPat w -> BitPat w -> [BitPat w] #

Eq (BitPat w) Source # 

Methods

(==) :: BitPat w -> BitPat w -> Bool #

(/=) :: BitPat w -> BitPat w -> Bool #

Size w => Integral (BitPat w) Source # 

Methods

quot :: BitPat w -> BitPat w -> BitPat w #

rem :: BitPat w -> BitPat w -> BitPat w #

div :: BitPat w -> BitPat w -> BitPat w #

mod :: BitPat w -> BitPat w -> BitPat w #

quotRem :: BitPat w -> BitPat w -> (BitPat w, BitPat w) #

divMod :: BitPat w -> BitPat w -> (BitPat w, BitPat w) #

toInteger :: BitPat w -> Integer #

Size w => Num (BitPat w) Source # 

Methods

(+) :: BitPat w -> BitPat w -> BitPat w #

(-) :: BitPat w -> BitPat w -> BitPat w #

(*) :: BitPat w -> BitPat w -> BitPat w #

negate :: BitPat w -> BitPat w #

abs :: BitPat w -> BitPat w #

signum :: BitPat w -> BitPat w #

fromInteger :: Integer -> BitPat w #

Ord (BitPat w) Source # 

Methods

compare :: BitPat w -> BitPat w -> Ordering #

(<) :: BitPat w -> BitPat w -> Bool #

(<=) :: BitPat w -> BitPat w -> Bool #

(>) :: BitPat w -> BitPat w -> Bool #

(>=) :: BitPat w -> BitPat w -> Bool #

max :: BitPat w -> BitPat w -> BitPat w #

min :: BitPat w -> BitPat w -> BitPat w #

Size w => Real (BitPat w) Source # 

Methods

toRational :: BitPat w -> Rational #

Show (BitPat w) Source # 

Methods

showsPrec :: Int -> BitPat w -> ShowS #

show :: BitPat w -> String #

showList :: [BitPat w] -> ShowS #

IsString (BitPat w) Source # 

Methods

fromString :: String -> 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

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.

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.

Minimal complete definition

dual

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) Source # 

Methods

dual :: (a -> b) -> (a -> b) -> a -> b Source #

(Dual a, Dual b) => Dual (a, b) Source # 

Methods

dual :: (a, b) -> (a, b) -> (a, b) Source #

Dual (Signal c a) Source # 

Methods

dual :: Signal c a -> Signal c a -> Signal c a Source #

(Dual a, Dual b, Dual c) => Dual (a, b, c) Source # 

Methods

dual :: (a, b, c) -> (a, b, c) -> (a, b, c) Source #

Our version of tuples

data a :> b infixr 5 Source #

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

Constructors

a :> b infixr 5 

Instances

(Eq b, Eq a) => Eq ((:>) a b) Source # 

Methods

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

(/=) :: (a :> b) -> (a :> b) -> Bool #

(Ord b, Ord a) => Ord ((:>) a b) Source # 

Methods

compare :: (a :> b) -> (a :> b) -> Ordering #

(<) :: (a :> b) -> (a :> b) -> Bool #

(<=) :: (a :> b) -> (a :> b) -> Bool #

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

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

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

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

(Read b, Read a) => Read ((:>) a b) Source # 

Methods

readsPrec :: Int -> ReadS (a :> b) #

readList :: ReadS [a :> b] #

readPrec :: ReadPrec (a :> b) #

readListPrec :: ReadPrec [a :> b] #

(Show b, Show a) => Show ((:>) a b) Source # 

Methods

showsPrec :: Int -> (a :> b) -> ShowS #

show :: (a :> b) -> String #

showList :: [a :> b] -> ShowS #

(Unit a, Unit b) => Unit ((:>) a b) Source # 

Methods

unit :: a :> b Source #

type W ((:>) a b) Source # 
type W ((:>) a b) = ADD (W a) (W b)
data X ((:>) a b) Source # 
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