knit-0.4.0.0: Ties the knot on data structures that reference each other by unique keys.
Safe HaskellSafe-Inferred
LanguageHaskell2010

Knit

Documentation

type family Fst a where ... Source #

Equations

Fst '(a, b) = a 

type family Snd a where ... Source #

Equations

Snd '(a, b) = b 

data Mode Source #

Constructors

Resolved 
Unresolved 
Done 

Instances

Instances details
(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 # 
Instance details

Defined in Knit

Methods

gResolve :: (TableName -> FieldName -> FieldValue -> Dynamic) -> (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 # 
Instance details

Defined in Knit

Methods

gResolve :: (TableName -> FieldName -> FieldValue -> Dynamic) -> (Named x (f (ForeignRecordId table field u)), us) -> (Named x (f (Lazy tables r)), rs) Source #

data RecordId t Source #

Constructors

Id t 
Remove t 

Instances

Instances details
Generic (RecordId t) Source # 
Instance details

Defined in Knit

Associated Types

type Rep (RecordId t) :: Type -> Type #

Methods

from :: RecordId t -> Rep (RecordId t) x #

to :: Rep (RecordId t) x -> RecordId t #

Show t => Show (RecordId t) Source # 
Instance details

Defined in Knit

Methods

showsPrec :: Int -> RecordId t -> ShowS #

show :: RecordId t -> String #

showList :: [RecordId t] -> ShowS #

NFData t => NFData (RecordId t) Source # 
Instance details

Defined in Knit

Methods

rnf :: RecordId t -> () #

Eq t => Eq (RecordId t) Source # 
Instance details

Defined in Knit

Methods

(==) :: RecordId t -> RecordId t -> Bool #

(/=) :: RecordId t -> RecordId t -> Bool #

Ord t => Ord (RecordId t) Source # 
Instance details

Defined in Knit

Methods

compare :: RecordId t -> RecordId t -> Ordering #

(<) :: RecordId t -> RecordId t -> Bool #

(<=) :: RecordId t -> RecordId t -> Bool #

(>) :: RecordId t -> RecordId t -> Bool #

(>=) :: RecordId t -> RecordId t -> Bool #

max :: RecordId t -> RecordId t -> RecordId t #

min :: RecordId t -> RecordId t -> RecordId t #

(Show t, GGatherIds us, KnownSymbol field) => GGatherIds (Named field (RecordId t), us) Source # 
Instance details

Defined in Knit

Methods

gGatherIds :: TableName -> Dynamic -> (Named field (RecordId t), us) -> [EId] Source #

(Show t, GGatherIds us, Foldable f, KnownSymbol field) => GGatherIds (Named field (f (RecordId t)), us) Source # 
Instance details

Defined in Knit

Methods

gGatherIds :: TableName -> Dynamic -> (Named field (f (RecordId t)), us) -> [EId] Source #

GResolve us rs => GResolve (Named x (RecordId u), us) (Named x u, rs) Source # 
Instance details

Defined in Knit

Methods

gResolve :: (TableName -> FieldName -> FieldValue -> Dynamic) -> (Named x (RecordId u), us) -> (Named x u, rs) Source #

(GResolve us rs, Functor f) => GResolve (Named x (f (RecordId u)), us) (Named x (f u), rs) Source # 
Instance details

Defined in Knit

Methods

gResolve :: (TableName -> FieldName -> FieldValue -> Dynamic) -> (Named x (f (RecordId u)), us) -> (Named x (f u), rs) Source #

type Rep (RecordId t) Source # 
Instance details

Defined in Knit

type Rep (RecordId t) = D1 ('MetaData "RecordId" "Knit" "knit-0.4.0.0-EsePURBTfZZ3w9ttWsAB7P" '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)))

type family Id (tables :: Mode -> *) (recordMode :: Mode) t where ... Source #

Equations

Id tables 'Done t = RecordId t 
Id tables 'Resolved t = t 
Id tables 'Unresolved t = RecordId t 

data Lazy tables a Source #

Constructors

Lazy 

Fields

Instances

