Safe Haskell | None |
---|---|
Language | Haskell2010 |
ProjectM36.Atomable
Synopsis
- class (Eq a, NFData a, Binary a, Show a) => Atomable a where
- toAtom :: a -> Atom
- fromAtom :: Atom -> a
- toAtomType :: proxy a -> AtomType
- toAddTypeExpr :: proxy a -> DatabaseContextExpr
- class AtomableG g where
- toAtomG :: g a -> AtomType -> Atom
- fromAtomG :: Atom -> [Atom] -> Maybe (g a)
- toAtomTypeG :: g a -> AtomType
- toAtomsG :: g a -> [Atom]
- toAddTypeExprG :: g a -> AtomType -> DatabaseContextExpr
- getConstructorsG :: g a -> [DataConstructorDef]
- getConstructorArgsG :: g a -> [DataConstructorDefArg]
- typeToTypeConstructor :: AtomType -> TypeConstructor
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.
Minimal complete definition
Nothing
Methods
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 # | |
Atomable Double Source # | |
Atomable Int Source # | |
Atomable Integer Source # | |
Atomable ByteString Source # | |
Defined in ProjectM36.Atomable Methods toAtom :: ByteString -> Atom Source # fromAtom :: Atom -> ByteString Source # toAtomType :: proxy ByteString -> AtomType Source # toAddTypeExpr :: proxy ByteString -> DatabaseContextExpr Source # | |
Atomable Text Source # | |
Atomable UTCTime Source # | |
Atomable Day Source # | |
Atomable a => Atomable [a] Source # | |
Defined in ProjectM36.Atomable | |
Atomable a => Atomable (Maybe a) Source # | |
Atomable a => Atomable (NonEmpty a) Source # | |
(Atomable a, Atomable b) => Atomable (Either a b) Source # | |
class AtomableG g where Source #
Methods
toAtomG :: g a -> AtomType -> Atom Source #
fromAtomG :: Atom -> [Atom] -> Maybe (g a) Source #
toAtomTypeG :: g a -> AtomType Source #
toAtomsG :: g a -> [Atom] Source #
toAddTypeExprG :: g a -> AtomType -> DatabaseContextExpr Source #
getConstructorsG :: g a -> [DataConstructorDef] Source #
getConstructorArgsG :: g a -> [DataConstructorDefArg] Source #