odpic-raw-0.3.0: Oracle Database Bindings

Copyright(c) Daniel YU
LicenseBSD3
Maintainerleptonyu@gmail.com
Stabilityexperimental
Portabilityportable
Safe HaskellNone
LanguageHaskell2010

Database.Dpi

Contents

Description

FFI raw bindings to ODPI-C

import Database.Dpi

conf :: OracleConfig
conf = defaultOracle "username" "password" "localhost:1521/dbname"


main :: IO ()
main = do
  withContext $ \cxt ->
    withPool cxt conf return $ \pool ->
      withPoolConnection pool $ \conn ->
        withStatement conn False "SELECT SYSDATE FROM DUAL" $ \st -> do
          r <- executeStatement st ModeExecDefault
          f <- fetch st
          mapM (getQueryValue st) [1..r] >>= print

Synopsis

Context Interface

Context handles are the top level handles created by the library and are used for all error handling as well as creating pools and standalone connections to the database. The first call to ODPI-C by any application must be createContext which will create the context as well as validate the version used by the application. Context handles are destroyed by using the function destroyContext.

createContext :: IO PtrContext Source #

Creates a new context for interaction with the library. This is the first function that must be called and it must have completed successfully before any other functions can be called, including in other threads.

destroyContext :: PtrContext -> IO Bool Source #

Destroys the context that was earlier created with the function createContext.

withContext :: (PtrContext -> IO a) -> IO a Source #

With Context, PtrContext will be destroyed after run

Information from Context

getClientVersion :: PtrContext -> IO Data_VersionInfo Source #

Return information about the version of the Oracle Client that is being used.

Connection Interface

Connection handles are used to represent connections to the database. These can be standalone connections created by calling the function createConnection. They can be closed by calling the function closeConnection or releasing the last reference to the connection by calling the function releaseConnection. Connection handles are used to create all handles other than session pools and context handles.

data OracleConfig Source #

Oracle Configuration

Constructors

OracleConfig 

Fields

type SQL = String Source #

SQL String

createConnection Source #

Arguments

:: PtrContext

Context

-> OracleConfig 
-> (Data_ConnCreateParams -> IO Data_ConnCreateParams)

custom Data_ConnCreateParams

-> IO PtrConn

a reference to the connection that is created. If a value is returned, a call to releaseConnection must be made in order to release the reference. This should be done after the error information has been retrieved.

Creates a standalone connection to a database or acquires a connection from a session pool and returns a reference to the connection.

closeConnection :: ConnCloseMode -> PtrConn -> IO Bool Source #

Closes the connection and makes it unusable for further activity. close connection, but not release resource, plese use releaseConnection to release and close connection

releaseConnection :: PtrConn -> IO Bool Source #

Releases a reference to the connection. A count of the references to the connection is maintained and when this count reaches zero, the memory associated with the connection is freed and the connection is closed or released back to the session pool if that has not already taken place using the function closeConnection.

commitConnection :: PtrConn -> IO Bool Source #

Commits the current active transaction.

rollbackConnection :: PtrConn -> IO Bool Source #

Rolls back the current active transaction.

pingConnection :: PtrConn -> IO Bool Source #

Pings the database to verify that the connection is still alive.

withConnection Source #

Arguments

:: PtrContext

Context

-> OracleConfig 
-> (Data_ConnCreateParams -> IO Data_ConnCreateParams)

custom Data_ConnCreateParams

-> (PtrConn -> IO a)

action use connection

-> IO a 

with connection

Transaction Interface

beginDistributedTransaction Source #

Arguments

:: PtrConn

Connection

-> Int64

the identifier of the format of the XID. A value of -1 indicates that the entire XID is null.

-> ByteString

the global transaction id of the XID as a byte string. The maximum length permitted is 64 bytes.

-> ByteString

the branch id of the XID as a byte string. The maximum length permitted is 64 bytes.

-> IO Bool 

Begins a distributed transaction using the specified transaction id (XID) made up of the formatId, transactionId and branchId.

prepareDistributedTransaction :: PtrConn -> IO Bool Source #

Prepares a distributed transaction for commit. This function should only be called after beginTransaction is called and before commitConnection is called.

Information from Connection

getCurrentSchema :: PtrConn -> IO ByteString Source #

Returns the current schema that is being used by the connection.

setCurrentSchema :: PtrConn -> ByteString -> IO Bool Source #

Sets the current schema to be used on the connection. This has the same effect as the SQL statement ALTER SESSION SET CURRENT_SCHEMA. The value be changed when the next call requiring a round trip to the server is performed. If the new schema name does not exist, the same error is returned as when the alter session statement is executed. The new schema name is placed before database objects in statement that you execute that do not already have a schema.

getEdition :: PtrConn -> IO ByteString Source #

Returns the edition that is being used by the connection.

getExternalName :: PtrConn -> IO ByteString Source #

Returns the external name that is being used by the connection. This value is used when logging distributed transactions.

setExternalName :: PtrConn -> ByteString -> IO Bool Source #

Sets the external name that is being used by the connection. This value is used when logging distributed transactions.

getInternalName :: PtrConn -> IO ByteString Source #

Returns the internal name that is being used by the connection. This value is used when logging distributed transactions.

setInternalName :: PtrConn -> ByteString -> IO Bool Source #

Sets the internal name that is being used by the connection. This value is used when logging distributed transactions.

getLTXID :: PtrConn -> IO ByteString Source #

Returns the logical transaction id for the connection. This value is used in Transaction Guard to determine if the last failed call was completed and if the transaction was committed using the procedure call dbms_app_cont.get_ltxid_outcome().

getServerVersion :: PtrConn -> IO (ByteString, Data_VersionInfo) Source #

Returns the version information of the Oracle Database to which the connection has been made.

getObjectType :: PtrConn -> ByteString -> IO PtrObjectType Source #

Looks up an object type by name in the database and returns a reference to it. The reference should be released as soon as it is no longer needed.

getEncodingInfo :: PtrConn -> IO Data_EncodingInfo Source #

Returns the encoding information used by the connection. This will be equivalent to the values passed when the standalone connection or session pool was created, or the values retrieved from the environment variables NLS_LANG and NLS_NCHAR.

getStmtCacheSize :: PtrConn -> IO Int Source #

Returns the size of the statement cache, in number of statements.

setStmtCacheSize :: PtrConn -> Int -> IO Bool Source #

Sets the size of the statement cache.

setClientInfo :: PtrConn -> ByteString -> IO Bool Source #

Sets the client info attribute on the connection. This is one of the end-to-end tracing attributes that can be tracked in database views, shown in audit trails and seen in tools such as Enterprise Manager.

setClientIdentifier :: PtrConn -> ByteString -> IO Bool Source #

