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
- toTuple :: a -> RelationTuple
- fromTuple :: RelationTuple -> Either RelationalError a
- toAttributes :: Proxy a -> Attributes
- genericToTuple :: (Generic a, TupleableG (Rep a)) => TupleableOptions -> a -> RelationTuple
- genericFromTuple :: (Generic a, TupleableG (Rep a)) => TupleableOptions -> RelationTuple -> Either RelationalError a
- genericToAttributes :: forall a. (Generic a, TupleableG (Rep a)) => TupleableOptions -> Proxy a -> Attributes
- class TupleableG g where
- toTupleG :: TupleableOptions -> g a -> RelationTuple
- toAttributesG :: TupleableOptions -> g a -> Attributes
- fromTupleG :: TupleableOptions -> RelationTuple -> Either RelationalError (g a)
- isRecordTypeG :: g a -> Bool
- defaultTupleableOptions :: TupleableOptions
- data TupleableOptions
- fieldModifier :: TupleableOptions -> Text -> Text
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 #
Types that can be converted to and from RelationTuple
.
deriving without customization:
data Example = Example { foo :: Integer , bar :: Text } deriving (Generic) instance Tupleable Example
deriving with customization using ProjectM36.Tupleable.Deriving:
data Example = Example { exampleFoo :: Integer , exampleBar :: Text } deriving stock (Generic) deriving (Tupleable) via Codec (Field (DropPrefix "example" >>> CamelCase)) Example
Nothing
toTuple :: a -> RelationTuple Source #
default toTuple :: (Generic a, TupleableG (Rep a)) => a -> RelationTuple Source #
fromTuple :: RelationTuple -> Either RelationalError a Source #
default fromTuple :: (Generic a, TupleableG (Rep a)) => RelationTuple -> Either RelationalError a Source #
toAttributes :: Proxy a -> Attributes Source #
default toAttributes :: (Generic a, TupleableG (Rep a)) => Proxy a -> Attributes Source #
Instances
(ModifyOptions tag, Generic a, TupleableG (Rep a)) => Tupleable (Codec tag a) Source # | |
Defined in ProjectM36.Tupleable.Deriving toTuple :: Codec tag a -> RelationTuple Source # fromTuple :: RelationTuple -> Either RelationalError (Codec tag a) Source # toAttributes :: Proxy (Codec tag a) -> Attributes Source # |
Generics
genericToTuple :: (Generic a, TupleableG (Rep a)) => TupleableOptions -> a -> RelationTuple Source #
genericFromTuple :: (Generic a, TupleableG (Rep a)) => TupleableOptions -> RelationTuple -> Either RelationalError a Source #
genericToAttributes :: forall a. (Generic a, TupleableG (Rep a)) => TupleableOptions -> Proxy a -> Attributes Source #
class TupleableG g where Source #
toTupleG :: TupleableOptions -> g a -> RelationTuple Source #
toAttributesG :: TupleableOptions -> g a -> Attributes Source #
fromTupleG :: TupleableOptions -> RelationTuple -> Either RelationalError (g a) Source #
isRecordTypeG :: g a -> Bool Source #
Instances
Options
defaultTupleableOptions :: TupleableOptions Source #
The default options for deriving Tupleable instances.
These options can be customized by using record update syntax. For example,
defaultTupleableOptions { fieldModifier = \fieldName -> case Data.Text.stripPrefix "example" fieldName of Nothing -> fieldName Just attributeName -> attributeName }
will result in record field names being translated into attribute names by removing the prefix "example" from the field names.
data TupleableOptions Source #
Options that influence deriving behavior.
fieldModifier :: TupleableOptions -> Text -> Text Source #
A function that translates record field names into attribute names.