| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Database.PostgreSQL.Pure.List
Description
This is a list interface version of Database.PostgreSQL.Pure.
Typical Example
Prepare a following table.
CREATE TABLE person (
id serial PRIMARY KEY,
name varchar(255) NOT NULL
);
INSERT INTO person (name) VALUES ('Ada');
You can run like following to get the record whose ID is 1.
>>>:set -XOverloadedStrings>>>:set -XFlexibleContexts>>>:set -XTypeApplications>>>>>>import Database.PostgreSQL.Pure.List>>>import Data.Default.Class (def)>>>import Data.Int (Int32)>>>import Data.ByteString (ByteString)>>>import Data.Tuple.Only (Only (Only))>>>>>>conn <- connect def>>>preparedStatementProcedure = parse "" "SELECT id, name FROM person WHERE id = $1" (Left (1, 2))>>>portalProcedure <- bind "" BinaryFormat BinaryFormat (parameters conn) (const $ fail "") (Only (1 :: Int32)) preparedStatementProcedure>>>executedProcedure = execute @_ @(Int32, ByteString) 0 (const $ fail "") portalProcedure>>>((_, _, e, _), _) <- sync conn executedProcedure>>>records e[(1,"Ada")]
Synopsis
- data Config = Config {}
- data Connection
- $sel:pid:Connection :: Connection -> Pid
- $sel:parameters:Connection :: Connection -> BackendParameters
- $sel:config:Connection :: Connection -> Config
- data Address
- type BackendParameters = Map ShortByteString ShortByteString
- type Pid = Int32
- withConnection :: Config -> (Connection -> IO a) -> IO a
- connect :: Config -> IO Connection
- disconnect :: Connection -> IO ()
- parse :: PreparedStatementName -> Query -> Either (Word, Word) ([Oid], [Oid]) -> PreparedStatementProcedure
- bind :: (Bind ps, ToRecord param, MonadFail m) => PortalName -> FormatCode -> FormatCode -> BackendParameters -> StringEncoder -> param -> ps -> m PortalProcedure
- execute :: (Execute p, FromRecord result) => Word -> StringDecoder -> p -> ExecutedProcedure result
- flush :: Message m => Connection -> m -> IO (MessageResult m)
- sync :: Message m => Connection -> m -> IO (MessageResult m, TransactionState)
- close :: Close p => p -> CloseProcedure
- data PreparedStatement
- data PreparedStatementProcedure
- newtype PreparedStatementName = PreparedStatementName ByteString
- data Portal
- data PortalProcedure
- newtype PortalName = PortalName ByteString
- data Executed r
- data ExecutedProcedure r
- data ExecuteResult
- data CommandTag
- newtype Query = Query ByteString
- data FormatCode
- data ColumnInfo
- class Message m
- type family MessageResult m :: Type
- class Bind ps
- class Execute p
- class Close p
- type StringEncoder = String -> Either String ByteString
- type StringDecoder = ByteString -> Either String String
- begin :: ExecutedProcedure ()
- commit :: ExecutedProcedure ()
- rollback :: ExecutedProcedure ()
- data TransactionState
- class FromField a where
- fromField :: MonadFail m => StringDecoder -> ColumnInfo -> Maybe ByteString -> m a
- class FromRecord a where
- fromRecord :: StringDecoder -> [ColumnInfo] -> Parser a
- class ToField a where
- toField :: MonadFail m => BackendParameters -> StringEncoder -> Maybe Oid -> FormatCode -> a -> m (Maybe ByteString)
- class ToRecord a where
- toRecord :: MonadFail m => BackendParameters -> StringEncoder -> Maybe [Oid] -> [FormatCode] -> a -> m [Maybe ByteString]
- data Raw where
- pattern Value :: ByteString -> Raw
- pattern Null :: Raw
- data Exception = Exception e => Exception e
- data ErrorResponse = ErrorResponse {}
- newtype ResponseParsingFailed = ResponseParsingFailed {}
- data Oid
Connection
A configuration of a connection.
Default configuration is def, which is following.
Config{ address =AddressResolved$SockAddrInet5432 $tupleToHostAddress(127, 0, 0, 1) , user = "postgres" , password = "" , database = "" , sendingBufferSize = 2 ^ (12 ::Int) , receptionBufferSize = 2 ^ (12 ::Int) }
Constructors
| Config | |
data Connection Source #
PostgreSQL connection.
$sel:pid:Connection :: Connection -> Pid Source #
The process ID of the server.
$sel:parameters:Connection :: Connection -> BackendParameters Source #
Set of server parameters.
$sel:config:Connection :: Connection -> Config Source #
Configuration of this connection.
IP address.
Constructors
| AddressResolved SockAddr | Address which is DNS resolved. |
| AddressNotResolved HostName ServiceName | Address which is not DNS resolved. |
type BackendParameters = Map ShortByteString ShortByteString Source #
Set of server parameters.
withConnection :: Config -> (Connection -> IO a) -> IO a Source #
Bracket function for a connection.
disconnect :: Connection -> IO () Source #
To disconnect to the server.
Extended Query
Arguments
| :: PreparedStatementName | A new name of prepared statement. |
| -> Query | SQL whose placeoholder style is dollar style. |
| -> Either (Word, Word) ([Oid], [Oid]) | A pair of the number of columns of the parameter and the result,
or a pair of the list of OIDs of the parameter and the result.
On |
| -> PreparedStatementProcedure |
To get the procedure to build the message of parsing SQL query and to parse its response.
Arguments
| :: (Bind ps, ToRecord param, MonadFail m) | |
| => PortalName | A new name of portal. |
| -> FormatCode | Binary format or text format for the parameter. |
| -> FormatCode | Binary format or text format for the results. |
| -> BackendParameters | The set of the server parameters. |
| -> StringEncoder | How to encode strings. |
| -> param | Parameter for this query. |
| -> ps | Prepared statement. |
| -> m PortalProcedure |
To get the procedure to build the message of binding the parameter and to parse its response.
Arguments
| :: (Execute p, FromRecord result) | |
| => Word | How many records to get. “0” means unlimited. |
| -> StringDecoder | How to decode strings. |
| -> p | Portal. |
| -> ExecutedProcedure result |
To get the procedure to build the message of execution and to parse its response.
flush :: Message m => Connection -> m -> IO (MessageResult m) Source #
To build and send the given message and a “Flush” message and to receive and parse those responses.
sync :: Message m => Connection -> m -> IO (MessageResult m, TransactionState) Source #
To build and send the given message and a “Sync” message and to receive and parse those responses.
close :: Close p => p -> CloseProcedure Source #
To build and send the “Close” message and to receive and parse its response.
data PreparedStatement Source #
This represents a prepared statement which is already processed by a server.
Instances
| Eq PreparedStatement Source # | |
Defined in Database.PostgreSQL.Pure.Internal.Data Methods (==) :: PreparedStatement -> PreparedStatement -> Bool # (/=) :: PreparedStatement -> PreparedStatement -> Bool # | |
| Show PreparedStatement Source # | |
Defined in Database.PostgreSQL.Pure.Internal.Data Methods showsPrec :: Int -> PreparedStatement -> ShowS # show :: PreparedStatement -> String # showList :: [PreparedStatement] -> ShowS # | |
| Close PreparedStatement Source # | |
Defined in Database.PostgreSQL.Pure.Internal.Query Methods | |
| Bind PreparedStatement Source # | |
Defined in Database.PostgreSQL.Pure.Internal.Query Methods bind :: (ToRecord param, MonadFail m) => PortalName -> FormatCode -> FormatCode -> BackendParameters -> StringEncoder -> param -> PreparedStatement -> m PortalProcedure Source # | |
data PreparedStatementProcedure Source #
This represents a prepared statemnt which is not yet processed by a server.
Instances
| Show PreparedStatementProcedure Source # | |
Defined in Database.PostgreSQL.Pure.Internal.Data Methods showsPrec :: Int -> PreparedStatementProcedure -> ShowS # show :: PreparedStatementProcedure -> String # showList :: [PreparedStatementProcedure] -> ShowS # | |
| Message PreparedStatementProcedure Source # | |
Defined in Database.PostgreSQL.Pure.Internal.Query | |
| Bind PreparedStatementProcedure Source # | |
Defined in Database.PostgreSQL.Pure.Internal.Query Methods bind :: (ToRecord param, MonadFail m) => PortalName -> FormatCode -> FormatCode -> BackendParameters -> StringEncoder -> param -> PreparedStatementProcedure -> m PortalProcedure Source # | |
| type MessageResult PreparedStatementProcedure Source # | |
newtype PreparedStatementName Source #
Name of a prepared statement.
Constructors
| PreparedStatementName ByteString |
Instances
This represents a portal which is already processed by a server.
Instances
| Eq Portal Source # | |
| Show Portal Source # | |
| Close Portal Source # | |
Defined in Database.PostgreSQL.Pure.Internal.Query Methods close :: Portal -> CloseProcedure Source # | |
| Execute Portal Source # | |
Defined in Database.PostgreSQL.Pure.Internal.Query Methods execute :: FromRecord result => Word -> StringDecoder -> Portal -> ExecutedProcedure result Source # | |
data PortalProcedure Source #
This represents a portal which is not yet processed by a server.
Instances
| Show PortalProcedure Source # | |
Defined in Database.PostgreSQL.Pure.Internal.Data Methods showsPrec :: Int -> PortalProcedure -> ShowS # show :: PortalProcedure -> String # showList :: [PortalProcedure] -> ShowS # | |
| Message PortalProcedure Source # | |
Defined in Database.PostgreSQL.Pure.Internal.Query Methods builder :: PortalProcedure -> Builder parser :: PortalProcedure -> Parser (MessageResult PortalProcedure) | |
| Execute PortalProcedure Source # | |
Defined in Database.PostgreSQL.Pure.Internal.Query Methods execute :: FromRecord result => Word -> StringDecoder -> PortalProcedure -> ExecutedProcedure result Source # | |
| type MessageResult PortalProcedure Source # | |
Defined in Database.PostgreSQL.Pure.Internal.Data | |
newtype PortalName Source #
Name of a portal.
Constructors
| PortalName ByteString |
Instances
This represents a result of a “Execute” message which is already processed by a server.
data ExecutedProcedure r Source #
This represents a result of a “Execute” message which is not yet processed by a server.
Instances
| Show (ExecutedProcedure r) Source # | |
Defined in Database.PostgreSQL.Pure.Internal.Data Methods showsPrec :: Int -> ExecutedProcedure r -> ShowS # show :: ExecutedProcedure r -> String # showList :: [ExecutedProcedure r] -> ShowS # | |
| Message (ExecutedProcedure r) Source # | |
Defined in Database.PostgreSQL.Pure.Internal.Query Methods builder :: ExecutedProcedure r -> Builder parser :: ExecutedProcedure r -> Parser (MessageResult (ExecutedProcedure r)) | |
| type MessageResult (ExecutedProcedure r) Source # | |
Defined in Database.PostgreSQL.Pure.Internal.Data | |
data ExecuteResult Source #
Result of a “Execute” message.
Constructors
| ExecuteComplete CommandTag | All records gotten. |
| ExecuteEmptyQuery | No records. |
| ExecuteSuspended | Records are left yet. |
Instances
| Eq ExecuteResult Source # | |
Defined in Database.PostgreSQL.Pure.Internal.Data Methods (==) :: ExecuteResult -> ExecuteResult -> Bool # (/=) :: ExecuteResult -> ExecuteResult -> Bool # | |
| Read ExecuteResult Source # | |
Defined in Database.PostgreSQL.Pure.Internal.Data Methods readsPrec :: Int -> ReadS ExecuteResult # readList :: ReadS [ExecuteResult] # | |
| Show ExecuteResult Source # | |
Defined in Database.PostgreSQL.Pure.Internal.Data Methods showsPrec :: Int -> ExecuteResult -> ShowS # show :: ExecuteResult -> String # showList :: [ExecuteResult] -> ShowS # | |
data CommandTag Source #
Command tag, which means which SQL command is completed.
Constructors
| InsertTag Oid Int | |
| DeleteTag Int | |
| UpdateTag Int | |
| SelectTag Int | |
| MoveTag Int | |
| FetchTag Int | |
| CopyTag Int | |
| CreateTableTag | |
| DropTableTag | |
| BeginTag | |
| CommitTag | |
| RollbackTag | |
| SetTag |
Instances
| Eq CommandTag Source # | |
Defined in Database.PostgreSQL.Pure.Internal.Data | |
| Read CommandTag Source # | |
Defined in Database.PostgreSQL.Pure.Internal.Data Methods readsPrec :: Int -> ReadS CommandTag # readList :: ReadS [CommandTag] # readPrec :: ReadPrec CommandTag # readListPrec :: ReadPrec [CommandTag] # | |
| Show CommandTag Source # | |
Defined in Database.PostgreSQL.Pure.Internal.Data Methods showsPrec :: Int -> CommandTag -> ShowS # show :: CommandTag -> String # showList :: [CommandTag] -> ShowS # | |
SQL query.
This fromString counts only ASCII, becouse it is the same with ByteString.
Constructors
| Query ByteString |
data FormatCode Source #
Format code of patameters of results.
Constructors
| TextFormat | |
| BinaryFormat |
Instances
| Enum FormatCode Source # | |
Defined in Database.PostgreSQL.Pure.Internal.Data Methods succ :: FormatCode -> FormatCode # pred :: FormatCode -> FormatCode # toEnum :: Int -> FormatCode # fromEnum :: FormatCode -> Int # enumFrom :: FormatCode -> [FormatCode] # enumFromThen :: FormatCode -> FormatCode -> [FormatCode] # enumFromTo :: FormatCode -> FormatCode -> [FormatCode] # enumFromThenTo :: FormatCode -> FormatCode -> FormatCode -> [FormatCode] # | |
| Eq FormatCode Source # | |
Defined in Database.PostgreSQL.Pure.Internal.Data | |
| Read FormatCode Source # | |
Defined in Database.PostgreSQL.Pure.Internal.Data Methods readsPrec :: Int -> ReadS FormatCode # readList :: ReadS [FormatCode] # readPrec :: ReadPrec FormatCode # readListPrec :: ReadPrec [FormatCode] # | |
| Show FormatCode Source # | |
Defined in Database.PostgreSQL.Pure.Internal.Data Methods showsPrec :: Int -> FormatCode -> ShowS # show :: FormatCode -> String # showList :: [FormatCode] -> ShowS # | |
data ColumnInfo Source #
Metadata of a column.
Instances
| Eq ColumnInfo Source # | |
Defined in Database.PostgreSQL.Pure.Internal.Data | |
| Read ColumnInfo Source # | |
Defined in Database.PostgreSQL.Pure.Internal.Data Methods readsPrec :: Int -> ReadS ColumnInfo # readList :: ReadS [ColumnInfo] # readPrec :: ReadPrec ColumnInfo # readListPrec :: ReadPrec [ColumnInfo] # | |
| Show ColumnInfo Source # | |
Defined in Database.PostgreSQL.Pure.Internal.Data Methods showsPrec :: Int -> ColumnInfo -> ShowS # show :: ColumnInfo -> String # showList :: [ColumnInfo] -> ShowS # | |
Instances
type family MessageResult m :: Type Source #
To convert a type which means that is is not prcessed by the server to a respective type which means that it is processed by the server.
Instances
This means that ps is a objective of bind.
Minimal complete definition
Instances
| Bind PreparedStatementProcedure Source # | |
Defined in Database.PostgreSQL.Pure.Internal.Query Methods bind :: (ToRecord param, MonadFail m) => PortalName -> FormatCode -> FormatCode -> BackendParameters -> StringEncoder -> param -> PreparedStatementProcedure -> m PortalProcedure Source # | |
| Bind PreparedStatement Source # | |
Defined in Database.PostgreSQL.Pure.Internal.Query Methods bind :: (ToRecord param, MonadFail m) => PortalName -> FormatCode -> FormatCode -> BackendParameters -> StringEncoder -> param -> PreparedStatement -> m PortalProcedure Source # | |
This means that p is a objective of execute.
Minimal complete definition
Instances
| Execute PortalProcedure Source # | |
Defined in Database.PostgreSQL.Pure.Internal.Query Methods execute :: FromRecord result => Word -> StringDecoder -> PortalProcedure -> ExecutedProcedure result Source # | |
| Execute Portal Source # | |
Defined in Database.PostgreSQL.Pure.Internal.Query Methods execute :: FromRecord result => Word -> StringDecoder -> Portal -> ExecutedProcedure result Source # | |
This means that p is a objective of close.
Minimal complete definition
Instances
| Close Portal Source # | |
Defined in Database.PostgreSQL.Pure.Internal.Query Methods close :: Portal -> CloseProcedure Source # | |
| Close PreparedStatement Source # | |
Defined in Database.PostgreSQL.Pure.Internal.Query Methods | |
| Close (Portal parameterLength resultLength) Source # | |
Defined in Database.PostgreSQL.Pure Methods close :: Portal parameterLength resultLength -> CloseProcedure Source # | |
| Close (PreparedStatement parameterLength resultLength) Source # | |
Defined in Database.PostgreSQL.Pure Methods close :: PreparedStatement parameterLength resultLength -> CloseProcedure Source # | |
type StringEncoder = String -> Either String ByteString Source #
Encoder of strings which may fail.
type StringDecoder = ByteString -> Either String String Source #
Decoder of strings which may fail.
Transaction
begin :: ExecutedProcedure () Source #
To send BEGIN SQL statement.
commit :: ExecutedProcedure () Source #
To send COMMIT SQL statement.
rollback :: ExecutedProcedure () Source #
To send ROLLBACK SQL statement.
data TransactionState Source #
Transaction state of a server.
Instances
Record
class FromField a where Source #
This means that a field can be decoded as a.
Methods
fromField :: MonadFail m => StringDecoder -> ColumnInfo -> Maybe ByteString -> m a Source #
Decoder of a field.
Instances
class FromRecord a where Source #
This means that a record can be parsed as a.
Instances
class ToField a where Source #
This means that a can be encoded to a field.
Methods
toField :: MonadFail m => BackendParameters -> StringEncoder -> Maybe Oid -> FormatCode -> a -> m (Maybe ByteString) Source #
Encoder of a field.
Instances
class ToRecord a where Source #
This means that a can be encoded to a record.
Methods
toRecord :: MonadFail m => BackendParameters -> StringEncoder -> Maybe [Oid] -> [FormatCode] -> a -> m [Maybe ByteString] Source #
Encoder of a field.
Instances
Data without encoding nor decoding of a field.
Bundled Patterns
| pattern Value :: ByteString -> Raw | Not |
| pattern Null :: Raw |
|
Exception
Root exception.
Exception├ErrorResponse└ResponseParsingFailed
Instances
| Show Exception Source # | |
| Exception Exception Source # | |
Defined in Database.PostgreSQL.Pure.Internal.Exception Methods toException :: Exception -> SomeException # fromException :: SomeException -> Maybe Exception # displayException :: Exception -> String # | |
data ErrorResponse Source #
This means that the server responds an error.
Constructors
| ErrorResponse | |
Fields | |
Instances
| Eq ErrorResponse Source # | |
Defined in Database.PostgreSQL.Pure.Internal.Exception Methods (==) :: ErrorResponse -> ErrorResponse -> Bool # (/=) :: ErrorResponse -> ErrorResponse -> Bool # | |
| Read ErrorResponse Source # | |
Defined in Database.PostgreSQL.Pure.Internal.Exception Methods readsPrec :: Int -> ReadS ErrorResponse # readList :: ReadS [ErrorResponse] # | |
| Show ErrorResponse Source # | |
Defined in Database.PostgreSQL.Pure.Internal.Exception Methods showsPrec :: Int -> ErrorResponse -> ShowS # show :: ErrorResponse -> String # showList :: [ErrorResponse] -> ShowS # | |
| Exception ErrorResponse Source # | |
Defined in Database.PostgreSQL.Pure.Internal.Exception Methods toException :: ErrorResponse -> SomeException # fromException :: SomeException -> Maybe ErrorResponse # displayException :: ErrorResponse -> String # | |
newtype ResponseParsingFailed Source #
This means that the server responds an unknown message.
Constructors
| ResponseParsingFailed | |
Instances
| Show ResponseParsingFailed Source # | |
Defined in Database.PostgreSQL.Pure.Internal.Exception Methods showsPrec :: Int -> ResponseParsingFailed -> ShowS # show :: ResponseParsingFailed -> String # showList :: [ResponseParsingFailed] -> ShowS # | |
| Exception ResponseParsingFailed Source # | |
Defined in Database.PostgreSQL.Pure.Internal.Exception | |
OID
OID.
Constant values are listed in Database.PostgreSQL.Pure.Oid.
Instances
| Eq Oid Source # | |
| Num Oid Source # | |
| Read Oid Source # | |
| Show Oid Source # | |
| ToField Oid Source # | |
Defined in Database.PostgreSQL.Pure.Internal.Builder Methods toField :: MonadFail m => BackendParameters -> StringEncoder -> Maybe Oid -> FormatCode -> Oid -> m (Maybe ByteString) Source # | |
| FromField Oid Source # | |
Defined in Database.PostgreSQL.Pure.Internal.Parser Methods fromField :: MonadFail m => StringDecoder -> ColumnInfo -> Maybe ByteString -> m Oid Source # | |
| Convertible Oid SqlTypeId Source # | |
Defined in Database.HDBC.PostgreSQL.Pure Methods safeConvert :: Oid -> ConvertResult SqlTypeId # | |