Sets the client identifier attribute on the connection. This is one of the end-to-end tracing attributes that can be tracked in database views, shown in audit trails and seen in tools such as Enterprise Manager.

setAction :: PtrConn -> ByteString -> IO Bool Source #

Sets the action attribute on the connection. This is one of the end-to-end tracing attributes that can be tracked in database views, shown in audit trails and seen in tools such as Enterprise Manager.

setDbOp :: PtrConn -> ByteString -> IO Bool Source #

Sets the database operation attribute on the connection. This is one of the end-to-end tracing attributes that can be tracked in database views, shown in audit trails and seen in tools such as Enterprise Manager.

setModule :: PtrConn -> ByteString -> IO Bool Source #

Sets the module attribute on the connection. This is one of the end-to-end tracing attributes that can be tracked in database views, shown in audit trails and seen in tools such as Enterprise Manager.

getHandler :: PtrConn -> IO (Ptr ()) Source #

Returns the OCI service context handle in use by the connection.

Connection Management

connectionAddRef :: PtrConn -> IO Bool Source #

Adds a reference to the connection. This is intended for situations where a reference to the connection needs to be maintained independently of the reference returned when the connection was created.

breakException :: PtrConn -> IO Bool Source #

Performs an immediate (asynchronous) termination of any currently executing function on the server associated with the connection.

changePassword Source #

Arguments

:: PtrConn

Connection

-> ByteString

the name of the user whose password is to be changed

-> ByteString

the old password of the user whose password is to be changed

-> ByteString

the new password of the user whose password is to be changed

-> IO Bool 

Changes the password of the specified user.

shutdownDatabase Source #

Arguments

:: PtrConn

a reference to the connection to the database which is to be shut down. The connection needs to have been established at least with authorization mode set to ModeAuthSysdba or ModeAuthSysoper.

-> ShutdownMode 
-> IO Bool 

Shuts down the database. This function must be called twice for the database to be shut down successfully. After calling this function the first time, the SQL statements “alter database close normal” and “alter database dismount” must be executed. Once that is complete this function should be called again with the mode ModeShutdownFinal in order to complete the orderly shutdown of the database.

startupDatabase Source #

Arguments

:: PtrConn

a reference to the connection to the database which is to be started up. A connection like this can only be created with the authorization mode set to ModeAuthPrelim along with one of ModeAuthSysdba or ModeAuthSysoper.

-> StartupMode

one of the values from the enumeration StartupMode

-> IO Bool 

Starts up a database.

ConnectionPool Interace

Pool handles are used to represent session pools. They are created using the function createPool and can be closed by calling the function closePool or releasing the last reference to the pool by calling the function releasePool. Pools can be used to create connections by calling the function acquiredConnection.

acquiredConnection :: PtrPool -> IO PtrConn Source #

Acquires a connection from the pool and returns a reference to it. This reference should be released as soon as it is no longer needed.

poolAddRef :: PtrPool -> IO Bool Source #

Adds a reference to the pool. This is intended for situations where a reference to the pool needs to be maintained independently of the reference returned when the pool was created.

createPool Source #

Creates a session pool which creates and maintains a group of stateless sessions to the database. The main benefit of session pooling is performance since making a connection to the database is a time-consuming activity, especially when the database is remote.

closePool :: PtrPool -> PoolCloseMode -> IO Bool Source #

Closes the pool and makes it unusable for further activity.

releasePool :: PtrPool -> IO Bool Source #

Releases a reference to the pool. A count of the references to the pool is maintained and when this count reaches zero, the memory associated with the pool is freed and the session pool is closed if that has not already taken place using the function closePool.

withPool Source #

Arguments

:: PtrContext

Context

-> OracleConfig 
-> (Data_PoolCreateParams -> IO Data_PoolCreateParams) 
-> (PtrPool -> IO a)

action use connection

-> IO a 

with pool

withPoolConnection :: PtrPool -> (PtrConn -> IO a) -> IO a Source #

with pool provide a connection will released after action

getPoolBusyCount :: PtrPool -> IO Int Source #

Returns the number of sessions in the pool that are busy.

getPoolEncodingInfo :: PtrPool -> IO Data_EncodingInfo Source #

Returns the encoding information used by the pool. This will be equivalent to the values passed when the pool was created, or the values retrieved from the environment variables NLS_LANG and NLS_NCHAR.

getPoolMode :: PtrPool -> IO PoolGetMode Source #

Returns the mode used for acquiring or getting connections from the pool.

getPoolMaxLifetimeSession :: PtrPool -> IO Int Source #

Returns the maximum lifetime of all sessions in the pool, in seconds. Sessions in the pool are terminated when this value has been reached, but only when another session is released back to the pool.

getPoolOpenCount :: PtrPool -> IO Int Source #

Returns the number of sessions in the pool that are open.

getPoolStmtCacheSize :: PtrPool -> IO Int Source #

Returns the default size of the statement cache for sessions in the pool, in number of statements.

getPoolTimeout :: PtrPool -> IO Int Source #

Returns the amount of time, in seconds, after which idle sessions in the pool are terminated, but only when another session is released back to the pool.

getPoolWaitTimeout :: PtrPool -> IO Int Source #

Returns the amount of time (in milliseconds) that the caller will wait for a session to become available in the pool before returning an error.

@since ODPI-C 2.4.0

setPoolGetMode :: PtrPool -> PoolGetMode -> IO Bool Source #

Sets the mode used for acquiring or getting connections from the pool.

setPoolMaxLifetimeSession :: PtrPool -> Int -> IO Bool Source #

Sets the maximum lifetime of all sessions in the pool, in seconds. Sessions in the pool are terminated when this value has been reached, but only when another session is released back to the pool.

setPoolStmtCacheSize :: PtrPool -> Int -> IO Bool Source #

Sets the default size of the statement cache for sessions in the pool.

setPoolTimeout :: PtrPool -> Int -> IO Bool Source #

Sets the amount of time, in seconds, after which idle sessions in the pool are terminated, but only when another session is released back to the pool.

setPoolWaitTimeout :: PtrPool -> Int -> IO Bool Source #

Sets the amount of time (in milliseconds) that the caller should wait for a session to be available in the pool before returning with an error.

@since ODPI-C 2.4.0

Statement Interface

Statement handles are used to represent statements of all types (queries, DML, DDL and PL/SQL). They are created by calling the function prepareStatement. They are also created implicitly when a variable of type OracleTypeStmt is created. Statement handles can be closed by calling the function closeStatement or by releasing the last reference to the statement by calling the function releaseStatement.

prepareStatement Source #

Arguments

:: PtrConn

Connection

-> Bool

