squeal-postgresql-0.8.0.0: Squeal PostgreSQL Library
Copyright(c) Eitan Chatav 2019
Maintainereitan@morphism.tech
Stabilityexperimental
Safe HaskellNone
LanguageHaskell2010

Squeal.PostgreSQL.Session.Decode

Description

decoding of result values

Synopsis

Decode Types

class IsPG y => FromPG y where Source #

A FromPG constraint gives a parser from the binary format of a PostgreSQL PGType into a Haskell Type.

Methods

fromPG :: StateT ByteString (Except Text) y Source #

>>> :set -XMultiParamTypeClasses -XGeneralizedNewtypeDeriving -XDerivingStrategies -XDerivingVia -XUndecidableInstances
>>> import GHC.Generics as GHC
>>> :{
newtype UserId = UserId { getId :: Int64 }
  deriving newtype (IsPG, FromPG)
:}
>>> :{
data Complex = Complex
  { real :: Double
  , imaginary :: Double
  } deriving stock GHC.Generic
    deriving anyclass (SOP.Generic, SOP.HasDatatypeInfo)
    deriving (IsPG, FromPG) via Composite Complex
:}
>>> :{
data Direction = North | South | East | West
  deriving stock GHC.Generic
  deriving anyclass (SOP.Generic, SOP.HasDatatypeInfo)
  deriving (IsPG, FromPG) via Enumerated Direction
:}

Instances

Instances details
FromPG Bool Source # 
Instance details

Defined in Squeal.PostgreSQL.Session.Decode

FromPG Char Source # 
Instance details

Defined in Squeal.PostgreSQL.Session.Decode

FromPG Double Source # 
Instance details

Defined in Squeal.PostgreSQL.Session.Decode

FromPG Float Source # 
Instance details

Defined in Squeal.PostgreSQL.Session.Decode

FromPG Int16 Source # 
Instance details

Defined in Squeal.PostgreSQL.Session.Decode

FromPG Int32 Source # 
Instance details

Defined in Squeal.PostgreSQL.Session.Decode

FromPG Int64 Source # 
Instance details

Defined in Squeal.PostgreSQL.Session.Decode

FromPG ByteString Source # 
Instance details

Defined in Squeal.PostgreSQL.Session.Decode

FromPG ByteString Source # 
Instance details

Defined in Squeal.PostgreSQL.Session.Decode

FromPG Scientific Source # 
Instance details

Defined in Squeal.PostgreSQL.Session.Decode

FromPG String Source # 
Instance details

Defined in Squeal.PostgreSQL.Session.Decode

FromPG UTCTime Source # 
Instance details

Defined in Squeal.PostgreSQL.Session.Decode

FromPG Text Source # 
Instance details

Defined in Squeal.PostgreSQL.Session.Decode

FromPG Value Source # 
Instance details

Defined in Squeal.PostgreSQL.Session.Decode

FromPG Text Source # 
Instance details

Defined in Squeal.PostgreSQL.Session.Decode

FromPG UUID Source # 
Instance details

Defined in Squeal.PostgreSQL.Session.Decode

FromPG Day Source # 
Instance details

Defined in Squeal.PostgreSQL.Session.Decode

FromPG DiffTime Source # 
Instance details

Defined in Squeal.PostgreSQL.Session.Decode

FromPG TimeOfDay Source # 
Instance details

Defined in Squeal.PostgreSQL.Session.Decode

FromPG LocalTime Source # 
Instance details

Defined in Squeal.PostgreSQL.Session.Decode

FromPG Oid Source # 
Instance details

Defined in Squeal.PostgreSQL.Session.Decode

FromPG Money Source # 
Instance details

Defined in Squeal.PostgreSQL.Session.Decode

FromPG (NetAddr IP) Source # 
Instance details

Defined in Squeal.PostgreSQL.Session.Decode

KnownNat n => FromPG (FixChar n) Source # 
Instance details

Defined in Squeal.PostgreSQL.Session.Decode

KnownNat n => FromPG (VarChar n) Source # 
Instance details

Defined in Squeal.PostgreSQL.Session.Decode

FromArray dims ty y => FromPG (FixArray y) Source # 
Instance details

Defined in Squeal.PostgreSQL.Session.Decode

