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

ProjectM36.Atomable

Synopsis

Documentation

class (Eq a, NFData a, Serialise a, Show a) => Atomable a where Source #

All database values ("atoms") adhere to the Atomable typeclass. This class is derivable allowing new datatypes to be easily marshaling between Haskell values and database values.

Minimal complete definition

Nothing

Methods

toAtom :: a -> Atom Source #

default toAtom :: (Generic a, AtomableG (Rep a)) => a -> Atom Source #

fromAtom :: Atom -> a Source #

default fromAtom :: (Generic a, AtomableG (Rep a)) => Atom -> a Source #

toAtomType :: proxy a -> AtomType Source #

default toAtomType :: (Generic a, AtomableG (Rep a)) => proxy a -> AtomType Source #

toAddTypeExpr :: proxy a -> DatabaseContextExpr Source #

Creates DatabaseContextExpr necessary to load the type constructor and data constructor into the database.

default toAddTypeExpr :: (Generic a, AtomableG (Rep a)) => proxy a -> DatabaseContextExpr Source #

Instances

Instances details
Atomable Bool Source # 
Instance details

Defined in ProjectM36.Atomable

Atomable Double Source # 
Instance details

Defined in ProjectM36.Atomable

Atomable Int Source # 
Instance details

Defined in ProjectM36.Atomable

Atomable Integer Source # 
Instance details

Defined in ProjectM36.Atomable

Atomable ByteString Source # 
Instance details

Defined in ProjectM36.Atomable

Atomable UTCTime Source # 
Instance details

Defined in ProjectM36.Atomable

Atomable Text Source # 
Instance details

Defined in ProjectM36.Atomable

Atomable Day Source # 
Instance details

Defined in ProjectM36.Atomable

Atomable UUID Source # 
Instance details

Defined in ProjectM36.Atomable

Atomable a => Atomable [a] Source # 
Instance details

Defined in ProjectM36.Atomable

Methods

toAtom :: [a] -> Atom Source #

fromAtom :: Atom -> [a] Source #

toAtomType :: proxy [a] -> AtomType Source #

toAddTypeExpr :: proxy [a] -> DatabaseContextExpr Source #

Atomable a => Atomable (Maybe a) Source # 
Instance details

Defined in ProjectM36.Atomable

Atomable a => Atomable (NonEmpty a) Source # 
Instance details

Defined in ProjectM36.Atomable

(Atomable a, Atomable b) => Atomable (Either a b) Source # 
Instance details

Defined in ProjectM36.Atomable

class AtomableG g where Source #

Instances

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

Defined in ProjectM36.Atomable

Methods

toAtomG :: forall (a :: k0). U1 a -> AtomType -> Atom Source #

fromAtomG :: forall (a :: k0). Atom -> [Atom] -> Maybe (U1 a) Source #

toAtomTypeG :: forall (a :: k0). U1 a -> AtomType Source #

toAtomsG :: forall (a :: k0). U1 a -> [Atom] Source #

toAddTypeExprG :: forall (a :: k0). U1 a -> AtomType -> DatabaseContextExpr Source #

getConstructorsG :: forall (a :: k0). U1 a -> [DataConstructorDef] Source #

getConstructorArgsG :: forall (a :: k0). U1 a -> [DataConstructorDefArg] Source #

(AtomableG a, AtomableG b) => AtomableG (a :+: b :: k -> Type) Source # 
Instance details

Defined in ProjectM36.Atomable

Methods

toAtomG :: forall (a0 :: k0). (a :+: b) a0 -> AtomType -> Atom Source #

fromAtomG :: forall (a0 :: k0). Atom -> [Atom] -> Maybe ((a :+: b) a0) Source #

toAtomTypeG :: forall (a0 :: k0). (a :+: b) a0 -> AtomType Source #

toAtomsG :: forall (a0 :: k0). (a :+: b) a0 -> [Atom] Source #

toAddTypeExprG :: forall (a0 :: k0). (a :+: b) a0 -> AtomType -> DatabaseContextExpr Source #

getConstructorsG :: forall (a0 :: k0). (a :+: b) a0 -> [DataConstructorDef] Source #

getConstructorArgsG :: forall (a0 :: k0). (a :+: b) a0 -> [DataConstructorDefArg] Source #

(AtomableG a, AtomableG b) => AtomableG (a :*: b :: k -> Type) Source # 
Instance details

Defined in ProjectM36.Atomable

Methods

toAtomG :: forall (a0 :: k0). (a :*: b) a0 -> AtomType -> Atom Source #

