takusen-oracle-0.9.4.1: Database library with left-fold interface for Oracle.

Copyright(c) 2004 Oleg Kiselyov, Alistair Bayley
LicenseBSD-style
Maintaineroleg@pobox.com, alistair@abayley.org
Stabilityexperimental
Portabilitynon-portable
Safe HaskellSafe
LanguageHaskell2010

Database.Oracle.OCIFunctions

Description

 

Synopsis

Documentation

data OCIStruct Source #

  • Each handle type has its own data type, to prevent stupid errors i.e. using the wrong handle at the wrong time.

Constructors

OCIStruct 

data OCIBuffer Source #

Constructors

OCIBuffer 

data Context Source #

Constructors

Context 

data EnvStruct Source #

Constructors

EnvStruct 

data ErrorStruct Source #

Constructors

ErrorStruct 

data ServerStruct Source #

Constructors

ServerStruct 

data UserStruct Source #

Constructors

UserStruct 

data ConnStruct Source #

Constructors

ConnStruct 

data SessStruct Source #

Constructors

SessStruct 

data StmtStruct Source #

Constructors

StmtStruct 

data DefnStruct Source #

Constructors

DefnStruct 

data ParamStruct Source #

Constructors

ParamStruct 

data BindStruct Source #

Constructors

BindStruct 

catchOCI :: IO a -> (OCIException -> IO a) -> IO a Source #

ociEnvCreate :: Ptr EnvHandle -> CInt -> Ptr a -> FunPtr a -> FunPtr a -> FunPtr a -> CInt -> Ptr (Ptr a) -> IO CInt Source #

ociBindByPos Source #

Arguments

:: StmtHandle 
-> Ptr BindHandle 
-> ErrorHandle 
-> CUInt

position

-> BufferPtr

buffer containing data

-> CInt

max size of buffer

-> CUShort

SQL data type

-> Ptr CShort

null indicator ptr

-> Ptr CUShort

input + output size, or array of sizes

-> Ptr CUShort

array of return codes

-> CUInt

max array elements

-> Ptr CUInt

number of array elements

-> CUInt

mode

-> IO CInt 

getOCIErrorMsg2 :: OCIHandle -> CInt -> Ptr CInt -> CString -> CInt -> IO (CInt, String) Source #

This is just an auxiliary function for getOCIErrorMsg.

formatOCIMsg :: CInt -> String -> OCIHandle -> CInt -> IO (Int, String) Source #

Given the two parts of an OCIException (the error number and text) get the actual error message from the DBMS and construct an error message from all of these pieces.

formatMsgCommon :: OCIException -> OCIHandle -> CInt -> IO (Int, String) Source #

We have two format functions: formatEnvMsg takes the EnvHandle, formatErrorMsg takes the ErrorHandle. They're just type-safe wrappers for formatMsgCommon.

testForError :: CInt -> String -> a -> IO a Source #

The testForError functions are the only places where OCIException is thrown, so if you want to change or embellish it, your changes will be localised here. These functions factor out common error handling code from the OCI wrapper functions that follow.

testForErrorWithPtr :: Storable a => CInt -> String -> Ptr a -> IO a Source #

Like testForError but when the value you want to return is at the end of a pointer. Either there was an error, in which case the pointer probably isn't valid, or there is something at the end of the pointer to return. See dbLogon and getHandleAttr for example usage.

dbLogon :: String -> String -> String -> EnvHandle -> ErrorHandle -> IO ConnHandle Source #

The OCI Logon function doesn't behave as you'd expect when the password is due to expire. ociLogon returns oci_SUCCESS_WITH_INFO, but the ConnHandle returned is not valid. In this case we have to change oci_SUCCESS_WITH_INFO to oci_ERROR, so that the error handling code will catch it and abort. I don't know why the handle returned isn't valid, as the logon process should be able to complete successfully in this case.

getSession :: ErrorHandle -> ConnHandle -> IO SessHandle Source #

Having established a connection (Service Context), now get the Session. You can have more than one session per connection, but I haven't implemented it yet.

stmtPrepare :: ErrorHandle -> StmtHandle -> String -> IO () Source #

With the OCI you do queries with these steps:

defineByPos Source #

Arguments

:: ErrorHandle 
-> StmtHandle 
-> Int

Position

-> Int

Buffer size in bytes

-> CInt

SQL Datatype (from Database.Oracle.OCIConstants)

-> IO ColumnInfo

tuple: (DefnHandle, Ptr to buffer, Ptr to null indicator, Ptr to size of value in buffer)

defineByPos allocates memory for a single column value. The allocated components are:

substituteBindPlaceHolders :: String -> String Source #

Oracle only understands bind variable placeholders using syntax :x, where x is a number or a variable name. Most other DBMS's use ? as a placeholder, so we have this function to substitute ? with :n, where n starts at one and increases with each ?.

bindByPos Source #

Arguments

:: ErrorHandle 
-> StmtHandle 
-> Int

Position

-> CShort

Null ind: 0 == not null, -1 == null

-> BufferPtr

payload

-> Int

payload size in bytes

-> CInt

SQL Datatype (from Database.Oracle.OCIConstants)

-> IO () 

bindOutputByPos Source #

Arguments

:: ErrorHandle 
-> StmtHandle 
-> Int

Position

-> BindBuffer

triple of (null-ind, payload, input-size)

-> Int

buffer max size in bytes

-> CInt

SQL Datatype (from Database.Oracle.OCIConstants)

-> IO BindHandle 

stmtFetch :: ErrorHandle -> StmtHandle -> IO CInt Source #

Fetch a single row into the buffers. If you have specified a prefetch count > 1 then the row might already be cached by the OCI library.

maybeBufferNull :: ForeignPtr CShort -> Maybe a -> IO a -> IO (Maybe a) Source #

Short-circuit null test: if the buffer contains a null then return Nothing. Otherwise, run the IO action to extract a value from the buffer and return Just it.

makeYear :: Int -> Int -> Int Source #

Oracle's excess-something-or-other encoding for years: year = 100*(c - 100) + (y - 100), c = (year div 100) + 100, y = (year mod 100) + 100.

calTimeToBuffer :: BufferPtr -> CalendarTime -> IO () Source #