york-lava-0.1: A library for circuit description.

Lava.Vector

Description

Modest library for statically-typed sized vectors, inspired by Oleg Kiselyov's "Number-Parameterized Types", The Monad.Reader, Issue 5. Type synonyms N0 to N255 exported along with zero (Z) and successor (S). Values n0 to n255 with types N0 to N255 are also exported.

Documentation

(+>) :: a -> Vec n a -> Vec (S n) aSource

(<+) :: Vec n a -> a -> Vec (S n) aSource

velems :: Vec n a -> [a]Source

vsize :: Vec n a -> nSource

sized :: N n => (Int -> Vec n a) -> Vec n aSource

vec :: N n => [a] -> Vec n aSource

vecOf :: N n => a -> Vec n aSource

ofSize :: Vec n a -> n -> Vec n aSource

sameSize :: Vec n a -> Vec n a -> Vec n aSource

vecn :: N n => n -> [a] -> Vec n aSource

vextend :: N m => a -> Vec n a -> Vec m aSource

vsingle :: a -> Vec N1 aSource

vhead :: Vec (S n) a -> aSource

vtail :: Vec (S n) a -> Vec n aSource

vlast :: Vec (S n) a -> aSource

vinit :: Vec (S n) a -> Vec n aSource

vmap :: (a -> b) -> Vec n a -> Vec n bSource

vzipWith :: (a -> b -> c) -> Vec n a -> Vec n b -> Vec n cSource

vreverse :: Vec n a -> Vec n aSource

vfoldl :: (a -> b -> a) -> a -> Vec n b -> aSource

vfoldr :: (a -> b -> b) -> b -> Vec n a -> bSource

vmapAccumL :: (a -> b -> (a, c)) -> a -> Vec n b -> (a, Vec n c)Source

vmapAccumR :: (a -> b -> (a, c)) -> a -> Vec n b -> (a, Vec n c)Source

(<++>) :: Add n m o => Vec n a -> Vec m a -> Vec o aSource

vconcat :: Mul n m o => Vec n (Vec m a) -> Vec o aSource

vat :: (N n, Less n m) => Vec m a -> n -> aSource

vtake :: N n => n -> Vec m a -> Vec n aSource

vdrop :: (N n, Add n o m) => n -> Vec m a -> Vec o aSource

vsplitAt :: (N m, Add m n o) => m -> Vec o a -> (Vec m a, Vec n a)Source

vgroup :: (N n, Mul n o m) => n -> Vec m a -> Vec o (Vec n a)Source

vtranspose :: Vec n (Vec m a) -> Vec m (Vec n a)Source

vshr :: a -> Vec n a -> Vec n aSource

vshl :: Vec n a -> a -> Vec n aSource

vreplicate :: N n => n -> a -> Vec n aSource

vrepeat :: N n => a -> Vec n aSource

vsequence :: Monad m => Vec n (m a) -> m (Vec n a)Source

vrigid :: N n => Vec n a -> Vec n aSource

type N0 = ZSource

type N1 = S N0Source

type N2 = S N1Source

type N3 = S N2Source

type N4 = S N3Source

type N5 = S N4Source

type N6 = S N5Source

type N7 = S N6Source

type N8 = S N7Source

type N9 = S N8Source

type N10 = S N9Source

type N11 = S N10Source

type N12 = S N11Source

type N13 = S N12Source

type N14 = S N13Source

type N15 = S N14Source

type N16 = S N15Source

type N17 = S N16Source

type N18 = S N17Source

type N19 = S N18Source

type N20 = S N19Source

type N21 = S N20Source

type N22 = S N21Source

type N23 = S N22Source

type N24 = S N23Source

type N25 = S N24Source

type N26 = S N25Source

type N27 = S N26Source

type N28 = S N27Source

type N29 = S N28Source

type N30 = S N29Source

type N31 = S N30Source

type N32 = S N31Source

type N33 = S N32Source

type N34 = S N33Source

type N35 = S N34Source

type N36 = S N35Source

type N37 = S N36Source

type N38 = S N37Source

type N39 = S N38Source

type N40 = S N39Source

type N41 = S N40Source

type N42 = S N41Source

type N43 = S N42Source

type N44 = S N43Source

type N45 = S N44Source

type N46 = S N45Source

type N47 = S N46Source

type N48 = S N47Source

type N49 = S N48Source

type N50 = S N49Source

type N51 = S N50Source

type N52 = S N51Source

type N53 = S N52Source

type N54 = S N53Source

type N55 = S N54Source

type N56 = S N55Source

type N57 = S N56Source

type N58 = S N57Source

type N59 = S N58Source

type N60 = S N59Source

type N61 = S N60Source

type N62 = S N61Source

type N63 = S N62Source

type N64 = S N63Source

type N65 = S N64Source

type N66 = S N65Source

type N67 = S N66Source

type N68 = S N67Source

type N69 = S N68Source

type N70 = S N69Source

type N71 = S N70Source

type N72 = S N71Source

type N73 = S N72Source

type N74 = S N73Source

type N75 = S N74Source

type N76 = S N75Source

type N77 = S N76Source

type N78 = S N77Source

type N79 = S N78Source

type N80 = S N79Source

type N81 = S N80Source

type N82 = S N81Source

type N83 = S N82Source

type N84 = S N83Source

type N85 = S N84Source

type N86 = S N85Source

type N87 = S N86Source

type N88 = S N87Source

type N89 = S N88Source

type N90 = S N89Source

type N91 = S N90Source

type N92 = S N91Source

type N93 = S N92Source

type N94 = S N93Source

type N95 = S N94Source

type N96 = S N95Source

type N97 = S N96Source

type N98 = S N97Source

type N99 = S N98Source

data Z Source

Instances

N Z 
Mul Z b Z 
Add Z b b 
Less Z (S a) 

data S a Source

Instances

Less Z (S a) 
N a => N (S a) 
(Mul a b x, Add x b c) => Mul (S a) b c 
Add a b c => Add (S a) b (S c) 
Less a b => Less (S a) (S b) 

newtype Vec n a Source

Constructors

Vec [a] 

Instances

Functor (Vec n) 
Eq (Vec n Bit) 
N n => Num (Vec n Bit) 
Show a => Show (Vec n a) 
Generic a => Generic (Vec n a) 
Ordered (Vec n Bit) 

class N a whereSource

Methods

value :: a -> IntSource

Instances

N Z 
N a => N (S a) 

class Add a b c | a b -> cSource

Instances

Add Z b b 
Add a b c => Add (S a) b (S c) 

class Mul a b c | a b -> cSource

Instances

Mul Z b Z 
(Mul a b x, Add x b c) => Mul (S a) b c 

class Less a b Source

Instances

Less Z (S a) 
Less a b => Less (S a) (S b)