Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Documentation
type family CompNameData a info where ... Source #
CompNameData _ ('ADT _ name _ _) = name | |
CompNameData a _ = TypeError (("The type " <> a) <> " is not an ADT.") |
type family RecordFields (fields :: [FieldInfo]) (ass :: [Type]) :: [ProductField] where ... Source #
RecordFields '[] '[] = '[] | |
RecordFields ('FieldInfo name ': fields) (a ': as) = 'ProductField name a ': RecordFields fields as |
type family ConstructorFields (name :: Symbol) (index :: Nat) (ass :: [Type]) :: [ProductField] where ... Source #
ConstructorFields _ _ '[] = '[] | |
ConstructorFields name n (a ': as) = 'ProductField (AppendSymbol name (NatSymbol n)) a ': ConstructorFields name (n + 1) as |
type family ProductFields (info :: DatatypeInfo) (ass :: [[Type]]) :: [ProductField] where ... Source #
ProductFields ('ADT _ _ '['Record _ fields] _) '[ass] = RecordFields fields ass |
class Column a fieldName s0 s | a fieldName s0 -> s where Source #
Instances
a ~ b => Column a fname ('DdK ('SelSymbol name) mods b ('Comp tsel c 'Nest s)) ('DdK ('SelSymbol name) mods a ('Comp tsel c 'Nest s)) Source # | |
a ~ b => Column a fname ('DdK ('SelSymbol name) mods b 'Prim) ('DdK ('SelSymbol name) mods a 'Prim) Source # | |
a ~ b => Column a name ('DdK 'SelAuto mods b ('Comp tsel c 'Merge s)) ('DdK 'SelAuto mods a ('Comp tsel c 'Merge s)) Source # | |
(a ~ b, KnownSymbol name) => Column a name ('DdK 'SelAuto mods b ('Comp tsel c 'Nest s)) ('DdK ('SelSymbol name) mods a ('Comp tsel c 'Nest s)) Source # | |
(a ~ b, KnownSymbol name) => Column a name ('DdK 'SelAuto mods b 'Prim) ('DdK ('SelSymbol name) mods a 'Prim) Source # | |
a ~ b => Column a name ('DdK 'SelUnused mods b 'Prim) ('DdK 'SelUnused mods a 'Prim) Source # | |
CompMeta | |
|
Instances
Generic CompMeta Source # | |
type Rep CompMeta Source # | |
Defined in Sqel.Comp type Rep CompMeta = D1 ('MetaData "CompMeta" "Sqel.Comp" "sqel-0.0.1.0-5k4czMecwS553bFrfF1Jzu" 'False) (C1 ('MetaCons "CompMeta" 'PrefixI 'True) ((S1 ('MetaSel ('Just "desc") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Symbol) :*: S1 ('MetaSel ('Just "name") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ErrorMessage)) :*: (S1 ('MetaSel ('Just "combinator") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Symbol) :*: S1 ('MetaSel ('Just "index") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Nat)))) |
type InvalidElem name i arg = DelayError ((((((("Element number " <> i) <> " in the call to ") <> Quoted name) <> " has type ") <> QuotedType arg) <> ".") % ((((("Columns should only be constructed with combinators like " <> Quoted "prim") <> ", ") <> Quoted "prod") <> ",") % ((((Quoted "column" <> " that return the proper type, ") <> Quoted "Dd") <> ".") % (("Consult the module " <> Quoted "Sqel.Combinators") <> " for the full API.")))) Source #
class CompItemOrError err field arg s | field arg -> s where Source #
compItemOrError :: Proxy err -> arg -> Dd s Source #
Instances
Column a fieldName s0 s1 => CompItemOrError err ('ProductField fieldName a) (Dd s0) s1 Source # | |
class CheckCompItem meta field arg s | field arg -> s where Source #
checkCompItem :: arg -> Dd s Source #
Instances
(meta ~ 'CompMeta desc name combinator index, error ~ InvalidElem combinator index arg, CompItemOrError error field arg s1) => CheckCompItem meta field arg s1 Source # | |
Defined in Sqel.Comp checkCompItem :: arg -> Dd s1 Source # |
type family MetaFor (desc :: Symbol) (name :: ErrorMessage) (combinator :: Symbol) :: CompMeta where ... Source #
Instances
(a ~ b, CompColumn' meta ('Right 'SpecNP :: Either Void SpecType) fields a (NP Dd s0) s1) => CompColumn' meta ('Right 'SpecPrims :: Either Void SpecType) fields a (Prims b s0) s1 Source # | |
CompColumn' meta ('Right 'SpecNP :: Either Void SpecType) ('[] :: [ProductField]) a (NP f ('[] :: [k])) ('[] :: [DdK]) Source # | |
CheckCompItem meta field arg s => CompColumn' meta ('Right 'SpecDsl :: Either Void SpecType) '[field] a arg '[s] Source # | |
(CheckCompItem meta field arg0 s0, CompColumn' (MetaNext meta) ('Right 'SpecDsl :: Either Void SpecType) fields a args s1) => CompColumn' meta ('Right 'SpecDsl :: Either Void SpecType) (field ': fields) a (arg0 :> args) (s0 ': s1) Source # | |
(CheckCompItem meta field (f arg0) s0, CompColumn' (MetaNext meta) ('Right 'SpecNP :: Either Void SpecType) fields a2 (NP f args) s1) => CompColumn' meta ('Right 'SpecNP :: Either Void SpecType) (field ': fields) a2 (NP f (arg0 ': args)) (s0 ': s1) Source # | |
type family CheckFields (meta :: CompMeta) (len :: Nat) (fieldLen :: Nat) (t :: SpecType) :: Either Void SpecType where ... Source #
CheckFields _ n n t = 'Right t | |
CheckFields ('CompMeta desc name _ _) arg f _ = 'Left (DelayError (CountMismatch desc name arg f)) |
type family TriageComp (meta :: CompMeta) (arg :: Type) (fields :: [ProductField]) :: Either Void SpecType where ... Source #
TriageComp _ (Prims _ _) _ = 'Right 'SpecPrims | |
TriageComp meta (NP _ s) fs = CheckFields meta (Length @@ s) (Length @@ fs) 'SpecNP | |
TriageComp meta args fs = CheckFields meta (DslSize args) (Length @@ fs) 'SpecDsl |
class CompColumn' meta spec fields a arg s | fields arg -> s where Source #
compColumn' :: arg -> NP Dd s Source #
Instances
(a ~ b, CompColumn' meta ('Right 'SpecNP :: Either Void SpecType) fields a (NP Dd s0) s1) => CompColumn' meta ('Right 'SpecPrims :: Either Void SpecType) fields a (Prims b s0) s1 Source # | |
CompColumn' meta ('Right 'SpecNP :: Either Void SpecType) ('[] :: [ProductField]) a (NP f ('[] :: [k])) ('[] :: [DdK]) Source # | |
CheckCompItem meta field arg s => CompColumn' meta ('Right 'SpecDsl :: Either Void SpecType) '[field] a arg '[s] Source # | |
(CheckCompItem meta field arg0 s0, CompColumn' (MetaNext meta) ('Right 'SpecDsl :: Either Void SpecType) fields a args s1) => CompColumn' meta ('Right 'SpecDsl :: Either Void SpecType) (field ': fields) a (arg0 :> args) (s0 ': s1) Source # | |
(CheckCompItem meta field (f arg0) s0, CompColumn' (MetaNext meta) ('Right 'SpecNP :: Either Void SpecType) fields a2 (NP f args) s1) => CompColumn' meta ('Right 'SpecNP :: Either Void SpecType) (field ': fields) a2 (NP f (arg0 ': args)) (s0 ': s1) Source # | |
class CompColumn meta fields a arg s | fields arg -> s where Source #
compColumn :: arg -> NP Dd s Source #
Instances
(spec ~ TriageComp meta arg fields, CompColumn' meta spec fields a arg s) => CompColumn meta fields a arg s Source # | |
class SetTypePrefix prefix s0 s1 | prefix s0 -> s1 where Source #
setTypePrefix :: Dd s0 -> Dd s1 Source #
typePrefix :: forall prefix s0 s1. SetTypePrefix prefix s0 s1 => Dd s0 -> Dd s1 Source #