knit-0.1.0.0: Ties the knot on data structures that reference each other by unique keys.

Safe HaskellNone
LanguageHaskell2010

Knit

Documentation

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

data Mode Source #

Constructors

Resolved 
Unresolved 
Done 

type family Table (tables :: Mode -> *) (c :: Mode) table where ... Source #

Equations

Table tables r table = [table tables r] 

data Lazy tables a Source #

Constructors

Lazy 

Fields

Instances
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 #

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 

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 RecordId t Source #

Constructors

Id t 
Remove t 
Instances
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 => Show (RecordId t) Source # 
Instance details

Defined in Knit

Methods

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

show :: RecordId t -> String #

showList :: [RecordId t] -> ShowS #

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 #

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

Defined in Knit

Methods

rnf :: RecordId t -> () #

type Rep (RecordId t) Source # 
Instance details

Defined in Knit

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

Constructors

ForeignId t 
Instances
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 #

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 #

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 #

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 #

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 #

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

Defined in Knit

Methods

rnf :: 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.1.0.0-IeVUuDIPBWkGBI6KyrmIF7" True) (C1 (MetaCons "ForeignId" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 t)))

data ResolveError Source #

Constructors

MissingIds [(TableName, FieldName, FieldValue)] 
RepeatingIds [(TableName, FieldName, FieldValue)] 
Instances
Show ResolveError Source # 
Instance details

Defined in Knit

Generic ResolveError Source # 
Instance details

Defined in Knit

Associated Types

type Rep ResolveError :: Type -> Type #

NFData ResolveError Source # 
Instance details

Defined in Knit

Methods

rnf :: ResolveError -> () #

type Rep ResolveError Source # 
Instance details

Defined in Knit