a boolean indicating if the statement is scrollable or not. If it is scrollable, scrollStatement can be used to reposition the cursor; otherwise, rows are retrieved in order from the statement until the rows are exhausted. This value is ignored for statements that do not refer to a query.

-> SQL

SQL String, not allow to use multi lines or semicolon as end of sql. use normalize use normalize sql ByteString.

-> IO PtrStmt 

Returns a reference to a statement prepared for execution. The reference should be released as soon as it is no longer needed.

closeStatement :: PtrStmt -> IO Bool Source #

Closes the statement and makes it unusable for further work immediately, rather than when the reference count reaches zero.

releaseStatement :: PtrStmt -> IO Bool Source #

Releases a reference to the statement. A count of the references to the statement is maintained and when this count reaches zero, the memory associated with the statement is freed and the statement is closed if that has not already taken place using the function closeStatement.

withStatement Source #

Arguments

:: PtrConn

Connection

-> Bool

a boolean indicating if the statement is scrollable or not. If it is scrollable, scrollStatement can be used to reposition the cursor; otherwise, rows are retrieved in order from the statement until the rows are exhausted. This value is ignored for statements that do not refer to a query.

-> SQL

SQL String, not allow to use multi lines or semicolon as end of sql. use normalize use normalize sql ByteString.

-> (PtrStmt -> IO a) 
-> IO a 

with statement provide a prepared statement will released after action

scrollStatement :: PtrStmt -> FetchMode -> Int -> Int -> IO Bool Source #

Scrolls the statement to the position in the cursor specified by the mode and offset.

statementAddRef :: PtrStmt -> IO Bool Source #

Adds a reference to the statement. This is intended for situations where a reference to the statement needs to be maintained independently of the reference returned when the statement was created.

Statement Bind Vars

bindByName Source #

Arguments

:: PtrStmt

Statement

-> ByteString

a byte string in the encoding used for CHAR data giving the name of the placeholder which is to be bound.

-> PtrVar

a reference to the variable which is to be bound.

-> IO Bool 

Binds a variable to a named placeholder in the statement. A reference to the variable is retained by the library and is released when the statement itself is released or a new variable is bound to the same name.

bindByPosition Source #

Arguments

:: PtrStmt

Statement

-> Int

the position which is to be bound. The position of a placeholder is determined by its location in the statement. Placeholders are numbered from left to right, starting from 1, and duplicate names do not count as additional placeholders.

-> PtrVar

a reference to the variable which is to be bound.

-> IO Bool 

Binds a variable to a placeholder in the statement by position. A reference to the variable is retained by the library and is released when the statement itself is released or a new variable is bound to the same position.

bindValueByName Source #

Arguments

:: PtrStmt

Statement

-> ByteString

a byte string in the encoding used for CHAR data giving the name of the placeholder which is to be bound.

-> DataValue

Value Once the statement has been executed, this new variable will be released.

-> IO Bool 

Binds a value to a named placeholder in the statement without the need to create a variable directly. One is created implicitly and released when the statement is released or a new value is bound to the same name.

bindValueByPosition Source #

Arguments

:: PtrStmt

Statement

-> Int

the position which is to be bound. The position of a placeholder is determined by its location in the statement. Placeholders are numbered from left to right, starting from 1, and duplicate names do not count as additional placeholders.

-> DataValue

Value Once the statement has been executed, this new variable will be released.

-> IO Bool 

Binds a value to a placeholder in the statement without the need to create a variable directly. One is created implicitly and released when the statement is released or a new value is bound to the same position.

define Source #

Arguments

:: PtrStmt

Statement

-> Int

the position which is to be defined. The first position is 1.

-> PtrVar

a reference to the variable which is to be used for fetching rows from the statement at the given position.

-> IO Bool 

Defines the variable that will be used to fetch rows from the statement. A reference to the variable will be retained until the next define is performed on the same position or the statement is closed.

defineValue Source #

Arguments

:: PtrStmt

Statement

-> Int

the position which is to be defined. The first position is 1.

-> OracleTypeNum

the type of Oracle data that is to be used.

-> NativeTypeNum

the type of native C data that is to be used.

-> Int

the maximum size of the buffer used for transferring data to/from Oracle. This value is only used for variables transferred as byte strings. Size is either in characters or bytes depending on the value of the sizeIsBytes parameter. If the value is in characters, internally the value will be multipled by the maximum number of bytes for each character and that value used instead when determining the necessary buffer size.

-> Bool

boolean value indicating if the size parameter refers to characters or bytes. This flag is only used if the variable refers to character data.

-> PtrObjectType

a reference to the object type of the object that is being bound or fetched. This value is only used if the Oracle type is OracleTypeObject.

-> IO Bool 

Defines the type of data that will be used to fetch rows from the statement. This is intended for use with the function getQueryValue, when the default data type derived from the column metadata needs to be overridden by the application. Internally, a variable is created with the specified data type and size.

getBindCount :: PtrStmt -> IO Int Source #

Returns the number of bind variables in the prepared statement. In SQL statements this is the total number of bind variables whereas in PL/SQL statements this is the count of the unique bind variables.

getBindNames :: PtrStmt -> IO [ByteString] Source #

Returns the names of the unique bind variables in the prepared statement.

getStatementInfo :: PtrStmt -> IO Data_StmtInfo Source #

Returns information about the statement.

getFetchArraySize :: PtrStmt -> IO Int Source #

Gets the array size used for performing fetches.

setFetchArraySize :: PtrStmt -> Int -> IO Bool Source #

Sets the array size used for performing fetches. All variables defined for fetching must have this many (or more) elements allocated for them. The higher this value is the less network round trips are required to fetch rows from the database but more memory is also required. A value of zero will reset the array size to the default value of DPI_DEFAULT_FETCH_ARRAY_SIZE.

getImplicitResult :: PtrStmt -> IO (Maybe PtrStmt) Source #

Returns the next implicit result available from the last execution of the statement. Implicit results are only available when both the client and server are 12.1 or higher.

getNumberQueryColumns :: PtrStmt -> IO Int Source #

Returns the number of columns that are being queried.

getQueryInfo Source #

Arguments

:: PtrStmt

Statement

-> Int

the position of the column whose metadata is to be retrieved. The first position is 1.

-> IO Data_QueryInfo 

Returns information about the column that is being queried.

getQueryValue Source #

Arguments

:: PtrStmt

Statement

-> Int

the position of the column whose metadata is to be retrieved. The first position is 1.

-> IO DataValue 

Returns the value of the column at the given position for the currently fetched row, without needing to provide a variable. If the data type of the column needs to be overridden, the function defineValue can be called to specify a different type after executing the statement but before fetching any data.

Execute Statement

executeStatement :: PtrStmt -> ExecMode -> IO Int Source #

