| Copyright | (c) 2010 Grant Monroe (c) 2011 Leon P Smith | 
|---|---|
| License | BSD3 | 
| Maintainer | [email protected] | 
| Stability | experimental | 
| Safe Haskell | None | 
| Language | Haskell2010 | 
Database.PostgreSQL.LibPQ
Contents
- Database Connection Control Functions
- Connection Status Functions
- Command Execution Functions
- Retrieving Query Result Information
- Escaping Strings for Inclusion in SQL Commands
- Escaping Binary Strings for Inclusion in SQL Commands
- Escaping Identifiers for Inclusion in SQL Commands
- Using COPY
- Asynchronous Command Processing
- Cancelling Queries in Progress
- Asynchronous Notification
- Control Functions
- Nonfatal Error Reporting
- Large Objects
Description
This is a binding to libpq: the C application programmer's interface to PostgreSQL. libpq is a set of library functions that allow client programs to pass queries to the PostgreSQL backend server and to receive the results of these queries.
This is intended to be a very low-level interface to libpq. It provides memory management and a somewhat more consistent interface to error conditions. Application code should typically use a higher-level PostgreSQL binding.
This interface is not safe,  because libpq unfortunately conflates
 explicit disconnects with memory management.   A use-after-free memory
 fault will result if a connection is used in any way after finish is
 called.  This will likely cause a segfault,  or return an error if memory
 has not yet been reused.  Other more bizarre behaviors are possible,
 though unlikely by chance.  Higher-level bindings need to be aware of
 this issue and need to ensure that application code cannot cause the
 functions in this module to be called on an finished connection.
One possibility is to represent a connection in a higher-level interface
 as MVar (Maybe Connection), using Nothing to represent an explicitly
 disconnected state.  This was done in an earlier incarnation of this
 library,  however this was removed because a higher level binding is
 likely to use a similar construct to deal with other issues.  Thus
 incorporating that in this module results in extra layers of indirection
 for relatively little functionality.
