Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Synopsis
- class (Eq a, NFData a, Serialise 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, 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.
Nothing
fromAtom :: Atom -> a Source #
toAtomType :: 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
Atomable ByteString Source # | |
Defined in ProjectM36.Atomable toAtom :: ByteString -> Atom Source # fromAtom :: Atom -> ByteString Source # toAtomType :: proxy ByteString -> AtomType Source # toAddTypeExpr :: proxy ByteString -> DatabaseContextExpr Source # | |
Atomable Text Source # | |
Atomable Day Source # | |
Atomable UTCTime Source # | |
Atomable UUID Source # | |
Atomable Integer Source # | |
Atomable Bool Source # | |
Atomable Double Source # | |
Atomable Int Source # | |
Atomable a => Atomable (NonEmpty a) Source # | |
Atomable a => Atomable (Maybe a) Source # | |
Atomable a => Atomable [a] Source # | |
Defined in ProjectM36.Atomable | |
(Atomable a, Atomable b) => Atomable (Either a b) Source # | |
class AtomableG g where Source #
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 #
Instances
AtomableG (U1 :: k -> Type) Source # | |
Defined in ProjectM36.Atomable 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 # | |
Defined in ProjectM36.Atomable 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 # | |
Defined in ProjectM36.Atomable 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 # | |
Defined in ProjectM36.Atomable 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 # | |
(Constructor c, AtomableG a) => AtomableG (M1 C c a :: k -> Type) Source # | |
Defined in ProjectM36.Atomable 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 # | |
Defined in ProjectM36.Atomable 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 # | |
(Selector c, AtomableG a) => AtomableG (M1 S c a :: k -> Type) Source # | |
Defined in ProjectM36.Atomable 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 # |