fromAtomG :: forall (a0 :: k0). Atom -> [Atom] -> Maybe ((a :*: b) a0) Source #

toAtomTypeG :: forall (a0 :: k0). (a :*: b) a0 -> AtomType Source #

toAtomsG :: forall (a0 :: k0). (a :*: b) a0 -> [Atom] Source #

toAddTypeExprG :: forall (a0 :: k0). (a :*: b) a0 -> AtomType -> DatabaseContextExpr Source #

getConstructorsG :: forall (a0 :: k0). (a :*: b) a0 -> [DataConstructorDef] Source #

getConstructorArgsG :: forall (a0 :: k0). (a :*: b) a0 -> [DataConstructorDefArg] Source #

Atomable a => AtomableG (K1 c a :: k -> Type) Source # 
Instance details

Defined in ProjectM36.Atomable

Methods

toAtomG :: forall (a0 :: k0). K1 c a a0 -> AtomType -> Atom Source #

fromAtomG :: forall (a0 :: k0). Atom -> [Atom] -> Maybe (K1 c a a0) Source #

toAtomTypeG :: forall (a0 :: k0). K1 c a a0 -> AtomType Source #

toAtomsG :: forall (a0 :: k0). K1 c a a0 -> [Atom] Source #

toAddTypeExprG :: forall (a0 :: k0). K1 c a a0 -> AtomType -> DatabaseContextExpr Source #

getConstructorsG :: forall (a0 :: k0). K1 c a a0 -> [DataConstructorDef] Source #

getConstructorArgsG :: forall (a0 :: k0). K1 c a a0 -> [DataConstructorDefArg] Source #

(Selector c, AtomableG a) => AtomableG (M1 S c a :: k -> Type) Source # 
Instance details

Defined in ProjectM36.Atomable

Methods

toAtomG :: forall (a0 :: k0). M1 S c a a0 -> AtomType -> Atom Source #

fromAtomG :: forall (a0 :: k0). Atom -> [Atom] -> Maybe (M1 S c a a0) Source #

toAtomTypeG :: forall (a0 :: k0). M1 S c a a0 -> AtomType Source #

toAtomsG :: forall (a0 :: k0). M1 S c a a0 -> [Atom] Source #

toAddTypeExprG :: forall (a0 :: k0). M1 S c a a0 -> AtomType -> DatabaseContextExpr Source #

getConstructorsG :: forall (a0 :: k0). M1 S c a a0 -> [DataConstructorDef] Source #

getConstructorArgsG :: forall (a0 :: k0). M1 S c a a0 -> [DataConstructorDefArg] Source #

(Constructor c, AtomableG a) => AtomableG (M1 C c a :: k -> Type) Source # 
Instance details

Defined in ProjectM36.Atomable

Methods

toAtomG :: forall (a0 :: k0). M1 C c a a0 -> AtomType -> Atom Source #

fromAtomG :: forall (a0 :: k0). Atom -> [Atom] -> Maybe (M1 C c a a0) Source #

toAtomTypeG :: forall (a0 :: k0). M1 C c a a0 -> AtomType Source #

toAtomsG :: forall (a0 :: k0). M1 C c a a0 -> [Atom] Source #

toAddTypeExprG :: forall (a0 :: k0). M1 C c a a0 -> AtomType -> DatabaseContextExpr Source #

getConstructorsG :: forall (a0 :: k0). M1 C c a a0 -> [DataConstructorDef] Source #

getConstructorArgsG :: forall (a0 :: k0). M1 C c a a0 -> [DataConstructorDefArg] Source #

(Datatype c, AtomableG a) => AtomableG (M1 D c a :: k -> Type) Source # 
Instance details

Defined in ProjectM36.Atomable

Methods

toAtomG :: forall (a0 :: k0). M1 D c a a0 -> AtomType -> Atom Source #

fromAtomG :: forall (a0 :: k0). Atom -> [Atom] -> Maybe (M1 D c a a0) Source #

toAtomTypeG :: forall (a0 :: k0). M1 D c a a0 -> AtomType Source #

toAtomsG :: forall (a0 :: k0). M1 D c a a0 -> [Atom] Source #

toAddTypeExprG :: forall (a0 :: k0). M1 D c a a0 -> AtomType -> DatabaseContextExpr Source #

getConstructorsG :: forall (a0 :: k0). M1 D c a a0 -> [DataConstructorDef] Source #

getConstructorArgsG :: forall (a0 :: k0). M1 D c a a0 -> [DataConstructorDefArg] Source #