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

Safe HaskellNone
LanguageHaskell2010

Language.KansasLava.Rep

Contents

Description

KansasLava is designed for generating hardware circuits. This module provides a Rep class that allows us to model, in the shallow embedding of KL, two important features of hardware signals. First, all signals must have some static width, as they will be synthsized to a collection of hardware wires. Second, a value represented by a signal may be unknown, in part or in whole.

Synopsis

Documentation

allOkayRep :: Size w => Matrix w (X Bool) -> Maybe (Matrix w Bool) Source #

Check to see if all bits in a bitvector (represented as a Matrix) are valid. Returns Nothing if any of the bits are unknown.

data IntegerWidth Source #

Integers are unbounded in size. We use the type IntegerWidth as the associated type representing this size in the instance of Rep for Integers.

Constructors

IntegerWidth 

log2 :: Integral a => a -> a Source #

Calculate the base-2 logrithim of a integral value.

sizedFromRepToIntegral :: forall w. (Rep w, Integral w, Size w) => RepValue -> X w Source #

This is a version of fromRepToIntegral that check to see if the result is inside the size bounds.

class Rep w where Source #

A 'Rep a' is an a value that we Represent, aka we can push it over a wire. The general idea is that instances of Rep should have a width (for the corresponding bitvector representation) and that Rep instances should be able to represent the "unknown" -- X -- value. For example, Bools can be represented with one bit, and the inclusion of the unknown X value corresponds to three-valued logic.

Minimal complete definition

unX, optX, toRep, fromRep, repType

Associated Types

type W w Source #

the width of the represented value, as a type-level number.

data X w Source #

X are lifted inputs to this wire.

Methods

unX :: X w -> Maybe w Source #

check for bad things.

optX :: Maybe w -> X w Source #

and, put the good or bad things back.

toRep :: X w -> RepValue Source #

convert to binary (rep) format

fromRep :: RepValue -> X w Source #

convert from binary (rep) format

repType :: Witness w -> Type Source #

Each wire has a known type.

showRep :: X w -> String Source #

class (Size (W a), Eq a, Rep a) => BitRep a where Source #

Bitrep is list of values, and their bitwise representation. It is used to derive (via Template Haskell) the Rep for user Haskell datatypes.

Minimal complete definition

bitRep

Methods

bitRep :: [(a, BitPat (W a))] Source #

allReps :: Rep w => Witness w -> [RepValue] Source #

Given a witness of a representable type, generate all (2^n) possible values of that type.

repWidth :: Rep w => Witness w -> Int Source #

Figure out the width in bits of a type.

unknownRepValue :: Rep w => Witness w -> RepValue Source #

unknownRepValue returns a RepValue that is completely filled with X.

pureX :: Rep w => w -> X w Source #

pureX lifts a value to a (known) representable value.

unknownX :: forall w. Rep w => X w Source #

unknownX is an unknown value of every representable type.

liftX :: (Rep a, Rep b) => (a -> b) -> X a -> X b Source #

liftX converts a function over values to a function over possibly unknown values.

showRepDefault :: forall w. (Show w, Rep w) => X w -> String Source #

showRepDefault will print a Representable value, with "?" for unknown. This is not wired into the class because of the extra Show requirement.

toRepFromIntegral :: forall v. (Rep v, Integral v) => X v -> RepValue Source #

Convert an integral value to a RepValue -- its bitvector representation.

fromRepToIntegral :: forall v. (Rep v, Integral v) => RepValue -> X v Source #

Convert a RepValue representing an integral value to a representable value of that integral type.

fromRepToInteger :: RepValue -> Integer Source #

fromRepToInteger always a positve number, unknowns defin

cmpRep :: Rep a => X a -> X a -> Bool Source #

Compare a golden value with a generated value.

bitRepEnum :: (Rep a, Enum a, Bounded a, Size (W a)) => [(a, BitPat (W a))] Source #

Helper for generating the bit pattern mappings.

bitRepToRep :: forall w. (BitRep w, Ord w) => X w -> RepValue Source #

bitRepToRep' :: forall w. (BitRep w, Ord w) => Map w RepValue -> X w -> RepValue Source #

bitRepFromRep :: forall w. (Ord w, BitRep w) => RepValue -> X w Source #

bitRepFromRep' :: forall w. (Ord w, BitRep w) => Map RepValue w -> RepValue -> X w Source #

bitRepMap :: forall w. (BitRep w, Ord w) => Map RepValue w Source #

Orphan instances

Rep Bool Source # 
Rep Int Source # 

Associated Types

type W Int :: * Source #

data X Int :: * Source #

Rep Integer Source # 
Rep Word8 Source # 
Rep Word32 Source # 
Rep () Source # 

Associated Types

type W () :: * Source #

data X () :: * Source #

Methods

unX :: X () -> Maybe () Source #

optX :: Maybe () -> X () Source #

toRep :: X () -> RepValue Source #

fromRep :: RepValue -> X () Source #

repType :: Witness () -> Type Source #

showRep :: X () -> String Source #

Rep X0 Source # 

Associated Types

type W X0 :: * Source #

