Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Documentation
type FieldValue = String Source #
Instances
(Show u, KnitRecord tables r, GResolve us rs, KnownSymbol table, KnownSymbol field) => GResolve (Named x (ForeignRecordId table field u), us) (Named x (Lazy tables r), rs) Source # | |
(Show u, KnitRecord tables r, GResolve us rs, Functor f, KnownSymbol table, KnownSymbol field) => GResolve (Named x (f (ForeignRecordId table field u)), us) (Named x (f (Lazy tables r)), rs) Source # | |
Instances
Instances
(Show u, KnitRecord tables r, GResolve us rs, KnownSymbol table, KnownSymbol field) => GResolve (Named x (ForeignRecordId table field u), us) (Named x (Lazy tables r), rs) Source # | |
(Show u, KnitRecord tables r, GResolve us rs, Functor f, KnownSymbol table, KnownSymbol field) => GResolve (Named x (f (ForeignRecordId table field u)), us) (Named x (f (Lazy tables r)), rs) Source # | |
Show (Lazy tables a) Source # | |
newtype ForeignRecordId (table :: Symbol) (field :: Symbol) t Source #
Instances
(Show t, GGatherIds us, KnownSymbol table, KnownSymbol field) => GGatherIds (Named field' (ForeignRecordId table field t), us) Source # | |
Defined in Knit gGatherIds :: TableName -> Dynamic -> (Named field' (ForeignRecordId table field t), us) -> [EId] Source # | |
(Show t, GGatherIds us, Foldable f, KnownSymbol table, KnownSymbol field) => GGatherIds (Named field' (f (ForeignRecordId table field t)), us) Source # | |
Defined in Knit gGatherIds :: TableName -> Dynamic -> (Named field' (f (ForeignRecordId table field t)), us) -> [EId] Source # | |
(Show u, KnitRecord tables r, GResolve us rs, KnownSymbol table, KnownSymbol field) => GResolve (Named x (ForeignRecordId table field u), us) (Named x (Lazy tables r), rs) Source # | |
(Show u, KnitRecord tables r, GResolve us rs, Functor f, KnownSymbol table, KnownSymbol field) => GResolve (Named x (f (ForeignRecordId table field u)), us) (Named x (f (Lazy tables r)), rs) Source # | |
Generic (ForeignRecordId table field t) Source # | |
Defined in Knit type Rep (ForeignRecordId table field t) :: Type -> Type # from :: ForeignRecordId table field t -> Rep (ForeignRecordId table field t) x # to :: Rep (ForeignRecordId table field t) x -> ForeignRecordId table field t # | |
Num t => Num (ForeignRecordId table field t) Source # | |
Defined in Knit (+) :: ForeignRecordId table field t -> ForeignRecordId table field t -> ForeignRecordId table field t # (-) :: ForeignRecordId table field t -> ForeignRecordId table field t -> ForeignRecordId table field t # (*) :: ForeignRecordId table field t -> ForeignRecordId table field t -> ForeignRecordId table field t # negate :: ForeignRecordId table field t -> ForeignRecordId table field t # abs :: ForeignRecordId table field t -> ForeignRecordId table field t # signum :: ForeignRecordId table field t -> ForeignRecordId table field t # fromInteger :: Integer -> ForeignRecordId table field t # | |
Show t => Show (ForeignRecordId table field t) Source # | |
Defined in Knit showsPrec :: Int -> ForeignRecordId table field t -> ShowS # show :: ForeignRecordId table field t -> String # showList :: [ForeignRecordId table field t] -> ShowS # | |
NFData t => NFData (ForeignRecordId table field t) Source # | |
Defined in Knit rnf :: ForeignRecordId table field t -> () # | |
Eq t => Eq (ForeignRecordId table field t) Source # | |
Defined in Knit (==) :: ForeignRecordId table field t -> ForeignRecordId table field t -> Bool # (/=) :: ForeignRecordId table field t -> ForeignRecordId table field t -> Bool # | |
Ord t => Ord (ForeignRecordId table field t) Source # | |
Defined in Knit compare :: ForeignRecordId table field t -> ForeignRecordId table field t -> Ordering # (<) :: ForeignRecordId table field t -> ForeignRecordId table field t -> Bool # (<=) :: ForeignRecordId table field t -> ForeignRecordId table field t -> Bool # (>) :: ForeignRecordId table field t -> ForeignRecordId table field t -> Bool # (>=) :: ForeignRecordId table field t -> ForeignRecordId table field t -> Bool # max :: ForeignRecordId table field t -> ForeignRecordId table field t -> ForeignRecordId table field t # min :: ForeignRecordId table field t -> ForeignRecordId table field t -> ForeignRecordId table field t # | |
type Rep (ForeignRecordId table field t) Source # | |
Defined in Knit type Rep (ForeignRecordId table field t) = D1 ('MetaData "ForeignRecordId" "Knit" "knit-0.4.0.0-EsePURBTfZZ3w9ttWsAB7P" 'True) (C1 ('MetaCons "ForeignId" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 t))) |
type family ForeignId (tables :: Mode -> *) (recordMode :: Mode) (table :: Symbol) (field :: Symbol) where ... Source #
ForeignId tables 'Done table field = () | |
ForeignId tables 'Unresolved table field = ForeignRecordId table field (LookupFieldType field (Snd (LookupTableType table (Eot (tables 'Unresolved))))) | |
ForeignId tables 'Resolved table field = Lazy tables (Fst (LookupTableType table (Eot (tables 'Resolved)))) |
Dynamic () |
fromDynamic :: Dynamic -> a Source #
class GGatherIds u where Source #
Instances
class GGatherTableIds t where Source #
gGatherTableIds :: t -> [(TableName, [[EId]])] Source #
Instances
GGatherTableIds Void Source # | |
GGatherTableIds () Source # | |
(GGatherTableIds t, GGatherTableIds u) => GGatherTableIds (Either t u) Source # | |
(GGatherTableIds ts, KnitRecord tables r, KnownSymbol table) => GGatherTableIds (Named table [r tables 'Unresolved], ts) Source # | |
Defined in Knit gGatherTableIds :: (Named table [r tables 'Unresolved], ts) -> [(TableName, [[EId]])] Source # | |
(GGatherTableIds ts, KnownSymbol table) => GGatherTableIds (Named table a, ts) Source # | |
data ResolveError Source #
Instances
class GResolve u r where Source #
Instances
GResolve Void Void Source # | |
GResolve () () Source # | |
(GResolve u r, GResolve t s) => GResolve (Either u t) (Either r s) Source # | |
(Show u, KnitRecord tables r, GResolve us rs, KnownSymbol table, KnownSymbol field) => GResolve (Named x (ForeignRecordId table field u), us) (Named x (Lazy tables r), rs) Source # | |
GResolve us rs => GResolve (Named x (RecordId u), us) (Named x u, rs) Source # | |
(Show u, KnitRecord tables r, GResolve us rs, Functor f, KnownSymbol table, KnownSymbol field) => GResolve (Named x (f (ForeignRecordId table field u)), us) (Named x (f (Lazy tables r)), rs) Source # | |
(GResolve us rs, Functor f) => GResolve (Named x (f (RecordId u)), us) (Named x (f u), rs) Source # | |
(KnitRecord tables r, GResolve us rs, Functor f) => GResolve (Named x (f (r tables 'Unresolved)), us) (Named x (f (r tables 'Resolved)), rs) Source # | |
(KnitRecord tables r, GResolve us rs) => GResolve (Named x (r tables 'Unresolved), us) (Named x (r tables 'Resolved), rs) Source # | |
GResolve us rs => GResolve (Named x u, us) (Named x u, rs) Source # | |
class GResolveTables u t where Source #
gResolveTables :: [[Bool]] -> (TableName -> FieldName -> FieldValue -> Dynamic) -> u -> t Source #
Instances
GResolveTables () () Source # | |
Defined in Knit gResolveTables :: [[Bool]] -> (TableName -> FieldName -> FieldValue -> Dynamic) -> () -> () Source # | |
GResolveTables u t => GResolveTables (Either u Void) (Either t Void) Source # | |
(GResolveTables us ts, KnitRecord tables t) => GResolveTables (Named table [t tables 'Unresolved], us) (Named table [t tables 'Resolved], ts) Source # | |
Defined in Knit gResolveTables :: [[Bool]] -> (TableName -> FieldName -> FieldValue -> Dynamic) -> (Named table [t tables 'Unresolved], us) -> (Named table [t tables 'Resolved], ts) Source # | |
GResolveTables us ts => GResolveTables (Named table a, us) (Named table a, ts) Source # | |
class KnitRecord (tables :: Mode -> *) u where Source #
Nothing
resolve :: (TableName -> FieldName -> FieldValue -> Dynamic) -> u tables 'Unresolved -> u tables 'Resolved Source #
default resolve :: HasEot (u tables 'Unresolved) => HasEot (u tables 'Resolved) => GResolve (Eot (u tables 'Unresolved)) (Eot (u tables 'Resolved)) => (TableName -> FieldName -> FieldValue -> Dynamic) -> u tables 'Unresolved -> u tables 'Resolved Source #
gatherIds :: TableName -> Dynamic -> u tables 'Unresolved -> [EId] Source #
default gatherIds :: HasEot (u tables 'Unresolved) => GGatherIds (Eot (u tables 'Unresolved)) => TableName -> Dynamic -> u tables 'Unresolved -> [EId] Source #
class KnitTables t where Source #
Nothing
resolveTables :: (TableName -> FieldName -> FieldValue -> Dynamic) -> t 'Unresolved -> Either ResolveError (t 'Resolved) Source #
default resolveTables :: HasEot (t 'Unresolved) => HasEot (t 'Resolved) => GResolveTables (Eot (t 'Unresolved)) (Eot (t 'Resolved)) => KnitTables t => (TableName -> FieldName -> FieldValue -> Dynamic) -> t 'Unresolved -> Either ResolveError (t 'Resolved) Source #
gatherTableIds :: t 'Unresolved -> [(TableName, [[EId]])] Source #
default gatherTableIds :: HasEot (t 'Unresolved) => GGatherTableIds (Eot (t 'Unresolved)) => t 'Unresolved -> [(TableName, [[EId]])] Source #
type family ExpandRecord (parent :: Symbol) (record :: *) where ... Source #
ExpandRecord parent () = () | |
ExpandRecord parent (Either fields Void) = ExpandRecord parent fields | |
ExpandRecord parent (Named name (RecordId a), fields) = (Named name a, ExpandRecord parent fields) | |
ExpandRecord parent (Named name (f (RecordId a)), fields) = (Named name (f a), ExpandRecord parent fields) | |
ExpandRecord parent (a, fields) = ExpandRecord parent fields |
type family LookupTableType (table :: Symbol) (eot :: *) :: ((Mode -> *) -> Mode -> *, *) where ... Source #
LookupTableType name (Either records Void) = LookupTableType name records | |
LookupTableType name (Named name [record tables recordMode], records) = '(record, ExpandRecord name (Eot (record tables 'Done))) | |
LookupTableType name (Named otherName a, records) = LookupTableType name records | |
LookupTableType name eot = TypeError ('Text "Can't lookup table type") |
type family LookupFieldType (field :: Symbol) (eot :: *) :: * where ... Source #
LookupFieldType name (Either records Void) = LookupFieldType name records | |
LookupFieldType name (Named name (Maybe field), fields) = field | |
LookupFieldType name (Named name field, fields) = field | |
LookupFieldType name (Named otherName field, fields) = LookupFieldType name fields | |
LookupFieldType name eot = TypeError ('Text "Can't lookup field type") |
type family Table (tables :: Mode -> *) (c :: Mode) table where ... Source #
Table tables r table = [table tables r] |
knit :: KnitTables t => t 'Unresolved -> Either ResolveError (t 'Resolved) Source #