Instances details
(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 # 
Instance details

Defined in Knit

Methods

gResolve :: (TableName -> FieldName -> FieldValue -> Dynamic) -> (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 # 
Instance details

Defined in Knit

Methods

gResolve :: (TableName -> FieldName -> FieldValue -> Dynamic) -> (Named x (f (ForeignRecordId table field u)), us) -> (Named x (f (Lazy tables r)), rs) Source #

Show (Lazy tables a) Source # 
Instance details

Defined in Knit

Methods

showsPrec :: Int -> Lazy tables a -> ShowS #

show :: Lazy tables a -> String #

showList :: [Lazy tables a] -> ShowS #

newtype ForeignRecordId (table :: Symbol) (field :: Symbol) t Source #

Constructors

ForeignId t 

Instances

Instances details
(Show t, GGatherIds us, KnownSymbol table, KnownSymbol field) => GGatherIds (Named field' (ForeignRecordId table field t), us) Source # 
Instance details

Defined in Knit

Methods

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 # 
Instance details

Defined in Knit

Methods

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 # 
Instance details

Defined in Knit

Methods

gResolve :: (TableName -> FieldName -> FieldValue -> Dynamic) -> (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 # 
Instance details

Defined in Knit

Methods

gResolve :: (TableName -> FieldName -> FieldValue -> Dynamic) -> (Named x (f (ForeignRecordId table field u)), us) -> (Named x (f (Lazy tables r)), rs) Source #

Generic (ForeignRecordId table field t) Source # 
Instance details

Defined in Knit

Associated Types

type Rep (ForeignRecordId table field t) :: Type -> Type #

Methods

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 # 
Instance details

Defined in Knit

Methods

(+) :: 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 # 
Instance details

Defined in Knit

Methods

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 # 
Instance details

Defined in Knit

Methods

rnf :: ForeignRecordId table field t -> () #

Eq t => Eq (ForeignRecordId table field t) Source # 
Instance details

Defined in Knit

Methods

(==) :: 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 # 
Instance details

Defined in Knit

Methods

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 # 
Instance details

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 #

Equations

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)))) 

data EId Source #

Constructors

forall t.Show t => EId TableName FieldName t Dynamic 
forall t.Show t => ERemove TableName FieldName t Dynamic 
forall t.Show t => EForeignId TableName FieldName t 

Instances

Instances details
Show EId Source # 
Instance details

Defined in Knit

Methods

showsPrec :: Int -> EId -> ShowS #

show :: EId -> String #

showList :: [EId] -> ShowS #

newtype Dynamic Source #

Constructors

Dynamic () 

Instances

Instances details
Show Dynamic Source # 
Instance details

Defined in Knit

class GGatherIds u where Source #

Methods

gGatherIds :: TableName -> Dynamic -> u -> [EId] Source #

Instances

Instances details
GGatherIds Void Source # 
Instance details

Defined in Knit

Methods

gGatherIds :: TableName -> Dynamic -> Void -> [EId] Source #

GGatherIds () Source # 
Instance details

Defined in Knit

Methods

gGatherIds :: TableName -> Dynamic -> () -> [EId] Source #

(GGatherIds u, GGatherIds v) => GGatherIds (Either u v) Source # 
Instance details

Defined in Knit

Methods

gGatherIds :: TableName -> Dynamic -> Either u v -> [EId] Source #

(Show t, GGatherIds us, KnownSymbol field) => GGatherIds (Named field (RecordId t), us) Source # 
Instance details

Defined in Knit

Methods

gGatherIds :: TableName -> Dynamic -> (Named field (RecordId t), us) -> [EId] Source #

(Show t, GGatherIds us, Foldable f, KnownSymbol field) => GGatherIds (Named field (f (RecordId t)), us) Source # 
Instance details

Defined in Knit

Methods

gGatherIds :: TableName -> Dynamic -> (Named field (f (RecordId t)), us) -> [EId] Source #