Executes the statement using the bound values. For queries this makes available metadata which can be acquired using the function getQueryInfo. For non-queries, out and in-out variables are populated with their values.

fetch :: PtrStmt -> IO (Maybe PageOffset) Source #

Fetches a single row from the statement. If the statement does not refer to a query an error is returned. All columns that have not been defined prior to this call are implicitly defined using the metadata made available when the statement was executed.

type FetchRows a = PtrStmt -> Page -> IO a Source #

fetchRows Source #

Arguments

:: PtrStmt

Statement

-> Int

the maximum number of rows to fetch. If the number of rows available exceeds this value only this number will be fetched.

-> IO (Bool, [DataValue]) 

Returns the number of rows that are available in the buffers defined for the query. If no rows are currently available in the buffers, an internal fetch takes place in order to populate them, if rows are available. If the statement does not refer to a query an error is returned. All columns that have not been defined prior to this call are implicitly defined using the metadata made available when the statement was executed.

getRowCount :: PtrStmt -> IO Int Source #

Returns the number of rows affected by the last DML statement that was executed or the number of rows currently fetched from a query. In all other cases 0 is returned.

getRowCounts :: PtrStmt -> IO [Int] Source #

Returns an array of row counts affected by the last invocation of executeMany with the array DML rowcounts mode enabled. This feature is only available if both client and server are at 12.1.

getSubscrQueryId :: PtrStmt -> IO Word64 Source #

Returns the id of the query that was just registered on the subscription by calling executeStatement on a statement prepared by calling prepareStatement.

Lob Interface

LOB handles are used to represent large objects (CLOB, BLOB, NCLOB, BFILE). Both persistent and temporary large objects can be represented. LOB handles can be created by calling the function newTempLob or are created implicitly when a variable of type OracleTypeClob, OracleTypeNclob, OracleTypeBlob or OracleTypeBfile is created and are destroyed when the last reference is released by calling the function releaseLob. They are used for reading and writing data to the database in smaller pieces than is contained in the large object.

lobAddRef :: PtrLob -> IO Bool Source #

Adds a reference to the LOB. This is intended for situations where a reference to the LOB needs to be maintained independently of the reference returned when the LOB was created.

newTempLob :: PtrConn -> OracleTypeNum -> IO PtrLob Source #

Returns a reference to a new temporary LOB which may subsequently be written and bound to a statement. The reference should be released as soon as it is no longer needed.

closeLob :: PtrLob -> IO Bool Source #

close lob

releaseLob :: PtrLob -> IO Bool Source #

Releases a reference to the LOB. A count of the references to the LOB is maintained and when this count reaches zero, the memory associated with the LOB is freed. The LOB is also closed unless that has already taken place using the function closeLob.

trimLob :: PtrLob -> Int64 -> IO Bool Source #

Trims the data in the LOB so that it only contains the specified amount of data.

closeLobResource :: PtrLob -> IO Bool Source #

Closes the LOB resource. This should be done when a batch of writes has been completed so that the indexes associated with the LOB can be updated. It should only be performed if a call to function openLobResource has been performed.

openLobResource :: PtrLob -> IO Bool Source #

Opens the LOB resource for writing. This will improve performance when writing to the LOB in chunks and there are functional or extensible indexes associated with the LOB. If this function is not called, the LOB resource will be opened and closed for each write that is performed. A call to the function closeLobResource should be done before performing a call to the function commitConnection.

isLobResourceOpen :: PtrLob -> IO Bool Source #

Returns a boolean value indicating if the LOB resource has been opened by making a call to the function openLobResource (1) or not (0).

copyLob :: PtrLob -> IO PtrLob Source #

Creates an independent copy of a LOB and returns a reference to the newly created LOB. This reference should be released as soon as it is no longer needed.

flushLob :: PtrLob -> IO Bool Source #

Flush or write all buffers for this LOB to the server.

getLobBufferSize :: PtrLob -> Word64 -> IO Word64 Source #

Returns the size of the buffer needed to hold the number of characters specified for a buffer of the type associated with the LOB. If the LOB does not refer to a character LOB the value is returned unchanged.

getLobChunkSize :: PtrLob -> IO Int64 Source #

Returns the chunk size of the internal LOB. Reading and writing to the LOB in multiples of this size will improve performance.

getLobDirectoryAndFileName :: PtrLob -> IO (FilePath, String) Source #

Returns the directory alias name and file name for a BFILE type LOB.

setLobDirectoryAndFileName :: PtrLob -> (FilePath, String) -> IO Bool Source #

Sets the directory alias name and file name for a BFILE type LOB.

lobFileExists :: PtrLob -> IO Bool Source #

Returns a boolean value indicating if the file referenced by the BFILE type LOB exists (1) or not (0).

getLobSize :: PtrLob -> IO Int64 Source #

Returns the size of the data stored in the LOB. For character LOBs the size is in characters; for binary LOBs the size is in bytes.

setLobFromBytes :: PtrLob -> ByteString -> IO Bool Source #

Replaces all of the data in the LOB with the contents of the provided buffer. The LOB will first be cleared and then the provided data will be written.

readLobBytes :: PtrLob -> Page -> BufferSize -> IO ByteString Source #

Reads data from the LOB at the specified offset into the provided buffer.

writeLobBytes :: PtrLob -> PageOffset -> ByteString -> IO Bool Source #

Write data to the LOB at the specified offset using the provided buffer as the source. If multiple calls to this function are planned, the LOB should first be opened using the function openLob.

Object Interface

Object handles are used to represent instances of the types created by the SQL command CREATE OR REPLACE TYPE. They are created by calling the function createObject or calling the function copyObject or implicitly by creating a variable of the type OracleTypeObject. The are destroyed when the last reference is released by calling the function releaseObject.

createObject :: PtrObjectType -> IO PtrObject Source #

Creates an object of the specified type and returns a reference to it. This reference should be released as soon as it is no longer needed.

releaseObject :: PtrObject -> IO Bool Source #

Releases a reference to the object. A count of the references to the object is maintained and when this count reaches zero, the memory associated with the object is freed.

objectAddRef :: PtrObject -> IO Bool Source #

Adds a reference to the object. This is intended for situations where a reference to the object needs to be maintained independently of the reference returned when the object was created.

objectAppendElement :: PtrObject -> NativeTypeNum -> PtrData -> IO Bool Source #

Sets the value of the element found at the specified index.

copyObject :: PtrObject -> IO PtrObject Source #

Creates an independent copy of an object and returns a reference to the newly created object. This reference should be released as soon as it is no longer needed.

trimObject :: PtrObject -> Int -> IO Bool Source #

Trims a number of elements from the end of a collection.

objectDeleteElementByIndex :: PtrObject -> Int -> IO Bool Source #

