vec-0.4: Vec: length-indexed (sized) list
Safe HaskellSafe
LanguageHaskell2010

Data.Vec.DataFamily.SpineStrict.Pigeonhole

Synopsis

Documentation

class Pigeonhole f where Source #

Generic pigeonholes.

Examples:

>>> from (Identity 'a')
'a' ::: VNil
>>> data Values a = Values a a a deriving (Generic1)
>>> instance Pigeonhole Values
>>> from (Values 1 2 3)
1 ::: 2 ::: 3 ::: VNil

Minimal complete definition

Nothing

Associated Types

type PigeonholeSize f :: Nat Source #

The size of a pigeonhole

Methods

from :: f x -> Vec (PigeonholeSize f) x Source #

Converts a value to vector

default from :: (Generic1 f, GFrom f, PigeonholeSize f ~ GPigeonholeSize f) => f x -> Vec (PigeonholeSize f) x Source #

to :: Vec (PigeonholeSize f) x -> f x Source #

Converts back from vector.

default to :: (Generic1 f, GTo f, PigeonholeSize f ~ GPigeonholeSize f) => Vec (PigeonholeSize f) x -> f x Source #

Instances

Instances details
Pigeonhole Identity Source #

Identity x ~ x ^ 1

Instance details

Defined in Data.Vec.DataFamily.SpineStrict.Pigeonhole

Associated Types

type PigeonholeSize Identity :: Nat Source #

Pigeonhole (Proxy :: Type -> Type) Source #

Proxy x ~ x ^ 0

Instance details

Defined in Data.Vec.DataFamily.SpineStrict.Pigeonhole

Associated Types

type PigeonholeSize Proxy :: Nat Source #

(Pigeonhole f, Pigeonhole g, SNatI (PigeonholeSize f)) => Pigeonhole (Product f g) Source #

Product f g x ~ x ^ (size f + size g)

Instance details

Defined in Data.Vec.DataFamily.SpineStrict.Pigeonhole

Associated Types

type PigeonholeSize (Product f g) :: Nat Source #

Methods

from :: Product f g x -> Vec (PigeonholeSize (Product f g)) x Source #

to :: Vec (PigeonholeSize (Product f g)) x -> Product f g x Source #

Representable

gindex :: (Generic i, GFrom i, Generic1 f, GFrom f, GEnumSize i ~ GPigeonholeSize f, SNatI (GPigeonholeSize f)) => f a -> i -> a Source #

Index.

>>> gindex (Identity 'y') (Proxy :: Proxy Int)
'y'
>>> data Key = Key1 | Key2 | Key3 deriving (Generic)
>>> data Values a = Values a a a deriving (Generic1)
>>> gindex (Values 'a' 'b' 'c') Key2
'b'

gtabulate :: (Generic i, GTo i, Generic1 f, GTo f, GEnumSize i ~ GPigeonholeSize f, SNatI (GPigeonholeSize f)) => (i -> a) -> f a Source #

Tabulate.

>>> gtabulate (\() -> 'x') :: Identity Char
Identity 'x'
>>> gtabulate absurd :: Proxy Integer
Proxy
>>> gtabulate absurd :: Proxy Integer
Proxy

gix :: (Generic i, GFrom i, Generic1 t, GTo t, GFrom t, GEnumSize i ~ GPigeonholeSize t, SNatI (GPigeonholeSize t), Functor f) => i -> (a -> f a) -> t a -> f (t a) Source #

A lens. i -> Lens' (t a) a

>>> Lens.view (gix ()) (Identity 'x')
'x'
>>> Lens.over (gix ()) toUpper (Identity 'x')
Identity 'X'

Traversable with index

gtraverse :: (Generic1 t, GFrom t, GTo t, SNatI (GPigeonholeSize t), Applicative f) => (a -> f b) -> t a -> f (t b) Source #

Generic traverse.

Don't use, rather use DeriveTraversable

gitraverse :: (Generic i, GTo i, Generic1 t, GFrom t, GTo t, GEnumSize i ~ GPigeonholeSize t, SNatI (GPigeonholeSize t), Applicative f) => (i -> a -> f b) -> t a -> f (t b) Source #

Traverse with index.

>>> data Key = Key1 | Key2 | Key3 deriving (Show, Generic)
>>> data Values a = Values a a a deriving (Generic1)
>>> gitraverse (\i a -> Const [(i :: Key, a)]) (Values 'a' 'b' 'c')
Const [(Key1,'a'),(Key2,'b'),(Key3,'c')]

Generic implementation

gfrom :: (Generic1 c, GFrom c) => c a -> Vec (GPigeonholeSize c) a Source #

Generic version of from.

type GFrom c = GFromRep1 (Rep1 c) Source #

Constraint for the class that computes gfrom.

gto :: forall c a. (Generic1 c, GTo c) => Vec (GPigeonholeSize c) a -> c a Source #

Generic version of to.

type GTo c = GToRep1 (Rep1 c) Source #

Constraint for the class that computes gto.

type GPigeonholeSize c = PigeonholeSizeRep (Rep1 c) Nat0 Source #

Compute the size from the type.