beam-core-0.8.0.0: Type-safe, feature-complete SQL query and manipulation interface for Haskell

Safe HaskellNone
LanguageHaskell2010

Database.Beam.Backend.SQL.Row

Contents

Synopsis

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 # 
Instance details

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
Monad (FromBackendRowM be) Source # 
Instance details

Defined in Database.Beam.Backend.SQL.Row

Functor (FromBackendRowM be) Source # 
Instance details

Defined in Database.Beam.Backend.SQL.Row

Methods

fmap :: (a -> b) -> FromBackendRowM be a -> FromBackendRowM be b #

(<$) :: a -> FromBackendRowM be b -> FromBackendRowM be a #

Applicative (FromBackendRowM be) Source # 
Instance details

Defined in Database.Beam.Backend.SQL.Row

Methods

pure :: a -> FromBackendRowM be a #

(<*>) :: FromBackendRowM be (a -> b) -> FromBackendRowM be a -> FromBackendRowM be b #

liftA2 :: (a -> b -> c) -> FromBackendRowM be a -> FromBackendRowM be b -> FromBackendRowM be c #

(*>) :: FromBackendRowM be a -> FromBackendRowM be b -> FromBackendRowM be b #

(<*) :: FromBackendRowM be a -> FromBackendRowM be b -> FromBackendRowM be a #

Alternative (FromBackendRowM be) Source # 
Instance details

Defined in Database.Beam.Backend.SQL.Row

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.

fromBackendRow :: (Typeable a, BackendFromField be a) => 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.

valuesNeeded :: Proxy be -> Proxy a -> Int Source #

Instances
BeamBackend be => FromBackendRow be () Source # 
Instance details

Defined in Database.Beam.Backend.SQL.Row

FromBackendRow be x => FromBackendRow be (SqlSerial x) Source # 
Instance details

Defined in Database.Beam.Backend.SQL.Row

(FromBackendRow be x, FromBackendRow be SqlNull) => FromBackendRow be (Maybe x) Source # 
Instance details

Defined in Database.Beam.Backend.SQL.Row

(BeamBackend be, Generic (tbl (Nullable Identity)), Generic (tbl (Nullable Exposed)), GFromBackendRow be (Rep (tbl (Nullable Exposed))) (Rep (tbl (Nullable Identity)))) => FromBackendRow be (tbl (Nullable Identity)) Source # 
Instance details

Defined in Database.Beam.Backend.SQL.Row

(BeamBackend be, Generic (tbl Identity), Generic (tbl Exposed), GFromBackendRow be (Rep (tbl Exposed)) (Rep (tbl Identity))) => FromBackendRow be (tbl Identity) Source # 
Instance details

Defined in Database.Beam.Backend.SQL.Row

(BeamBackend be, FromBackendRow be a, FromBackendRow be b) => FromBackendRow be (a, b) Source # 
Instance details

Defined in Database.Beam.Backend.SQL.Row

Methods

fromBackendRow :: FromBackendRowM be (a, b) Source #

valuesNeeded :: Proxy be -> Proxy (a, b) -> Int Source #

(BeamBackend be, KnownNat n, FromBackendRow be a) => FromBackendRow be (Vector n a) Source # 
Instance details

Defined in Database.Beam.Backend.SQL.Row

(BeamBackend be, FromBackendRow be t) => FromBackendRow be (Tagged tag t) Source # 
Instance details

Defined in Database.Beam.Backend.SQL.Row

(BeamBackend be, FromBackendRow be a, FromBackendRow be b, FromBackendRow be c) => FromBackendRow be (a, b, c) Source # 
Instance details

Defined in Database.Beam.Backend.SQL.Row

Methods

fromBackendRow :: FromBackendRowM be (a, b, c) Source #

valuesNeeded :: Proxy be -> Proxy (a, b, c) -> Int Source #

(BeamBackend be, FromBackendRow be a, FromBackendRow be b, FromBackendRow be c, FromBackendRow be d) => FromBackendRow be (a, b, c, d) Source # 
Instance details

Defined in Database.Beam.Backend.SQL.Row

Methods

fromBackendRow :: FromBackendRowM be (a, b, c, d) Source #

valuesNeeded :: Proxy be -> Proxy (a, b, c, d) -> Int Source #

(BeamBackend be, FromBackendRow be a, FromBackendRow be b, FromBackendRow be c, FromBackendRow be d, FromBackendRow be e) => FromBackendRow be (a, b, c, d, e) Source # 
Instance details

Defined in Database.Beam.Backend.SQL.Row

Methods

fromBackendRow :: FromBackendRowM be (a, b, c, d, e) Source #

valuesNeeded :: Proxy be -> Proxy (a, b, c, d, e) -> Int Source #

(BeamBackend be, FromBackendRow be a, FromBackendRow be b, FromBackendRow be c, FromBackendRow be d, FromBackendRow be e, FromBackendRow be f) => FromBackendRow be (a, b, c, d, e, f) Source # 
Instance details

Defined in Database.Beam.Backend.SQL.Row

Methods

fromBackendRow :: FromBackendRowM be (a, b, c, d, e, f) Source #

valuesNeeded :: Proxy be -> Proxy (a, b, c, d, e, f) -> Int Source #

(BeamBackend be, FromBackendRow be a, FromBackendRow be b, FromBackendRow be c, FromBackendRow be d, FromBackendRow be e, FromBackendRow be f, FromBackendRow be g) => FromBackendRow be (a, b, c, d, e, f, g) Source # 
Instance details

Defined in Database.Beam.Backend.SQL.Row

Methods

fromBackendRow :: FromBackendRowM be (a, b, c, d, e, f, g) Source #

valuesNeeded :: Proxy be -> Proxy (a, b, c, d, e, f, g) -> Int Source #

(BeamBackend be, FromBackendRow be a, FromBackendRow be b, FromBackendRow be c, FromBackendRow be d, FromBackendRow be e, FromBackendRow be f, FromBackendRow be g, FromBackendRow be h) => FromBackendRow be (a, b, c, d, e, f, g, h) Source # 
Instance details

Defined in Database.Beam.Backend.SQL.Row

Methods

fromBackendRow :: FromBackendRowM be (a, b, c, d, e, f, g, h) Source #

valuesNeeded :: Proxy be -> Proxy (a, b, c, d, e, f, g, h) -> Int Source #

Orphan instances

Generic (a, b, c, d, e, f, g, h) Source # 
Instance details

Associated Types

type Rep (a, b, c, d, e, f, g, h) :: Type -> Type #

Methods

from :: (a, b, c, d, e, f, g, h) -> Rep (a, b, c, d, e, f, g, h) x #

to :: Rep (a, b, c, d, e, f, g, h) x -> (a, b, c, d, e, f, g, h) #