Safe Haskell | None |
---|---|
Language | Haskell2010 |
- toInsertExpr :: forall a t. (Tupleable a, Traversable t) => t a -> RelVarName -> Either RelationalError DatabaseContextExpr
- toDefineExpr :: forall a proxy. Tupleable a => proxy a -> RelVarName -> DatabaseContextExpr
- class Tupleable a where
- class TupleableG g where
Documentation
toInsertExpr :: forall a t. (Tupleable a, Traversable t) => t a -> RelVarName -> Either RelationalError DatabaseContextExpr Source #
Convert a Traverseable
of Tupleable
s to an Insert
DatabaseContextExpr
. This is useful for converting, for example, a list of data values to a set of Insert expressions which can be used to add the values to the database.
toDefineExpr :: forall a proxy. Tupleable a => proxy a -> RelVarName -> DatabaseContextExpr Source #
Convert a Tupleable
to a create a Define
expression which can be used to create an empty relation variable. Use toInsertExpr
to insert the actual tuple data. This function is typically used with Proxy
.
class Tupleable a where Source #
toTuple :: a -> RelationTuple Source #
fromTuple :: RelationTuple -> Either RelationalError a Source #
toAttributes :: proxy a -> Attributes Source #
toTuple :: (Generic a, TupleableG (Rep a)) => a -> RelationTuple Source #
fromTuple :: (Generic a, TupleableG (Rep a)) => RelationTuple -> Either RelationalError a Source #
toAttributes :: (Generic a, TupleableG (Rep a)) => proxy a -> Attributes Source #
class TupleableG g where Source #
toTupleG :: g a -> RelationTuple Source #
toAttributesG :: g a -> Attributes Source #
fromTupleG :: RelationTuple -> Either RelationalError (g a) Source #
TupleableG U1 Source # | |
(TupleableG a, TupleableG b) => TupleableG ((:*:) a b) Source # | |
(Datatype Meta c, TupleableG a) => TupleableG (M1 D c a) Source # | |
(Constructor Meta c, TupleableG a, AtomableG * a) => TupleableG (M1 C c a) Source # | |
(Selector Meta c, AtomableG * a) => TupleableG (M1 S c a) Source # | |