Safe Haskell | None |
---|---|
Language | Haskell2010 |
- class BeamBackend be where
- type BackendFromField be :: * -> Constraint
- data FromBackendRowF be f where
- ParseOneField :: BackendFromField be a => (a -> f) -> FromBackendRowF be f
- PeekField :: BackendFromField be a => (Maybe a -> f) -> FromBackendRowF be f
- CheckNextNNull :: Int -> (Bool -> f) -> FromBackendRowF be f
- type FromBackendRowM be = F (FromBackendRowF be)
- parseOneField :: BackendFromField be a => FromBackendRowM be a
- peekField :: BackendFromField be a => FromBackendRowM be (Maybe a)
- checkNextNNull :: Int -> FromBackendRowM be Bool
- class BeamBackend be => FromBackendRow be a where
- data Exposed x
- data Nullable (c :: * -> *) x
Documentation
class BeamBackend be Source #
Class for all beam backends
type BackendFromField be :: * -> Constraint Source #
Requirements to marshal a certain type from a database of a particular backend
data FromBackendRowF be f where Source #
ParseOneField :: BackendFromField be a => (a -> f) -> FromBackendRowF be f | |
PeekField :: BackendFromField be a => (Maybe a -> f) -> FromBackendRowF be f | |
CheckNextNNull :: Int -> (Bool -> f) -> FromBackendRowF be f |
Functor (FromBackendRowF be) Source # | |
type FromBackendRowM be = F (FromBackendRowF be) Source #
parseOneField :: BackendFromField be a => FromBackendRowM be a Source #
peekField :: BackendFromField be a => FromBackendRowM be (Maybe a) Source #
checkNextNNull :: Int -> FromBackendRowM be Bool Source #
class BeamBackend be => FromBackendRow be a where Source #
fromBackendRow :: FromBackendRowM be a Source #
fromBackendRow :: BackendFromField be a => FromBackendRowM be a Source #
newtype mainly used to inspect tho tag structure of a particular
Beamable
. Prevents overlapping instances in some case. Usually not used
in end-user code.
FieldsFulfillConstraintNullable c t => GFieldsFulfillConstraint c (K1 * R (t (Nullable Exposed))) (K1 * R (t (Nullable Identity))) (K1 * R (t (Nullable (WithConstraint c)))) Source # | |
FieldsFulfillConstraint c t => GFieldsFulfillConstraint c (K1 * R (t Exposed)) (K1 * R (t Identity)) (K1 * R (t (WithConstraint c))) Source # | |
c x => GFieldsFulfillConstraint c (K1 * R (Exposed x)) (K1 * R x) (K1 * R (WithConstraint c x)) Source # | |
data Nullable (c :: * -> *) x Source #
Support for NULLable Foreign Key references.
data MyTable f = MyTable { nullableRef :: PrimaryKey AnotherTable (Nullable f) , ... } deriving (Generic, Typeable)
See Columnar
for more information.