Deletes an element from the collection. Note that the position ordinals of the remaining elements are not changed. The delete operation creates holes in the collection.

setObjectAttributeValue :: PtrObject -> PtrObjectAttr -> DataValue -> IO Bool Source #

Sets the value of one of the object’s attributes.

getObjectAttributeValue :: PtrObject -> PtrObjectAttr -> NativeTypeNum -> OracleTypeNum -> IO DataValue Source #

Returns the value of one of the object’s attributes.

setObjectElementValueByIndex :: PtrObject -> Int -> DataValue -> IO Bool Source #

Sets the value of the element found at the specified index.

getObjectElementValueByIndex :: PtrObject -> Int -> NativeTypeNum -> OracleTypeNum -> IO DataValue Source #

Returns the value of the element found at the specified index.

getObjectFirstIndex :: PtrObject -> IO (Maybe Int) Source #

Returns the first index used in a collection.

getObjectLastIndex :: PtrObject -> IO (Maybe Int) Source #

Returns the last index used in a collection.

getObjectNextIndex :: PtrObject -> Int -> IO (Maybe Int) Source #

Returns the next index used in a collection following the specified index.

getObjectPrevIndex :: PtrObject -> Int -> IO (Maybe Int) Source #

Returns the previous index used in a collection preceding the specified index.

getObjectSize :: PtrObject -> IO Int Source #

Returns the number of elements in a collection.

ObjectAttr

Object attribute handles are used to represent the attributes of types such as those created by the SQL command CREATE OR REPLACE TYPE. They are created by calling the function getObjectTypeAttributes and are destroyed when the last reference is released by calling the function releaseObjectAttr.

getObjectAttrInfo :: PtrObjectAttr -> IO Data_ObjectAttrInfo Source #

Returns information about the attribute.

objectAttrAddRef :: PtrObjectAttr -> IO Bool Source #

Adds a reference to the attribute. This is intended for situations where a reference to the attribute needs to be maintained independently of the reference returned when the attribute was created.

releaseObjectAttr :: PtrObjectAttr -> IO Bool Source #

Releases a reference to the attribute. A count of the references to the attribute is maintained and when this count reaches zero, the memory associated with the attribute is freed.

ObjectType

Object type handles are used to represent types such as those created by the SQL command CREATE OR REPLACE TYPE. They are created using the function getObjectType or implicitly when fetching from a column containing objects by calling the function getQueryInfo. Object types are also retrieved when used as attributes in another object by calling the function getObjectAttrInfo or as the element type of a collection by calling the function getObjectTypeInfo. They are destroyed when the last reference is released by calling the function releaseObjectType.

objectTypeAddRef :: PtrObjectType -> IO Bool Source #

Adds a reference to the object type. This is intended for situations where a reference to the object type needs to be maintained independently of the reference returned when the object type was created.

releaseObjectType :: PtrObjectType -> IO Bool Source #

Releases a reference to the object type. A count of the references to the object type is maintained and when this count reaches zero, the memory associated with the object type is freed.

getObjectTypeAttributes :: PtrObjectType -> Int -> IO PtrObjectAttr Source #

Returns the list of attributes that belong to the object type.

getObjectTypeInfo :: PtrObjectType -> IO Data_ObjectTypeInfo Source #

Returns information about the object type.

Rowid Interface

Rowid handles are used to represent the unique identifier of a row in the database. They cannot be created or set directly but are created implicitly when a variable of type OracleTypeRowid is created. They are destroyed when the last reference is released by a call to the function releaseRowid.

rowidAddRef :: PtrRowid -> IO Bool Source #

Adds a reference to the rowid. This is intended for situations where a reference to the rowid needs to be maintained independently of the reference returned when the rowid was created.

releaseRowid :: PtrRowid -> IO Bool Source #

Releases a reference to the rowid. A count of the references to the rowid is maintained and when this count reaches zero, the memory associated with the rowid is freed.

rowidGetStringValue :: PtrRowid -> IO ByteString Source #

Returns the sting (base64) representation of the rowid.

Data Interface

All of these functions are used for getting and setting the various members of the dpiData structure. The members of the structure can be manipulated directly but some languages (such as Go) do not have the ability to manipulate structures containing unions or the ability to process macros. For this reason, none of these functions perform any error checking. They are assumed to be replacements for direct manipulation of the various members of the structure.

getBool :: PtrData -> IO Bool Source #

Returns the value of the data when the native type is NativeTypeBoolean.

setBool :: PtrData -> Bool -> IO () Source #

Sets the value of the data when the native type is NativeTypeBoolean.

getBytes :: PtrData -> IO ByteString Source #

Returns a pointer to the value of the data when the native type is NativeTypeBytes.

setBytes :: PtrData -> ByteString -> IO () Source #

Sets the value of the data when the native type is NativeTypeBytes. Do not use this function when setting data for variables. Instead, use the function setVarFromBytes.

getDouble :: PtrData -> IO Double Source #

Returns the value of the data when the native type is NativeTypeDouble.

setDouble :: PtrData -> Double -> IO () Source #

Sets the value of the data when the native type is NativeTypeDouble.

getFloat :: PtrData -> IO Float Source #

Returns the value of the data when the native type is NativeTypeFloat.

setFloat :: PtrData -> Float -> IO () Source #

Sets the value of the data when the native type is NativeTypeFloat.

getInt64 :: PtrData -> IO Int64 Source #

Returns the value of the data when the native type is NativeTypeInt64.

setInt64 :: PtrData -> Int64 -> IO () Source #

Sets the value of the data when the native type is NativeTypeInt64.

getUint64 :: PtrData -> IO Word64 Source #

Returns the value of the data when the native type is NativeTypeUint64.

setUint64 :: PtrData -> Word64 -> IO () Source #

Sets the value of the data when the native type is NativeTypeUint64.

getIntervalDs :: PtrData -> IO Data_IntervalDS Source #

Returns the value of the data when the native type is NativeTypeIntervalDs.

setIntervalDs :: PtrData -> Data_IntervalDS -> IO () Source #

Sets the value of the data when the native type is NativeTypeIntervalDs.

getIntervalYm :: PtrData -> IO Data_IntervalYM Source #

Returns the value of the data when the native type is NativeTypeIntervalYm.

setIntervalYm :: PtrData -> Data_IntervalYM -> IO () Source #

Sets the value of the data when the native type is NativeTypeIntervalYm.

getLob :: PtrData -> IO (Ptr DPI_Lob) Source #

Returns the value of the data when the native type is NativeTypeLob.

setLob :: PtrData -> Ptr DPI_Lob -> IO () Source #

Sets the value of the data when the native type is NativeTypeLob.

getObject :: PtrData -> IO (Ptr DPI_Object) Source #

Returns the value of the data when the native type is NativeTypeObject.

