groundhog-0.8.0.1: Type-safe datatype-database mapping library.

Safe HaskellNone
LanguageHaskell98

Database.Groundhog.Instances

Contents

Orphan instances

ToJSON PersistValue Source # 
FromJSON PersistValue Source # 
PrimitivePersistField Bool Source # 
PrimitivePersistField Double Source # 
PrimitivePersistField Int Source # 
PrimitivePersistField Int8 Source # 
PrimitivePersistField Int16 Source # 
PrimitivePersistField Int32 Source # 
PrimitivePersistField Int64 Source # 
PrimitivePersistField Word8 Source # 
PrimitivePersistField Word16 Source # 
PrimitivePersistField Word32 Source # 
PrimitivePersistField Word64 Source # 
PrimitivePersistField ByteString Source # 
PrimitivePersistField ByteString Source # 
PrimitivePersistField String Source # 
PrimitivePersistField Text Source # 
PrimitivePersistField UTCTime Source # 
PrimitivePersistField Text Source # 
PrimitivePersistField ZonedTime Source # 
PrimitivePersistField TimeOfDay Source # 
PrimitivePersistField Day Source # 
PurePersistField () Source # 
(PersistField a, PrimitivePersistField a) => PurePersistField a Source # 
(PersistField a, PrimitivePersistField a) => SinglePersistField a Source # 
PersistField Bool Source # 
PersistField Double Source # 
PersistField Int Source # 
PersistField Int8 Source # 
PersistField Int16 Source # 
PersistField Int32 Source # 
PersistField Int64 Source # 
PersistField Word8 Source # 
PersistField Word16 Source # 
PersistField Word32 Source # 
PersistField Word64 Source # 
PersistField () Source # 
PersistField ByteString Source # 
PersistField ByteString Source # 
PersistField String Source # 
PersistField Text Source # 
PersistField UTCTime Source # 
PersistField Text Source # 
PersistField ZonedTime Source # 
PersistField TimeOfDay Source # 
PersistField Day Source # 
NeverNull Bool Source # 
NeverNull Double Source # 
NeverNull Int Source # 
NeverNull Int8 Source # 
NeverNull Int16 Source # 
NeverNull Int32 Source # 
NeverNull Int64 Source # 
NeverNull Word8 Source # 
NeverNull Word16 Source # 
NeverNull Word32 Source # 
NeverNull Word64 Source # 
NeverNull ByteString Source # 
NeverNull ByteString Source # 
NeverNull String Source # 
NeverNull Text Source # 
NeverNull UTCTime Source # 
NeverNull Text Source # 
NeverNull ZonedTime Source # 
NeverNull TimeOfDay Source # 
NeverNull Day Source # 
(PersistEntity v, EntityConstr' (IsSumType v) c) => EntityConstr v c Source # 

Methods

entityConstrNum :: proxy v -> c a -> Int Source #

(PrimitivePersistField a, NeverNull a) => PrimitivePersistField (Maybe a) Source # 
PersistField a => PersistField [a] Source # 
(PersistField a, NeverNull a) => PersistField (Maybe a) Source # 
(PersistEntity v, IsUniqueKey k, (~) * k (Key v (Unique u))) => FieldLike (u (UniqueMarker v)) k Source # 

Methods

fieldChain :: (DbDescriptor db, ProjectionDb (u (UniqueMarker v)) db) => proxy db -> u (UniqueMarker v) -> FieldChain Source #

(PersistEntity v, IsUniqueKey k, (~) * k (Key v (Unique u))) => Assignable (u (UniqueMarker v)) k Source # 
(PersistEntity v, IsUniqueKey k, (~) * k (Key v (Unique u))) => Projection (u (UniqueMarker v)) k Source # 
EntityConstr v c => Projection (c (ConstructorMarker v)) v Source # 
Show (Key v u) => ToJSON (Key v u) Source # 

Methods

toJSON :: Key v u -> Value #

toEncoding :: Key v u -> Encoding #

toJSONList :: [Key v u] -> Value #

toEncodingList :: [Key v u] -> Encoding #

Read (Key v u) => FromJSON (Key v u) Source # 

Methods

parseJSON :: Value -> Parser (Key v u) #

parseJSONList :: Value -> Parser [Key v u] #

(DbDescriptor db, PersistEntity v, PersistField v) => PrimitivePersistField (KeyForBackend db v) Source # 
(PurePersistField a, PurePersistField b) => PurePersistField (a, b) Source # 
(PersistField a, PersistField b) => PersistField (a, b) Source # 

Methods

persistName :: (a, b) -> String Source #

toPersistValues :: PersistBackend m => (a, b) -> m ([PersistValue] -> [PersistValue]) Source #

fromPersistValues :: PersistBackend m => [PersistValue] -> m ((a, b), [PersistValue]) Source #

dbType :: DbDescriptor db => proxy db -> (a, b) -> DbType Source #

(DbDescriptor db, PersistEntity v, PersistField v) => PersistField (KeyForBackend db v) Source # 
NeverNull (KeyForBackend db v) Source # 
PrimitivePersistField (Key v u) => NeverNull (Key v u) Source # 
(PersistField a', PersistField b') => Embedded (a', b') Source # 

Associated Types

data Selector (a', b') a :: * Source #

Methods

selectorNum :: Selector (a', b') a -> Int Source #

(EntityConstr v c, (~) * a (AutoKey v)) => FieldLike (AutoKeyField v c) a Source # 

Methods

fieldChain :: (DbDescriptor db, ProjectionDb (AutoKeyField v c) db) => proxy db -> AutoKeyField v c -> FieldChain Source #

(EntityConstr v c, (~) * a (AutoKey v)) => Assignable (AutoKeyField v c) a Source # 
(EntityConstr v c, (~) * a (AutoKey v)) => Projection (AutoKeyField v c) a Source # 
(~) * a Bool => Projection (Cond db r) a Source # 

Associated Types

type ProjectionDb (Cond db r) db :: Constraint Source #

type ProjectionRestriction (Cond db r) r :: Constraint Source #

(Projection a1 a1', Projection a2 a2') => Projection (a1, a2) (a1', a2') Source # 

Associated Types

type ProjectionDb (a1, a2) db :: Constraint Source #

type ProjectionRestriction (a1, a2) r :: Constraint Source #

Methods

projectionExprs :: (DbDescriptor db, ProjectionDb (a1, a2) db, ProjectionRestriction (a1, a2) r) => (a1, a2) -> [UntypedExpr db r] -> [UntypedExpr db r] Source #

projectionResult :: PersistBackend m => (a1, a2) -> [PersistValue] -> m ((a1', a2'), [PersistValue]) Source #

(PurePersistField a, PurePersistField b, PurePersistField c) => PurePersistField (a, b, c) Source # 
(PersistField a, PersistField b, PersistField c) => PersistField (a, b, c) Source # 

Methods

persistName :: (a, b, c) -> String Source #

toPersistValues :: PersistBackend m => (a, b, c) -> m ([PersistValue] -> [PersistValue]) Source #

fromPersistValues :: PersistBackend m => [PersistValue] -> m ((a, b, c), [PersistValue]) Source #

dbType :: DbDescriptor db => proxy db -> (a, b, c) -> DbType Source #

(PersistField a', PersistField b', PersistField c') => Embedded (a', b', c') Source # 

Associated Types

data Selector (a', b', c') a :: * Source #

Methods

selectorNum :: Selector (a', b', c') a -> Int Source #

(EntityConstr v c, PersistField a) => FieldLike (Field v c a) a Source # 

Methods

fieldChain :: (DbDescriptor db, ProjectionDb (Field v c a) db) => proxy db -> Field v c a -> FieldChain Source #

(EntityConstr v c, PersistField a) => Assignable (Field v c a) a Source # 
PersistField a => Projection (Expr db r a) a Source # 

Associated Types

type ProjectionDb (Expr db r a) db :: Constraint Source #

type ProjectionRestriction (Expr db r a) r :: Constraint Source #

Methods

projectionExprs :: (DbDescriptor db, ProjectionDb (Expr db r a) db, ProjectionRestriction (Expr db r a) r) => Expr db r a -> [UntypedExpr db r] -> [UntypedExpr db r] Source #

projectionResult :: PersistBackend m => Expr db r a -> [PersistValue] -> m (a, [PersistValue]) Source #

(EntityConstr v c, PersistField a) => Projection (Field v c a) a Source # 

Associated Types

type ProjectionDb (Field v c a) db :: Constraint Source #

type ProjectionRestriction (Field v c a) r :: Constraint Source #

Methods

projectionExprs :: (DbDescriptor db, ProjectionDb (Field v c a) db, ProjectionRestriction (Field v c a) r) => Field v c a -> [UntypedExpr db r] -> [UntypedExpr db r] Source #

projectionResult :: PersistBackend m => Field v c a -> [PersistValue] -> m (a, [PersistValue]) Source #

(Projection a1 a1', Projection a2 a2', Projection a3 a3') => Projection (a1, a2, a3) (a1', a2', a3') Source # 

Associated Types

type ProjectionDb (a1, a2, a3) db :: Constraint Source #

type ProjectionRestriction (a1, a2, a3) r :: Constraint Source #

Methods

projectionExprs :: (DbDescriptor db, ProjectionDb (a1, a2, a3) db, ProjectionRestriction (a1, a2, a3) r) => (a1, a2, a3) -> [UntypedExpr db r] -> [UntypedExpr db r] Source #

projectionResult :: PersistBackend m => (a1, a2, a3) -> [PersistValue] -> m ((a1', a2', a3'), [PersistValue]) Source #

(PurePersistField a, PurePersistField b, PurePersistField c, PurePersistField d) => PurePersistField (a, b, c, d) Source # 
(PersistField a, PersistField b, PersistField c, PersistField d) => PersistField (a, b, c, d) Source # 

Methods

persistName :: (a, b, c, d) -> String Source #

toPersistValues :: PersistBackend m => (a, b, c, d) -> m ([PersistValue] -> [PersistValue]) Source #

fromPersistValues :: PersistBackend m => [PersistValue] -> m ((a, b, c, d), [PersistValue]) Source #

dbType :: DbDescriptor db => proxy db -> (a, b, c, d) -> DbType Source #

(PersistField a', PersistField b', PersistField c', PersistField d') => Embedded (a', b', c', d') Source # 

Associated Types

data Selector (a', b', c', d') a :: * Source #

Methods

selectorNum :: Selector (a', b', c', d') a -> Int Source #

(EntityConstr v c, PersistField a) => FieldLike (SubField db v c a) a Source # 

Methods

fieldChain :: (DbDescriptor db, ProjectionDb (SubField db v c a) db) => proxy db -> SubField db v c a -> FieldChain Source #

(EntityConstr v c, PersistField a) => Assignable (SubField db v c a) a Source # 
(EntityConstr v c, PersistField a) => Projection (SubField db v c a) a Source # 

Associated Types

type ProjectionDb (SubField db v c a) db :: Constraint Source #

type ProjectionRestriction (SubField db v c a) r :: Constraint Source #

Methods

projectionExprs :: (DbDescriptor db, ProjectionDb (SubField db v c a) db, ProjectionRestriction (SubField db v c a) r) => SubField db v c a -> [UntypedExpr db r] -> [UntypedExpr db r] Source #

projectionResult :: PersistBackend m => SubField db v c a -> [PersistValue] -> m (a, [PersistValue]) Source #

(Projection a1 a1', Projection a2 a2', Projection a3 a3', Projection a4 a4') => Projection (a1, a2, a3, a4) (a1', a2', a3', a4') Source # 

Associated Types

type ProjectionDb (a1, a2, a3, a4) db :: Constraint Source #

type ProjectionRestriction (a1, a2, a3, a4) r :: Constraint Source #

Methods

projectionExprs :: (DbDescriptor db, ProjectionDb (a1, a2, a3, a4) db, ProjectionRestriction (a1, a2, a3, a4) r) => (a1, a2, a3, a4) -> [UntypedExpr db r] -> [UntypedExpr db r] Source #

projectionResult :: PersistBackend m => (a1, a2, a3, a4) -> [PersistValue] -> m ((a1', a2', a3', a4'), [PersistValue]) Source #

(PurePersistField a, PurePersistField b, PurePersistField c, PurePersistField d, PurePersistField e) => PurePersistField (a, b, c, d, e) Source # 

Methods

toPurePersistValues :: (a, b, c, d, e) -> [PersistValue] -> [PersistValue] Source #

fromPurePersistValues :: [PersistValue] -> ((a, b, c, d, e), [PersistValue]) Source #

(PersistField a, PersistField b, PersistField c, PersistField d, PersistField e) => PersistField (a, b, c, d, e) Source # 

Methods

persistName :: (a, b, c, d, e) -> String Source #

toPersistValues :: PersistBackend m => (a, b, c, d, e) -> m ([PersistValue] -> [PersistValue]) Source #

fromPersistValues :: PersistBackend m => [PersistValue] -> m ((a, b, c, d, e), [PersistValue]) Source #

dbType :: DbDescriptor db => proxy db -> (a, b, c, d, e) -> DbType Source #

(PersistField a', PersistField b', PersistField c', PersistField d', PersistField e') => Embedded (a', b', c', d', e') Source # 

Associated Types

data Selector (a', b', c', d', e') a :: * Source #

Methods

selectorNum :: Selector (a', b', c', d', e') a -> Int Source #

(Projection a1 a1', Projection a2 a2', Projection a3 a3', Projection a4 a4', Projection a5 a5') => Projection (a1, a2, a3, a4, a5) (a1', a2', a3', a4', a5') Source # 

Associated Types

type ProjectionDb (a1, a2, a3, a4, a5) db :: Constraint Source #

type ProjectionRestriction (a1, a2, a3, a4, a5) r :: Constraint Source #

Methods

projectionExprs :: (DbDescriptor db, ProjectionDb (a1, a2, a3, a4, a5) db, ProjectionRestriction (a1, a2, a3, a4, a5) r) => (a1, a2, a3, a4, a5) -> [UntypedExpr db r] -> [UntypedExpr db r] Source #

projectionResult :: PersistBackend m => (a1, a2, a3, a4, a5) -> [PersistValue] -> m ((a1', a2', a3', a4', a5'), [PersistValue]) Source #