data X X0 :: * Source #

Rep a => Rep (Maybe a) Source # 

Associated Types

type W (Maybe a) :: * Source #

data X (Maybe a) :: * Source #

Size ix => Rep (Unsigned ix) Source # 

Associated Types

type W (Unsigned ix) :: * Source #

data X (Unsigned ix) :: * Source #

Size ix => Rep (Signed ix) Source # 

Associated Types

type W (Signed ix) :: * Source #

data X (Signed ix) :: * Source #

Methods

unX :: X (Signed ix) -> Maybe (Signed ix) Source #

optX :: Maybe (Signed ix) -> X (Signed ix) Source #

toRep :: X (Signed ix) -> RepValue Source #

fromRep :: RepValue -> X (Signed ix) Source #

repType :: Witness (Signed ix) -> Type Source #

showRep :: X (Signed ix) -> String Source #

(Integral x, Size x) => Rep (X0_ x) Source # 

Associated Types

type W (X0_ x) :: * Source #

data X (X0_ x) :: * Source #

Methods

unX :: X (X0_ x) -> Maybe (X0_ x) Source #

optX :: Maybe (X0_ x) -> X (X0_ x) Source #

toRep :: X (X0_ x) -> RepValue Source #

fromRep :: RepValue -> X (X0_ x) Source #

repType :: Witness (X0_ x) -> Type Source #

showRep :: X (X0_ x) -> String Source #

(Integral x, Size x) => Rep (X1_ x) Source # 

Associated Types

type W (X1_ x) :: * Source #

data X (X1_ x) :: * Source #

Methods

unX :: X (X1_ x) -> Maybe (X1_ x) Source #

optX :: Maybe (X1_ x) -> X (X1_ x) Source #

toRep :: X (X1_ x) -> RepValue Source #

fromRep :: RepValue -> X (X1_ x) Source #

repType :: Witness (X1_ x) -> Type Source #

showRep :: X (X1_ x) -> String Source #

(Size ix, Rep a, Rep ix) => Rep (ix -> a) Source # 

Associated Types

type W (ix -> a) :: * Source #

data X (ix -> a) :: * Source #

Methods

unX :: X (ix -> a) -> Maybe (ix -> a) Source #

optX :: Maybe (ix -> a) -> X (ix -> a) Source #

toRep :: X (ix -> a) -> RepValue Source #

fromRep :: RepValue -> X (ix -> a) Source #

repType :: Witness (ix -> a) -> Type Source #

showRep :: X (ix -> a) -> String Source #

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

Associated Types

type W (a, b) :: * Source #

data X (a, b) :: * Source #

Methods

unX :: X (a, b) -> Maybe (a, b) Source #

optX :: Maybe (a, b) -> X (a, b) Source #

toRep :: X (a, b) -> RepValue Source #

fromRep :: RepValue -> X (a, b) Source #

repType :: Witness (a, b) -> Type Source #

showRep :: X (a, b) -> String Source #

(Enum ix, Size m, Size ix) => Rep (Sampled m ix) Source # 

Associated Types

type W (Sampled m ix) :: * Source #

data X (Sampled m ix) :: * Source #

Methods

unX :: X (Sampled m ix) -> Maybe (Sampled m ix) Source #

optX :: Maybe (Sampled m ix) -> X (Sampled m ix) Source #

toRep :: X (Sampled m ix) -> RepValue Source #

fromRep :: RepValue -> X (Sampled m ix) Source #

repType :: Witness (Sampled m ix) -> Type Source #

showRep :: X (Sampled m ix) -> String Source #

(Size ix, Rep a) => Rep (Matrix ix a) Source # 

Associated Types

type W (Matrix ix a) :: * Source #

data X (Matrix ix a) :: * Source #

Methods

unX :: X (Matrix ix a) -> Maybe (Matrix ix a) Source #

optX :: Maybe (Matrix ix a) -> X (Matrix ix a) Source #

toRep :: X (Matrix ix a) -> RepValue Source #

fromRep :: RepValue -> X (Matrix ix a) Source #

repType :: Witness (Matrix ix a) -> Type Source #

showRep :: X (Matrix ix a) -> String Source #

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

Associated Types

type W (a :> b) :: * Source #

data X (a :> b) :: * Source #

Methods

unX :: X (a :> b) -> Maybe (a :> b) Source #

optX :: Maybe (a :> b) -> X (a :> b) Source #

toRep :: X (a :> b) -> RepValue Source #

fromRep :: RepValue -> X (a :> b) Source #

repType :: Witness (a :> b) -> Type Source #

showRep :: X (a :> b) -> String Source #

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

Associated Types

type W (a, b, c) :: * Source #

data X (a, b, c) :: * Source #

Methods

unX :: X (a, b, c) -> Maybe (a, b, c) Source #

optX :: Maybe (a, b, c) -> X (a, b, c) Source #

toRep :: X (a, b, c) -> RepValue Source #

fromRep :: RepValue -> X (a, b, c) Source #

repType :: Witness (a, b, c) -> Type Source #

showRep :: X (a, b, c) -> String Source #