setObject :: PtrData -> Ptr DPI_Object -> IO () Source #

Sets the value of the data when the native type is NativeTypeObject.

getStmt :: PtrData -> IO (Ptr DPI_Stmt) Source #

Returns the value of the data when the native type is NativeTypeStmt.

setStmt :: PtrData -> Ptr DPI_Stmt -> IO () Source #

Sets the value of the data when the native type is NativeTypeStmt.

getTimestamp :: PtrData -> IO Data_Timestamp Source #

Returns the value of the data when the native type is NativeTypeTimestamp.

setTimestamp :: PtrData -> Data_Timestamp -> IO () Source #

Sets the value of the data when the native type is NativeTypeTimestamp.

Var Interface

Variable handles are used to represent memory areas used for transferring data to and from the database. They are created by calling the function newVar. They are destroyed when the last reference to the variable is released by calling the function releaseVar. They are bound to statements by calling the function bindByName or the function bindByPosition. They can also be used for fetching data from the database by calling the function define.

newVar Source #

Arguments

:: PtrConn

Connection

-> OracleTypeNum

the type of Oracle data that is to be used.

-> NativeTypeNum

the type of native C data that is to be used.

-> Int

the maximum number of rows that can be fetched or bound at one time from the database, or the maximum number of elements that can be stored in a PL/SQL array.

-> Int

the maximum size of the buffer used for transferring data to/from Oracle. This value is only used for variables transferred as byte strings. Size is either in characters or bytes depending on the value of the sizeIsBytes parameter. If the value is in characters, internally the value will be multipled by the maximum number of bytes for each character and that value used instead when determining the necessary buffer size.

-> Bool

boolean value indicating if the size parameter refers to characters or bytes. This flag is only used if the variable refers to character data.

-> Bool

boolean value indicating if the variable refers to a PL/SQL array or simply to buffers used for binding or fetching data.

-> PtrObjectType

a reference to the object type of the object that is being bound or fetched. This value is only used if the Oracle type is OracleTypeObject.

-> IO (PtrVar, [PtrData]) 

Returns a reference to a new variable which can be used for binding data to a statement or providing a buffer for querying data from the database. The reference should be released as soon as it is no longer needed.

varAddRef :: PtrVar -> IO Bool Source #

Adds a reference to the variable. This is intended for situations where a reference to the variable needs to be maintained independently of the reference returned when the variable was created.

releaseVar :: PtrVar -> IO Bool Source #

Releases a reference to the variable. A count of the references to the variable is maintained and when this count reaches zero, the memory associated with the variable is freed.

copyVar :: PtrVar -> Int -> PtrVar -> Int -> IO Bool Source #

Copies the data from one variable to another variable.

getVarData :: PtrVar -> IO [Data] Source #

Returns a pointer to an array of dpiData structures used for transferring data to and from the database. These structures are allocated by the variable itself and are made available when the variable is first created using the function newVar. If a DML returning statement is executed, however, the number of allocated elements can change in addition to the memory location.

getVarReturnedData :: PtrVar -> Int -> IO [Data] Source #

Returns a pointer to an array of dpiData structures used for transferring data to and from the database. These structures are allocated by the variable itself when a DML returning statement is executed and the variable is bound.

@since ODPI-C 2.4.0

getVarElementsSize :: PtrVar -> IO Int Source #

Returns the number of elements in a PL/SQL index-by table if the variable was created as an array by the function newVar. If the variable is one of the output bind variables of a DML returning statement, however, the value returned will correspond to the number of rows returned by the DML returning statement. In all other cases, the value returned will be the number of elements the variable was created with.

getVarSizeInBytes :: PtrVar -> IO Int Source #

Returns the size of the buffer used for one element of the array used for fetching/binding Oracle data

setVarFromBytes :: PtrVar -> Int -> ByteString -> IO Bool Source #

Sets the variable value to the specified byte string. In the case of the variable’s Oracle type being OracleTypeNumber, the byte string is converted to an Oracle number during the call to this function.

setVarFromLob :: PtrVar -> Int -> PtrLob -> IO Bool Source #

Sets the variable value to the specified LOB.

setVarFromObject :: PtrVar -> Int -> PtrObject -> IO Bool Source #

Sets the variable value to the specified object.

setVarFromRowid :: PtrVar -> Int -> PtrRowid -> IO Bool Source #

Sets the variable value to the specified rowid.

setVarFromStatement :: PtrVar -> Int -> PtrStmt -> IO Bool Source #

Sets the variable value to the specified statement.

setVarNumberOfElements :: PtrVar -> Int -> IO Bool Source #

Sets the number of elements in a PL/SQL index-by table.

DeqOptions Interface

deqOptions Dequeue option handles are used to represent the options specified when dequeuing messages using advanced queueing. They are created by calling the function newDeqOptions and are destroyed by releasing the last reference by calling the function releaseDeqOptions.

newDeqOptions :: PtrConn -> IO PtrDeqOptions Source #

Returns a reference to a new set of dequeue options, used in dequeuing objects from a queue. The reference should be released as soon as it is no longer needed.

deqObject Source #

Arguments

:: PtrConn

a reference to the connection from which the message is to be dequeued

-> ByteString

the name of the queue from which the message is to be dequeued

-> PtrDeqOptions

a reference to the dequeue options that should be used when dequeuing the message from the queue.

-> PtrMsgProps

a reference to the message properties that will be populated with information from the message that is dequeued.

-> PtrObject

a reference to the object which will be populated with the message that is dequeued.

-> IO (Maybe ByteString)

a pointer to a byte string which will be populated with the id of the message that is dequeued

Dequeues a message from a queue.

releaseDeqOptions :: PtrDeqOptions -> IO Bool Source #

Releases a reference to the dequeue options. A count of the references to the dequeue options is maintained and when this count reaches zero, the memory associated with the options is freed.

deqOptionsAddRef :: PtrDeqOptions -> IO Bool Source #

Adds a reference to the dequeue options. This is intended for situations where a reference to the dequeue options needs to be maintained independently of the reference returned when the handle was created.

getDeqOptionsCondition :: PtrDeqOptions -> IO ByteString Source #

Returns the condition that must be satisfied in order for a message to be dequeued. See function setDeqOptionsCondition for more information.

setDeqOptionsCondition :: PtrDeqOptions -> ByteString -> IO Bool Source #

Sets the condition which must be true for messages to be dequeued. The condition must be a valid boolean expression similar to the where clause of a SQL query. The expression can include conditions on message properties, user data properties and PL/SQL or SQL functions. User data properties must be prefixed with tab.user_data as a qualifier to indicate the specific column of the queue table that stores the message payload.

getDeqOptionsConsumerName :: PtrDeqOptions -> IO ByteString Source #

