RepLib-0.2.1: Generic programming library with representation typesSource codeContentsIndex
Data.RepLib.RepAux
Portabilitynon-portable
Stabilityexperimental
Maintainersweirich@cis.upenn.edu
Contents
Casting operations
Operations for heterogeneous lists
SYB style operations (Rep)
SYB style operations (Rep1)
SYB Reloaded
Description
Auxiliary operations to aid in the definition of type-indexed functions
Synopsis
compR :: R a -> R b -> Bool
cast :: forall a b. (Rep a, Rep b) => a -> Maybe b
castR :: R a -> R b -> a -> Maybe b
gcast :: forall a b c. (Rep a, Rep b) => c a -> Maybe (c b)
gcastR :: forall a b c. R a -> R b -> c a -> Maybe (c b)
findCon :: [Con ctx a] -> a -> Val ctx a
data Val ctx a = forall l . Val (Emb l a) (MTup ctx l) l
foldl_l :: (forall a. Rep a => ctx a -> b -> a -> b) -> b -> MTup ctx l -> l -> b
foldr_l :: (forall a. Rep a => ctx a -> a -> b -> b) -> b -> MTup ctx l -> l -> b
map_l :: (forall a. Rep a => ctx a -> a -> a) -> MTup ctx l -> l -> l
mapQ_l :: (forall a. Rep a => ctx a -> a -> r) -> MTup ctx l -> l -> [r]
mapM_l :: Monad m => (forall a. Rep a => ctx a -> a -> m a) -> MTup ctx l -> l -> m l
fromTup :: (forall a. Rep a => ctx a -> a) -> MTup ctx l -> l
fromTupM :: Monad m => (forall a. Rep a => ctx a -> m a) -> MTup ctx l -> m l
toList :: (forall a. Rep a => ctx a -> b) -> MTup ctx l -> [b]
type Traversal = forall a. Rep a => a -> a
type Query r = forall a. Rep a => a -> r
type MapM m = forall a. Rep a => a -> m a
gmapT :: forall a. Rep a => Traversal -> a -> a
gmapQ :: forall a r. Rep a => Query r -> a -> [r]
gmapM :: forall a m. (Rep a, Monad m) => MapM m -> a -> m a
type Traversal1 ctx = forall a. Rep a => ctx a -> a -> a
type Query1 ctx r = forall a. Rep a => ctx a -> a -> r
type MapM1 ctx m = forall a. Rep a => ctx a -> a -> m a
gmapT1 :: forall a ctx. Rep1 ctx a => Traversal1 ctx -> a -> a
gmapQ1 :: forall a ctx r. Rep1 ctx a => Query1 ctx r -> a -> [r]
gmapM1 :: forall a ctx m. (Rep1 ctx a, Monad m) => MapM1 ctx m -> a -> m a
data Typed a = a ::: (R a)
data Spine a where
Constr :: a -> Spine a
:<> :: Spine (a -> b) -> Typed a -> Spine b
toSpine :: Rep a => a -> Spine a
fromSpine :: Spine a -> a
Casting operations
compR :: R a -> R b -> BoolSource
Determine if two reps are for the same type
cast :: forall a b. (Rep a, Rep b) => a -> Maybe bSource
The type-safe cast operation, implicit arguments
castR :: R a -> R b -> a -> Maybe bSource
The type-safe cast operation, explicit arguments
gcast :: forall a b c. (Rep a, Rep b) => c a -> Maybe (c b)Source
Leibniz equality between types, implicity representations
gcastR :: forall a b c. R a -> R b -> c a -> Maybe (c b)Source
Leibniz equality between types, explicit representations
Operations for heterogeneous lists
findCon :: [Con ctx a] -> a -> Val ctx aSource
Given a list of constructor representations for a datatype, determine which constructor formed the datatype.
data Val ctx a Source
A datastructure to store the results of findCon
Constructors
forall l . Val (Emb l a) (MTup ctx l) l
foldl_l :: (forall a. Rep a => ctx a -> b -> a -> b) -> b -> MTup ctx l -> l -> bSource
A fold left for heterogeneous lists
foldr_l :: (forall a. Rep a => ctx a -> a -> b -> b) -> b -> MTup ctx l -> l -> bSource
A fold right operation for heterogeneous lists, that folds a function expecting a type type representation across each element of the list.
map_l :: (forall a. Rep a => ctx a -> a -> a) -> MTup ctx l -> l -> lSource
A map for heterogeneous lists
mapQ_l :: (forall a. Rep a => ctx a -> a -> r) -> MTup ctx l -> l -> [r]Source
Transform a heterogeneous list in to a standard list
mapM_l :: Monad m => (forall a. Rep a => ctx a -> a -> m a) -> MTup ctx l -> l -> m lSource
mapM for heterogeneous lists
fromTup :: (forall a. Rep a => ctx a -> a) -> MTup ctx l -> lSource
Generate a heterogeneous list from metadata
fromTupM :: Monad m => (forall a. Rep a => ctx a -> m a) -> MTup ctx l -> m lSource
Generate a heterogeneous list from metadata, in a monad
toList :: (forall a. Rep a => ctx a -> b) -> MTup ctx l -> [b]Source
Generate a normal lists from metadata
SYB style operations (Rep)
type Traversal = forall a. Rep a => a -> aSource
A SYB style traversal
type Query r = forall a. Rep a => a -> rSource
SYB style query type
type MapM m = forall a. Rep a => a -> m aSource
SYB style monadic map type
gmapT :: forall a. Rep a => Traversal -> a -> aSource
Map a traversal across the kids of a data structure
gmapQ :: forall a r. Rep a => Query r -> a -> [r]Source
gmapM :: forall a m. (Rep a, Monad m) => MapM m -> a -> m aSource
SYB style operations (Rep1)
type Traversal1 ctx = forall a. Rep a => ctx a -> a -> aSource
type Query1 ctx r = forall a. Rep a => ctx a -> a -> rSource
type MapM1 ctx m = forall a. Rep a => ctx a -> a -> m aSource
gmapT1 :: forall a ctx. Rep1 ctx a => Traversal1 ctx -> a -> aSource
gmapQ1 :: forall a ctx r. Rep1 ctx a => Query1 ctx r -> a -> [r]Source
gmapM1 :: forall a ctx m. (Rep1 ctx a, Monad m) => MapM1 ctx m -> a -> m aSource
SYB Reloaded
data Typed a Source
Constructors
a ::: (R a)
data Spine a whereSource
Constructors
Constr :: a -> Spine a
:<> :: Spine (a -> b) -> Typed a -> Spine b
toSpine :: Rep a => a -> Spine aSource
fromSpine :: Spine a -> aSource
Produced by Haddock version 2.4.2