{-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE TemplateHaskell #-} {-# LANGUAGE QuasiQuotes #-} -- | -- Module: Database.Ocilib.Bindings -- Copyright: (c) 2016 Thierry Bourrillon -- (c) 2016 FPInsight, Eurl. -- License: BSD3 -- Maintainer: Thierry Bourrillon -- Stability: experimental -- Portability: portable -- -- module Database.Ocilib.Bindings ( ociBindArraySetSize , ociBindArrayGetSize , ociAllowRebinding , ociIsRebindingAllowed --, ociBindBoolean --, ociBindShort --, ociBindArrayOfShorts --, ociBindUnsignedShort --, ociBindArrayOfUnsignedShorts --, ociBindInt --, ociBindArrayOfInts --, ociBindUnsignedInt --, ociBindArrayOfUnsignedInts --, ociBindBigInt --, ociBindArrayOfBigInts --, ociBindUnsignedBigInts --, ociBindArrayOfUnsignedBigInts , ociBindString , ociBindArrayOfStrings --, ociBindRaw --, ociBindArrayOfRaws --, ociBindDouble --, ociBindArrayOfDoubles --, ociBindFloat --, ociBindArrayOfFloats --, ociBindDate --, ociBindArrayOfDates --, ociBindTimestamp --, ociBindArrayOfTimestamps --, ociBindInterval --, ociBindArrayOfIntervals --, ociBindLob --, ociBindArrayOfLobs --, ociBindFile --, ociBindArrayOfFiles --, ociBindObject --, ociBindArrayOfObjects --, ociBindColl --, ociBindArrayOfColls --, ociBindRef --, ociBindArrayOfRefs --, ociBindStatement --, ociBindLong --, ociGetBatchError --, ociGetBatchErrorCount --, ociGetBindCount --, ociGetBind --, ociGetBind2 --, ociGetBindIndex --, ociBindGetName --, ociBindSetDirection --, ociBindGetDirection --, ociBindGetType --, ociBindGetSubtype --, ociBindGetDataCount --, ociBindGetData --, ociBindGetStatement --, ociBindSetDataSize --, ociBindGetDataSize --, ociBindGetDataSizeAtPos --, ociBindSetNull --, ociBindSetNullAtPos --, ociBindSetNotNull --, ociBindSetNotNullAtPos --, ociBindIsNull --, ociBindIsNullAtPos --, ociBindSetCharsetForm ) where import Data.Monoid ((<>)) import Foreign.C.Types import Foreign.C.String import Foreign.Marshal.Utils import Foreign.Ptr import qualified Language.C.Inline as C import Database.Ocilib.Oci --import Database.Ocilib.Enums C.context (C.baseCtx <> C.funCtx <> ociCtx) C.include "" -- Binding variables and arrays -- | Set the input array size for bulk operations. ociBindArraySetSize :: Ptr OCI_Statement -> CUInt -> IO Bool ociBindArraySetSize st s = fmap toBool [C.exp| int { OCI_BindArraySetSize($(OCI_Statement *st), $(unsigned int s)) } |] -- | Return the current input array size for bulk operations. ociBindArrayGetSize :: Ptr OCI_Statement -> IO CUInt ociBindArrayGetSize st = [C.exp| unsigned int { OCI_BindArrayGetSize($(OCI_Statement *st)) } |] -- | Allow different host variables to be binded using the same bind name or position between executions of a prepared statement. ociAllowRebinding :: Ptr OCI_Statement -> Bool -> IO Bool ociAllowRebinding st value = do let v = fromIntegral $ fromEnum value fmap toBool [C.exp| int { OCI_AllowRebinding($(OCI_Statement *st), $(int v)) }|] -- | Indicate if rebinding is allowed on the given statement. ociIsRebindingAllowed :: Ptr OCI_Statement -> IO Bool ociIsRebindingAllowed st = fmap toBool [C.exp| int { OCI_IsRebindingAllowed($(OCI_Statement *st)) } |] {- -- | Bind a boolean variable (PL/SQL ONLY) -- boolean OCI_BindBoolean (OCI_Statement *stmt, const otext *name, boolean *data) -- | Bind an short variable. -- boolean OCI_BindShort (OCI_Statement *stmt, const otext *name, short *data) -- | Bind an array of shorts. -- boolean OCI_BindArrayOfShorts (OCI_Statement *stmt, const otext *name, short *data, unsigned int nbelem) -- | Bind an unsigned short variable. -- boolean OCI_BindUnsignedShort (OCI_Statement *stmt, const otext *name, unsigned short *data) -- | Bind an array of unsigned shorts. -- boolean OCI_BindArrayOfUnsignedShorts (OCI_Statement *stmt, const otext *name, unsigned short *data, unsigned int nbelem) -- | Bind an integer variable. -- boolean OCI_BindInt (OCI_Statement *stmt, const otext *name, int *data) -- | Bind an array of integers. -- boolean OCI_BindArrayOfInts (OCI_Statement *stmt, const otext *name, int *data, unsigned int nbelem) -- | Bind an unsigned integer variable. -- boolean OCI_BindUnsignedInt (OCI_Statement *stmt, const otext *name, unsigned int *data) -- | Bind an array of unsigned integers. -- boolean OCI_BindArrayOfUnsignedInts (OCI_Statement *stmt, const otext *name, unsigned int *data, unsigned int nbelem) -- | Bind a big integer variable. -- boolean OCI_BindBigInt (OCI_Statement *stmt, const otext *name, big_int *data) -- | Bind an array of big integers. -- boolean OCI_BindArrayOfBigInts (OCI_Statement *stmt, const otext *name, big_int *data, unsigned int nbelem) -- | Bind an unsigned big integer variable. -- boolean OCI_BindUnsignedBigInt (OCI_Statement *stmt, const otext *name, big_uint *data) -- | Bind an array of unsigned big integers. -- boolean OCI_BindArrayOfUnsignedBigInts (OCI_Statement *stmt, const otext *name, big_uint *data, unsigned int nbelem) -} -- | Bind a string variable. ociBindString :: Ptr OCI_Statement -> String -> String -> CUInt -> IO Bool ociBindString st name d l = withCString name (\n -> withCString d (\d' -> fmap toBool [C.exp| int { OCI_BindString($(OCI_Statement *st), $(char *n), $(char *d'), $(unsigned int l))} |] ) ) -- | Bind an array of strings. ociBindArrayOfStrings :: Ptr OCI_Statement -> String -> String -> CUInt -> CUInt -> IO Bool ociBindArrayOfStrings st name d len nbElem = withCString name (\n -> withCString d (\d' -> fmap toBool [C.exp| int { OCI_BindArrayOfStrings($(OCI_Statement *st), $(char *n), $(char *d'), $(unsigned int len), $(unsigned int nbElem)) } |] ) ) {- -- | Bind a raw buffer. -- boolean OCI_BindRaw (OCI_Statement *stmt, const otext *name, void *data, unsigned int len) -- | Bind an array of raw buffers. -- boolean OCI_BindArrayOfRaws (OCI_Statement *stmt, const otext *name, void *data, unsigned int len, unsigned int nbelem) -- | Bind a double variable. -- boolean OCI_BindDouble (OCI_Statement *stmt, const otext *name, double *data) -- | Bind an array of doubles. -- boolean OCI_BindArrayOfDoubles (OCI_Statement *stmt, const otext *name, double *data, unsigned int nbelem) -- | Bind a float variable. -- boolean OCI_BindFloat (OCI_Statement *stmt, const otext *name, float *data) -- | Bind an array of floats. -- boolean OCI_BindArrayOfFloats (OCI_Statement *stmt, const otext *name, float *data, unsigned int nbelem) -- | Bind a date variable. -- boolean OCI_BindDate (OCI_Statement *stmt, const otext *name, OCI_Date *data) -- | Bind an array of dates. -- boolean OCI_BindArrayOfDates (OCI_Statement *stmt, const otext *name, OCI_Date **data, unsigned int nbelem) -- | Bind a timestamp variable. -- boolean OCI_BindTimestamp (OCI_Statement *stmt, const otext *name, OCI_Timestamp *data) -- | Bind an array of timestamp handles. -- boolean OCI_BindArrayOfTimestamps (OCI_Statement *stmt, const otext *name, OCI_Timestamp **data, unsigned int type, unsigned int nbelem) -- | Bind an interval variable. -- boolean OCI_BindInterval (OCI_Statement *stmt, const otext *name, OCI_Interval *data) -- | Bind an array of interval handles. -- boolean OCI_BindArrayOfIntervals (OCI_Statement *stmt, const otext *name, OCI_Interval **data, unsigned int type, unsigned int nbelem) -- | Bind a Lob variable. -- boolean OCI_BindLob (OCI_Statement *stmt, const otext *name, OCI_Lob *data) -- | Bind an array of Lob handles. -- boolean OCI_BindArrayOfLobs (OCI_Statement *stmt, const otext *name, OCI_Lob **data, unsigned int type, unsigned int nbelem) -- | Bind a File variable. -- boolean OCI_BindFile (OCI_Statement *stmt, const otext *name, OCI_File *data) -- | Bind an array of File handles. -- boolean OCI_BindArrayOfFiles (OCI_Statement *stmt, const otext *name, OCI_File **data, unsigned int type, unsigned int nbelem) -- | Bind an object (named type) variable. -- boolean OCI_BindObject (OCI_Statement *stmt, const otext *name, OCI_Object *data) -- | Bind an array of object handles. -- boolean OCI_BindArrayOfObjects (OCI_Statement *stmt, const otext *name, OCI_Object **data, OCI_TypeInfo *typinf, unsigned int nbelem) -- | Bind a Collection variable. -- boolean OCI_BindColl (OCI_Statement *stmt, const otext *name, OCI_Coll *data) -- | Bind an array of Collection handles. -- boolean OCI_BindArrayOfColls (OCI_Statement *stmt, const otext *name, OCI_Coll **data, OCI_TypeInfo *typinf, unsigned int nbelem) -- | Bind a Ref variable. -- boolean OCI_BindRef (OCI_Statement *stmt, const otext *name, OCI_Ref *data) -- | Bind an array of Ref handles. -- boolean OCI_BindArrayOfRefs (OCI_Statement *stmt, const otext *name, OCI_Ref **data, OCI_TypeInfo *typinf, unsigned int nbelem) -- | Bind a Statement variable (PL/SQL Ref Cursor) -- boolean OCI_BindStatement (OCI_Statement *stmt, const otext *name, OCI_Statement *data) -- | Bind a Long variable. -- boolean OCI_BindLong (OCI_Statement *stmt, const otext *name, OCI_Long *data, unsigned int size) -- | Returns the first or next error that occurred within a DML array statement execution. -- OCI_Error *OCI_GetBatchError (OCI_Statement *stmt) -- | Returns the number of errors that occurred within the last DML array statement. -- unsigned int OCI_GetBatchErrorCount (OCI_Statement *stmt) -- | Return the number of binds currently associated to a statement. -- unsigned int OCI_GetBindCount (OCI_Statement *stmt) -- | Return the bind handle at the given index in the internal array of bind handle. -- OCI_Bind *OCI_GetBind (OCI_Statement *stmt, unsigned int index) -- | Return a bind handle from its name. -- OCI_Bind *OCI_GetBind2 (OCI_Statement *stmt, const otext *name) -- | Return the index of the bind from its name belonging to the given statement. -- unsigned int OCI_GetBindIndex (OCI_Statement *stmt, const otext *name) -- | Return the name of the given bind. -- const otext *OCI_BindGetName (OCI_Bind *bnd) -- | Set the direction mode of a bind handle. -- boolean OCI_BindSetDirection (OCI_Bind *bnd, unsigned int direction) -- | Get the direction mode of a bind handle. -- unsigned int OCI_BindGetDirection (OCI_Bind *bnd) -- | Return the OCILIB type of the given bind. -- unsigned int OCI_BindGetType (OCI_Bind *bnd) -- | Return the OCILIB object subtype of the given bind. -- unsigned int OCI_BindGetSubtype (OCI_Bind *bnd) -- | Return the number of elements of the bind handle. -- unsigned int OCI_BindGetDataCount (OCI_Bind *bnd) -- | Return the user defined data associated with a bind handle. -- void *OCI_BindGetData (OCI_Bind *bnd) -- | Return the statement handle associated with a bind handle. -- OCI_Statement *OCI_BindGetStatement (OCI_Bind *bnd) -- | Set the actual size of the element held by the given bind handle. -- boolean OCI_BindSetDataSize (OCI_Bind *bnd, unsigned int size) -- | Set the size of the element at the given position in the bind input array. -- boolean OCI_BindSetDataSizeAtPos (OCI_Bind *bnd, unsigned int position, unsigned int size) -- | Return the actual size of the element held by the given bind handle. -- unsigned int OCI_BindGetDataSize (OCI_Bind *bnd) -- | Return the actual size of the element at the given position in the bind input array. -- unsigned int OCI_BindGetDataSizeAtPos (OCI_Bind *bnd, unsigned int position) -- | Set the bind variable to null. -- boolean OCI_BindSetNull (OCI_Bind *bnd) -- | Set to null the entry in the bind variable input array. -- boolean OCI_BindSetNullAtPos (OCI_Bind *bnd, unsigned int position) -- | Set the bind variable to NOT null. -- boolean OCI_BindSetNotNull (OCI_Bind *bnd) -- | Set to NOT null the entry in the bind variable input array. -- boolean OCI_BindSetNotNullAtPos (OCI_Bind *bnd, unsigned int position) -- | Check if the current value of the binded variable is marked as NULL. -- boolean OCI_BindIsNull (OCI_Bind *bnd) -- | Check if the current entry value at the given index of the binded array is marked as NULL. -- boolean OCI_BindIsNullAtPos (OCI_Bind *bnd, unsigned int position) -- | Set the charset form of the given character based bind variable. -- boolean OCI_BindSetCharsetForm (OCI_Bind *bnd, unsigned int csfrm) -}