Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- toInsertExpr :: forall a t. (Tupleable a, Traversable t) => t a -> RelVarName -> Either RelationalError DatabaseContextExpr
- toDefineExpr :: forall a proxy. Tupleable a => proxy a -> RelVarName -> DatabaseContextExpr
- tupleAssocsEqualityPredicate :: [(AttributeName, Atom)] -> RestrictionPredicateExpr
- partitionByAttributes :: Tupleable a => [AttributeName] -> a -> ([(AttributeName, Atom)], [(AttributeName, Atom)])
- toUpdateExpr :: forall a. Tupleable a => RelVarName -> [AttributeName] -> a -> Either RelationalError DatabaseContextExpr
- toDeleteExpr :: forall a. Tupleable a => RelVarName -> [AttributeName] -> a -> Either RelationalError DatabaseContextExpr
- validateAttributes :: Set AttributeName -> Set AttributeName -> a -> Either RelationalError a
- 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
.
partitionByAttributes :: Tupleable a => [AttributeName] -> a -> ([(AttributeName, Atom)], [(AttributeName, Atom)]) Source #
toUpdateExpr :: forall a. Tupleable a => RelVarName -> [AttributeName] -> a -> Either RelationalError DatabaseContextExpr Source #
toDeleteExpr :: forall a. Tupleable a => RelVarName -> [AttributeName] -> a -> Either RelationalError DatabaseContextExpr Source #
validateAttributes :: Set AttributeName -> Set AttributeName -> a -> Either RelationalError a Source #
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 #
isRecordTypeG :: g a -> Bool Source #