project-m36-0.9.4: Relational Algebra Engine
Safe HaskellNone
LanguageHaskell2010

ProjectM36.Tupleable

Synopsis

Documentation

toInsertExpr :: forall a t. (Tupleable a, Traversable t) => t a -> RelVarName -> Either RelationalError DatabaseContextExpr Source #

Convert a Traverseable of Tupleables 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.

toUpdateExpr :: forall a. Tupleable a => RelVarName -> [AttributeName] -> a -> Either RelationalError DatabaseContextExpr Source #

Convert a list of key attributes and a Tupleable value to an Update expression. This expression flushes the non-key attributes of the value to a tuple with the matching key attributes.

toDeleteExpr :: forall a. Tupleable a => RelVarName -> [AttributeName] -> a -> Either RelationalError DatabaseContextExpr Source #

Convert a list of key attributes and a Tupleable value to a Delete expression. This expression deletes tuples matching the key attributes from the value.

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

Minimal complete definition

Nothing

Instances

Instances details
(ModifyOptions tag, Generic a, TupleableG (Rep a)) => Tupleable (Codec tag a) Source # 
Instance details

Defined in ProjectM36.Tupleable.Deriving

Generics

class TupleableG g where Source #

Instances

Instances details
TupleableG (U1 :: Type -> Type) Source # 
Instance details

Defined in ProjectM36.Tupleable

(TupleableG a, TupleableG b) => TupleableG (a :*: b) Source # 
Instance details

Defined in ProjectM36.Tupleable

(Datatype c, TupleableG a) => TupleableG (M1 D c a) Source # 
Instance details

Defined in ProjectM36.Tupleable

(Constructor c, TupleableG a, AtomableG a) => TupleableG (M1 C c a) Source # 
Instance details

Defined in ProjectM36.Tupleable

(Selector c, AtomableG a) => TupleableG (M1 S c a) Source # 
Instance details

Defined in ProjectM36.Tupleable

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.