vector-heterogenous-0.1.1: A type-safe library for vectors whose elements can be of any type, or any type satisfying some constraints

Safe HaskellNone

Data.Vector.Heterogenous.HList

Contents

Synopsis

Heterogenous List

data HList whereSource

The heterogenous list

Constructors

HNil :: HList `[]` 
::: :: t -> HList ts -> HList (t : ts) 

Instances

(Eq x, Eq (HList xs)) => Eq (HList (: * x xs)) 
Eq (HList ([] *)) 
(Ord x, Ord (HList xs)) => Ord (HList (: * x xs)) 
Ord (HList ([] *)) 
(Show x, Show (HList xs)) => Show (HList (: * x xs)) 
Show (HList ([] *)) 
(Monoid x, Monoid (HList xs)) => Monoid (HList (: * x xs)) 
Monoid (HList ([] *)) 
HLength (HList xs) => HLength (HList (: * x xs)) 
HLength (HList ([] *)) 
(ConstraintBox box x, Downcast (HList xs) box) => Downcast (HList (: * x xs)) box 
Downcast (HList ([] *)) a 
HList2List (HList xs) a => HList2List (HList (: * a xs)) a 
HList2List (HList ([] *)) a 
HTake1 (Nat1Box n) (HList xs1) (HList xs2) => HTake1 (Nat1Box (Succ n)) (HList (: * x xs1)) (HList (: * x xs2)) 
HTake1 (Nat1Box Zero) (HList xs1) (HList ([] *)) 
HDrop1 (Nat1Box n) (HList xs1) (HList xs2) => HDrop1 (Nat1Box (Succ n)) (HList (: * x xs1)) (HList xs2) 
HDrop1 (Nat1Box Zero) (HList xs1) (HList xs1) 

class HLength xs whereSource

Used only for the HList class to determine its length

Methods

hlength :: xs -> IntSource

Instances

HLength (HList xs) => HLength (HList (: * x xs)) 
HLength (HList ([] *)) 

class List2HList x xs whereSource

For construction from lists

Methods

list2hlist :: [x] -> HList (x : xs)Source

Instances

List2HList x ([] *) 
List2HList x xs => List2HList x (: * x xs) 

class HList2List xs a | xs -> a whereSource

For converting into a list

Methods

hlist2list :: xs -> [a]Source

Instances

HList2List (HList xs) a => HList2List (HList (: * a xs)) a 
HList2List (HList ([] *)) a 

class HTake1 n xs1 xs2 | n xs1 -> xs2 whereSource

Equivalent to prelude's take

Methods

htake1 :: n -> xs1 -> xs2Source

Instances

HTake1 (Nat1Box n) (HList xs1) (HList xs2) => HTake1 (Nat1Box (Succ n)) (HList (: * x xs1)) (HList (: * x xs2)) 
HTake1 (Nat1Box Zero) (HList xs1) (HList ([] *)) 

class HDrop1 n xs1 xs2 | n xs1 -> xs2 whereSource

Equivalent to prelude's drop

Methods

hdrop1 :: n -> xs1 -> xs2Source

Instances

HDrop1 (Nat1Box n) (HList xs1) (HList xs2) => HDrop1 (Nat1Box (Succ n)) (HList (: * x xs1)) (HList xs2) 
HDrop1 (Nat1Box Zero) (HList xs1) (HList xs1) 

Downcasting

class ConstraintBox box a whereSource

Methods

box :: a -> boxSource

unsafeUnbox :: box -> aSource

Instances

class Downcast h box whereSource

Methods

downcast :: h -> [box]Source

downcastAs :: (a -> box) -> h -> [box]Source

Instances

(ConstraintBox box x, Downcast (HList xs) box) => Downcast (HList (: * x xs)) box 
Downcast (HList ([] *)) a 

Boxes

data ShowBox Source

Use this box unless you know for certain that your types won't have a show instance.

Constructors

forall a . Show a => ShowBox !a 

data AnyBox Source

Most generic box, can be used on any type.

Constructors

forall a . AnyBox !a 

Type functions

HList

type family HCons x xs :: *Source

type family UnHList xs :: [a]Source

type family HAppend xs ys :: *Source

Type Lists

type family Distribute xs t :: [b]Source

type family Replicate n x :: [a]Source

type family Map f xs :: [a]Source

type family Reverse xs :: [a]Source

type family xs :! i :: aSource

type family Index xs i :: aSource

type family xs (++) ys :: [a]Source

type family f ($) a :: bSource

type family Concat xs :: [a]Source

type family Length xs :: NatSource

type family Length1 xs :: Nat1Source

Type Nats

data Nat1 Source

Constructors

Zero 
Succ Nat1 

data Nat1Box n Source

Constructors

Nat1Box 

Instances

HTake1 (Nat1Box n) (HList xs1) (HList xs2) => HTake1 (Nat1Box (Succ n)) (HList (: * x xs1)) (HList (: * x xs2)) 
HTake1 (Nat1Box Zero) (HList xs1) (HList ([] *)) 
HDrop1 (Nat1Box n) (HList xs1) (HList xs2) => HDrop1 (Nat1Box (Succ n)) (HList (: * x xs1)) (HList xs2) 
HDrop1 (Nat1Box Zero) (HList xs1) (HList xs1) 

type family ToNat1 n :: Nat1Source

type family FromNat1 n :: NatSource