sqel-0.0.1.0: Guided derivation for Hasql statements
Safe HaskellSafe-Inferred
LanguageHaskell2010

Sqel.Type

Documentation

type family Prod (a :: Type) :: DdK where ... Source #

Equations

Prod a = 'DdK 'SelAuto NoMods a ('Comp ('TSel 'DefaultPrefix (DataName a)) ('Prod 'Reg) 'Nest '[]) 

type family Merge (dd :: DdK) :: DdK where ... Source #

Equations

Merge ('DdK sel mods a ('Comp tsel c _ sub)) = 'DdK sel mods a ('Comp tsel c 'Merge sub) 
Merge s = s 

type family base *> sub infix 4 Source #

Instances

Instances details
type ('DdK sel mods a ('Comp tsel c i ('[] :: [DdK]))) *> (sub :: DdK) Source # 
Instance details

Defined in Sqel.Type

type ('DdK sel mods a ('Comp tsel c i ('[] :: [DdK]))) *> (sub :: DdK) = 'DdK sel mods a ('Comp tsel c i '[sub])
type ('DdK sel mods a ('Comp tsel c i ('[] :: [DdK]))) *> (sub :: [DdK]) Source # 
Instance details

Defined in Sqel.Type

type ('DdK sel mods a ('Comp tsel c i ('[] :: [DdK]))) *> (sub :: [DdK]) = 'DdK sel mods a ('Comp tsel c i sub)

type family a > b infixr 5 Source #

Instances

Instances details
type a > (b :: DdK) Source # 
Instance details

Defined in Sqel.Type

type a > (b :: DdK) = '[a, b]
type a > (b :: [DdK]) Source # 
Instance details

Defined in Sqel.Type

type a > (b :: [DdK]) = a ': b

type family PrimSel (sel :: Sel) (a :: Type) :: DdK where ... Source #

Equations

PrimSel sel a = 'DdK sel NoMods a 'Prim 

type family PrimUnused (a :: Type) :: DdK where ... Source #

Equations

PrimUnused a = PrimSel 'SelUnused a 

type family Prim (name :: Symbol) (a :: Type) :: DdK where ... Source #

Equations

Prim name a = PrimSel ('SelSymbol name) a 

type family NewtypeWrapped' (a :: Type) (ass :: [[Type]]) :: Type where ... Source #

Equations

NewtypeWrapped' _ '['[w]] = w 
NewtypeWrapped' a _ = TypeError (QuotedType a <> " is not a newtype.") 

type family NewtypeWrapped (a :: Type) :: Type where ... Source #

Equations

NewtypeWrapped a = NewtypeWrapped' a (GCode a) 

type family PrimNewtype (name :: Symbol) (a :: Type) :: DdK where ... Source #

Equations

PrimNewtype name a = Mod (Newtype a (NewtypeWrapped a)) (Prim name a) 

type family Name (name :: Symbol) (dd :: DdK) :: DdK where ... Source #

Equations

Name name ('DdK _ mods a s) = 'DdK ('SelSymbol name) mods a s 

type family TypeSel (tsel :: TSel) (dd :: DdK) :: DdK where ... Source #

Equations

TypeSel tsel ('DdK sel mods a ('Comp _ c i sub)) = 'DdK sel mods a ('Comp tsel c i sub) 

type family ProdPrimFields (as :: [Type]) (fields :: [FieldInfo]) :: [DdK] where ... Source #

Equations

ProdPrimFields '[] '[] = '[] 
ProdPrimFields (a ': as) ('FieldInfo name ': fields) = Prim name a ': ProdPrimFields as fields 

type family ProdPrims' (a :: Type) (code :: [[Type]]) (info :: DatatypeInfo) :: DdK where ... Source #

Equations

ProdPrims' a '[as] ('ADT _ name '['Record _ fields] _) = 'DdK 'SelAuto NoMods a ('Comp ('TSel 'DefaultPrefix name) ('Prod 'Reg) 'Nest (ProdPrimFields as fields)) 

type family ProdPrims (a :: Type) :: DdK where ... Source #

Equations

ProdPrims a = ProdPrims' a (GCode a) (GDatatypeInfoOf a) 

type family ProdPrimNewtypeFields (as :: [Type]) (fields :: [FieldInfo]) :: [DdK] where ... Source #

Equations

ProdPrimNewtypeFields '[] '[] = '[] 
ProdPrimNewtypeFields (a ': as) ('FieldInfo name ': fields) = PrimNewtype name a ': ProdPrimNewtypeFields as fields 

type family ProdPrimsNewtype' (a :: Type) (code :: [[Type]]) (info :: DatatypeInfo) :: DdK where ... Source #

Equations

ProdPrimsNewtype' a '[as] ('ADT _ name '['Record _ fields] _) = 'DdK 'SelAuto NoMods a ('Comp ('TSel 'DefaultPrefix name) ('Prod 'Reg) 'Nest (ProdPrimNewtypeFields as fields)) 

type family ProdPrimsNewtype (a :: Type) :: DdK where ... Source #

type family Mods (mods :: [Type]) (dd :: DdK) :: DdK where ... Source #

Equations

Mods new ('DdK sel old a s) = 'DdK sel (new ++ old) a s 

type family ModsR (mods :: [Type]) (dd :: DdK) :: DdK where ... Source #

Equations

ModsR new ('DdK sel old a s) = 'DdK sel (old ++ new) a s 

type family Mod (mod :: Type) (dd :: DdK) :: DdK where ... Source #

Equations

Mod mod dd = Mods '[mod] dd 

type family MSelect (dd :: DdK) :: DdK where ... Source #

Equations

MSelect dd = Mod SelectAtom dd