Returns the name of the consumer that is dequeuing messages. See function setDeqOptionsConsumerName for more information.

setDeqOptionsConsumerName :: PtrDeqOptions -> ByteString -> IO Bool Source #

Sets the name of the consumer which will be dequeuing messages. This value should only be set if the queue is set up for multiple consumers.

getDeqOptionsCorrelation :: PtrDeqOptions -> IO ByteString Source #

Returns the correlation of the message to be dequeued. See function setDeqOptionsCorrelation for more information.

setDeqOptionsCorrelation :: PtrDeqOptions -> ByteString -> IO Bool Source #

Sets the correlation of the message to be dequeued. Special pattern matching characters such as the percent sign (%) and the underscore (_) can be used. If multiple messages satisfy the pattern, the order of dequeuing is undetermined.

getDeqOptionsMode :: PtrDeqOptions -> IO DeqMode Source #

Returns the mode that is to be used when dequeuing messages.

setDeqOptionsMode :: PtrDeqOptions -> DeqMode -> IO Bool Source #

Sets the mode that is to be used when dequeuing messages.

getDeqOptionsMsgId :: PtrDeqOptions -> IO ByteString Source #

Returns the identifier of the specific message that is to be dequeued.

setDeqOptionsMsgId :: PtrDeqOptions -> ByteString -> IO Bool Source #

Sets the identifier of the specific message to be dequeued.

getDeqOptionsNavigation :: PtrDeqOptions -> IO DeqNavigation Source #

Returns the position of the message that is to be dequeued.

setDeqOptionsNavigation :: PtrDeqOptions -> DeqNavigation -> IO Bool Source #

Sets the position in the queue of the message that is to be dequeued.

getDeqOptionsTransformation :: PtrDeqOptions -> IO ByteString Source #

Returns the transformation of the message to be dequeued. See function setDeqOptionsTransformation for more information.

setDeqOptionsTransformation :: PtrDeqOptions -> ByteString -> IO Bool Source #

Sets the transformation of the message to be dequeued. The transformation is applied after the message is dequeued but before it is returned to the application. It must be created using DBMS_TRANSFORM.

getDeqOptionsVisibility :: PtrDeqOptions -> IO Visibility Source #

Returns whether the message being dequeued is part of the current transaction or constitutes a transaction on its own.

setDeqOptionsVisibility :: PtrDeqOptions -> Visibility -> IO Bool Source #

Sets whether the message being dequeued is part of the current transaction or constitutes a transaction on its own.

getDeqOptionsWait :: PtrDeqOptions -> IO Int Source #

Returns the time to wait, in seconds, for a message matching the search criteria. See function setDeqOptionsWait for more information.

setDeqOptionsWait :: PtrDeqOptions -> Int -> IO Bool Source #

Set the time to wait, in seconds, for a message matching the search criteria.

setDeqOptionsDeliveryMode :: PtrDeqOptions -> MessageDeliveryMode -> IO Bool Source #

Sets the message delivery mode that is to be used when dequeuing messages.

EnqOptions Interface

Enqueue option handles are used to represent the options specified when enqueuing messages using advanced queueing. They are created by calling the function newEnqOptions and are destroyed by releasing the last reference by calling the function releaseEnqOptions.

newEnqOptions :: PtrConn -> IO PtrEnqOptions Source #

Returns a reference to a new set of enqueue options, used in enqueuing objects into a queue. The reference should be released as soon as it is no longer needed.

enqObject Source #

Arguments

:: PtrConn

a reference to the connection from which the message is to be enqueued

-> ByteString

the name of the queue from which the message is to be enqueued

-> PtrEnqOptions

a reference to the enqueue options that should be used when enqueued the message from the queue.

-> PtrMsgProps

a reference to the message properties that will be populated with information from the message that is enqueued.

-> PtrObject

a reference to the object which will be populated with the message that is enqueued.

-> IO (Maybe ByteString)

a pointer to a byte string which will be populated with the id of the message that is enqueued

Enqueues a message to a queue.

enqOptionsAddRef :: PtrEnqOptions -> IO Bool Source #

Adds a reference to the enqueue options. This is intended for situations where a reference to the enqueue options needs to be maintained independently of the reference returned when the handle was created.

releaseEnqOptions :: PtrEnqOptions -> IO Bool Source #

Releases a reference to the enqueue options. A count of the references to the enqueue options is maintained and when this count reaches zero, the memory associated with the options is freed.

getEnqOptionsTransformation :: PtrEnqOptions -> IO ByteString Source #

Returns the transformation of the message to be enqueued. See function setEnqOptionsTransformation for more information.

setEnqOptionsTransformation :: PtrEnqOptions -> ByteString -> IO Bool Source #

Sets the transformation of the message to be enqueued. The transformation is applied after the message is enqueued but before it is returned to the application. It must be created using DBMS_TRANSFORM.

getEnqOptionsVisibility :: PtrEnqOptions -> IO Visibility Source #

Returns whether the message being enqueued is part of the current transaction or constitutes a transaction on its own.

setEnqOptionsVisibility :: PtrEnqOptions -> Visibility -> IO Bool Source #

Sets whether the message being enqueued is part of the current transaction or constitutes a transaction on its own.

setEnqOptionsDeliveryMode :: PtrEnqOptions -> MessageDeliveryMode -> IO Bool Source #

Sets the message delivery mode that is to be used when enqueuing messages.

MsgProps Interface

msg Message properties handles are used to represent the properties of messages that are enqueued and dequeued using advanced queuing. They are created by calling the function newMsgProps and are destroyed by releasing the last reference by calling the function releaseMsgProps.

newMsgProps :: PtrConn -> IO PtrMsgProps Source #

Returns a reference to a new set of message properties, used in enqueuing and dequeuing objects in a queue. The reference should be released as soon as it is no longer needed.

msgPropsAddRef :: PtrMsgProps -> IO Bool Source #

Adds a reference to the message properties. This is intended for situations where a reference to the message properties needs to be maintained independently of the reference returned when the handle was created.

releaseMsgProps :: PtrMsgProps -> IO Bool Source #

Releases a reference to the message properties. A count of the references to the message properties is maintained and when this count reaches zero, the memory associated with the properties is freed.

getMsgPropsCorrelation :: PtrMsgProps -> IO ByteString Source #

Returns the correlation supplied by the producer when the message was enqueued.

setMsgPropsCorrelation :: PtrMsgProps -> ByteString -> IO Bool Source #

Sets the correlation of the message to be dequeued. Special pattern matching characters such as the percent sign (%) and the underscore (_) can be used. If multiple messages satisfy the pattern, the order of dequeuing is undetermined.

getMsgPropsNumAttempts :: PtrMsgProps -> IO Int Source #

