chalmers-lava2000-1.6.1: Hardware description EDSL

Safe HaskellNone
LanguageHaskell98

Lava.Generic

Documentation

data Struct a Source #

Constructors

Compound [Struct a] 
Object a 

Instances

Functor Struct Source # 

Methods

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

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

Sequent Struct Source # 

Methods

sequent :: Monad m => Struct (m a) -> m (Struct a) Source #

Eq a => Eq (Struct a) Source # 

Methods

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

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

Show a => Show (Struct a) Source # 

Methods

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

show :: Struct a -> String #

showList :: [Struct a] -> ShowS #

flatten :: Struct a -> [a] Source #

class Generic a where Source #

Minimal complete definition

struct, construct

Instances

Generic () Source # 
Generic Symbol Source # 
Generic a => Generic [a] Source # 
Generic (Signal a) Source # 
(Generic a, Generic b) => Generic (a, b) Source # 

Methods

struct :: (a, b) -> Struct Symbol Source #

construct :: Struct Symbol -> (a, b) Source #

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

Methods

struct :: (a, b, c) -> Struct Symbol Source #

construct :: Struct Symbol -> (a, b, c) Source #

(Generic a, Generic b, Generic c, Generic d) => Generic (a, b, c, d) Source # 

Methods

struct :: (a, b, c, d) -> Struct Symbol Source #

construct :: Struct Symbol -> (a, b, c, d) Source #

(Generic a, Generic b, Generic c, Generic d, Generic e) => Generic (a, b, c, d, e) Source # 

Methods

struct :: (a, b, c, d, e) -> Struct Symbol Source #

construct :: Struct Symbol -> (a, b, c, d, e) Source #

(Generic a, Generic b, Generic c, Generic d, Generic e, Generic f) => Generic (a, b, c, d, e, f) Source # 

Methods

struct :: (a, b, c, d, e, f) -> Struct Symbol Source #

construct :: Struct Symbol -> (a, b, c, d, e, f) Source #

(Generic a, Generic b, Generic c, Generic d, Generic e, Generic f, Generic g) => Generic (a, b, c, d, e, f, g) Source # 

Methods

struct :: (a, b, c, d, e, f, g) -> Struct Symbol Source #

construct :: Struct Symbol -> (a, b, c, d, e, f, g) Source #

equal :: Generic a => (a, a) -> Signal Bool Source #

delay :: Generic a => a -> a -> a Source #

zeroify :: Generic a => a -> a Source #

symbolize :: Generic a => String -> a -> a Source #

class Generic a => Constructive a where Source #

Minimal complete definition

zero, var, random

Methods

zero :: a Source #

var :: String -> a Source #

random :: Rnd -> a Source #

Instances

Constructive () Source # 

Methods

zero :: () Source #

var :: String -> () Source #

random :: Rnd -> () Source #

ConstructiveSig a => Constructive (Signal a) Source # 
(Constructive a, Constructive b) => Constructive (a, b) Source # 

Methods

zero :: (a, b) Source #

var :: String -> (a, b) Source #

random :: Rnd -> (a, b) Source #

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

Methods

zero :: (a, b, c) Source #

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

random :: Rnd -> (a, b, c) Source #

(Constructive a, Constructive b, Constructive c, Constructive d) => Constructive (a, b, c, d) Source # 

Methods

zero :: (a, b, c, d) Source #

var :: String -> (a, b, c, d) Source #

random :: Rnd -> (a, b, c, d) Source #

(Constructive a, Constructive b, Constructive c, Constructive d, Constructive e) => Constructive (a, b, c, d, e) Source # 

Methods

zero :: (a, b, c, d, e) Source #

var :: String -> (a, b, c, d, e) Source #

random :: Rnd -> (a, b, c, d, e) Source #

(Constructive a, Constructive b, Constructive c, Constructive d, Constructive e, Constructive f) => Constructive (a, b, c, d, e, f) Source # 

Methods

zero :: (a, b, c, d, e, f) Source #

var :: String -> (a, b, c, d, e, f) Source #

random :: Rnd -> (a, b, c, d, e, f) Source #

