Safe Haskell | None |
---|---|
Language | Haskell2010 |
Documentation
class KnitRecord (tables :: Mode -> *) u Source #
class KnitTables t Source #
type family Table (tables :: Mode -> *) (c :: Mode) table where ... Source #
Table tables r table = [table tables r] |
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)))) |
Instances
Eq t => Eq (RecordId t) Source # | |
Ord t => Ord (RecordId t) Source # | |
Show t => Show (RecordId t) Source # | |
Generic (RecordId t) Source # | |
NFData t => NFData (RecordId t) Source # | |
type Rep (RecordId t) Source # | |
Defined in Knit type Rep (RecordId t) = D1 (MetaData "RecordId" "Knit" "knit-0.1.0.0-IeVUuDIPBWkGBI6KyrmIF7" False) (C1 (MetaCons "Id" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 t)) :+: C1 (MetaCons "Remove" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 t))) |
newtype ForeignRecordId (table :: Symbol) (field :: Symbol) t Source #
Instances
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 # | |
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 # | |
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 # | |
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 # | |
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 # | |
NFData t => NFData (ForeignRecordId table field t) Source # | |
Defined in Knit rnf :: 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.1.0.0-IeVUuDIPBWkGBI6KyrmIF7" True) (C1 (MetaCons "ForeignId" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 t))) |
data ResolveError Source #
MissingIds [(TableName, FieldName, FieldValue)] | |
RepeatingIds [(TableName, FieldName, FieldValue)] |
Instances
Show ResolveError Source # | |
Defined in Knit showsPrec :: Int -> ResolveError -> ShowS # show :: ResolveError -> String # showList :: [ResolveError] -> ShowS # | |
Generic ResolveError Source # | |
Defined in Knit type Rep ResolveError :: Type -> Type # from :: ResolveError -> Rep ResolveError x # to :: Rep ResolveError x -> ResolveError # | |
NFData ResolveError Source # | |
Defined in Knit rnf :: ResolveError -> () # | |
type Rep ResolveError Source # | |
Defined in Knit |
knit :: KnitTables t => t Unresolved -> Either ResolveError (t Resolved) Source #