Returns the number of attempts that have been made to dequeue a message.

getMsgPropsDelay :: PtrMsgProps -> IO Int Source #

Returns the number of seconds the enqueued message will be delayed.

setMsgPropsDelay :: PtrMsgProps -> Int -> IO Bool Source #

Sets the number of seconds to delay the message before it can be dequeued. Messages enqueued with a delay are put into the MsgStateWaiting state. When the delay expires the message is put into the MsgStateReady state. Dequeuing directly by message id overrides this delay specification. Note that delay processing requires the queue monitor to be started.

getMsgPropsDeliveryMode :: PtrMsgProps -> IO MessageDeliveryMode Source #

Returns the mode that was used to deliver the message.

getMsgPropsEnqTime :: PtrMsgProps -> IO Data_Timestamp Source #

Returns the time that the message was enqueued.

getMsgPropsExceptionQ :: PtrMsgProps -> IO ByteString Source #

Returns the name of the queue to which the message is moved if it cannot be processed successfully. See function setMsgPropsExceptionQ for more information.

setMsgPropsExceptionQ :: PtrMsgProps -> ByteString -> IO Bool Source #

Sets the name of the queue to which the message is moved if it cannot be processed successfully. Messages are moved if the number of unsuccessful dequeue attempts has reached the maximum allowed number or if the message has expired. All messages in the exception queue are in the MsgStateExpired state.

getMsgPropsExpiration :: PtrMsgProps -> IO Int Source #

Returns the number of seconds the message is available to be dequeued. See function setMsgPropsExpiration for more information.

setMsgPropsExpiration :: PtrMsgProps -> Int -> IO Bool Source #

Sets the number of seconds the message is available to be dequeued. This value is an offset from the delay. Expiration processing requires the queue monitor to be running. Until this time elapses, the messages are in the queue in the state MsgStateReady. After this time elapses messages are moved to the exception queue in the MsgStateExpired state.

getMsgPropsOriginalMsgId :: PtrMsgProps -> IO ByteString Source #

Returns the id of the message in the last queue that generated this message. See function setMsgPropsOriginalMsgId for more information.

setMsgPropsOriginalMsgId :: PtrMsgProps -> ByteString -> IO Bool Source #

Sets the id of the message in the last queue that generated this message.

getMsgPropsPriority :: PtrMsgProps -> IO Int Source #

Returns the priority assigned to the message. See function setMsgPropsPriority for more information.

setMsgPropsPriority :: PtrMsgProps -> Int -> IO Bool Source #

Sets the priority assigned to the message. A smaller number indicates a higher priority. The priority can be any number, including negative numbers.

getMsgPropsState :: PtrMsgProps -> IO MessageState Source #

Returns the state of the message at the time of dequeue.

Subscr Interface

Subscription handles are used to represent subscriptions to events such as continuous query notification and object change notification. They are created by calling the function newSubscr and are destroyed by calling the function closeSubscr or releasing the last reference by calling the function releaseSubscr.

newSubscr :: PtrConn -> (Data_SubscrCreateParams -> Data_SubscrCreateParams) -> IO PtrSubscr Source #

Returns a reference to a subscription which is used for requesting notifications of changes on tables or queries that are made in the database. The reference should be released as soon as it is no longer needed.

subscribe :: PtrConn -> (Data_SubscrCreateParams -> Data_SubscrCreateParams) -> IO PtrSubscr Source #

Returns a reference to a subscription which is used for requesting notifications of events that take place in the database. Events that are supported are changes on tables or queries (continuous query notification) and the availability of messages to dequeue (advanced queuing). The reference should be released as soon as it is no longer needed.

@since ODPI-C 2.4.0

unsubscribe :: PtrConn -> PtrSubscr -> IO Bool Source #

Unubscribes from the events that were earlier subscribed to via the function subscribe. Once this function completes successfully no further notifications will be sent for this subscription. Note that this method does not generate a notification either.

@since ODPI-C 2.4.0

subscrAddRef :: PtrSubscr -> IO Bool Source #

Adds a reference to the subscription. This is intended for situations where a reference to the subscription needs to be maintained independently of the reference returned when the subscription was created.

closeSubscr :: PtrSubscr -> IO Bool Source #

Closes the subscription now, rather than when the last reference is released. This deregisters it so that notifications will no longer be sent.

releaseSubscr :: PtrSubscr -> IO Bool Source #

Releases a reference to the subscription. A count of the references to the subscription is maintained and when this count reaches zero, the memory associated with the subscription is freed. The subscription is also deregistered so that notifications are no longer sent, if this was not already done using the function closeSubscr.

subscrPrepareStatement Source #

Arguments

:: PtrSubscr

a reference to the subscription on which the statement is to be prepared for registration.

-> ByteString

the SQL that is to be prepared

-> IO PtrStmt

a reference to the statement that was prepared

Prepares a statement for registration on the subscription. The statement is then registered by calling the function prepareStatement. The reference to the statement that is returned should be released as soon as it is no longer needed.

type PtrConn = HasCxtPtr DPI_Conn Source #

type PtrPool = HasCxtPtr DPI_Pool Source #

type PtrStmt = HasCxtPtr DPI_Stmt Source #

type PtrVar = HasCxtPtr DPI_Var Source #

type PtrLob = HasCxtPtr DPI_Lob Source #

type PtrObject = HasCxtPtr DPI_Object Source #

type PtrObjectAttr = HasCxtPtr DPI_ObjectAttr Source #

type PtrObjectType = HasCxtPtr DPI_ObjectType Source #

type PtrRowid = HasCxtPtr DPI_Rowid Source #

type PtrSubscr = HasCxtPtr DPI_Subscr Source #

type PtrDeqOptions = HasCxtPtr DPI_DeqOptions Source #

type PtrEnqOptions = HasCxtPtr DPI_EnqOptions Source #

type PtrMsgProps = HasCxtPtr DPI_MsgProps Source #

type PtrContext = Ptr DPI_Context Source #

newtype Data Source #

Instances

Storable Data Source # 

Methods

sizeOf :: Data -> Int #

alignment :: Data -> Int #

peekElemOff :: Ptr Data -> Int -> IO Data #

pokeElemOff :: Ptr Data -> Int -> Data -> IO () #

peekByteOff :: Ptr b -> Int -> IO Data #

pokeByteOff :: Ptr b -> Int -> Data -> IO () #

peek :: Ptr Data -> IO Data #

poke :: Ptr Data -> Data -> IO () #

getContextError :: PtrContext -> IO Data_ErrorInfo Source #

Returns error information for the last error that was raised by the library. This function must be called with the same thread that generated the error. It must also be called before any other ODPI-C library calls are made on the calling thread since the error information specific to that thread is cleared at the start of every ODPI-C function call.