Synopsis
- data Connection
- connectdb :: ByteString -> IO Connection
- connectStart :: ByteString -> IO Connection
- connectPoll :: Connection -> IO PollingStatus
- newNullConnection :: IO Connection
- isNullConnection :: Connection -> Bool
- reset :: Connection -> IO ()
- resetStart :: Connection -> IO Bool
- resetPoll :: Connection -> IO PollingStatus
- data PollingStatus
- finish :: Connection -> IO ()
- db :: Connection -> IO (Maybe ByteString)
- user :: Connection -> IO (Maybe ByteString)
- pass :: Connection -> IO (Maybe ByteString)
- host :: Connection -> IO (Maybe ByteString)
- port :: Connection -> IO (Maybe ByteString)
- options :: Connection -> IO (Maybe ByteString)
- data ConnStatus
- status :: Connection -> IO ConnStatus
- data TransactionStatus
- transactionStatus :: Connection -> IO TransactionStatus
- parameterStatus :: Connection -> ByteString -> IO (Maybe ByteString)
- protocolVersion :: Connection -> IO Int
- serverVersion :: Connection -> IO Int
- libpqVersion :: IO Int
- errorMessage :: Connection -> IO (Maybe ByteString)
- socket :: Connection -> IO (Maybe Fd)
- backendPID :: Connection -> IO CPid
- connectionNeedsPassword :: Connection -> IO Bool
- connectionUsedPassword :: Connection -> IO Bool
- data Result
- exec :: Connection -> ByteString -> IO (Maybe Result)
- data Format
- newtype Oid = Oid CUInt
- invalidOid :: Oid
- execParams :: Connection -> ByteString -> [Maybe (Oid, ByteString, Format)] -> Format -> IO (Maybe Result)
- prepare :: Connection -> ByteString -> ByteString -> Maybe [Oid] -> IO (Maybe Result)
- execPrepared :: Connection -> ByteString -> [Maybe (ByteString, Format)] -> Format -> IO (Maybe Result)
- describePrepared :: Connection -> ByteString -> IO (Maybe Result)
- describePortal :: Connection -> ByteString -> IO (Maybe Result)
- data ExecStatus
- resultStatus :: Result -> IO ExecStatus
- resStatus :: ExecStatus -> IO ByteString
- resultErrorMessage :: Result -> IO (Maybe ByteString)
- data FieldCode
- resultErrorField :: Result -> FieldCode -> IO (Maybe ByteString)
- unsafeFreeResult :: Result -> IO ()
- ntuples :: Result -> IO Row
- nfields :: Result -> IO Column
- newtype Row = Row CInt
- newtype Column = Col CInt
- toRow :: Integral a => a -> Row
- toColumn :: Integral a => a -> Column
- fname :: Result -> Column -> IO (Maybe ByteString)
- fnumber :: Result -> ByteString -> IO (Maybe Column)
- ftable :: Result -> Column -> IO Oid
- ftablecol :: Result -> Column -> IO Column
- fformat :: Result -> Column -> IO Format
- ftype :: Result -> Column -> IO Oid
- fmod :: Result -> Column -> IO Int
- fsize :: Result -> Column -> IO Int
- getvalue :: Result -> Row -> Column -> IO (Maybe ByteString)
- getvalue' :: Result -> Row -> Column -> IO (Maybe ByteString)
- getisnull :: Result -> Row -> Column -> IO Bool
- getlength :: Result -> Row -> Column -> IO Int
- nparams :: Result -> IO Int
- paramtype :: Result -> Int -> IO Oid
- cmdStatus :: Result -> IO (Maybe ByteString)
- cmdTuples :: Result -> IO (Maybe ByteString)
- escapeStringConn :: Connection -> ByteString -> IO (Maybe ByteString)
- escapeByteaConn :: Connection -> ByteString -> IO (Maybe ByteString)
- unescapeBytea :: ByteString -> IO (Maybe ByteString)
- escapeIdentifier :: Connection -> ByteString -> IO (Maybe ByteString)
- data CopyInResult
- putCopyData :: Connection -> ByteString -> IO CopyInResult
- putCopyEnd :: Connection -> Maybe ByteString -> IO CopyInResult
- data CopyOutResult
- getCopyData :: Connection -> Bool -> IO CopyOutResult
- sendQuery :: Connection -> ByteString -> IO Bool
- sendQueryParams :: Connection -> ByteString -> [Maybe (Oid, ByteString, Format)] -> Format -> IO Bool
- sendPrepare :: Connection -> ByteString -> ByteString -> Maybe [Oid] -> IO Bool
- sendQueryPrepared :: Connection -> ByteString -> [Maybe (ByteString, Format)] -> Format -> IO Bool
- sendDescribePrepared :: Connection -> ByteString -> IO Bool
- sendDescribePortal :: Connection -> ByteString -> IO Bool
- getResult :: Connection -> IO (Maybe Result)
- consumeInput :: Connection -> IO Bool
- isBusy :: Connection -> IO Bool
- setnonblocking :: Connection -> Bool -> IO Bool
- isnonblocking :: Connection -> IO Bool
- setSingleRowMode :: Connection -> IO Bool
- data FlushStatus
- flush :: Connection -> IO FlushStatus
- data Cancel
- getCancel :: Connection -> IO (Maybe Cancel)
- cancel :: Cancel -> IO (Either ByteString ())
- data Notify = Notify {- notifyRelname :: !ByteString
- notifyBePid :: !CPid
- notifyExtra :: !ByteString
 
- notifies :: Connection -> IO (Maybe Notify)
- clientEncoding :: Connection -> IO ByteString
- setClientEncoding :: Connection -> ByteString -> IO Bool
- data Verbosity
- setErrorVerbosity :: Connection -> Verbosity -> IO Verbosity
- disableNoticeReporting :: Connection -> IO ()
- enableNoticeReporting :: Connection -> IO ()
- getNotice :: Connection -> IO (Maybe ByteString)
- newtype LoFd = LoFd CInt
- loCreat :: Connection -> IO (Maybe Oid)
- loCreate :: Connection -> Oid -> IO (Maybe Oid)
- loImport :: Connection -> FilePath -> IO (Maybe Oid)
- loImportWithOid :: Connection -> FilePath -> Oid -> IO (Maybe Oid)
- loExport :: Connection -> Oid -> FilePath -> IO (Maybe ())
- loOpen :: Connection -> Oid -> IOMode -> IO (Maybe LoFd)
- loWrite :: Connection -> LoFd -> ByteString -> IO (Maybe Int)
- loRead :: Connection -> LoFd -> Int -> IO (Maybe ByteString)
- loSeek :: Connection -> LoFd -> SeekMode -> Int -> IO (Maybe Int)
- loTell :: Connection -> LoFd -> IO (Maybe Int)
- loTruncate :: Connection -> LoFd -> Int -> IO (Maybe ())
- loClose :: Connection -> LoFd -> IO (Maybe ())
- loUnlink :: Connection -> Oid -> IO (Maybe ())
Database Connection Control Functions
The following functions deal with making a connection to a
 PostgreSQL backend server. An application program can have several
 backend connections open at one time. (One reason to do that is to
 access more than one database.) Each connection is represented by a
 Connection, which is obtained from the function connectdb, or
 connectStart. The status function should be called to check
 whether a connection was successfully made before queries are sent
 via the connection object.
data Connection Source #
Connection encapsulates a connection to the backend.
Instances
| Eq Connection Source # | |
| Defined in Database.PostgreSQL.LibPQ.Internal | |
Arguments
| :: ByteString | Connection Info | 
| -> IO Connection | 
Makes a new connection to the database server.
This function opens a new database connection using the parameters
  taken from the string conninfo. Its nonblocking analogues are
  connectStart and connectPoll.
The passed string can be empty to use all default parameters, or it can contain one or more parameter settings separated by whitespace. Each parameter setting is in the form keyword = value. Spaces around the equal sign are optional. To write an empty value or a value containing spaces, surround it with single quotes, e.g., keyword = 'a value'. Single quotes and backslashes within the value must be escaped with a backslash, i.e., ' and \.
Arguments
| :: ByteString | Connection Info | 
| -> IO Connection | 
Make a connection to the database server in a nonblocking manner.
connectPoll :: Connection -> IO PollingStatus Source #
If connectStart succeeds, the next stage is to poll libpq so
 that it can proceed with the connection sequence. Use socket to
 obtain the Fd of the socket underlying the database
 connection. Loop thus: If connectPoll last returned
 PollingReading, wait until the socket is ready to read (as
 indicated by select(), poll(), or similar system function). Then
 call connectPoll again. Conversely, if connectPoll last
 returned PollingWriting, wait until the socket is ready to write,
 then call connectPoll again. If you have yet to call
 connectPoll, i.e., just after the call to connectStart, behave
 as if it last returned PollingWriting. Continue this loop until
 connectPoll returns PollingFailed, indicating the connection
 procedure has failed, or PollingOk, indicating the connection has
 been successfully made.
newNullConnection :: IO Connection Source #
Allocate a Null Connection, which all libpq functions should safely fail on.
isNullConnection :: Connection -> Bool Source #
Test if a connection is the Null Connection.
reset :: Connection -> IO () Source #
Resets the communication channel to the server.
This function will close the connection to the server and attempt to reestablish a new connection to the same server, using all the same parameters previously used. This might be useful for error recovery if a working connection is lost.
resetStart :: Connection -> IO Bool Source #
Reset the communication channel to the server, in a nonblocking manner.
resetPoll :: Connection -> IO PollingStatus Source #
To initiate a connection reset, call resetStart. If it returns
 False, the reset has failed. If it returns True, poll the reset
 using resetPoll in exactly the same way as you would create the
 connection using connectPoll.
data PollingStatus Source #
Constructors
| PollingFailed | |
| PollingReading | |
| PollingWriting | |
| PollingOk | 
Instances
| Eq PollingStatus Source # | |
| Defined in Database.PostgreSQL.LibPQ Methods (==) :: PollingStatus -> PollingStatus -> Bool # (/=) :: PollingStatus -> PollingStatus -> Bool # | |
| Show PollingStatus Source # | |
| Defined in Database.PostgreSQL.LibPQ Methods showsPrec :: Int -> PollingStatus -> ShowS # show :: PollingStatus -> String # showList :: [PollingStatus] -> ShowS # | |
finish :: Connection -> IO () Source #
Closes the connection to the server.
Note that the Connection must not be used again after finish
 has been called.
Connection Status Functions
These functions can be used to interrogate the status of an existing database connection object.
db :: Connection -> IO (Maybe ByteString) Source #
Returns the database name of the connection.
user :: Connection -> IO (Maybe ByteString) Source #
Returns the user name of the connection.
pass :: Connection -> IO (Maybe ByteString) Source #
Returns the password of the connection.
host :: Connection -> IO (Maybe ByteString) Source #
Returns the server host name of the connection.
port :: Connection -> IO (Maybe ByteString) Source #
Returns the port of the connection.
options :: Connection -> IO (Maybe ByteString) Source #
Returns the command-line options passed in the connection request.
data ConnStatus Source #
Constructors
| ConnectionOk | The  | 
| ConnectionBad | The connection procedure has failed. | 
| ConnectionStarted | Waiting for connection to be made. | 
| ConnectionMade | Connection OK; waiting to send. | 
| ConnectionAwaitingResponse | Waiting for a response from the server. | 
| ConnectionAuthOk | Received authentication; waiting for backend start-up to finish. | 
| ConnectionSetEnv | Negotiating environment-driven parameter settings. | 
| ConnectionSSLStartup | Negotiating SSL encryption. | 
Instances
| Eq ConnStatus Source # | |
| Defined in Database.PostgreSQL.LibPQ | |
| Show ConnStatus Source # | |
| Defined in Database.PostgreSQL.LibPQ Methods showsPrec :: Int -> ConnStatus -> ShowS # show :: ConnStatus -> String # showList :: [ConnStatus] -> ShowS # | |
status :: Connection -> IO ConnStatus Source #
Returns the status of the connection.
The status can be one of a number of values. However, only two of
 these are seen outside of an asynchronous connection procedure:
 ConnectionOk and ConnectionBad. A good connection to the
 database has the status ConnectionOk. A failed connection attempt
 is signaled by status ConnectionBad. Ordinarily, an OK status
 will remain so until finish, but a communications failure might
 result in the status changing to ConnectionBad prematurely. In
 that case the application could try to recover by calling reset.
See the entry for connectStart and connectPoll with regards to
 other status codes that might be seen.
data TransactionStatus Source #
Constructors
| TransIdle | currently idle | 
| TransActive | a command is in progress | 
| TransInTrans | idle, in a valid transaction block | 
| TransInError | idle, in a failed transaction block | 
| TransUnknown | the connection is bad | 
Instances
| Eq TransactionStatus Source # | |
| Defined in Database.PostgreSQL.LibPQ Methods (==) :: TransactionStatus -> TransactionStatus -> Bool # (/=) :: TransactionStatus -> TransactionStatus -> Bool # | |
| Show TransactionStatus Source # | |
| Defined in Database.PostgreSQL.LibPQ Methods showsPrec :: Int -> TransactionStatus -> ShowS # show :: TransactionStatus -> String # showList :: [TransactionStatus] -> ShowS # | |
transactionStatus :: Connection -> IO TransactionStatus Source #
Returns the current in-transaction status of the server.
TransActive is reported only when a query has been sent to the
 server and not yet completed.
Arguments
| :: Connection | |
| -> ByteString | paramName | 
| -> IO (Maybe ByteString) | 
Looks up a current parameter setting of the server.
Certain parameter values are reported by the server automatically
 at connection startup or whenever their values
 change. parameterStatus can be used to interrogate these
 settings. It returns the current value of a parameter if known, or
 Nothing if the parameter is not known.
protocolVersion :: Connection -> IO Int Source #
Interrogates the frontend/backend protocol being used.
Applications might wish to use this to determine whether certain features are supported. Currently, the possible values are 2 (2.0 protocol), 3 (3.0 protocol), or zero (connection bad). This will not change after connection startup is complete, but it could theoretically change during a connection reset. The 3.0 protocol will normally be used when communicating with PostgreSQL 7.4 or later servers; pre-7.4 servers support only protocol 2.0. (Protocol 1.0 is obsolete and not supported by libpq.)
serverVersion :: Connection -> IO Int Source #
Returns an integer representing the backend version.
Applications might use this to determine the version of the database server they are connected to. The number is formed by converting the major, minor, and revision numbers into two-decimal-digit numbers and appending them together. For example, version 8.1.5 will be returned as 80105, and version 8.2 will be returned as 80200 (leading zeroes are not shown). Zero is returned if the connection is bad.
libpqVersion :: IO Int Source #
Return the version of libpq that is being used.
The result of this function can be used to determine, at run time, if specific functionality is available in the currently loaded version of libpq. The function can be used, for example, to determine which connection options are available for PQconnectdb or if the hex bytea output added in PostgreSQL 9.0 is supported.
This function appeared in PostgreSQL version 9.1, so it cannot be used to detect required functionality in earlier versions, since linking to it will create a link dependency on version 9.1.
errorMessage :: Connection -> IO (Maybe ByteString) Source #
Returns the error message most recently generated by an operation on the connection.
Nearly all libpq functions will set a message for errorMessage if
 they fail. Note that by libpq convention, a nonempty errorMessage
 result can be multiple lines, and will include a trailing
 newline. The result string should not be expected to remain the
 same across operations on the Connection.
socket :: Connection -> IO (Maybe Fd) Source #
Obtains the file descriptor number of the connection socket to the server. (This will not change during normal operation, but could change during connection setup or reset.)
backendPID :: Connection -> IO CPid Source #
Returns the process CPid of the backend server process
 handling this connection.
The backend PID is useful for debugging purposes and for comparison to NOTIFY messages (which include the PID of the notifying backend process). Note that the PID belongs to a process executing on the database server host, not the local host!
Command Execution Functions
Once a connection to a database server has been successfully established, the functions described here are used to perform SQL queries and commands.
Result encapsulates the result of a query (or more precisely,
 of a single SQL command --- a query string given to sendQuery can
 contain multiple commands and thus return multiple instances of
 Result.
Instances
Arguments
| :: Connection | connection | 
| -> ByteString | statement | 
| -> IO (Maybe Result) | result | 
Submits a command to the server and waits for the result.
Returns a Result or possibly Nothing. A Result will generally
 be returned except in out-of-memory conditions or serious errors
 such as inability to send the command to the server. If a Nothing
 is returned, it should be treated like a FatalError result. Use
 errorMessage to get more information about such errors.
It is allowed to include multiple SQL commands (separated by
 semicolons) in the command string. Multiple queries sent in a
 single exec call are processed in a single transaction, unless
 there are explicit BEGIN/COMMIT commands included in the query
 string to divide it into multiple transactions. Note however that
 the returned Result structure describes only the result of the
 last command executed from the string. Should one of the commands
 fail, processing of the string stops with it and the returned
 Result describes the error condition.
invalidOid :: Oid Source #
Arguments
| :: Connection | connection | 
| -> ByteString | statement | 
| -> [Maybe (Oid, ByteString, Format)] | parameters | 
| -> Format | result format | 
| -> IO (Maybe Result) | result | 
Submits a command to the server and waits for the result, with the ability to pass parameters separately from the SQL command text.
execParams is like exec, but offers additional functionality:
 parameter values can be specified separately from the command
 string proper, and query results can be requested in either text or
 binary format. execParams is supported only in protocol 3.0 and
 later connections; it will fail when using protocol 2.0.
The primary advantage of execParams over exec is that parameter
 values can be separated from the command string, thus avoiding the
 need for tedious and error-prone quoting and escaping.
Unlike exec, execParams allows at most one SQL command in the
 given string. (There can be semicolons in it, but not more than one
 nonempty command.) This is a limitation of the underlying protocol,
 but has some usefulness as an extra defense against SQL-injection
 attacks.
Tip: Specifying parameter types via OIDs is tedious, particularly if you prefer not to hard-wire particular OID values into your program. However, you can avoid doing so even in cases where the server by itself cannot determine the type of the parameter, or chooses a different type than you want. In the SQL command text, attach an explicit cast to the parameter symbol to show what data type you will send. For example: SELECT * FROM mytable WHERE x = $1::bigint; This forces parameter $1 to be treated as bigint, whereas by default it would be assigned the same type as x. Forcing the parameter type decision, either this way or by specifying a numeric type OID, is strongly recommended when sending parameter values in binary format, because binary format has less redundancy than text format and so there is less chance that the server will detect a type mismatch mistake for you.
Arguments
| :: Connection | connection | 
| -> ByteString | stmtName | 
| -> ByteString | query | 
| -> Maybe [Oid] | paramTypes | 
| -> IO (Maybe Result) | result | 
Submits a request to create a prepared statement with the given parameters, and waits for completion.
prepare creates a prepared statement for later execution with
 execPrepared. This feature allows commands that will be used
 repeatedly to be parsed and planned just once, rather than each
 time they are executed. prepare is supported only in protocol 3.0
 and later connections; it will fail when using protocol 2.0.
The function creates a prepared statement named stmtName from the
 query string, which must contain a single SQL command. stmtName can
 be "" to create an unnamed statement, in which case any
 pre-existing unnamed statement is automatically replaced; otherwise
 it is an error if the statement name is already defined in the
 current session. If any parameters are used, they are referred to
 in the query as $1, $2, etc. paramTypes specifies, by Oid, the
 data types to be assigned to the parameter symbols. If paramTypes
 is Nothing, or any particular element in the array is zero, the
 server assigns a data type to the parameter symbol in the same way
 it would do for an untyped literal string. Also, the query can use
 parameter symbols with numbers higher than the length of
 paramTypes; data types will be inferred for these symbols as
 well. (See describePrepared for a means to find out what data
 types were inferred.)
As with exec, the result is normally a Result whose contents
 indicate server-side success or failure. A Nothing result
 indicates out-of-memory or inability to send the command at
 all. Use errorMessage to get more information about such errors.
Prepared statements for use with execPrepared can also be created
 by executing SQL PREPARE statements. (But prepare is more
 flexible since it does not require parameter types to be
 pre-specified.) Also, although there is no libpq function for
 deleting a prepared statement, the SQL DEALLOCATE statement can be
 used for that purpose.
Arguments
| :: Connection | connection | 
| -> ByteString | stmtName | 
| -> [Maybe (ByteString, Format)] | parameters | 
| -> Format | result format | 
| -> IO (Maybe Result) | result | 
Sends a request to execute a prepared statement with given parameters, and waits for the result.
execPrepared is like execParams, but the command to be executed
 is specified by naming a previously-prepared statement, instead of
 giving a query string. This feature allows commands that will be
 used repeatedly to be parsed and planned just once, rather than
 each time they are executed. The statement must have been prepared
 previously in the current session. execPrepared is supported only
 in protocol 3.0 and later connections; it will fail when using
 protocol 2.0.
The parameters are identical to execParams, except that the name
 of a prepared statement is given instead of a query string, and the
 paramTypes parameter is not present (it is not needed since the
 prepared statement's parameter types were determined when it was
 created).
Arguments
| :: Connection | |
| -> ByteString | stmtName | 
| -> IO (Maybe Result) | 
Submits a request to obtain information about the specified prepared statement, and waits for completion.
describePrepared allows an application to obtain information
 about a previously prepared statement. describePrepared is
 supported only in protocol 3.0 and later connections; it will fail
 when using protocol 2.0.
stmtName can be empty to reference the unnamed statement, otherwise
 it must be the name of an existing prepared statement. On success,
 a Result with status CommandOk is returned. The functions
 nparams and paramtype can be applied to this Result to obtain
 information about the parameters of the prepared statement, and the
 functions nfields, fname, ftype, etc provide information
 about the result columns (if any) of the statement.
Arguments
| :: Connection | |
| -> ByteString | portalName | 
| -> IO (Maybe Result) | 
Submits a request to obtain information about the specified portal, and waits for completion.
describePortal allows an application to obtain information about
 a previously created portal. (libpq does not provide any direct
 access to portals, but you can use this function to inspect the
 properties of a cursor created with a DECLARE CURSOR SQL command.)
 describePortal is supported only in protocol 3.0 and later
 connections; it will fail when using protocol 2.0.
portalName can be empty to reference the unnamed portal, otherwise
 it must be the name of an existing portal. On success, a Result
 with status CommandOk is returned. The functions nfields,
 fname, ftype, etc can be applied to the Result to obtain
 information about the result columns (if any) of the portal.
data ExecStatus Source #
Constructors
| EmptyQuery | The string sent to the server was empty. | 
| CommandOk | Successful completion of a command returning no data. | 
| TuplesOk | Successful completion of a command returning data (such as a SELECT or SHOW). | 
| CopyOut | Copy Out (from server) data transfer started. | 
| CopyIn | Copy In (to server) data transfer started. | 
| CopyBoth | Copy In/Out data transfer started. | 
| BadResponse | The server's response was not understood. | 
| NonfatalError | A nonfatal error (a notice or warning) occurred. | 
| FatalError | A fatal error occurred. | 
| SingleTuple | The PGresult contains a single result tuple from the current command. This status occurs only when single-row mode has been selected for the query. | 
Instances
| Enum ExecStatus Source # | |
| Defined in Database.PostgreSQL.LibPQ Methods succ :: ExecStatus -> ExecStatus # pred :: ExecStatus -> ExecStatus # toEnum :: Int -> ExecStatus # fromEnum :: ExecStatus -> Int # enumFrom :: ExecStatus -> [ExecStatus] # enumFromThen :: ExecStatus -> ExecStatus -> [ExecStatus] # enumFromTo :: ExecStatus -> ExecStatus -> [ExecStatus] # enumFromThenTo :: ExecStatus -> ExecStatus -> ExecStatus -> [ExecStatus] # | |
| Eq ExecStatus Source # | |
| Defined in Database.PostgreSQL.LibPQ | |
| Show ExecStatus Source # | |
| Defined in Database.PostgreSQL.LibPQ Methods showsPrec :: Int -> ExecStatus -> ShowS # show :: ExecStatus -> String # showList :: [ExecStatus] -> ShowS # | |
resultStatus :: Result -> IO ExecStatus Source #
Returns the result status of the command.
resStatus :: ExecStatus -> IO ByteString Source #
Converts the ExecStatus returned by resultStatus into a
 string describing the status code. The caller should not
 free the result.
resultErrorMessage :: Result -> IO (Maybe ByteString) Source #
Returns the error message associated with the command, or an empty string if there was no error.
Constructors
| DiagSeverity | The severity; the field contents are ERROR, FATAL, or PANIC (in an error message), or WARNING, NOTICE, DEBUG, INFO, or LOG (in a notice message), or a localized translation of one of these. Always present. | 
| DiagSqlstate | The SQLSTATE code for the error. The SQLSTATE code identifies the type of error that has occurred; it can be used by front-end applications to perform specific operations (such as error handling) in response to a particular database error. For a list of the possible SQLSTATE codes, see Appendix A. This field is not localizable, and is always present. | 
| DiagMessagePrimary | The primary human-readable error message (typically one line). Always present. | 
| DiagMessageDetail | Detail: an optional secondary error message carrying more detail about the problem. Might run to multiple lines. | 
| DiagMessageHint | Hint: an optional suggestion what to do about the problem. This is intended to differ from detail in that it offers advice (potentially inappropriate) rather than hard facts. Might run to multiple lines. | 
| DiagStatementPosition | A string containing a decimal integer indicating an error cursor position as an index into the original statement string. The first character has index 1, and positions are measured in characters not bytes. | 
| DiagInternalPosition | This is defined the same as the
  | 
| DiagInternalQuery | The text of a failed internally-generated command. This could be, for example, a SQL query issued by a PL/pgSQL function. | 
| DiagContext | An indication of the context in which the error occurred. Presently this includes a call stack traceback of active procedural language functions and internally-generated queries. The trace is one entry per line, most recent first. | 
| DiagSourceFile | The file name of the source-code location where the error was reported. | 
| DiagSourceLine | The line number of the source-code location where the error was reported. | 
| DiagSourceFunction | The name of the source-code function reporting the error. | 
Instances
| Enum FieldCode Source # | |
| Defined in Database.PostgreSQL.LibPQ Methods succ :: FieldCode -> FieldCode # pred :: FieldCode -> FieldCode # fromEnum :: FieldCode -> Int # enumFrom :: FieldCode -> [FieldCode] # enumFromThen :: FieldCode -> FieldCode -> [FieldCode] # enumFromTo :: FieldCode -> FieldCode -> [FieldCode] # enumFromThenTo :: FieldCode -> FieldCode -> FieldCode -> [FieldCode] # | |
| Eq FieldCode Source # | |
| Show FieldCode Source # | |
resultErrorField :: Result -> FieldCode -> IO (Maybe ByteString) Source #
Returns an individual field of an error report.
fieldcode is an error field identifier; see the symbols listed
 below. Nothing is returned if the PGresult is not an error or
 warning result, or does not include the specified field. Field
 values will normally not include a trailing newline.
The client is responsible for formatting displayed information to meet its needs; in particular it should break long lines as needed. Newline characters appearing in the error message fields should be treated as paragraph breaks, not line breaks.
Errors generated internally by libpq will have severity and primary message, but typically no other fields. Errors returned by a pre-3.0-protocol server will include severity and primary message, and sometimes a detail message, but no other fields.
Note that error fields are only available from Result objects,
 not Connection objects; there is no errorField function.
unsafeFreeResult :: Result -> IO () Source #
Frees the memory associated with a result.  Note that using this
 function correctly is especially tricky;  you need to ensure that
 no references to the result.   This means no references to a value
 returned by getvalue,  no references hiding inside an unevaluated
 thunk,  etc.    Improper use of this function is likely to cause a
 segfault.   Also,  the use of this function is not strictly necessary;
 the memory will get freed by the garbage collector when there are no
 more references to the result.
Retrieving Query Result Information
These functions are used to extract information from a Result
 that represents a successful query result (that is, one that has
 status TuplesOk). They can also be used to extract information
 from a successful Describe operation: a Describe's result has all
 the same column information that actual execution of the query
 would provide, but it has zero rows. For objects with other status
 values, these functions will act as though the result has zero rows
 and zero columns.
ntuples :: Result -> IO Row Source #
Returns the number of rows (tuples) in the query result. (Note that PGresult objects are limited to no more than INT_MAX rows, so an int result is sufficient.)
nfields :: Result -> IO Column Source #
Returns the number of columns (fields) in each row of the query result.
fname :: Result -> Column -> IO (Maybe ByteString) Source #
Returns the column name associated with the given Column
 number. Column numbers start at 0.
fnumber :: Result -> ByteString -> IO (Maybe Column) Source #
Returns the column number associated with the given column name.
ftable :: Result -> Column -> IO Oid Source #
Returns the OID of the table from which the given column was fetched. Column numbers start at 0.
ftablecol :: Result -> Column -> IO Column Source #
Returns the column number (within its table) of the column making up the specified query result column. Query-result column numbers start at 0, but table columns have nonzero numbers.
fformat :: Result -> Column -> IO Format Source #
Returns the Format of the given column. Column numbers start at
 0.
ftype :: Result -> Column -> IO Oid Source #
Returns the data type associated with the given column
 number. The Oid returned is the internal OID number of the
 type. Column numbers start at 0.
You can query the system table pg_type to obtain the names and properties of the various data types. The OIDs of the built-in data types are defined in the file srcincludecatalog/pg_type.h in the source tree.
fmod :: Result -> Column -> IO Int Source #
Returns the type modifier of the column associated with the given column number. Column numbers start at 0.
The interpretation of modifier values is type-specific; they typically indicate precision or size limits. The value -1 is used to indicate "no information available". Most data types do not use modifiers, in which case the value is always -1.
fsize :: Result -> Column -> IO Int Source #
Returns the size in bytes of the column associated with the given column number. Column numbers start at 0.
fsize returns the space allocated for this column in a database
 row, in other words the size of the server's internal
 representation of the data type. (Accordingly, it is not really
 very useful to clients.) A negative value indicates the data type
 is variable-length.
getvalue :: Result -> Row -> Column -> IO (Maybe ByteString) Source #
Returns a single field value of one row of a PGresult. Row and column numbers start at 0.
For convenience, this binding uses getisnull and getlength to
 help construct the result.
Note: The ByteString returned holds a reference to the Result. As
 long as ByteString is live, the Result will not be garbage
 collected. getvalue' returns a copy of the data.
getisnull :: Result -> Row -> Column -> IO Bool Source #
Tests a field for a null value. Row and column numbers start at 0.
getlength :: Result -> Row -> Column -> IO Int Source #
Returns the actual length of a field value in bytes. Row and column numbers start at 0.
This is the actual data length for the particular data value, that
 is, the size of the object pointed to by getvalue. For text data
 format this is the same as strlen(). For binary format this is
 essential information. Note that one should not rely on fsize to
 obtain the actual data length.
nparams :: Result -> IO Int Source #
Returns the number of parameters of a prepared statement.
This function is only useful when inspecting the result of PQdescribePrepared. For other types of queries it will return zero.
Returns the data type of the indicated statement parameter. Parameter numbers start at 0.
This function is only useful when inspecting the result of
 describePrepared. For other types of queries it will return zero.
These functions are used to extract other information from PGresult objects.
cmdStatus :: Result -> IO (Maybe ByteString) Source #
Returns the command status tag from the SQL command that generated the PGresult.
Commonly this is just the name of the command, but it might include additional data such as the number of rows processed.
cmdTuples :: Result -> IO (Maybe ByteString) Source #
Returns the number of rows affected by the SQL command.
This function returns a string containing the number of rows
 affected by the SQL statement that generated the Result. This
 function can only be used following the execution of a SELECT,
 CREATE TABLE AS, INSERT, UPDATE, DELETE, MOVE, FETCH, or COPY
 statement, or an EXECUTE of a prepared query that contains an
 INSERT, UPDATE, or DELETE statement. If the command that generated
 the Result was anything else, cmdTuples returns an empty
 string.
Escaping Strings for Inclusion in SQL Commands
escapeStringConn :: Connection -> ByteString -> IO (Maybe ByteString) Source #
Escapes a string for use within an SQL command. This is useful when inserting data values as literal constants in SQL commands. Certain characters (such as quotes and backslashes) must be escaped to prevent them from being interpreted specially by the SQL parser.
Escaping Binary Strings for Inclusion in SQL Commands
escapeByteaConn :: Connection -> ByteString -> IO (Maybe ByteString) Source #
Escapes binary data for use within an SQL command with the type
 bytea. As with escapeStringConn, this is only used when inserting
 data directly into an SQL command string.
unescapeBytea :: ByteString -> IO (Maybe ByteString) Source #
Converts a ByteString representation of binary data into binary
 data - the reverse of PQescapeByteaConn. This is needed when
 retrieving bytea data in text format, but not when retrieving it in
 binary format.
The parameter points to a string such as might be returned by
 getvalue when applied to a bytea column. unescapeBytea converts
 this string representation into its binary representation. It
 returns a ByteString, or Nothing on error.
This conversion is not exactly the inverse of escapeByteaConn,
 because the string is not expected to be "escaped" when received
 from getvalue. In particular this means there is no need for
 string quoting considerations, and so no need for a Connection
 parameter.
Escaping Identifiers for Inclusion in SQL Commands
escapeIdentifier :: Connection -> ByteString -> IO (Maybe ByteString) Source #
escapeIdentifier escapes a string for use as an SQL identifier, such
   as a table, column, or function name. This is useful when a user-supplied
   identifier might contain special characters that would otherwise not be
   interpreted as part of the identifier by the SQL parser, or when the
   identifier might contain upper case characters whose case should be
   preserved.
The return string has all special characters replaced so that it will be properly processed as an SQL identifier. The return string will also be surrounded by double quotes.
On error, escapeIdentifier returns Nothing and a suitable message
   is stored in the conn object.
Using COPY
This provides support for PostgreSQL's COPY FROM facility.
For more information, see:
data CopyInResult Source #
Constructors
| CopyInOk | The data was sent. | 
| CopyInError | An error occurred (use  | 
| CopyInWouldBlock | The data was not sent because the
   attempt would block (this case is only
   possible if the connection is in
   nonblocking mode)  Wait for
   write-ready (e.g. by using
    | 
Instances
| Eq CopyInResult Source # | |
| Defined in Database.PostgreSQL.LibPQ | |
| Show CopyInResult Source # | |
| Defined in Database.PostgreSQL.LibPQ Methods showsPrec :: Int -> CopyInResult -> ShowS # show :: CopyInResult -> String # showList :: [CopyInResult] -> ShowS # | |
putCopyData :: Connection -> ByteString -> IO CopyInResult Source #
Send raw COPY data to the server during the CopyIn state.
putCopyEnd :: Connection -> Maybe ByteString -> IO CopyInResult Source #
Send end-of-data indication to the server during the CopyIn state.
- putCopyEnd conn Nothingends the- CopyInoperation successfully.
- putCopyEnd conn (Just errormsg)forces the- COPYto fail, with- errormsgused as the error message.
After putCopyEnd returns CopyOk, call getResult to obtain the final
 result status of the COPY command.  Then return to normal operation.
data CopyOutResult Source #
Constructors
| CopyOutRow !ByteString | Data representing a single row of the result | 
| CopyOutWouldBlock | A complete row is not yet available.  This
   case is only possible when  | 
| CopyOutDone | No more rows are available | 
| CopyOutError | An error occurred (e.g. the connection is
   not in the  | 
Instances
| Show CopyOutResult Source # | |
| Defined in Database.PostgreSQL.LibPQ Methods showsPrec :: Int -> CopyOutResult -> ShowS # show :: CopyOutResult -> String # showList :: [CopyOutResult] -> ShowS # | |
getCopyData :: Connection -> Bool -> IO CopyOutResult Source #
Receive raw COPY data from the server during the CopyOut state.
   The boolean parameter determines whether or not the call will block
   while waiting for data.
Asynchronous Command Processing
The exec function is adequate for submitting commands in normal,
 synchronous applications. It has a couple of deficiencies, however,
 that can be of importance to some users:
- execwaits for the command to be completed. The application might have other work to do (such as maintaining a user interface), in which case it won't want to block waiting for the response.
- Since the execution of the client application is suspended while it waits for the result, it is hard for the application to decide that it would like to try to cancel the ongoing command. (It can be done from a signal handler, but not otherwise.)
- execcan return only one- Result. If the submitted command string contains multiple SQL commands, all but the last- Resultare discarded by- exec.
Applications that do not like these limitations can instead use the
 underlying functions that exec is built from: sendQuery and
 getResult. There are also sendQueryParams, sendPrepare,
 sendQueryPrepared, sendDescribePrepared, and
 sendDescribePortal, which can be used with getResult to
 duplicate the functionality of execParams, prepare,
 execPrepared, describePrepared, and describePortal
 respectively.
sendQuery :: Connection -> ByteString -> IO Bool Source #
Submits a command to the server without waiting for the
 result(s). True is returned if the command was successfully
 dispatched and False if not (in which case, use errorMessage to
 get more information about the failure).
sendQueryParams :: Connection -> ByteString -> [Maybe (Oid, ByteString, Format)] -> Format -> IO Bool Source #
Submits a command and separate parameters to the server without waiting for the result(s).
sendPrepare :: Connection -> ByteString -> ByteString -> Maybe [Oid] -> IO Bool Source #
Sends a request to create a prepared statement with the given parameters, without waiting for completion.
sendQueryPrepared :: Connection -> ByteString -> [Maybe (ByteString, Format)] -> Format -> IO Bool Source #
Sends a request to execute a prepared statement with given parameters, without waiting for the result(s).
Arguments
| :: Connection | |
| -> ByteString | stmtName | 
| -> IO Bool | 
Submits a request to obtain information about the specified prepared statement, without waiting for completion.
This is an asynchronous version of describePrepared: it returns
 True if it was able to dispatch the request, and False if
 not. After a successful call, call getResult to obtain the
 results. The function's parameters are handled identically to
 describePrepared. Like describePrepared, it will not work on
 2.0-protocol connections.
Arguments
| :: Connection | |
| -> ByteString | portalName | 
| -> IO Bool | 
Submits a request to obtain information about the specified portal, without waiting for completion.
This is an asynchronous version of describePortal: it returns
 True if it was able to dispatch the request, and False if
 not. After a successful call, call getResult to obtain the
 results. The function's parameters are handled identically to
 describePortal. Like describePortal, it will not work on
 2.0-protocol connections.
getResult :: Connection -> IO (Maybe Result) Source #
Waits for the next result from a prior sendQuery,
 sendQueryParams, sendPrepare, or sendQueryPrepared call, and
 returns it. A null pointer is returned when the command is complete
 and there will be no more results.
consumeInput :: Connection -> IO Bool Source #
If input is available from the server, consume it.
consumeInput normally returns True indicating "no error", but
 returns False if there was some kind of trouble (in which case
 errorMessage can be consulted). Note that the result does not say
 whether any input data was actually collected. After calling
 consumeInput, the application can check isBusy and/or
 notifies to see if their state has changed.
isBusy :: Connection -> IO Bool Source #
Returns True if a command is busy, that is, getResult would block waiting for input. A False return indicates that getResult can be called with assurance of not blocking.
isBusy will not itself attempt to read data from the server;
 therefore consumeInput must be invoked first, or the busy state
 will never end.
setnonblocking :: Connection -> Bool -> IO Bool Source #
Sets the nonblocking status of the connection.
isnonblocking :: Connection -> IO Bool Source #
Returns the blocking status of the database connection.
setSingleRowMode :: Connection -> IO Bool Source #
Select single-row mode for the currently-executing query.
This function can only be called immediately after PQsendQuery or one of its sibling functions, before any other operation on the connection such as PQconsumeInput or PQgetResult. If called at the correct time, the function activates single-row mode for the current query and returns 1. Otherwise the mode stays unchanged and the function returns 0. In any case, the mode reverts to normal after completion of the current query.
data FlushStatus Source #
Constructors
| FlushOk | |
| FlushFailed | |
| FlushWriting | 
Instances
| Eq FlushStatus Source # | |
| Defined in Database.PostgreSQL.LibPQ | |
| Show FlushStatus Source # | |
| Defined in Database.PostgreSQL.LibPQ Methods showsPrec :: Int -> FlushStatus -> ShowS # show :: FlushStatus -> String # showList :: [FlushStatus] -> ShowS # | |
flush :: Connection -> IO FlushStatus Source #
Attempts to flush any queued output data to the server. Returns
 FlushOk if successful (or if the send queue is empty),
 FlushFailed if it failed for some reason, or FlushWriting if it
 was unable to send all the data in the send queue yet (this case
 can only occur if the connection is nonblocking).
Cancelling Queries in Progress
A client application can request cancellation of a command that is still being processed by the server, using the functions described in this section.
Contains the information needed to cancel a command issued through a particular database connection.
Instances
getCancel :: Connection -> IO (Maybe Cancel) Source #
Creates a data structure containing the information needed to cancel a command issued through a particular database connection.
getCancel creates a Cancel object given a Connection. It will
 return Nothing if the given conn is an invalid connection.
cancel :: Cancel -> IO (Either ByteString ()) Source #
Requests that the server abandon processing of the current command.
The return value is 'Right ()' if the cancel request was successfully dispatched and if not, 'Left B.ByteString' containing an error message explaining why not.
Successful dispatch is no guarantee that the request will have any effect, however. If the cancellation is effective, the current command will terminate early and return an error result. If the cancellation fails (say, because the server was already done processing the command), then there will be no visible result at all.
Asynchronous Notification
PostgreSQL offers asynchronous notification via the LISTEN and NOTIFY commands. A client session registers its interest in a particular notification channel with the LISTEN command (and can stop listening with the UNLISTEN command). All sessions listening on a particular channel will be notified asynchronously when a NOTIFY command with that channel name is executed by any session. A "payload" string can be passed to communicate additional data to the listeners.
libpq applications submit LISTEN, UNLISTEN, and NOTIFY commands as
 ordinary SQL commands. The arrival of NOTIFY messages can
 subsequently be detected by calling notifies.
Constructors
| Notify | |
| Fields 
 | |
Instances
| Show Notify Source # | |
| Storable Notify Source # | |
notifies :: Connection -> IO (Maybe Notify) Source #
Returns the next notification from a list of unhandled
 notification messages received from the server. It returns a
 Nothing if there are no pending notifications. Once a
 notification is returned from notifies, it is considered handled
 and will be removed from the list of notifications.
Control Functions
These functions control miscellaneous details of libpq's behavior.
clientEncoding :: Connection -> IO ByteString Source #
Returns the client encoding.
setClientEncoding :: Connection -> ByteString -> IO Bool Source #
Sets the client encoding.
Constructors
| ErrorsTerse | |
| ErrorsDefault | |
| ErrorsVerbose | 
Instances
| Enum Verbosity Source # | |
| Defined in Database.PostgreSQL.LibPQ Methods succ :: Verbosity -> Verbosity # pred :: Verbosity -> Verbosity # fromEnum :: Verbosity -> Int # enumFrom :: Verbosity -> [Verbosity] # enumFromThen :: Verbosity -> Verbosity -> [Verbosity] # enumFromTo :: Verbosity -> Verbosity -> [Verbosity] # enumFromThenTo :: Verbosity -> Verbosity -> Verbosity -> [Verbosity] # | |
| Eq Verbosity Source # | |
| Show Verbosity Source # | |
setErrorVerbosity :: Connection -> Verbosity -> IO Verbosity Source #
Determines the verbosity of messages returned by errorMessage
 and resultErrorMessage.
setErrorVerbosity sets the verbosity mode, returning the
 connection's previous setting. In ErrorsTerse mode, returned
 messages include severity, primary text, and position only; this
 will normally fit on a single line. The default mode produces
 messages that include the above plus any detail, hint, or context
 fields (these might span multiple lines). The ErrorsVerbose mode
 includes all available fields. Changing the verbosity does not
 affect the messages available from already-existing Result
 objects, only subsequently-created ones.
Nonfatal Error Reporting
disableNoticeReporting :: Connection -> IO () Source #
Upon connection initialization, any notices received from the server are
   normally written to the console.  Notices are akin to warnings, and
   are distinct from notifications.  This function suppresses notices.
   You may later call enableNoticeReporting after calling this function.
enableNoticeReporting :: Connection -> IO () Source #
Upon connection initialization, any notices received from the server are
   normally written to the console.  Notices are akin to warnings, and
   are distinct from notifications.  This function enables notices to be
   programmatically retreived using the getNotice function.   You may
   later call disableNoticeReporting after calling this function.
getNotice :: Connection -> IO (Maybe ByteString) Source #
This function retrieves any notices received from the backend.
    Because multiple notices can be received at a time,  you will
    typically want to call this function in a loop until you get
    back a Nothing.
Large Objects
LoFd is a Large Object (pseudo) File Descriptor. It is understood by libpq but not by operating system calls.
loCreat :: Connection -> IO (Maybe Oid) Source #
Creates a new large object, returns the Object ID of the newly created object.
loCreate :: Connection -> Oid -> IO (Maybe Oid) Source #
Creates a new large object with a particular Object ID.  Returns
 Nothing if the requested Object ID is already in use by some other
 large object or other failure.  If invalidOid is used as a parameter,
 then loCreate will assign an unused Oid.
loImport :: Connection -> FilePath -> IO (Maybe Oid) Source #
Imports an operating system file as a large object. Note that the file is read by the client interface library, not by the server; so it must exist in the client file system and be readable by the client application.
loImportWithOid :: Connection -> FilePath -> Oid -> IO (Maybe Oid) Source #
loExport :: Connection -> Oid -> FilePath -> IO (Maybe ()) Source #
Exports a large object into a operating system file.  Note that
 the file is written by the client interface library, not the server.
 Returns 'Just ()' on success,  Nothing on failure.
loOpen :: Connection -> Oid -> IOMode -> IO (Maybe LoFd) Source #
Opens an existing large object for reading or writing.  The Oid specifies
 the large object to open.  A large object cannot be opened before it is
 created.  A large object descriptor is returned for later use in loRead,
 loWrite, loSeek, loTell, and loClose.   The descriptor is only valid
 for the duration of the current transation.   On failure,  Nothing is
 returned.
The server currently does not distinguish between WriteMode and
 ReadWriteMode;  write-only modes are not enforced.  However there
 is a significant difference between ReadMode and the other modes:
 with ReadMode you cannot write on the descriptor,  and the data read
 from it will reflect the contents of the large object at the time of
 the transaction snapshot that was active when loOpen was executed,
 regardless of later writes by this or other transactions.   Reading from
 a descriptor opened in WriteMode, ReadWriteMode, or AppendMode
 returns data that reflects all writes of other committed transactions
 as well as the writes of the current transaction.   This is similar to
 the behavior of REPEATABLE READ versus READ COMMITTED transaction
 modes for ordinary SQL SELECT commands.
loWrite :: Connection -> LoFd -> ByteString -> IO (Maybe Int) Source #
loWrite conn fd buf writes the bytestring buf to the large object
 descriptor fd.  The number of bytes actually written is returned.
 In the event of an error, Nothing is returned.
loRead :: Connection -> LoFd -> Int -> IO (Maybe ByteString) Source #
loRead conn fd len reads up to len bytes from the large object
 descriptor fd.  In the event of an error,  Nothing is returned.
loSeek :: Connection -> LoFd -> SeekMode -> Int -> IO (Maybe Int) Source #
Changes the current read or write location associated with
 a large object descriptor.    The return value is the new location
 pointer,  or Nothing on error.
loTell :: Connection -> LoFd -> IO (Maybe Int) Source #
Obtains the current read or write location of a large object descriptor.
loTruncate :: Connection -> LoFd -> Int -> IO (Maybe ()) Source #
Truncates a large object to a given length. If the length is greater than the current large object, then the large object is extended with null bytes. ('x00')
The file offest is not changed.
loTruncate is new as of PostgreSQL 8.3; if this function is run against
 an older server version, it will fail and return Nothing