(FromArray ('[] :: [Nat]) ty y, ty ~ NullPG y) => FromPG (VarArray [y]) Source # 
Instance details

Defined in Squeal.PostgreSQL.Session.Decode

(FromArray ('[] :: [Nat]) ty y, ty ~ NullPG y) => FromPG (VarArray (Vector y)) Source # 
Instance details

Defined in Squeal.PostgreSQL.Session.Decode

(IsEnumType y, HasDatatypeInfo y, LabelsPG y ~ labels) => FromPG (Enumerated y) Source # 
Instance details

Defined in Squeal.PostgreSQL.Session.Decode

(IsRecord y ys, AllZip FromField row ys, RowPG y ~ row) => FromPG (Composite y) Source # 
Instance details

Defined in Squeal.PostgreSQL.Session.Decode

FromJSON x => FromPG (Jsonb x) Source # 
Instance details

Defined in Squeal.PostgreSQL.Session.Decode

FromJSON x => FromPG (Json x) Source # 
Instance details

Defined in Squeal.PostgreSQL.Session.Decode

FromPG y => FromPG (Range y) Source # 
Instance details

Defined in Squeal.PostgreSQL.Session.Decode

FromPG (TimeOfDay, TimeZone) Source # 
Instance details

Defined in Squeal.PostgreSQL.Session.Decode

FromPG x => FromPG (Const x tag) Source # 
Instance details

Defined in Squeal.PostgreSQL.Session.Decode

FromPG x => FromPG (K x tag) Source # 
Instance details

Defined in Squeal.PostgreSQL.Session.Decode

Methods

fromPG :: StateT ByteString (Except Text) (K x tag) Source #

FromPG x => FromPG (Constant x tag) Source # 
Instance details

Defined in Squeal.PostgreSQL.Session.Decode

devalue :: Value x -> StateT ByteString (Except Text) x Source #

Converts a Value type from postgresql-binary for use in the fromPG method of FromPG.

rowValue Source #

Arguments

:: (PG y ~ 'PGcomposite row, SListI row) 
=> DecodeRow row y

fields

-> StateT ByteString (Except Text) y 
>>> :set -XTypeFamilies
>>> :{
data Complex = Complex
  { real :: Double
  , imaginary :: Double
  }
instance IsPG Complex where
  type PG Complex = 'PGcomposite '[
    "re" ::: 'NotNull 'PGfloat8,
    "im" ::: 'NotNull 'PGfloat8]
instance FromPG Complex where
  fromPG = rowValue $ do
    re <- #re
    im <- #im
    return Complex {real = re, imaginary = im}
:}

enumValue Source #

Arguments

:: (All KnownSymbol labels, PG y ~ 'PGenum labels) 
=> NP (K y) labels

labels

-> StateT ByteString (Except Text) y 
>>> :{
data Dir = North | East | South | West
instance IsPG Dir where
  type PG Dir = 'PGenum '["north", "south", "east", "west"]
instance FromPG Dir where
  fromPG = enumValue $
    label @"north" North :*
    label @"south" South :*
    label @"east" East :*
    label @"west" West
:}

Decode Rows

newtype DecodeRow (row :: RowType) (y :: Type) Source #

DecodeRow describes a decoding of a PostgreSQL RowType into a Haskell Type.

DecodeRow has an interface given by the classes Functor, Applicative, Alternative, Monad, MonadPlus, MonadError Text, and IsLabel.

>>> :set -XOverloadedLabels
>>> :{
let
  decode :: DecodeRow
    '[ "fst" ::: 'NotNull 'PGint2, "snd" ::: 'NotNull ('PGchar 1)]
    (Int16, Char)
  decode = (,) <$> #fst <*> #snd
in runDecodeRow decode (SOP.K (Just "\NUL\SOH") :* SOP.K (Just "a") :* Nil)
:}
Right (1,'a')

There is also an IsLabel instance for MaybeT DecodeRows, useful for decoding outer joined rows.

>>> :{
let
  decode :: DecodeRow
    '[ "fst" ::: 'Null 'PGint2, "snd" ::: 'Null ('PGchar 1)]
    (Maybe (Int16, Char))
  decode = runMaybeT $ (,) <$> #fst <*> #snd
in runDecodeRow decode (SOP.K (Just "\NUL\SOH") :* SOP.K (Just "a") :* Nil)
:}
Right (Just (1,'a'))

Constructors

DecodeRow 

Fields

Instances

Instances details
MonadError Text (DecodeRow row) Source # 
Instance details

Defined in Squeal.PostgreSQL.Session.Decode

Methods

throwError :: Text -> DecodeRow row a #

catchError :: DecodeRow row a -> (Text -> DecodeRow row a) -> DecodeRow row a #

IsLabel fld (MaybeT (DecodeRow row) y) => IsLabel fld (MaybeT (DecodeRow (field ': row)) y) Source # 
Instance details

Defined in Squeal.PostgreSQL.Session.Decode

Methods

fromLabel :: MaybeT (DecodeRow (field ': row)) y #

(KnownSymbol fld, FromValue ty (Maybe y)) => IsLabel fld (MaybeT (DecodeRow ((fld ::: ty) ': row)) y) Source # 
Instance details

Defined in Squeal.PostgreSQL.Session.Decode

Methods

fromLabel :: MaybeT (DecodeRow ((fld ::: ty) ': row)) y #

IsLabel fld (DecodeRow row y) => IsLabel fld (DecodeRow (field ': row) y) Source # 
Instance details

Defined in Squeal.PostgreSQL.Session.Decode

Methods

fromLabel :: DecodeRow (field ': row) y #

(KnownSymbol fld, FromValue ty y) => IsLabel fld (DecodeRow ((fld ::: ty) ': row) y) Source # 
Instance details

Defined in Squeal.PostgreSQL.Session.Decode

Methods

fromLabel :: DecodeRow ((fld ::: ty) ': row) y #

Monad (DecodeRow row) Source # 
Instance details

Defined in Squeal.PostgreSQL.Session.Decode

Methods

(>>=) :: DecodeRow row a -> (a -> DecodeRow row b) -> DecodeRow row b #

(>>) :: DecodeRow row a -> DecodeRow row b -> DecodeRow row b #

return :: a -> DecodeRow row a #

Functor (DecodeRow row) Source # 
Instance details

Defined in Squeal.PostgreSQL.Session.Decode

Methods

fmap :: (a -> b) -> DecodeRow row a -> DecodeRow row b #

(<$) :: a -> DecodeRow row b -> DecodeRow row a #

MonadFail (DecodeRow row) Source # 
Instance details

Defined in Squeal.PostgreSQL.Session.Decode

Methods

fail :: String -> DecodeRow row a #

Applicative (DecodeRow row) Source # 
Instance details

Defined in Squeal.PostgreSQL.Session.Decode

Methods

pure :: a -> DecodeRow row a #

(<*>) :: DecodeRow row (a -> b) -> DecodeRow row a -> DecodeRow row b #

liftA2 :: (a -> b -> c) -> DecodeRow row a -> DecodeRow row b -> DecodeRow row c #

(*>) :: DecodeRow row a -> DecodeRow row b -> DecodeRow row b #

(<*) :: DecodeRow row a -> DecodeRow row b -> DecodeRow row a #

Alternative (DecodeRow row) Source # 
Instance details

Defined in Squeal.PostgreSQL.Session.Decode

Methods

empty :: DecodeRow row a #

(<|>) :: DecodeRow row a -> DecodeRow row a -> DecodeRow row a #

some :: DecodeRow row a -> DecodeRow row [a] #

many :: DecodeRow row a -> DecodeRow row [a] #

MonadPlus (DecodeRow row) Source # 
Instance details

Defined in Squeal.PostgreSQL.Session.Decode

Methods

mzero :: DecodeRow row a #

mplus :: DecodeRow row a -> DecodeRow row a -> DecodeRow row a #

decodeRow :: (NP (K (Maybe ByteString)) row -> Either Text y) -> DecodeRow row y Source #

Smart constructor for a DecodeRow.

class (IsRecord y ys, row ~ RowPG y, AllZip FromField row ys) => GenericRow row y ys where Source #

A GenericRow constraint to ensure that a Haskell type is a record type, has a RowPG, and all its fields and can be decoded from corresponding Postgres fields.

Methods

genericRow :: DecodeRow row y Source #

Row decoder for Generic records.

>>> import qualified GHC.Generics as GHC
>>> import qualified Generics.SOP as SOP
>>> data Two = Two {frst :: Int16, scnd :: String} deriving (Show, GHC.Generic, SOP.Generic, SOP.HasDatatypeInfo)
>>> :{
let
  decode :: DecodeRow '[ "frst" ::: 'NotNull 'PGint2, "scnd" ::: 'NotNull 'PGtext] Two
  decode = genericRow
in runDecodeRow decode (SOP.K (Just "\NUL\STX") :* SOP.K (Just "two") :* Nil)
:}
Right (Two {frst = 2, scnd = "two"})

Instances

Instances details
(row ~ RowPG y, IsRecord y ys, AllZip FromField row ys) => GenericRow row y ys Source # 
Instance details

Defined in Squeal.PostgreSQL.Session.Decode

Methods

genericRow :: DecodeRow row y Source #

appendRows Source #

Arguments

:: SListI left 
=> (l -> r -> z)

combining function

-> DecodeRow left l

left decoder

-> DecodeRow right r

right decoder

-> DecodeRow (Join left right) z 

Append two row decoders with a combining function.

>>> import GHC.Generics as GHC
>>> :{
data L = L {fst :: Int16, snd :: Char}
  deriving stock (GHC.Generic, Show)
  deriving anyclass (SOP.Generic, SOP.HasDatatypeInfo)
data R = R {thrd :: Bool, frth :: Bool}
  deriving stock (GHC.Generic, Show)
  deriving anyclass (SOP.Generic, SOP.HasDatatypeInfo)
type Row = '[
  "fst" ::: 'NotNull 'PGint2,
  "snd" ::: 'NotNull ('PGchar 1),
  "thrd" ::: 'NotNull 'PGbool,
  "frth" ::: 'NotNull 'PGbool]
:}
>>> :{
let
  decode :: DecodeRow Row (L,R)
  decode = appendRows (,) genericRow genericRow
  row4 =
    SOP.K (Just "\NUL\SOH") :*
    SOP.K (Just "a") :*
    SOP.K (Just "\NUL") :*
    SOP.K (Just "\NUL") :* Nil
in runDecodeRow decode row4
:}
Right (L {fst = 1, snd = 'a'},R {thrd = False, frth = False})

consRow Source #

Arguments

:: FromValue head h 
=> (h -> t -> z)

combining function

-> Alias col

alias of head

-> DecodeRow tail t

tail decoder

-> DecodeRow ((col ::: head) ': tail) z 

Cons a column and a row decoder with a combining function.

>>> :{
let
  decode :: DecodeRow
    '["fst" ::: 'NotNull 'PGtext, "snd" ::: 'NotNull 'PGint2, "thrd" ::: 'NotNull ('PGchar 1)]
    (String, (Int16, Char))
  decode = consRow (,) #fst (consRow (,) #snd #thrd)
in runDecodeRow decode (SOP.K (Just "hi") :* SOP.K (Just "\NUL\SOH") :* SOP.K (Just "a") :* Nil)
:}
Right ("hi",(1,'a'))

Decoding Classes

class FromValue (ty :: NullType) (y :: Type) where Source #

A FromValue constraint lifts the FromPG parser to a decoding of a NullityType to a Type, decoding Nulls to Maybes. You should not define instances for FromValue, just use the provided instances.

Instances

Instances details
(FromPG y, pg ~ PG y) => FromValue ('NotNull pg) y Source # 
Instance details

Defined in Squeal.PostgreSQL.Session.Decode

(FromPG y, pg ~ PG y) => FromValue ('Null pg) (Maybe y) Source # 
Instance details

Defined in Squeal.PostgreSQL.Session.Decode

class FromField (field :: (Symbol, NullType)) (y :: (Symbol, Type)) where Source #

A FromField constraint lifts the FromPG parser to a decoding of a (Symbol, NullityType) to a Type, decoding Nulls to Maybes. You should not define instances for FromField, just use the provided instances.

Instances

Instances details
(FromValue ty y, fld0 ~ fld1) => FromField (fld0 ::: ty) (fld1 ::: y) Source # 
Instance details

Defined in Squeal.PostgreSQL.Session.Decode

Methods

fromField :: Maybe ByteString -> Either Text (P (fld1 ::: y)) Source #

class FromArray (dims :: [Nat]) (ty :: NullType) (y :: Type) where Source #

A FromArray constraint gives a decoding to a Haskell Type from the binary format of a PostgreSQL fixed-length array. You should not define instances for FromArray, just use the provided instances.

Methods

fromArray :: Array y Source #

Instances

Instances details
(FromPG y, pg ~ PG y) => FromArray ('[] :: [Nat]) ('NotNull pg) y Source # 
Instance details

Defined in Squeal.PostgreSQL.Session.Decode

Methods

fromArray :: Array y Source #

(FromPG y, pg ~ PG y) => FromArray ('[] :: [Nat]) ('Null pg) (Maybe y) Source # 
Instance details

Defined in Squeal.PostgreSQL.Session.Decode

Methods

fromArray :: Array (Maybe y) Source #

(IsProductType product ys, Length ys ~ dim, All (Type ~ y) ys, FromArray dims ty y) => FromArray (dim ': dims) ty product Source # 
Instance details

Defined in Squeal.PostgreSQL.Session.Decode

Methods

fromArray :: Array product Source #

newtype StateT s (m :: Type -> Type) a #

A state transformer monad parameterized by:

  • s - The state.
  • m - The inner monad.

The return function leaves the state unchanged, while >>= uses the final state of the first computation as the initial state of the second.

Constructors

StateT 

Fields

Instances

Instances details
MonadError e m => MonadError e (StateT s m) 
Instance details

Defined in Control.Monad.Error.Class

Methods

throwError :: e -> StateT s m a #

catchError :: StateT s m a -> (e -> StateT s m a) -> StateT s m a #

MonadReader r m => MonadReader r (StateT s m) 
Instance details

Defined in Control.Monad.Reader.Class

Methods

ask :: StateT s m r #

local :: (r -> r) -> StateT s m a -> StateT s m a #

reader :: (r -> a) -> StateT s m a #

Monad m => MonadState s (StateT s m) 
Instance details

Defined in Control.Monad.State.Class

Methods

get :: StateT s m s #

put :: s -> StateT s m () #

state :: (s -> (a, s)) -> StateT s m a #

MonadBase b m => MonadBase b (StateT s m) 
Instance details

Defined in Control.Monad.Base

Methods

liftBase :: b α -> StateT s m α #

MonadBaseControl b m => MonadBaseControl b (StateT s m) 
Instance details

Defined in Control.Monad.Trans.Control

Associated Types

type StM (StateT s m) a #

Methods

liftBaseWith :: (RunInBase (StateT s m) b -> b a) -> StateT s m a #

restoreM :: StM (StateT s m) a -> StateT s m a #

MonadPQ db m => MonadPQ db (StateT s m) Source # 
Instance details

Defined in Squeal.PostgreSQL.Session.Monad

Methods

executeParams :: Statement db x y -> x -> StateT s m (Result y) Source #

executeParams_ :: Statement db x () -> x -> StateT s m () Source #

execute :: Statement db () y -> StateT s m (Result y) Source #

execute_ :: Statement db () () -> StateT s m () Source #

executePrepared :: Traversable list => Statement db x y -> list x -> StateT s m (list (Result y)) Source #

executePrepared_ :: Foldable list => Statement db x () -> list x -> StateT s m () Source #

MonadTrans (StateT s) 
Instance details

Defined in Control.Monad.Trans.State.Strict

Methods

lift :: Monad m => m a -> StateT s m a #

MonadTransControl (StateT s) 
Instance details

Defined in Control.Monad.Trans.Control

Associated Types

type StT (StateT s) a #

Methods

liftWith :: Monad m => (Run (StateT s) -> m a) -> StateT s m a #

restoreT :: Monad m => m (StT (StateT s) a) -> StateT s m a #

MFunctor (StateT s :: (Type -> Type) -> Type -> Type) 
Instance details

Defined in Control.Monad.Morph

Methods

hoist :: forall m n (b :: k). Monad m => (forall a. m a -> n a) -> StateT s m b -> StateT s n b #

Monad m => Monad (StateT s m) 
Instance details

Defined in Control.Monad.Trans.State.Strict

Methods

(>>=) :: StateT s m a -> (a -> StateT s m b) -> StateT s m b #

(>>) :: StateT s m a -> StateT s m b -> StateT s m b #

return :: a -> StateT s m a #

Functor m => Functor (StateT s m) 
Instance details

Defined in Control.Monad.Trans.State.Strict

Methods

fmap :: (a -> b) -> StateT s m a -> StateT s m b #

(<$) :: a -> StateT s m b -> StateT s m a #

MonadFix m => MonadFix (StateT s m) 
Instance details

Defined in Control.Monad.Trans.State.Strict

Methods

mfix :: (a -> StateT s m a) -> StateT s m a #

MonadFail m => MonadFail (StateT s m) 
Instance details

Defined in Control.Monad.Trans.State.Strict

Methods

fail :: String -> StateT s m a #

(Functor m, Monad m) => Applicative (StateT s m) 
Instance details

Defined in Control.Monad.Trans.State.Strict

Methods

pure :: a -> StateT s m a #

(<*>) :: StateT s m (a -> b) -> StateT s m a -> StateT s m b #

liftA2 :: (a -> b -> c) -> StateT s m a -> StateT s m b -> StateT s m c #

(*>) :: StateT s m a -> StateT s m b -> StateT s m b #

(<*) :: StateT s m a -> StateT s m b -> StateT s m a #

(Functor m, MonadPlus m) => Alternative (StateT s m) 
Instance details

Defined in Control.Monad.Trans.State.Strict

Methods

empty :: StateT s m a #

(<|>) :: StateT s m a -> StateT s m a -> StateT s m a #

some :: StateT s m a -> StateT s m [a] #

many :: StateT s m a -> StateT s m [a] #

MonadPlus m => MonadPlus (StateT s m) 
Instance details

Defined in Control.Monad.Trans.State.Strict

Methods

mzero :: StateT s m a #

mplus :: StateT s m a -> StateT s m a -> StateT s m a #

Contravariant m => Contravariant (StateT s m) 
Instance details

Defined in Control.Monad.Trans.State.Strict

Methods

contramap :: (a -> b) -> StateT s m b -> StateT s m a #

(>$) :: b -> StateT s m b -> StateT s m a #

MonadIO m => MonadIO (StateT s m) 
Instance details

Defined in Control.Monad.Trans.State.Strict

Methods

liftIO :: IO a -> StateT s m a #

MonadThrow m => MonadThrow (StateT s m) 
Instance details

Defined in Control.Monad.Catch

Methods

throwM :: Exception e => e -> StateT s m a #

MonadCatch m => MonadCatch (StateT s m) 
Instance details

Defined in Control.Monad.Catch

Methods

catch :: Exception e => StateT s m a -> (e -> StateT s m a) -> StateT s m a #

MonadMask m => MonadMask (StateT s m) 
Instance details

Defined in Control.Monad.Catch

Methods

mask :: ((forall a. StateT s m a -> StateT s m a) -> StateT s m b) -> StateT s m b #

uninterruptibleMask :: ((forall a. StateT s m a -> StateT s m a) -> StateT s m b) -> StateT s m b #

generalBracket :: StateT s m a -> (a -> ExitCase b -> StateT s m c) -> (a -> StateT s m b) -> StateT s m (b, c) #

PrimMonad m => PrimMonad (StateT s m) 
Instance details

Defined in Control.Monad.Primitive

Associated Types

type PrimState (StateT s m) #

Methods

primitive :: (State# (PrimState (StateT s m)) -> (# State# (PrimState (StateT s m)), a #)) -> StateT s m a #

type StT (StateT s) a 
Instance details

Defined in Control.Monad.Trans.Control

type StT (StateT s) a = (a, s)
type PrimState (StateT s m) 
Instance details

Defined in Control.Monad.Primitive

type PrimState (StateT s m) = PrimState m
type StM (StateT s m) a 
Instance details

Defined in Control.Monad.Trans.Control

type StM (StateT s m) a = ComposeSt (StateT s) m a

newtype ExceptT e (m :: Type -> Type) a #

A monad transformer that adds exceptions to other monads.

ExceptT constructs a monad parameterized over two things:

  • e - The exception type.
  • m - The inner monad.

The return function yields a computation that produces the given value, while >>= sequences two subcomputations, exiting on the first exception.

Constructors

ExceptT (m (Either e a)) 

Instances

Instances details
Monad m => MonadError e (ExceptT e m)

Since: mtl-2.2

Instance details

Defined in Control.Monad.Error.Class

Methods

throwError :: e -> ExceptT e m a #

catchError :: ExceptT e m a -> (e -> ExceptT e m a) -> ExceptT e m a #

MonadReader r m => MonadReader r (ExceptT e m)

Since: mtl-2.2

Instance details

Defined in Control.Monad.Reader.Class

Methods

ask :: ExceptT e m r #

local :: (r -> r) -> ExceptT e m a -> ExceptT e m a #

reader :: (r -> a) -> ExceptT e m a #

MonadState s m => MonadState s (ExceptT e m)

Since: mtl-2.2

Instance details

Defined in Control.Monad.State.Class

Methods

get :: ExceptT e m s #

put :: s -> ExceptT e m () #

state :: (s -> (a, s)) -> ExceptT e m a #

MonadBase b m => MonadBase b (ExceptT e m) 
Instance details

Defined in Control.Monad.Base

Methods

liftBase :: b α -> ExceptT e m α #

MonadBaseControl b m => MonadBaseControl b (ExceptT e m) 
Instance details

Defined in Control.Monad.Trans.Control

Associated Types

type StM (ExceptT e m) a #

Methods

liftBaseWith :: (RunInBase (ExceptT e m) b -> b a) -> ExceptT e m a #

restoreM :: StM (ExceptT e m) a -> ExceptT e m a #

MonadPQ db m => MonadPQ db (ExceptT e m) Source # 
Instance details

Defined in Squeal.PostgreSQL.Session.Monad

Methods

executeParams :: Statement db x y -> x -> ExceptT e m (Result y) Source #

executeParams_ :: Statement db x () -> x -> ExceptT e m () Source #

execute :: Statement db () y -> ExceptT e m (Result y) Source #

execute_ :: Statement db () () -> ExceptT e m () Source #

executePrepared :: Traversable list => Statement db x y -> list x -> ExceptT e m (list (Result y)) Source #

executePrepared_ :: Foldable list => Statement db x () -> list x -> ExceptT e m () Source #

MonadTrans (ExceptT e) 
Instance details

Defined in Control.Monad.Trans.Except

Methods

lift :: Monad m => m a -> ExceptT e m a #

MMonad (ExceptT e) 
Instance details

Defined in Control.Monad.Morph

Methods

embed :: forall (n :: Type -> Type) m b. Monad n => (forall a. m a -> ExceptT e n a) -> ExceptT e m b -> ExceptT e n b #

MonadTransControl (ExceptT e) 
Instance details

Defined in Control.Monad.Trans.Control

Associated Types

type StT (ExceptT e) a #

Methods

liftWith :: Monad m => (Run (ExceptT e) -> m a) -> ExceptT e m a #

restoreT :: Monad m => m (StT (ExceptT e) a) -> ExceptT e m a #

MFunctor (ExceptT e :: (Type -> Type) -> Type -> Type) 
Instance details

Defined in Control.Monad.Morph

Methods

hoist :: forall m n (b :: k). Monad m => (forall a. m a -> n a) -> ExceptT e m b -> ExceptT e n b #

Monad m => Monad (ExceptT e m) 
Instance details

Defined in Control.Monad.Trans.Except

Methods

(>>=) :: ExceptT e m a -> (a -> ExceptT e m b) -> ExceptT e m b #

(>>) :: ExceptT e m a -> ExceptT e m b -> ExceptT e m b #

return :: a -> ExceptT e m a #

Functor m => Functor (ExceptT e m) 
Instance details

Defined in Control.Monad.Trans.Except

Methods

fmap :: (a -> b) -> ExceptT e m a -> ExceptT e m b #

(<$) :: a -> ExceptT e m b -> ExceptT e m a #

MonadFix m => MonadFix (ExceptT e m) 
Instance details

Defined in Control.Monad.Trans.Except

Methods

mfix :: (a -> ExceptT e m a) -> ExceptT e m a #

MonadFail m => MonadFail (ExceptT e m) 
Instance details

Defined in Control.Monad.Trans.Except

Methods

fail :: String -> ExceptT e m a #

(Functor m, Monad m) => Applicative (ExceptT e m) 
Instance details

Defined in Control.Monad.Trans.Except

Methods

pure :: a -> ExceptT e m a #

(<*>) :: ExceptT e m (a -> b) -> ExceptT e m a -> ExceptT e m b #

liftA2 :: (a -> b -> c) -> ExceptT e m a -> ExceptT e m b -> ExceptT e m c #

(*>) :: ExceptT e m a -> ExceptT e m b -> ExceptT e m b #

(<*) :: ExceptT e m a -> ExceptT e m b -> ExceptT e m a #

Foldable f => Foldable (ExceptT e f) 
Instance details

Defined in Control.Monad.Trans.Except

Methods

fold :: Monoid m => ExceptT e f m -> m #

foldMap :: Monoid m => (a -> m) -> ExceptT e f a -> m #

foldMap' :: Monoid m => (a -> m) -> ExceptT e f a -> m #

foldr :: (a -> b -> b) -> b -> ExceptT e f a -> b #

foldr' :: (a -> b -> b) -> b -> ExceptT e f a -> b #

foldl :: (b -> a -> b) -> b -> ExceptT e f a -> b #

foldl' :: (b -> a -> b) -> b -> ExceptT e f a -> b #

foldr1 :: (a -> a -> a) -> ExceptT e f a -> a #

foldl1 :: (a -> a -> a) -> ExceptT e f a -> a #

toList :: ExceptT e f a -> [a] #

null :: ExceptT e f a -> Bool #

length :: ExceptT e f a -> Int #

elem :: Eq a => a -> ExceptT e f a -> Bool #

maximum :: Ord a => ExceptT e f a -> a #

minimum :: Ord a => ExceptT e f a -> a #

sum :: Num a => ExceptT e f a -> a #

product :: Num a => ExceptT e f a -> a #

Traversable f => Traversable (ExceptT e f) 
Instance details

Defined in Control.Monad.Trans.Except

Methods

traverse :: Applicative f0 => (a -> f0 b) -> ExceptT e f a -> f0 (ExceptT e f b) #

sequenceA :: Applicative f0 => ExceptT e f (f0 a) -> f0 (ExceptT e f a) #

mapM :: Monad m => (a -> m b) -> ExceptT e f a -> m (ExceptT e f b) #

sequence :: Monad m => ExceptT e f (m a) -> m (ExceptT e f a) #

(Functor m, Monad m, Monoid e) => Alternative (ExceptT e m) 
Instance details

Defined in Control.Monad.Trans.Except

Methods

empty :: ExceptT e m a #

(<|>) :: ExceptT e m a -> ExceptT e m a -> ExceptT e m a #

some :: ExceptT e m a -> ExceptT e m [a] #

many :: ExceptT e m a -> ExceptT e m [a] #

(Monad m, Monoid e) => MonadPlus (ExceptT e m) 
Instance details

Defined in Control.Monad.Trans.Except

Methods

mzero :: ExceptT e m a #

mplus :: ExceptT e m a -> ExceptT e m a -> ExceptT e m a #

Contravariant m => Contravariant (ExceptT e m) 
Instance details

Defined in Control.Monad.Trans.Except

Methods

contramap :: (a -> b) -> ExceptT e m b -> ExceptT e m a #

(>$) :: b -> ExceptT e m b -> ExceptT e m a #

(Eq e, Eq1 m) => Eq1 (ExceptT e m) 
Instance details

Defined in Control.Monad.Trans.Except

Methods

liftEq :: (a -> b -> Bool) -> ExceptT e m a -> ExceptT e m b -> Bool #

(Ord e, Ord1 m) => Ord1 (ExceptT e m) 
Instance details

Defined in Control.Monad.Trans.Except

Methods

liftCompare :: (a -> b -> Ordering) -> ExceptT e m a -> ExceptT e m b -> Ordering #

(Read e, Read1 m) => Read1 (ExceptT e m) 
Instance details

Defined in Control.Monad.Trans.Except

Methods

liftReadsPrec :: (Int -> ReadS a) -> ReadS [a] -> Int -> ReadS (ExceptT e m a) #

liftReadList :: (Int -> ReadS a) -> ReadS [a] -> ReadS [ExceptT e m a] #

liftReadPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec (ExceptT e m a) #

liftReadListPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec [ExceptT e m a] #

(Show e, Show1 m) => Show1 (ExceptT e m) 
Instance details

Defined in Control.Monad.Trans.Except

Methods

liftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> ExceptT e m a -> ShowS #

liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [ExceptT e m a] -> ShowS #

MonadZip m => MonadZip (ExceptT e m) 
Instance details

Defined in Control.Monad.Trans.Except

Methods

mzip :: ExceptT e m a -> ExceptT e m b -> ExceptT e m (a, b) #

mzipWith :: (a -> b -> c) -> ExceptT e m a -> ExceptT e m b -> ExceptT e m c #

munzip :: ExceptT e m (a, b) -> (ExceptT e m a, ExceptT e m b) #

MonadIO m => MonadIO (ExceptT e m) 
Instance details

Defined in Control.Monad.Trans.Except

Methods

liftIO :: IO a -> ExceptT e m a #

MonadThrow m => MonadThrow (ExceptT e m)

Throws exceptions into the base monad.

Instance details

Defined in Control.Monad.Catch

Methods

throwM :: Exception e0 => e0 -> ExceptT e m a #

MonadCatch m => MonadCatch (ExceptT e m)

Catches exceptions from the base monad.

Instance details

Defined in Control.Monad.Catch

Methods

catch :: Exception e0 => ExceptT e m a -> (e0 -> ExceptT e m a) -> ExceptT e m a #

MonadMask m => MonadMask (ExceptT e m)

Since: exceptions-0.9.0

Instance details

Defined in Control.Monad.Catch

Methods

mask :: ((forall a. ExceptT e m a -> ExceptT e m a) -> ExceptT e m b) -> ExceptT e m b #

uninterruptibleMask :: ((forall a. ExceptT e m a -> ExceptT e m a) -> ExceptT e m b) -> ExceptT e m b #

generalBracket :: ExceptT e m a -> (a -> ExitCase b -> ExceptT e m c) -> (a -> ExceptT e m b) -> ExceptT e m (b, c) #

PrimMonad m => PrimMonad (ExceptT e m) 
Instance details

Defined in Control.Monad.Primitive

Associated Types

type PrimState (ExceptT e m) #

Methods

primitive :: (State# (PrimState (ExceptT e m)) -> (# State# (PrimState (ExceptT e m)), a #)) -> ExceptT e m a #

(Eq e, Eq1 m, Eq a) => Eq (ExceptT e m a) 
Instance details

Defined in Control.Monad.Trans.Except

Methods

(==) :: ExceptT e m a -> ExceptT e m a -> Bool #

(/=) :: ExceptT e m a -> ExceptT e m a -> Bool #

(Ord e, Ord1 m, Ord a) => Ord (ExceptT e m a) 
Instance details

Defined in Control.Monad.Trans.Except

Methods

compare :: ExceptT e m a -> ExceptT e m a -> Ordering #

(<) :: ExceptT e m a -> ExceptT e m a -> Bool #

(<=) :: ExceptT e m a -> ExceptT e m a -> Bool #

(>) :: ExceptT e m a -> ExceptT e m a -> Bool #

(>=) :: ExceptT e m a -> ExceptT e m a -> Bool #

max :: ExceptT e m a -> ExceptT e m a -> ExceptT e m a #

min :: ExceptT e m a -> ExceptT e m a -> ExceptT e m a #

(Read e, Read1 m, Read a) => Read (ExceptT e m a) 
Instance details

Defined in Control.Monad.Trans.Except

Methods

readsPrec :: Int -> ReadS (ExceptT e m a) #

readList :: ReadS [ExceptT e m a] #

readPrec :: ReadPrec (ExceptT e m a) #

readListPrec :: ReadPrec [ExceptT e m a] #

(Show e, Show1 m, Show a) => Show (ExceptT e m a) 
Instance details

Defined in Control.Monad.Trans.Except

Methods

showsPrec :: Int -> ExceptT e m a -> ShowS #

show :: ExceptT e m a -> String #

showList :: [ExceptT e m a] -> ShowS #

type StT (ExceptT e) a 
Instance details

Defined in Control.Monad.Trans.Control

type StT (ExceptT e) a = Either e a
type PrimState (ExceptT e m) 
Instance details

Defined in Control.Monad.Primitive

type PrimState (ExceptT e m) = PrimState m
type StM (ExceptT e m) a 
Instance details

Defined in Control.Monad.Trans.Control

type StM (ExceptT e m) a = ComposeSt (ExceptT e) m a