| Safe Haskell | Safe-Inferred |
|---|---|
| Language | Haskell2010 |
Sqel.Type
Documentation
type family PrimUnused (a :: Type) :: DdK where ... Source #
Equations
| PrimUnused a = PrimSel 'SelUnused 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 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 #
Equations
| ProdPrimsNewtype a = ProdPrimsNewtype' a (GCode a) (GDatatypeInfoOf a) |