| Safe Haskell | Safe-Inferred | 
|---|---|
| Language | Haskell2010 | 
Hasql.Session
Synopsis
- data Session a
 - sql :: ByteString -> Session ()
 - statement :: params -> Statement params result -> Session result
 - run :: Session a -> Connection -> IO (Either QueryError a)
 - data QueryError = QueryError ByteString [Text] CommandError
 - data CommandError
 - data ResultError
 - data RowError
 
Documentation
A batch of actions to be executed in the context of a database connection.
Instances
| MonadIO Session Source # | |
Defined in Hasql.Private.Session  | |
| Applicative Session Source # | |
| Functor Session Source # | |
| Monad Session Source # | |
| MonadError QueryError Session Source # | |
Defined in Hasql.Private.Session Methods throwError :: QueryError -> Session a # catchError :: Session a -> (QueryError -> Session a) -> Session a #  | |
| MonadReader Connection Session Source # | |
Defined in Hasql.Private.Session Methods ask :: Session Connection # local :: (Connection -> Connection) -> Session a -> Session a # reader :: (Connection -> a) -> Session a #  | |
sql :: ByteString -> Session () Source #
Possibly a multi-statement query, which however cannot be parameterized or prepared, nor can any results of it be collected.
statement :: params -> Statement params result -> Session result Source #
Parameters and a specification of a parametric single-statement query to apply them to.
Execution
run :: Session a -> Connection -> IO (Either QueryError a) Source #
Executes a bunch of commands on the provided connection.
Errors
data QueryError Source #
An error during the execution of a query. Comes packed with the query template and a textual representation of the provided params.
Constructors
| QueryError ByteString [Text] CommandError | 
Instances
| Exception QueryError Source # | |
Defined in Hasql.Private.Errors Methods toException :: QueryError -> SomeException # fromException :: SomeException -> Maybe QueryError # displayException :: QueryError -> String #  | |
| Show QueryError Source # | |
Defined in Hasql.Private.Errors Methods showsPrec :: Int -> QueryError -> ShowS # show :: QueryError -> String # showList :: [QueryError] -> ShowS #  | |
| Eq QueryError Source # | |
Defined in Hasql.Private.Errors  | |
| MonadError QueryError Session Source # | |
Defined in Hasql.Private.Session Methods throwError :: QueryError -> Session a # catchError :: Session a -> (QueryError -> Session a) -> Session a #  | |
data CommandError Source #
An error of some command in the session.
Constructors
| ClientError (Maybe ByteString) | An error on the client-side, with a message generated by the "libpq" library. Usually indicates problems with connection.  | 
| ResultError ResultError | Some error with a command result.  | 
Instances
| Show CommandError Source # | |
Defined in Hasql.Private.Errors Methods showsPrec :: Int -> CommandError -> ShowS # show :: CommandError -> String # showList :: [CommandError] -> ShowS #  | |
| Eq CommandError Source # | |
Defined in Hasql.Private.Errors  | |
data ResultError Source #
An error with a command result.
Constructors
| ServerError | An error reported by the DB.  | 
Fields 
  | |
| UnexpectedResult Text | The database returned an unexpected result. Indicates an improper statement or a schema mismatch.  | 
| RowError Int Int RowError | An error of the row reader, preceded by the indexes of the row and column.  | 
| UnexpectedAmountOfRows Int | An unexpected amount of rows.  | 
Instances
| Show ResultError Source # | |
Defined in Hasql.Private.Errors Methods showsPrec :: Int -> ResultError -> ShowS # show :: ResultError -> String # showList :: [ResultError] -> ShowS #  | |
| Eq ResultError Source # | |
Defined in Hasql.Private.Errors  | |
An error during the decoding of a specific row.
Constructors
| EndOfInput | Appears on the attempt to parse more columns than there are in the result.  | 
| UnexpectedNull | Appears on the attempt to parse a   | 
| ValueError Text | Appears when a wrong value parser is used. Comes with the error details.  |