(GGatherIds us, Foldable f, KnitRecord tables r) => GGatherIds (Named field (f (r tables 'Unresolved)), us) Source # 
Instance details

Defined in Knit

Methods

gGatherIds :: TableName -> Dynamic -> (Named field (f (r tables 'Unresolved)), us) -> [EId] Source #

(GGatherIds us, KnitRecord tables r) => GGatherIds (Named field (r tables 'Unresolved), us) Source # 
Instance details

Defined in Knit

Methods

gGatherIds :: TableName -> Dynamic -> (Named field (r tables 'Unresolved), us) -> [EId] Source #

GGatherIds us => GGatherIds (Named field u, us) Source # 
Instance details

Defined in Knit

Methods

gGatherIds :: TableName -> Dynamic -> (Named field u, us) -> [EId] Source #

(Show t, GGatherIds us, KnownSymbol table, KnownSymbol field) => GGatherIds (Named field' (ForeignRecordId table field t), us) Source # 
Instance details

Defined in Knit

Methods

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 # 
Instance details

Defined in Knit

Methods

gGatherIds :: TableName -> Dynamic -> (Named field' (f (ForeignRecordId table field t)), us) -> [EId] Source #

class GGatherTableIds t where Source #

Methods

gGatherTableIds :: t -> [(TableName, [[EId]])] Source #

Instances

Instances details
GGatherTableIds Void Source # 
Instance details

Defined in Knit

Methods

gGatherTableIds :: Void -> [(TableName, [[EId]])] Source #

GGatherTableIds () Source # 
Instance details

Defined in Knit

Methods

gGatherTableIds :: () -> [(TableName, [[EId]])] Source #

(GGatherTableIds t, GGatherTableIds u) => GGatherTableIds (Either t u) Source # 
Instance details

Defined in Knit

Methods

gGatherTableIds :: Either t u -> [(TableName, [[EId]])] Source #

(GGatherTableIds ts, KnitRecord tables r, KnownSymbol table) => GGatherTableIds (Named table [r tables 'Unresolved], ts) Source # 
Instance details

Defined in Knit

Methods

gGatherTableIds :: (Named table [r tables 'Unresolved], ts) -> [(TableName, [[EId]])] Source #

(GGatherTableIds ts, KnownSymbol table) => GGatherTableIds (Named table a, ts) Source # 
Instance details

Defined in Knit

Methods

gGatherTableIds :: (Named table a, ts) -> [(TableName, [[EId]])] Source #

data ResolveError Source #

Instances

Instances details
Generic ResolveError Source # 
Instance details

Defined in Knit

Associated Types

type Rep ResolveError :: Type -> Type #

Show ResolveError Source # 
Instance details

Defined in Knit

NFData ResolveError Source # 
Instance details

Defined in Knit

Methods

rnf :: ResolveError -> () #

Eq ResolveError Source # 
Instance details

Defined in Knit

Ord ResolveError Source # 
Instance details

Defined in Knit

type Rep ResolveError Source # 
Instance details

Defined in Knit

class GResolve u r where Source #

Methods

gResolve :: (TableName -> FieldName -> FieldValue -> Dynamic) -> u -> r Source #

Instances

Instances details
GResolve Void Void Source # 
Instance details

Defined in Knit

GResolve () () Source # 
Instance details

Defined in Knit

Methods

gResolve :: (TableName -> FieldName -> FieldValue -> Dynamic) -> () -> () Source #

(GResolve u r, GResolve t s) => GResolve (Either u t) (Either r s) Source # 
Instance details

Defined in Knit

Methods

gResolve :: (TableName -> FieldName -> FieldValue -> Dynamic) -> 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 # 
Instance details

Defined in Knit

Methods

gResolve :: (TableName -> FieldName -> FieldValue -> Dynamic) -> (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 # 
Instance details

Defined in Knit

Methods

gResolve :: (TableName -> FieldName -> FieldValue -> Dynamic) -> (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 # 
Instance details

Defined in Knit

Methods

gResolve :: (TableName -> FieldName -> FieldValue -> Dynamic) -> (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 # 
Instance details

Defined in Knit

Methods

gResolve :: (TableName -> FieldName -> FieldValue -> Dynamic) -> (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 # 
Instance details

Defined in Knit

Methods

gResolve :: (TableName -> FieldName -> FieldValue -> Dynamic) -> (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 # 
Instance details

Defined in Knit

Methods

gResolve :: (TableName -> FieldName -> FieldValue -> Dynamic) -> (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 # 
Instance details

Defined in Knit

Methods

gResolve :: (TableName -> FieldName -> FieldValue -> Dynamic) -> (Named x u, us) -> (Named x u, rs) Source #

class GResolveTables u t where Source #

Methods

gResolveTables :: [[Bool]] -> (TableName -> FieldName -> FieldValue -> Dynamic) -> u -> t Source #

Instances

Instances details
GResolveTables () () Source # 
Instance details

Defined in Knit

Methods

gResolveTables :: [[Bool]] -> (TableName -> FieldName -> FieldValue -> Dynamic) -> () -> () Source #

GResolveTables u t => GResolveTables (Either u Void) (Either t Void) Source # 
Instance details

Defined in Knit

(GResolveTables us ts, KnitRecord tables t) => GResolveTables (Named table [t tables 'Unresolved], us) (Named table [t tables 'Resolved], ts) Source # 
Instance details

Defined in Knit

Methods

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 # 
Instance details

Defined in Knit

Methods

gResolveTables :: [[Bool]] -> (TableName -> FieldName -> FieldValue -> Dynamic) -> (Named table a, us) -> (Named table a, ts) Source #

class KnitRecord (tables :: Mode -> *) u where Source #

Minimal complete definition

Nothing

Methods

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 #

type family ExpandRecord (parent :: Symbol) (record :: *) where ... Source #

Equations

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 #

Equations

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 #

Equations

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 #

Equations

Table tables r table = [table tables r]