(Constructive a, Constructive b, Constructive c, Constructive d, Constructive e, Constructive f, Constructive g) => Constructive (a, b, c, d, e, f, g) Source # 

Methods

zero :: (a, b, c, d, e, f, g) Source #

var :: String -> (a, b, c, d, e, f, g) Source #

random :: Rnd -> (a, b, c, d, e, f, g) Source #

class ConstructiveSig a => FiniteSig a where Source #

Minimal complete definition

domainSig

Methods

domainSig :: [Signal a] Source #

Instances

class Constructive a => Finite a where Source #

Minimal complete definition

domain

Methods

domain :: [a] Source #

Instances

Finite () Source # 

Methods

domain :: [()] Source #

FiniteSig a => Finite (Signal a) Source # 

Methods

domain :: [Signal a] Source #

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

Methods

domain :: [(a, b)] Source #

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

Methods

domain :: [(a, b, c)] Source #

(Finite a, Finite b, Finite c, Finite d) => Finite (a, b, c, d) Source # 

Methods

domain :: [(a, b, c, d)] Source #

(Finite a, Finite b, Finite c, Finite d, Finite e) => Finite (a, b, c, d, e) Source # 

Methods

domain :: [(a, b, c, d, e)] Source #

(Finite a, Finite b, Finite c, Finite d, Finite e, Finite f) => Finite (a, b, c, d, e, f) Source # 

Methods

domain :: [(a, b, c, d, e, f)] Source #

(Finite a, Finite b, Finite c, Finite d, Finite e, Finite f, Finite g) => Finite (a, b, c, d, e, f, g) Source # 

Methods

domain :: [(a, b, c, d, e, f, g)] Source #

domainList :: Finite a => Int -> [[a]] Source #

class Choice a where Source #

Minimal complete definition

ifThenElse

Methods

ifThenElse :: Signal Bool -> (a, a) -> a Source #

Instances

Choice () Source # 

Methods

ifThenElse :: Signal Bool -> ((), ()) -> () Source #

Choice Symbol Source # 
Choice a => Choice [a] Source # 

Methods

ifThenElse :: Signal Bool -> ([a], [a]) -> [a] Source #

Choice (Signal a) Source # 

Methods

ifThenElse :: Signal Bool -> (Signal a, Signal a) -> Signal a Source #

Choice b => Choice (a -> b) Source # 

Methods

ifThenElse :: Signal Bool -> (a -> b, a -> b) -> a -> b Source #

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

Methods

ifThenElse :: Signal Bool -> ((a, b), (a, b)) -> (a, b) Source #

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

Methods

ifThenElse :: Signal Bool -> ((a, b, c), (a, b, c)) -> (a, b, c) Source #

(Choice a, Choice b, Choice c, Choice d) => Choice (a, b, c, d) Source # 

Methods

ifThenElse :: Signal Bool -> ((a, b, c, d), (a, b, c, d)) -> (a, b, c, d) Source #

(Choice a, Choice b, Choice c, Choice d, Choice e) => Choice (a, b, c, d, e) Source # 

Methods

ifThenElse :: Signal Bool -> ((a, b, c, d, e), (a, b, c, d, e)) -> (a, b, c, d, e) Source #

(Choice a, Choice b, Choice c, Choice d, Choice e, Choice f) => Choice (a, b, c, d, e, f) Source # 

Methods

ifThenElse :: Signal Bool -> ((a, b, c, d, e, f), (a, b, c, d, e, f)) -> (a, b, c, d, e, f) Source #

(Choice a, Choice b, Choice c, Choice d, Choice e, Choice f, Choice g) => Choice (a, b, c, d, e, f, g) Source # 

Methods

ifThenElse :: Signal Bool -> ((a, b, c, d, e, f, g), (a, b, c, d, e, f, g)) -> (a, b, c, d, e, f, g) Source #

mux :: Choice a => (Signal Bool, (a, a)) -> a Source #

strongZipWith :: (a -> b -> c) -> [a] -> [b] -> [c] Source #

lazyZipWith :: (a -> b -> c) -> [a] -> [b] -> [c] Source #