Takusen-0.8: Database library with left-fold interface, for PostgreSQL, Oracle, SQLite, ODBC.

Portabilitynon-portable
Stabilityexperimental
Maintaineroleg@pobox.com, alistair@abayley.org

Database.Oracle.OCIFunctions

Description

Simple wrappers for OCI functions (FFI).

The functions in this file are simple wrappers for OCI functions. The wrappers add error detection and exceptions; functions in this module raise OCIException. The next layer up traps these and turns them into Database.Enumerator.DBException.

Note that OCIException does not contain the error number and text returned by getOCIErrorMsg. It is the job of the next layer (module) up to catch the OCIException and then call getOCIErrorMsg to get the actual error details. The OCIException simply contains the error number returned by the OCI call, and some text identifying the wrapper function. See formatErrorCodeDesc for the set of possible values for the OCI error numbers.

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.
  • In GHC you can simply say data OCIStruct i.e. there's no need for = OCIStruct. I've decided to be more portable, as it doesn't cost much.
  • Use castPtr if you need to convert handles (say OCIHandle to a more specific type, or vice versa).

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 

data OCIException Source

Low-level, OCI library errors.

Constructors

OCIException CInt String 

catchOCI :: IO a -> (OCIException -> IO a) -> IO aSource

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

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 aSource

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.

Typically an OCI wrapper function would look like:

 handleAlloc handleType env = alloca ptr -> do
   rc <- ociHandleAlloc env ptr handleType 0 nullPtr
   if rc < 0
     then throwOCI (OCIException rc msg)
     else return ()

where the code from if rc < 0 onwards was identical. testForError replaces the code from if rc < 0 ... onwards.

testForErrorWithPtr :: Storable a => CInt -> String -> Ptr a -> IO aSource

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 ConnHandleSource

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 SessHandleSource

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:

  • prepare your statement (it's just a String) - no communication with DBMS
  • execute it (this sends it to the DBMS for parsing etc)
  • allocate result set buffers by calling defineByPos for each column
  • call fetch for each row.
  • call handleFree for the StmtHandle (I assume this is the approved way of terminating the query; the OCI docs aren't explicit about this.)

defineByPosSource

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:

  • the result (i.e. value) - you have to say how big with bufsize.
  • the null indicator (int16)
  • the size of the returned data (int16)

Previously it was the caller's responsibility to free the memory after they're done with it. Now we use Foreign.ForeignPtr.mallocForeignPtr, so manual memory management is hopefully a thing of the past. The caller will also have to cast the data in bufferptr to the expected type (using Foreign.Ptr.castPtr).

sbph :: String -> Int -> Bool -> String -> StringSource

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

We don't use this function into this library though; it's used in the higher-level implementation of Enumerator. We prefer to retain flexibility at this lower-level, and not force arbitrary implementation choices too soon. If you want to use this library and use :x style syntax, you can.

bindByPosSource

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

bindOutputByPosSource

Arguments

:: ErrorHandle 
-> StmtHandle 
-> Int

Position

-> BindBuffer

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

-> Int

payload input size in bytes

-> CInt

SQL Datatype (from Database.Oracle.OCIConstants)

-> IO BindHandle 

stmtFetch :: ErrorHandle -> StmtHandle -> IO CIntSource

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

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.

+1999 -> 119, 199 +0100 -> 101, 100 +0001 -> 100, 101 -0001 -> 100, 99 -0100 -> 99, 100 -1999 -> 81, 1