| Safe Haskell | None | 
|---|---|
| Language | Haskell2010 | 
Database.Beam.Backend.SQL.Row
Contents
Synopsis
- data FromBackendRowF be f where
- ParseOneField :: (BackendFromField be a, Typeable a) => (a -> f) -> FromBackendRowF be f
 - Alt :: FromBackendRowM be a -> FromBackendRowM be a -> (a -> f) -> FromBackendRowF be f
 - FailParseWith :: BeamRowReadError -> FromBackendRowF be f
 
 - newtype FromBackendRowM be a = FromBackendRowM (F (FromBackendRowF be) a)
 - parseOneField :: (BackendFromField be a, Typeable a) => FromBackendRowM be a
 - peekField :: (Typeable a, BackendFromField be a) => FromBackendRowM be (Maybe a)
 - data ColumnParseError
 - data BeamRowReadError = BeamRowReadError {
- brreColumn :: !(Maybe Int)
 - brreError :: !ColumnParseError
 
 - class BeamBackend be => FromBackendRow be a where
- fromBackendRow :: FromBackendRowM be a
 - valuesNeeded :: Proxy be -> Proxy a -> Int
 
 
Documentation
data FromBackendRowF be f where Source #
Constructors
| ParseOneField :: (BackendFromField be a, Typeable a) => (a -> f) -> FromBackendRowF be f | |
| Alt :: FromBackendRowM be a -> FromBackendRowM be a -> (a -> f) -> FromBackendRowF be f | |
| FailParseWith :: BeamRowReadError -> FromBackendRowF be f | 
Instances
| Functor (FromBackendRowF be) Source # | |
Defined in Database.Beam.Backend.SQL.Row Methods fmap :: (a -> b) -> FromBackendRowF be a -> FromBackendRowF be b # (<$) :: a -> FromBackendRowF be b -> FromBackendRowF be a #  | |
newtype FromBackendRowM be a Source #
Constructors
| FromBackendRowM (F (FromBackendRowF be) a) | 
Instances
parseOneField :: (BackendFromField be a, Typeable a) => FromBackendRowM be a Source #
peekField :: (Typeable a, BackendFromField be a) => FromBackendRowM be (Maybe a) Source #
data ColumnParseError Source #
The exact error encountered
Constructors
| ColumnUnexpectedNull | |
| ColumnNotEnoughColumns !Int | |
| ColumnTypeMismatch | |
Fields 
  | |
| ColumnErrorInternal String | |
Instances
| Eq ColumnParseError Source # | |
Defined in Database.Beam.Backend.SQL.Row Methods (==) :: ColumnParseError -> ColumnParseError -> Bool # (/=) :: ColumnParseError -> ColumnParseError -> Bool #  | |
| Ord ColumnParseError Source # | |
Defined in Database.Beam.Backend.SQL.Row Methods compare :: ColumnParseError -> ColumnParseError -> Ordering # (<) :: ColumnParseError -> ColumnParseError -> Bool # (<=) :: ColumnParseError -> ColumnParseError -> Bool # (>) :: ColumnParseError -> ColumnParseError -> Bool # (>=) :: ColumnParseError -> ColumnParseError -> Bool # max :: ColumnParseError -> ColumnParseError -> ColumnParseError # min :: ColumnParseError -> ColumnParseError -> ColumnParseError #  | |
| Show ColumnParseError Source # | |
Defined in Database.Beam.Backend.SQL.Row Methods showsPrec :: Int -> ColumnParseError -> ShowS # show :: ColumnParseError -> String # showList :: [ColumnParseError] -> ShowS #  | |
data BeamRowReadError Source #
An error that may occur when parsing a row. Contains an optional annotation of which column was being parsed (if available).
Constructors
| BeamRowReadError | |
Fields 
  | |
Instances
class BeamBackend be => FromBackendRow be a where Source #
Minimal complete definition
Nothing
Methods
fromBackendRow :: FromBackendRowM be a Source #
Parses a beam row. This should not fail, except in the case of
 an internal bug in beam deserialization code. If it does fail,
 this should throw a BeamRowParseError.
default fromBackendRow :: (Typeable a, BackendFromField be a) => FromBackendRowM be a Source #