RepLib-0.2.2: Generic programming library with representation types

Portabilitynon-portable
Stabilityexperimental
Maintainersweirich@cis.upenn.edu

Data.RepLib.R1

Description

 

Synopsis

Documentation

data R1 ctx a whereSource

Constructors

Int1 :: R1 ctx Int 
Char1 :: R1 ctx Char 
Integer1 :: R1 ctx Integer 
Float1 :: R1 ctx Float 
Double1 :: R1 ctx Double 
Rational1 :: R1 ctx Rational 
IOError1 :: R1 ctx IOError 
IO1 :: Rep a => ctx a -> R1 ctx (IO a) 
Arrow1 :: (Rep a, Rep b) => ctx a -> ctx b -> R1 ctx (a -> b) 
Data1 :: DT -> [Con ctx a] -> R1 ctx a 

Instances

Show (R1 c a) 

class Sat a whereSource

Methods

dict :: aSource

Instances

Show a => Sat (ShowD a) 
Bounded a => Sat (BoundedD a) 
Ord a => Sat (OrdD a) 
Eq a => Sat (EqD a) 
Shrink a => Sat (ShrinkD a) 
Enumerate a => Sat (EnumerateD a) 
Generate a => Sat (GenerateD a) 
Zero a => Sat (ZeroD a) 
GSum a => Sat (GSumD a) 
Lreduce b a => Sat (LreduceD b a) 
Rreduce b a => Sat (RreduceD b a) 
(Unify n a b, Subst n a b, Occurs n a b) => Sat (UnifySubD n a b) 

class Rep a => Rep1 ctx a whereSource

Methods

rep1 :: R1 ctx aSource

Instances

Rep1 ctx () 
Rep1 ctx Rational 
Rep1 ctx IOError 
Rep1 ctx Double 
Rep1 ctx Float 
Rep1 ctx Integer 
Rep1 ctx Char 
Rep1 ctx Int 
Rep1 ctx[acHK] Bool 
Rep1 ctx[acH4] Ordering 
(Rep a, Sat (ctx a), Sat (ctx [a])) => Rep1 ctx [a] 
(Rep a, Sat (ctx a)) => Rep1 ctx (IO a) 
(Rep a[a1Nk], Sat (ctx[acHA] a[a1Nk])) => Rep1 ctx[acHA] (Maybe a[a1Nk]) 
(Rep a, Sat (ctx a), Rep b, Sat (ctx b)) => Rep1 ctx (a, b) 
(Rep a, Rep b, Sat (ctx a), Sat (ctx b)) => Rep1 ctx (a -> b) 
(Rep a[acHc], Rep b[acHb], Sat (ctx[acHl] a[acHc]), Sat (ctx[acHl] b[acHb])) => Rep1 ctx[acHl] (Either a[acHc] b[acHb]) 
(Rep a[12], Rep b[13], Rep c[14], Sat (ctx[acGM] a[12]), Sat (ctx[acGM] b[13]), Sat (ctx[acGM] c[14])) => Rep1 ctx[acGM] (a[12], b[13], c[14]) 
(Rep a[12], Rep b[13], Rep c[14], Rep d[15], Sat (ctx[acGp] a[12]), Sat (ctx[acGp] b[13]), Sat (ctx[acGp] c[14]), Sat (ctx[acGp] d[15])) => Rep1 ctx[acGp] (a[12], b[13], c[14], d[15]) 
(Rep a[12], Rep b[13], Rep c[14], Rep d[15], Rep e[16], Sat (ctx[acFX] a[12]), Sat (ctx[acFX] b[13]), Sat (ctx[acFX] c[14]), Sat (ctx[acFX] d[15]), Sat (ctx[acFX] e[16])) => Rep1 ctx[acFX] (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], Sat (ctx[acFq] a[12]), Sat (ctx[acFq] b[13]), Sat (ctx[acFq] c[14]), Sat (ctx[acFq] d[15]), Sat (ctx[acFq] e[16]), Sat (ctx[acFq] f[17])) => Rep1 ctx[acFq] (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], Sat (ctx[acEO] a[12]), Sat (ctx[acEO] b[13]), Sat (ctx[acEO] c[14]), Sat (ctx[acEO] d[15]), Sat (ctx[acEO] e[16]), Sat (ctx[acEO] f[17]), Sat (ctx[acEO] g[18])) => Rep1 ctx[acEO] (a[12], b[13], c[14], d[15], e[16], f[17], g[18]) 

getRep :: Rep b => c b -> R bSource

Access a representation, given a proxy

toR :: R1 c a -> R aSource

Transform a parameterized rep to a vanilla rep

rTup2_1 :: forall a b ctx. (Rep a, Rep b) => ctx a -> ctx b -> R1 ctx (a, b)Source

rList1 :: forall a ctx. Rep a => ctx a -> ctx [a] -> R1 ctx [a]Source

rNil1 :: Con ctx [a]Source

rCons1 :: Rep a => ctx a -> ctx [a] -> Con ctx [a]Source