project-m36-0.7: Relational Algebra Engine

Safe HaskellNone
LanguageHaskell2010

ProjectM36.Atomable

Synopsis

Documentation

class (Eq a, NFData a, Binary 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.

Methods

toAtom :: a -> Atom Source #

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

fromAtom :: Atom -> a Source #

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

toAtomType :: proxy a -> AtomType Source #

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.

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

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

Instances
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 Text Source # 
Instance details

Defined in ProjectM36.Atomable

Atomable UTCTime Source # 
Instance details

Defined in ProjectM36.Atomable

Atomable Day 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
AtomableG (U1 :: k -> *) Source # 
Instance details

Defined in ProjectM36.Atomable

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

Defined in ProjectM36.Atomable

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

Defined in ProjectM36.Atomable

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

Defined in ProjectM36.Atomable

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

Defined in ProjectM36.Atomable

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

Defined in ProjectM36.Atomable

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

Defined in ProjectM36.Atomable