RepLib-0.2.1: Generic programming library with representation typesSource codeContentsIndex
Data.RepLib.R
Portabilitynon-portable
Stabilityexperimental
Maintainer[email protected]
Description
Documentation
data R a whereSource
Constructors
Int :: R Int
Char :: R Char
Integer :: R Integer
Float :: R Float
Double :: R Double
Rational :: R Rational
IOError :: R IOError
IO :: Rep a => R a -> R (IO a)
Arrow :: (Rep a, Rep b) => R a -> R b -> R (a -> b)
Data :: DT -> [Con R a] -> R a
show/hide Instances
Eq (R a)
Show (R a)
data Emb l a Source
Constructors
Emb
to :: l -> a
from :: a -> Maybe l
labels :: Maybe [String]
name :: String
fixity :: Fixity
data Fixity Source
Constructors
Nonfix
Infix
prec :: Int
Infixl
prec :: Int
Infixr
prec :: Int
data DT Source
Constructors
forall l . DT String (MTup R l)
show/hide Instances
data Con r a Source
Constructors
forall l . Con (Emb l a) (MTup r l)
data Nil Source
Constructors
Nil
data a :*: l Source
Constructors
a :*: l
data MTup r l whereSource
Constructors
MNil :: MTup ctx Nil
:+: :: Rep a => r a -> MTup r l -> MTup r (a :*: l)
show/hide Instances
Show (MTup R l)
class Rep a whereSource
Methods
rep :: R aSource
show/hide Instances
Rep Bool
Rep Char
Rep Double
Rep Float
Rep Int
Rep Integer
Rep Ordering
Rep Rational
Rep ()
Rep IOError
Rep a => Rep ([] a)
Rep a => Rep (IO a)
Rep a[a1ko] => Rep (Maybe a[a1ko])
(Rep a, Rep b) => Rep (a -> b)
(Rep a[a6ZO], Rep b[a6ZN]) => Rep (Either a[a6ZO] b[a6ZN])
(Rep a, Rep b) => Rep ((,) a b)
(Rep a[12], Rep b[13], Rep c[14]) => Rep ((,,) a[12] b[13] c[14])
(Rep a[12], Rep b[13], Rep c[14], Rep d[15]) => Rep ((,,,) a[12] b[13] c[14] d[15])
(Rep a[12], Rep b[13], Rep c[14], Rep d[15], Rep e[16]) => Rep ((,,,,) a[12] b[13] c[14] d[15] e[16])
(Rep a[12], Rep b[13], Rep c[14], Rep d[15], Rep e[16], Rep f[17]) => Rep ((,,,,,) a[12] b[13] c[14] d[15] e[16] f[17])
(Rep a[12], Rep b[13], Rep c[14], Rep d[15], Rep e[16], Rep f[17], Rep g[18]) => Rep ((,,,,,,) a[12] b[13] c[14] d[15] e[16] f[17] g[18])
rUnitEmb :: Emb Nil ()Source
rUnit :: R ()Source
rTup2 :: forall a b. (Rep a, Rep b) => R (a, b)Source
rPairEmb :: Emb (a :*: (b :*: Nil)) (a, b)Source
rList :: forall a. Rep a => R [a]Source
rNilEmb :: Emb Nil [a]Source
rConsEmb :: Emb (a :*: ([a] :*: Nil)) [a]Source
Produced by Haddock version 2.4.2