odpic-raw-0.1.2

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

Database.Dpi

Contents

Description

FFI raw bindings to ODPI-C

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.

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.

Connection Interface

Connection handles are used to represent connections to the database. These can be standalone connections created by calling the function createConnetion. 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.

createConnection Source #

Arguments

:: PtrContext

Context

-> ByteString

the name of the user used for authenticating the user

-> ByteString

the password to use for authenticating the user

-> ByteString

he connect string identifying the database to which a connection is to be established

-> (Data_CommonCreateParams -> Data_CommonCreateParams)

custom Data_CommonCreateParams

-> IO PtrConn 

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.

pingConnection :: PtrConn -> IO Bool Source #

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

withConnection Source #

Arguments

:: PtrContext

Context

-> ByteString

Username

-> ByteString

Password

-> ByteString

Connection String

-> ByteString

NLS_LANG encoding

-> ByteString

NLS_NCHAR encoding

-> (PtrConn -> IO a)

action use connection

-> IO a 

with connection

Transaction Interface

beginTransaction Source #

Arguments

:: PtrConn

Connection

-> Int64

formatId

-> ByteString

transactionId

-> ByteString

branchId

-> IO Bool 

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

prepareTransaction :: 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

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 createStatement. 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.

createStatement Source #

Arguments

:: PtrConn

Connection

-> Bool

scrollable

-> ByteString

SQL String

-> 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

scrollable

-> ByteString

SQL String

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

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

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

Statement Bind Vars

bindByName :: PtrStmt -> ByteString -> PtrVar -> IO Bool Source #

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 :: PtrStmt -> Int -> PtrVar -> IO Bool Source #

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 :: PtrStmt -> ByteString -> NativeTypeNum -> PtrData -> IO Bool Source #

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 :: PtrStmt -> Int -> NativeTypeNum -> PtrData -> IO Bool Source #

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 :: PtrStmt -> Int -> PtrVar -> IO Bool Source #

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 :: PtrStmt -> Int -> OracleTypeNum -> NativeTypeNum -> Int -> Bool -> PtrObjectType -> IO Bool Source #

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.

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.

Lob Interface

Object Interface

Rowid Interface

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

Oracle type enum

-> NativeTypeNum

Native type enum

-> Int

maxArraySize

-> Int

size

-> Bool

sizeIsBytes

-> Bool

isArray

-> PtrObjectType

Object type

-> 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.

type PtrConn = Ptr DPI_Conn Source #

type PtrPool = Ptr DPI_Pool Source #

type PtrStmt = Ptr DPI_Stmt Source #

type PtrVar = Ptr DPI_Var Source #

type PtrLob = Ptr DPI_Lob Source #

type PtrObject = Ptr DPI_Object Source #

type PtrObjectAttr = Ptr DPI_ObjectAttr Source #

type PtrObjectType = Ptr DPI_ObjectType Source #

type PtrRowid = Ptr DPI_Rowid Source #

type PtrSubscr = Ptr DPI_Subscr Source #

type PtrDeqOptions = Ptr DPI_DeqOptions Source #

type PtrEnqOptions = Ptr DPI_EnqOptions Source #

type PtrMsgProps = Ptr DPI_MsgProps Source #

type PtrContext = Ptr DPI_Context Source #

newtype Data Source #

Constructors

Data (NativeTypeNum -> IO DataValue) 

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 () #