-- GENERATED by C->Haskell Compiler, version 0.28.3 Switcheroo, 25 November 2017 (Haskell)
-- Edit the ORIGNAL .chs file instead!


{-# LINE 1 "src/Database/Dpi/Internal.chs" #-}
{-# LANGUAGE EmptyDataDecls           #-}
{-# LANGUAGE ForeignFunctionInterface #-}
{-# LANGUAGE RecordWildCards          #-}
{-# LANGUAGE DuplicateRecordFields    #-}
{-# LANGUAGE OverloadedStrings        #-}

module Database.Dpi.Internal where
import qualified Foreign.C.Types as C2HSImp
import qualified Foreign.ForeignPtr as C2HSImp
import qualified Foreign.Ptr as C2HSImp
import qualified Foreign.Storable as C2HSImp



import Control.Exception
import Database.Dpi.Prelude 
import qualified Data.Text as T
import qualified Data.Text.Lazy as L
import Data.Time




{-# LINE 17 "src/Database/Dpi/Internal.chs" #-}


{-# INLINE majorVersion #-}
majorVersion :: CUInt
majorVersion = 2
{-# LINE 21 "src/Database/Dpi/Internal.chs" #-}


{-# INLINE minorVersion #-}
minorVersion :: CUInt
minorVersion = 4
{-# LINE 25 "src/Database/Dpi/Internal.chs" #-}


{-# INLINE success #-}
success :: CInt
success = 0
{-# LINE 29 "src/Database/Dpi/Internal.chs" #-}


-- Enum
data AuthMode = ModeAuthDefault
              | ModeAuthSysdba
              | ModeAuthSysoper
              | ModeAuthPrelim
              | ModeAuthSysasm
              | ModeAuthSysbkp
              | ModeAuthSysdgd
              | ModeAuthSyskmt
              | ModeAuthSysrac
  deriving (Eq,Show)
instance Enum AuthMode where
  succ ModeAuthDefault = ModeAuthSysdba
  succ ModeAuthSysdba = ModeAuthSysoper
  succ ModeAuthSysoper = ModeAuthPrelim
  succ ModeAuthPrelim = ModeAuthSysasm
  succ ModeAuthSysasm = ModeAuthSysbkp
  succ ModeAuthSysbkp = ModeAuthSysdgd
  succ ModeAuthSysdgd = ModeAuthSyskmt
  succ ModeAuthSyskmt = ModeAuthSysrac
  succ ModeAuthSysrac = error "AuthMode.succ: ModeAuthSysrac has no successor"

  pred ModeAuthSysdba = ModeAuthDefault
  pred ModeAuthSysoper = ModeAuthSysdba
  pred ModeAuthPrelim = ModeAuthSysoper
  pred ModeAuthSysasm = ModeAuthPrelim
  pred ModeAuthSysbkp = ModeAuthSysasm
  pred ModeAuthSysdgd = ModeAuthSysbkp
  pred ModeAuthSyskmt = ModeAuthSysdgd
  pred ModeAuthSysrac = ModeAuthSyskmt
  pred ModeAuthDefault = error "AuthMode.pred: ModeAuthDefault has no predecessor"

  enumFromTo from to = go from
    where
      end = fromEnum to
      go v = case compare (fromEnum v) end of
                 LT -> v : go (succ v)
                 EQ -> [v]
                 GT -> []

  enumFrom from = enumFromTo from ModeAuthSysrac

  fromEnum ModeAuthDefault = 0
  fromEnum ModeAuthSysdba = 2
  fromEnum ModeAuthSysoper = 4
  fromEnum ModeAuthPrelim = 8
  fromEnum ModeAuthSysasm = 32768
  fromEnum ModeAuthSysbkp = 131072
  fromEnum ModeAuthSysdgd = 262144
  fromEnum ModeAuthSyskmt = 524288
  fromEnum ModeAuthSysrac = 1048576

  toEnum 0 = ModeAuthDefault
  toEnum 2 = ModeAuthSysdba
  toEnum 4 = ModeAuthSysoper
  toEnum 8 = ModeAuthPrelim
  toEnum 32768 = ModeAuthSysasm
  toEnum 131072 = ModeAuthSysbkp
  toEnum 262144 = ModeAuthSysdgd
  toEnum 524288 = ModeAuthSyskmt
  toEnum 1048576 = ModeAuthSysrac
  toEnum unmatched = error ("AuthMode.toEnum: Cannot match " ++ show unmatched)

{-# LINE 32 "src/Database/Dpi/Internal.chs" #-}

data ConnCloseMode = ModeConnCloseDefault
                   | ModeConnCloseDrop
                   | ModeConnCloseRetag
  deriving (Eq,Show)
instance Enum ConnCloseMode where
  succ ModeConnCloseDefault = ModeConnCloseDrop
  succ ModeConnCloseDrop = ModeConnCloseRetag
  succ ModeConnCloseRetag = error "ConnCloseMode.succ: ModeConnCloseRetag has no successor"

  pred ModeConnCloseDrop = ModeConnCloseDefault
  pred ModeConnCloseRetag = ModeConnCloseDrop
  pred ModeConnCloseDefault = error "ConnCloseMode.pred: ModeConnCloseDefault has no predecessor"

  enumFromTo from to = go from
    where
      end = fromEnum to
      go v = case compare (fromEnum v) end of
                 LT -> v : go (succ v)
                 EQ -> [v]
                 GT -> []

  enumFrom from = enumFromTo from ModeConnCloseRetag

  fromEnum ModeConnCloseDefault = 0
  fromEnum ModeConnCloseDrop = 1
  fromEnum ModeConnCloseRetag = 2

  toEnum 0 = ModeConnCloseDefault
  toEnum 1 = ModeConnCloseDrop
  toEnum 2 = ModeConnCloseRetag
  toEnum unmatched = error ("ConnCloseMode.toEnum: Cannot match " ++ show unmatched)

{-# LINE 33 "src/Database/Dpi/Internal.chs" #-}

data CreateMode = ModeCreateDefault
                | ModeCreateThreaded
                | ModeCreateEvents
  deriving (Eq,Show)
instance Enum CreateMode where
  succ ModeCreateDefault = ModeCreateThreaded
  succ ModeCreateThreaded = ModeCreateEvents
  succ ModeCreateEvents = error "CreateMode.succ: ModeCreateEvents has no successor"

  pred ModeCreateThreaded = ModeCreateDefault
  pred ModeCreateEvents = ModeCreateThreaded
  pred ModeCreateDefault = error "CreateMode.pred: ModeCreateDefault has no predecessor"

  enumFromTo from to = go from
    where
      end = fromEnum to
      go v = case compare (fromEnum v) end of
                 LT -> v : go (succ v)
                 EQ -> [v]
                 GT -> []

  enumFrom from = enumFromTo from ModeCreateEvents

  fromEnum ModeCreateDefault = 0
  fromEnum ModeCreateThreaded = 1
  fromEnum ModeCreateEvents = 4

  toEnum 0 = ModeCreateDefault
  toEnum 1 = ModeCreateThreaded
  toEnum 4 = ModeCreateEvents
  toEnum unmatched = error ("CreateMode.toEnum: Cannot match " ++ show unmatched)

{-# LINE 34 "src/Database/Dpi/Internal.chs" #-}

data DeqMode = ModeDeqBrowse
             | ModeDeqLocked
             | ModeDeqRemove
             | ModeDeqRemoveNoData
  deriving (Eq,Show)
instance Enum DeqMode where
  succ ModeDeqBrowse = ModeDeqLocked
  succ ModeDeqLocked = ModeDeqRemove
  succ ModeDeqRemove = ModeDeqRemoveNoData
  succ ModeDeqRemoveNoData = error "DeqMode.succ: ModeDeqRemoveNoData has no successor"

  pred ModeDeqLocked = ModeDeqBrowse
  pred ModeDeqRemove = ModeDeqLocked
  pred ModeDeqRemoveNoData = ModeDeqRemove
  pred ModeDeqBrowse = error "DeqMode.pred: ModeDeqBrowse has no predecessor"

  enumFromTo from to = go from
    where
      end = fromEnum to
      go v = case compare (fromEnum v) end of
                 LT -> v : go (succ v)
                 EQ -> [v]
                 GT -> []

  enumFrom from = enumFromTo from ModeDeqRemoveNoData

  fromEnum ModeDeqBrowse = 1
  fromEnum ModeDeqLocked = 2
  fromEnum ModeDeqRemove = 3
  fromEnum ModeDeqRemoveNoData = 4

  toEnum 1 = ModeDeqBrowse
  toEnum 2 = ModeDeqLocked
  toEnum 3 = ModeDeqRemove
  toEnum 4 = ModeDeqRemoveNoData
  toEnum unmatched = error ("DeqMode.toEnum: Cannot match " ++ show unmatched)

{-# LINE 35 "src/Database/Dpi/Internal.chs" #-}

data DeqNavigation = DeqNavFirstMsg
                   | DeqNavNextTransaction
                   | DeqNavNextMsg
  deriving (Eq,Show)
instance Enum DeqNavigation where
  succ DeqNavFirstMsg = DeqNavNextTransaction
  succ DeqNavNextTransaction = DeqNavNextMsg
  succ DeqNavNextMsg = error "DeqNavigation.succ: DeqNavNextMsg has no successor"

  pred DeqNavNextTransaction = DeqNavFirstMsg
  pred DeqNavNextMsg = DeqNavNextTransaction
  pred DeqNavFirstMsg = error "DeqNavigation.pred: DeqNavFirstMsg has no predecessor"

  enumFromTo from to = go from
    where
      end = fromEnum to
      go v = case compare (fromEnum v) end of
                 LT -> v : go (succ v)
                 EQ -> [v]
                 GT -> []

  enumFrom from = enumFromTo from DeqNavNextMsg

  fromEnum DeqNavFirstMsg = 1
  fromEnum DeqNavNextTransaction = 2
  fromEnum DeqNavNextMsg = 3

  toEnum 1 = DeqNavFirstMsg
  toEnum 2 = DeqNavNextTransaction
  toEnum 3 = DeqNavNextMsg
  toEnum unmatched = error ("DeqNavigation.toEnum: Cannot match " ++ show unmatched)

{-# LINE 36 "src/Database/Dpi/Internal.chs" #-}

data EventType = EventNone
               | EventStartup
               | EventShutdown
               | EventShutdownAny
               | EventDropDb
               | EventDereg
               | EventObjchange
               | EventQuerychange
               | EventAq
  deriving (Eq,Show)
instance Enum EventType where
  succ EventNone = EventStartup
  succ EventStartup = EventShutdown
  succ EventShutdown = EventShutdownAny
  succ EventShutdownAny = EventDropDb
  succ EventDropDb = EventDereg
  succ EventDereg = EventObjchange
  succ EventObjchange = EventQuerychange
  succ EventQuerychange = EventAq
  succ EventAq = error "EventType.succ: EventAq has no successor"

  pred EventStartup = EventNone
  pred EventShutdown = EventStartup
  pred EventShutdownAny = EventShutdown
  pred EventDropDb = EventShutdownAny
  pred EventDereg = EventDropDb
  pred EventObjchange = EventDereg
  pred EventQuerychange = EventObjchange
  pred EventAq = EventQuerychange
  pred EventNone = error "EventType.pred: EventNone has no predecessor"

  enumFromTo from to = go from
    where
      end = fromEnum to
      go v = case compare (fromEnum v) end of
                 LT -> v : go (succ v)
                 EQ -> [v]
                 GT -> []

  enumFrom from = enumFromTo from EventAq

  fromEnum EventNone = 0
  fromEnum EventStartup = 1
  fromEnum EventShutdown = 2
  fromEnum EventShutdownAny = 3
  fromEnum EventDropDb = 4
  fromEnum EventDereg = 5
  fromEnum EventObjchange = 6
  fromEnum EventQuerychange = 7
  fromEnum EventAq = 100

  toEnum 0 = EventNone
  toEnum 1 = EventStartup
  toEnum 2 = EventShutdown
  toEnum 3 = EventShutdownAny
  toEnum 4 = EventDropDb
  toEnum 5 = EventDereg
  toEnum 6 = EventObjchange
  toEnum 7 = EventQuerychange
  toEnum 100 = EventAq
  toEnum unmatched = error ("EventType.toEnum: Cannot match " ++ show unmatched)

{-# LINE 37 "src/Database/Dpi/Internal.chs" #-}

data ExecMode = ModeExecDefault
              | ModeExecDescribeOnly
              | ModeExecCommitOnSuccess
              | ModeExecBatchErrors
              | ModeExecParseOnly
              | ModeExecArrayDmlRowcounts
  deriving (Eq,Show)
instance Enum ExecMode where
  succ ModeExecDefault = ModeExecDescribeOnly
  succ ModeExecDescribeOnly = ModeExecCommitOnSuccess
  succ ModeExecCommitOnSuccess = ModeExecBatchErrors
  succ ModeExecBatchErrors = ModeExecParseOnly
  succ ModeExecParseOnly = ModeExecArrayDmlRowcounts
  succ ModeExecArrayDmlRowcounts = error "ExecMode.succ: ModeExecArrayDmlRowcounts has no successor"

  pred ModeExecDescribeOnly = ModeExecDefault
  pred ModeExecCommitOnSuccess = ModeExecDescribeOnly
  pred ModeExecBatchErrors = ModeExecCommitOnSuccess
  pred ModeExecParseOnly = ModeExecBatchErrors
  pred ModeExecArrayDmlRowcounts = ModeExecParseOnly
  pred ModeExecDefault = error "ExecMode.pred: ModeExecDefault has no predecessor"

  enumFromTo from to = go from
    where
      end = fromEnum to
      go v = case compare (fromEnum v) end of
                 LT -> v : go (succ v)
                 EQ -> [v]
                 GT -> []

  enumFrom from = enumFromTo from ModeExecArrayDmlRowcounts

  fromEnum ModeExecDefault = 0
  fromEnum ModeExecDescribeOnly = 16
  fromEnum ModeExecCommitOnSuccess = 32
  fromEnum ModeExecBatchErrors = 128
  fromEnum ModeExecParseOnly = 256
  fromEnum ModeExecArrayDmlRowcounts = 1048576

  toEnum 0 = ModeExecDefault
  toEnum 16 = ModeExecDescribeOnly
  toEnum 32 = ModeExecCommitOnSuccess
  toEnum 128 = ModeExecBatchErrors
  toEnum 256 = ModeExecParseOnly
  toEnum 1048576 = ModeExecArrayDmlRowcounts
  toEnum unmatched = error ("ExecMode.toEnum: Cannot match " ++ show unmatched)

{-# LINE 38 "src/Database/Dpi/Internal.chs" #-}

data FetchMode = ModeFetchNext
               | ModeFetchFirst
               | ModeFetchLast
               | ModeFetchPrior
               | ModeFetchAbsolute
               | ModeFetchRelative
  deriving (Eq,Show)
instance Enum FetchMode where
  succ ModeFetchNext = ModeFetchFirst
  succ ModeFetchFirst = ModeFetchLast
  succ ModeFetchLast = ModeFetchPrior
  succ ModeFetchPrior = ModeFetchAbsolute
  succ ModeFetchAbsolute = ModeFetchRelative
  succ ModeFetchRelative = error "FetchMode.succ: ModeFetchRelative has no successor"

  pred ModeFetchFirst = ModeFetchNext
  pred ModeFetchLast = ModeFetchFirst
  pred ModeFetchPrior = ModeFetchLast
  pred ModeFetchAbsolute = ModeFetchPrior
  pred ModeFetchRelative = ModeFetchAbsolute
  pred ModeFetchNext = error "FetchMode.pred: ModeFetchNext has no predecessor"

  enumFromTo from to = go from
    where
      end = fromEnum to
      go v = case compare (fromEnum v) end of
                 LT -> v : go (succ v)
                 EQ -> [v]
                 GT -> []

  enumFrom from = enumFromTo from ModeFetchRelative

  fromEnum ModeFetchNext = 2
  fromEnum ModeFetchFirst = 4
  fromEnum ModeFetchLast = 8
  fromEnum ModeFetchPrior = 16
  fromEnum ModeFetchAbsolute = 32
  fromEnum ModeFetchRelative = 64

  toEnum 2 = ModeFetchNext
  toEnum 4 = ModeFetchFirst
  toEnum 8 = ModeFetchLast
  toEnum 16 = ModeFetchPrior
  toEnum 32 = ModeFetchAbsolute
  toEnum 64 = ModeFetchRelative
  toEnum unmatched = error ("FetchMode.toEnum: Cannot match " ++ show unmatched)

{-# LINE 39 "src/Database/Dpi/Internal.chs" #-}

data MessageDeliveryMode = ModeMsgPersistent
                         | ModeMsgBuffered
                         | ModeMsgPersistentOrBuffered
  deriving (Eq,Show)
instance Enum MessageDeliveryMode where
  succ ModeMsgPersistent = ModeMsgBuffered
  succ ModeMsgBuffered = ModeMsgPersistentOrBuffered
  succ ModeMsgPersistentOrBuffered = error "MessageDeliveryMode.succ: ModeMsgPersistentOrBuffered has no successor"

  pred ModeMsgBuffered = ModeMsgPersistent
  pred ModeMsgPersistentOrBuffered = ModeMsgBuffered
  pred ModeMsgPersistent = error "MessageDeliveryMode.pred: ModeMsgPersistent has no predecessor"

  enumFromTo from to = go from
    where
      end = fromEnum to
      go v = case compare (fromEnum v) end of
                 LT -> v : go (succ v)
                 EQ -> [v]
                 GT -> []

  enumFrom from = enumFromTo from ModeMsgPersistentOrBuffered

  fromEnum ModeMsgPersistent = 1
  fromEnum ModeMsgBuffered = 2
  fromEnum ModeMsgPersistentOrBuffered = 3

  toEnum 1 = ModeMsgPersistent
  toEnum 2 = ModeMsgBuffered
  toEnum 3 = ModeMsgPersistentOrBuffered
  toEnum unmatched = error ("MessageDeliveryMode.toEnum: Cannot match " ++ show unmatched)

{-# LINE 40 "src/Database/Dpi/Internal.chs" #-}

data MessageState = MsgStateReady
                  | MsgStateWaiting
                  | MsgStateProcessed
                  | MsgStateExpired
  deriving (Eq,Show)
instance Enum MessageState where
  succ MsgStateReady = MsgStateWaiting
  succ MsgStateWaiting = MsgStateProcessed
  succ MsgStateProcessed = MsgStateExpired
  succ MsgStateExpired = error "MessageState.succ: MsgStateExpired has no successor"

  pred MsgStateWaiting = MsgStateReady
  pred MsgStateProcessed = MsgStateWaiting
  pred MsgStateExpired = MsgStateProcessed
  pred MsgStateReady = error "MessageState.pred: MsgStateReady has no predecessor"

  enumFromTo from to = go from
    where
      end = fromEnum to
      go v = case compare (fromEnum v) end of
                 LT -> v : go (succ v)
                 EQ -> [v]
                 GT -> []

  enumFrom from = enumFromTo from MsgStateExpired

  fromEnum MsgStateReady = 0
  fromEnum MsgStateWaiting = 1
  fromEnum MsgStateProcessed = 2
  fromEnum MsgStateExpired = 3

  toEnum 0 = MsgStateReady
  toEnum 1 = MsgStateWaiting
  toEnum 2 = MsgStateProcessed
  toEnum 3 = MsgStateExpired
  toEnum unmatched = error ("MessageState.toEnum: Cannot match " ++ show unmatched)

{-# LINE 41 "src/Database/Dpi/Internal.chs" #-}

data NativeTypeNum = NativeTypeInt64
                   | NativeTypeUint64
                   | NativeTypeFloat
                   | NativeTypeDouble
                   | NativeTypeBytes
                   | NativeTypeTimestamp
                   | NativeTypeIntervalDs
                   | NativeTypeIntervalYm
                   | NativeTypeLob
                   | NativeTypeObject
                   | NativeTypeStmt
                   | NativeTypeBoolean
                   | NativeTypeRowid
  deriving (Eq,Show)
instance Enum NativeTypeNum where
  succ NativeTypeInt64 = NativeTypeUint64
  succ NativeTypeUint64 = NativeTypeFloat
  succ NativeTypeFloat = NativeTypeDouble
  succ NativeTypeDouble = NativeTypeBytes
  succ NativeTypeBytes = NativeTypeTimestamp
  succ NativeTypeTimestamp = NativeTypeIntervalDs
  succ NativeTypeIntervalDs = NativeTypeIntervalYm
  succ NativeTypeIntervalYm = NativeTypeLob
  succ NativeTypeLob = NativeTypeObject
  succ NativeTypeObject = NativeTypeStmt
  succ NativeTypeStmt = NativeTypeBoolean
  succ NativeTypeBoolean = NativeTypeRowid
  succ NativeTypeRowid = error "NativeTypeNum.succ: NativeTypeRowid has no successor"

  pred NativeTypeUint64 = NativeTypeInt64
  pred NativeTypeFloat = NativeTypeUint64
  pred NativeTypeDouble = NativeTypeFloat
  pred NativeTypeBytes = NativeTypeDouble
  pred NativeTypeTimestamp = NativeTypeBytes
  pred NativeTypeIntervalDs = NativeTypeTimestamp
  pred NativeTypeIntervalYm = NativeTypeIntervalDs
  pred NativeTypeLob = NativeTypeIntervalYm
  pred NativeTypeObject = NativeTypeLob
  pred NativeTypeStmt = NativeTypeObject
  pred NativeTypeBoolean = NativeTypeStmt
  pred NativeTypeRowid = NativeTypeBoolean
  pred NativeTypeInt64 = error "NativeTypeNum.pred: NativeTypeInt64 has no predecessor"

  enumFromTo from to = go from
    where
      end = fromEnum to
      go v = case compare (fromEnum v) end of
                 LT -> v : go (succ v)
                 EQ -> [v]
                 GT -> []

  enumFrom from = enumFromTo from NativeTypeRowid

  fromEnum NativeTypeInt64 = 3000
  fromEnum NativeTypeUint64 = 3001
  fromEnum NativeTypeFloat = 3002
  fromEnum NativeTypeDouble = 3003
  fromEnum NativeTypeBytes = 3004
  fromEnum NativeTypeTimestamp = 3005
  fromEnum NativeTypeIntervalDs = 3006
  fromEnum NativeTypeIntervalYm = 3007
  fromEnum NativeTypeLob = 3008
  fromEnum NativeTypeObject = 3009
  fromEnum NativeTypeStmt = 3010
  fromEnum NativeTypeBoolean = 3011
  fromEnum NativeTypeRowid = 3012

  toEnum 3000 = NativeTypeInt64
  toEnum 3001 = NativeTypeUint64
  toEnum 3002 = NativeTypeFloat
  toEnum 3003 = NativeTypeDouble
  toEnum 3004 = NativeTypeBytes
  toEnum 3005 = NativeTypeTimestamp
  toEnum 3006 = NativeTypeIntervalDs
  toEnum 3007 = NativeTypeIntervalYm
  toEnum 3008 = NativeTypeLob
  toEnum 3009 = NativeTypeObject
  toEnum 3010 = NativeTypeStmt
  toEnum 3011 = NativeTypeBoolean
  toEnum 3012 = NativeTypeRowid
  toEnum unmatched = error ("NativeTypeNum.toEnum: Cannot match " ++ show unmatched)

{-# LINE 42 "src/Database/Dpi/Internal.chs" #-}

data OpCode = OpcodeAllOps
            | OpcodeAllRows
            | OpcodeInsert
            | OpcodeUpdate
            | OpcodeDelete
            | OpcodeAlter
            | OpcodeDrop
            | OpcodeUnknown
  deriving (Eq,Show)
instance Enum OpCode where
  succ OpcodeAllOps = OpcodeAllRows
  succ OpcodeAllRows = OpcodeInsert
  succ OpcodeInsert = OpcodeUpdate
  succ OpcodeUpdate = OpcodeDelete
  succ OpcodeDelete = OpcodeAlter
  succ OpcodeAlter = OpcodeDrop
  succ OpcodeDrop = OpcodeUnknown
  succ OpcodeUnknown = error "OpCode.succ: OpcodeUnknown has no successor"

  pred OpcodeAllRows = OpcodeAllOps
  pred OpcodeInsert = OpcodeAllRows
  pred OpcodeUpdate = OpcodeInsert
  pred OpcodeDelete = OpcodeUpdate
  pred OpcodeAlter = OpcodeDelete
  pred OpcodeDrop = OpcodeAlter
  pred OpcodeUnknown = OpcodeDrop
  pred OpcodeAllOps = error "OpCode.pred: OpcodeAllOps has no predecessor"

  enumFromTo from to = go from
    where
      end = fromEnum to
      go v = case compare (fromEnum v) end of
                 LT -> v : go (succ v)
                 EQ -> [v]
                 GT -> []

  enumFrom from = enumFromTo from OpcodeUnknown

  fromEnum OpcodeAllOps = 0
  fromEnum OpcodeAllRows = 1
  fromEnum OpcodeInsert = 2
  fromEnum OpcodeUpdate = 4
  fromEnum OpcodeDelete = 8
  fromEnum OpcodeAlter = 16
  fromEnum OpcodeDrop = 32
  fromEnum OpcodeUnknown = 64

  toEnum 0 = OpcodeAllOps
  toEnum 1 = OpcodeAllRows
  toEnum 2 = OpcodeInsert
  toEnum 4 = OpcodeUpdate
  toEnum 8 = OpcodeDelete
  toEnum 16 = OpcodeAlter
  toEnum 32 = OpcodeDrop
  toEnum 64 = OpcodeUnknown
  toEnum unmatched = error ("OpCode.toEnum: Cannot match " ++ show unmatched)

{-# LINE 43 "src/Database/Dpi/Internal.chs" #-}

data OracleTypeNum = OracleTypeNone
                   | OracleTypeVarchar
                   | OracleTypeNvarchar
                   | OracleTypeChar
                   | OracleTypeNchar
                   | OracleTypeRowid
                   | OracleTypeRaw
                   | OracleTypeNativeFloat
                   | OracleTypeNativeDouble
                   | OracleTypeNativeInt
                   | OracleTypeNumber
                   | OracleTypeDate
                   | OracleTypeTimestamp
                   | OracleTypeTimestampTz
                   | OracleTypeTimestampLtz
                   | OracleTypeIntervalDs
                   | OracleTypeIntervalYm
                   | OracleTypeClob
                   | OracleTypeNclob
                   | OracleTypeBlob
                   | OracleTypeBfile
                   | OracleTypeStmt
                   | OracleTypeBoolean
                   | OracleTypeObject
                   | OracleTypeLongVarchar
                   | OracleTypeLongRaw
                   | OracleTypeNativeUint
                   | OracleTypeMax
  deriving (Eq,Show)
instance Enum OracleTypeNum where
  succ OracleTypeNone = OracleTypeVarchar
  succ OracleTypeVarchar = OracleTypeNvarchar
  succ OracleTypeNvarchar = OracleTypeChar
  succ OracleTypeChar = OracleTypeNchar
  succ OracleTypeNchar = OracleTypeRowid
  succ OracleTypeRowid = OracleTypeRaw
  succ OracleTypeRaw = OracleTypeNativeFloat
  succ OracleTypeNativeFloat = OracleTypeNativeDouble
  succ OracleTypeNativeDouble = OracleTypeNativeInt
  succ OracleTypeNativeInt = OracleTypeNumber
  succ OracleTypeNumber = OracleTypeDate
  succ OracleTypeDate = OracleTypeTimestamp
  succ OracleTypeTimestamp = OracleTypeTimestampTz
  succ OracleTypeTimestampTz = OracleTypeTimestampLtz
  succ OracleTypeTimestampLtz = OracleTypeIntervalDs
  succ OracleTypeIntervalDs = OracleTypeIntervalYm
  succ OracleTypeIntervalYm = OracleTypeClob
  succ OracleTypeClob = OracleTypeNclob
  succ OracleTypeNclob = OracleTypeBlob
  succ OracleTypeBlob = OracleTypeBfile
  succ OracleTypeBfile = OracleTypeStmt
  succ OracleTypeStmt = OracleTypeBoolean
  succ OracleTypeBoolean = OracleTypeObject
  succ OracleTypeObject = OracleTypeLongVarchar
  succ OracleTypeLongVarchar = OracleTypeLongRaw
  succ OracleTypeLongRaw = OracleTypeNativeUint
  succ OracleTypeNativeUint = OracleTypeMax
  succ OracleTypeMax = error "OracleTypeNum.succ: OracleTypeMax has no successor"

  pred OracleTypeVarchar = OracleTypeNone
  pred OracleTypeNvarchar = OracleTypeVarchar
  pred OracleTypeChar = OracleTypeNvarchar
  pred OracleTypeNchar = OracleTypeChar
  pred OracleTypeRowid = OracleTypeNchar
  pred OracleTypeRaw = OracleTypeRowid
  pred OracleTypeNativeFloat = OracleTypeRaw
  pred OracleTypeNativeDouble = OracleTypeNativeFloat
  pred OracleTypeNativeInt = OracleTypeNativeDouble
  pred OracleTypeNumber = OracleTypeNativeInt
  pred OracleTypeDate = OracleTypeNumber
  pred OracleTypeTimestamp = OracleTypeDate
  pred OracleTypeTimestampTz = OracleTypeTimestamp
  pred OracleTypeTimestampLtz = OracleTypeTimestampTz
  pred OracleTypeIntervalDs = OracleTypeTimestampLtz
  pred OracleTypeIntervalYm = OracleTypeIntervalDs
  pred OracleTypeClob = OracleTypeIntervalYm
  pred OracleTypeNclob = OracleTypeClob
  pred OracleTypeBlob = OracleTypeNclob
  pred OracleTypeBfile = OracleTypeBlob
  pred OracleTypeStmt = OracleTypeBfile
  pred OracleTypeBoolean = OracleTypeStmt
  pred OracleTypeObject = OracleTypeBoolean
  pred OracleTypeLongVarchar = OracleTypeObject
  pred OracleTypeLongRaw = OracleTypeLongVarchar
  pred OracleTypeNativeUint = OracleTypeLongRaw
  pred OracleTypeMax = OracleTypeNativeUint
  pred OracleTypeNone = error "OracleTypeNum.pred: OracleTypeNone has no predecessor"

  enumFromTo from to = go from
    where
      end = fromEnum to
      go v = case compare (fromEnum v) end of
                 LT -> v : go (succ v)
                 EQ -> [v]
                 GT -> []

  enumFrom from = enumFromTo from OracleTypeMax

  fromEnum OracleTypeNone = 2000
  fromEnum OracleTypeVarchar = 2001
  fromEnum OracleTypeNvarchar = 2002
  fromEnum OracleTypeChar = 2003
  fromEnum OracleTypeNchar = 2004
  fromEnum OracleTypeRowid = 2005
  fromEnum OracleTypeRaw = 2006
  fromEnum OracleTypeNativeFloat = 2007
  fromEnum OracleTypeNativeDouble = 2008
  fromEnum OracleTypeNativeInt = 2009
  fromEnum OracleTypeNumber = 2010
  fromEnum OracleTypeDate = 2011
  fromEnum OracleTypeTimestamp = 2012
  fromEnum OracleTypeTimestampTz = 2013
  fromEnum OracleTypeTimestampLtz = 2014
  fromEnum OracleTypeIntervalDs = 2015
  fromEnum OracleTypeIntervalYm = 2016
  fromEnum OracleTypeClob = 2017
  fromEnum OracleTypeNclob = 2018
  fromEnum OracleTypeBlob = 2019
  fromEnum OracleTypeBfile = 2020
  fromEnum OracleTypeStmt = 2021
  fromEnum OracleTypeBoolean = 2022
  fromEnum OracleTypeObject = 2023
  fromEnum OracleTypeLongVarchar = 2024
  fromEnum OracleTypeLongRaw = 2025
  fromEnum OracleTypeNativeUint = 2026
  fromEnum OracleTypeMax = 2027

  toEnum 2000 = OracleTypeNone
  toEnum 2001 = OracleTypeVarchar
  toEnum 2002 = OracleTypeNvarchar
  toEnum 2003 = OracleTypeChar
  toEnum 2004 = OracleTypeNchar
  toEnum 2005 = OracleTypeRowid
  toEnum 2006 = OracleTypeRaw
  toEnum 2007 = OracleTypeNativeFloat
  toEnum 2008 = OracleTypeNativeDouble
  toEnum 2009 = OracleTypeNativeInt
  toEnum 2010 = OracleTypeNumber
  toEnum 2011 = OracleTypeDate
  toEnum 2012 = OracleTypeTimestamp
  toEnum 2013 = OracleTypeTimestampTz
  toEnum 2014 = OracleTypeTimestampLtz
  toEnum 2015 = OracleTypeIntervalDs
  toEnum 2016 = OracleTypeIntervalYm
  toEnum 2017 = OracleTypeClob
  toEnum 2018 = OracleTypeNclob
  toEnum 2019 = OracleTypeBlob
  toEnum 2020 = OracleTypeBfile
  toEnum 2021 = OracleTypeStmt
  toEnum 2022 = OracleTypeBoolean
  toEnum 2023 = OracleTypeObject
  toEnum 2024 = OracleTypeLongVarchar
  toEnum 2025 = OracleTypeLongRaw
  toEnum 2026 = OracleTypeNativeUint
  toEnum 2027 = OracleTypeMax
  toEnum unmatched = error ("OracleTypeNum.toEnum: Cannot match " ++ show unmatched)

{-# LINE 44 "src/Database/Dpi/Internal.chs" #-}

data PoolCloseMode = ModePoolCloseDefault
                   | ModePoolCloseForce
  deriving (Eq,Show)
instance Enum PoolCloseMode where
  succ ModePoolCloseDefault = ModePoolCloseForce
  succ ModePoolCloseForce = error "PoolCloseMode.succ: ModePoolCloseForce has no successor"

  pred ModePoolCloseForce = ModePoolCloseDefault
  pred ModePoolCloseDefault = error "PoolCloseMode.pred: ModePoolCloseDefault has no predecessor"

  enumFromTo from to = go from
    where
      end = fromEnum to
      go v = case compare (fromEnum v) end of
                 LT -> v : go (succ v)
                 EQ -> [v]
                 GT -> []

  enumFrom from = enumFromTo from ModePoolCloseForce

  fromEnum ModePoolCloseDefault = 0
  fromEnum ModePoolCloseForce = 1

  toEnum 0 = ModePoolCloseDefault
  toEnum 1 = ModePoolCloseForce
  toEnum unmatched = error ("PoolCloseMode.toEnum: Cannot match " ++ show unmatched)

{-# LINE 45 "src/Database/Dpi/Internal.chs" #-}

data PoolGetMode = ModePoolGetWait
                 | ModePoolGetNowait
                 | ModePoolGetForceget
                 | ModePoolGetTimedwait
  deriving (Eq,Show)
instance Enum PoolGetMode where
  succ ModePoolGetWait = ModePoolGetNowait
  succ ModePoolGetNowait = ModePoolGetForceget
  succ ModePoolGetForceget = ModePoolGetTimedwait
  succ ModePoolGetTimedwait = error "PoolGetMode.succ: ModePoolGetTimedwait has no successor"

  pred ModePoolGetNowait = ModePoolGetWait
  pred ModePoolGetForceget = ModePoolGetNowait
  pred ModePoolGetTimedwait = ModePoolGetForceget
  pred ModePoolGetWait = error "PoolGetMode.pred: ModePoolGetWait has no predecessor"

  enumFromTo from to = go from
    where
      end = fromEnum to
      go v = case compare (fromEnum v) end of
                 LT -> v : go (succ v)
                 EQ -> [v]
                 GT -> []

  enumFrom from = enumFromTo from ModePoolGetTimedwait

  fromEnum ModePoolGetWait = 0
  fromEnum ModePoolGetNowait = 1
  fromEnum ModePoolGetForceget = 2
  fromEnum ModePoolGetTimedwait = 3

  toEnum 0 = ModePoolGetWait
  toEnum 1 = ModePoolGetNowait
  toEnum 2 = ModePoolGetForceget
  toEnum 3 = ModePoolGetTimedwait
  toEnum unmatched = error ("PoolGetMode.toEnum: Cannot match " ++ show unmatched)

{-# LINE 46 "src/Database/Dpi/Internal.chs" #-}

data Purity = PurityDefault
            | PurityNew
            | PuritySelf
  deriving (Eq,Show)
instance Enum Purity where
  succ PurityDefault = PurityNew
  succ PurityNew = PuritySelf
  succ PuritySelf = error "Purity.succ: PuritySelf has no successor"

  pred PurityNew = PurityDefault
  pred PuritySelf = PurityNew
  pred PurityDefault = error "Purity.pred: PurityDefault has no predecessor"

  enumFromTo from to = go from
    where
      end = fromEnum to
      go v = case compare (fromEnum v) end of
                 LT -> v : go (succ v)
                 EQ -> [v]
                 GT -> []

  enumFrom from = enumFromTo from PuritySelf

  fromEnum PurityDefault = 0
  fromEnum PurityNew = 1
  fromEnum PuritySelf = 2

  toEnum 0 = PurityDefault
  toEnum 1 = PurityNew
  toEnum 2 = PuritySelf
  toEnum unmatched = error ("Purity.toEnum: Cannot match " ++ show unmatched)

{-# LINE 47 "src/Database/Dpi/Internal.chs" #-}

data ShutdownMode = ModeShutdownDefault
                  | ModeShutdownTransactional
                  | ModeShutdownTransactionalLocal
                  | ModeShutdownImmediate
                  | ModeShutdownAbort
                  | ModeShutdownFinal
  deriving (Eq,Show)
instance Enum ShutdownMode where
  succ ModeShutdownDefault = ModeShutdownTransactional
  succ ModeShutdownTransactional = ModeShutdownTransactionalLocal
  succ ModeShutdownTransactionalLocal = ModeShutdownImmediate
  succ ModeShutdownImmediate = ModeShutdownAbort
  succ ModeShutdownAbort = ModeShutdownFinal
  succ ModeShutdownFinal = error "ShutdownMode.succ: ModeShutdownFinal has no successor"

  pred ModeShutdownTransactional = ModeShutdownDefault
  pred ModeShutdownTransactionalLocal = ModeShutdownTransactional
  pred ModeShutdownImmediate = ModeShutdownTransactionalLocal
  pred ModeShutdownAbort = ModeShutdownImmediate
  pred ModeShutdownFinal = ModeShutdownAbort
  pred ModeShutdownDefault = error "ShutdownMode.pred: ModeShutdownDefault has no predecessor"

  enumFromTo from to = go from
    where
      end = fromEnum to
      go v = case compare (fromEnum v) end of
                 LT -> v : go (succ v)
                 EQ -> [v]
                 GT -> []

  enumFrom from = enumFromTo from ModeShutdownFinal

  fromEnum ModeShutdownDefault = 0
  fromEnum ModeShutdownTransactional = 1
  fromEnum ModeShutdownTransactionalLocal = 2
  fromEnum ModeShutdownImmediate = 3
  fromEnum ModeShutdownAbort = 4
  fromEnum ModeShutdownFinal = 5

  toEnum 0 = ModeShutdownDefault
  toEnum 1 = ModeShutdownTransactional
  toEnum 2 = ModeShutdownTransactionalLocal
  toEnum 3 = ModeShutdownImmediate
  toEnum 4 = ModeShutdownAbort
  toEnum 5 = ModeShutdownFinal
  toEnum unmatched = error ("ShutdownMode.toEnum: Cannot match " ++ show unmatched)

{-# LINE 48 "src/Database/Dpi/Internal.chs" #-}

data StartupMode = ModeStartupDefault
                 | ModeStartupForce
                 | ModeStartupRestrict
  deriving (Eq,Show)
instance Enum StartupMode where
  succ ModeStartupDefault = ModeStartupForce
  succ ModeStartupForce = ModeStartupRestrict
  succ ModeStartupRestrict = error "StartupMode.succ: ModeStartupRestrict has no successor"

  pred ModeStartupForce = ModeStartupDefault
  pred ModeStartupRestrict = ModeStartupForce
  pred ModeStartupDefault = error "StartupMode.pred: ModeStartupDefault has no predecessor"

  enumFromTo from to = go from
    where
      end = fromEnum to
      go v = case compare (fromEnum v) end of
                 LT -> v : go (succ v)
                 EQ -> [v]
                 GT -> []

  enumFrom from = enumFromTo from ModeStartupRestrict

  fromEnum ModeStartupDefault = 0
  fromEnum ModeStartupForce = 1
  fromEnum ModeStartupRestrict = 2

  toEnum 0 = ModeStartupDefault
  toEnum 1 = ModeStartupForce
  toEnum 2 = ModeStartupRestrict
  toEnum unmatched = error ("StartupMode.toEnum: Cannot match " ++ show unmatched)

{-# LINE 49 "src/Database/Dpi/Internal.chs" #-}

data StatementType = StmtTypeUnknown
                   | StmtTypeSelect
                   | StmtTypeUpdate
                   | StmtTypeDelete
                   | StmtTypeInsert
                   | StmtTypeCreate
                   | StmtTypeDrop
                   | StmtTypeAlter
                   | StmtTypeBegin
                   | StmtTypeDeclare
                   | StmtTypeCall
                   | StmtTypeExplainPlan
                   | StmtTypeMerge
                   | StmtTypeRollback
                   | StmtTypeCommit
  deriving (Eq,Show)
instance Enum StatementType where
  succ StmtTypeUnknown = StmtTypeSelect
  succ StmtTypeSelect = StmtTypeUpdate
  succ StmtTypeUpdate = StmtTypeDelete
  succ StmtTypeDelete = StmtTypeInsert
  succ StmtTypeInsert = StmtTypeCreate
  succ StmtTypeCreate = StmtTypeDrop
  succ StmtTypeDrop = StmtTypeAlter
  succ StmtTypeAlter = StmtTypeBegin
  succ StmtTypeBegin = StmtTypeDeclare
  succ StmtTypeDeclare = StmtTypeCall
  succ StmtTypeCall = StmtTypeExplainPlan
  succ StmtTypeExplainPlan = StmtTypeMerge
  succ StmtTypeMerge = StmtTypeRollback
  succ StmtTypeRollback = StmtTypeCommit
  succ StmtTypeCommit = error "StatementType.succ: StmtTypeCommit has no successor"

  pred StmtTypeSelect = StmtTypeUnknown
  pred StmtTypeUpdate = StmtTypeSelect
  pred StmtTypeDelete = StmtTypeUpdate
  pred StmtTypeInsert = StmtTypeDelete
  pred StmtTypeCreate = StmtTypeInsert
  pred StmtTypeDrop = StmtTypeCreate
  pred StmtTypeAlter = StmtTypeDrop
  pred StmtTypeBegin = StmtTypeAlter
  pred StmtTypeDeclare = StmtTypeBegin
  pred StmtTypeCall = StmtTypeDeclare
  pred StmtTypeExplainPlan = StmtTypeCall
  pred StmtTypeMerge = StmtTypeExplainPlan
  pred StmtTypeRollback = StmtTypeMerge
  pred StmtTypeCommit = StmtTypeRollback
  pred StmtTypeUnknown = error "StatementType.pred: StmtTypeUnknown has no predecessor"

  enumFromTo from to = go from
    where
      end = fromEnum to
      go v = case compare (fromEnum v) end of
                 LT -> v : go (succ v)
                 EQ -> [v]
                 GT -> []

  enumFrom from = enumFromTo from StmtTypeCommit

  fromEnum StmtTypeUnknown = 0
  fromEnum StmtTypeSelect = 1
  fromEnum StmtTypeUpdate = 2
  fromEnum StmtTypeDelete = 3
  fromEnum StmtTypeInsert = 4
  fromEnum StmtTypeCreate = 5
  fromEnum StmtTypeDrop = 6
  fromEnum StmtTypeAlter = 7
  fromEnum StmtTypeBegin = 8
  fromEnum StmtTypeDeclare = 9
  fromEnum StmtTypeCall = 10
  fromEnum StmtTypeExplainPlan = 15
  fromEnum StmtTypeMerge = 16
  fromEnum StmtTypeRollback = 17
  fromEnum StmtTypeCommit = 21

  toEnum 0 = StmtTypeUnknown
  toEnum 1 = StmtTypeSelect
  toEnum 2 = StmtTypeUpdate
  toEnum 3 = StmtTypeDelete
  toEnum 4 = StmtTypeInsert
  toEnum 5 = StmtTypeCreate
  toEnum 6 = StmtTypeDrop
  toEnum 7 = StmtTypeAlter
  toEnum 8 = StmtTypeBegin
  toEnum 9 = StmtTypeDeclare
  toEnum 10 = StmtTypeCall
  toEnum 15 = StmtTypeExplainPlan
  toEnum 16 = StmtTypeMerge
  toEnum 17 = StmtTypeRollback
  toEnum 21 = StmtTypeCommit
  toEnum unmatched = error ("StatementType.toEnum: Cannot match " ++ show unmatched)

{-# LINE 50 "src/Database/Dpi/Internal.chs" #-}

data SubscrNamespace = SubscrNamespaceAq
                     | SubscrNamespaceDbchange
  deriving (Eq,Show)
instance Enum SubscrNamespace where
  succ SubscrNamespaceAq = SubscrNamespaceDbchange
  succ SubscrNamespaceDbchange = error "SubscrNamespace.succ: SubscrNamespaceDbchange has no successor"

  pred SubscrNamespaceDbchange = SubscrNamespaceAq
  pred SubscrNamespaceAq = error "SubscrNamespace.pred: SubscrNamespaceAq has no predecessor"

  enumFromTo from to = go from
    where
      end = fromEnum to
      go v = case compare (fromEnum v) end of
                 LT -> v : go (succ v)
                 EQ -> [v]
                 GT -> []

  enumFrom from = enumFromTo from SubscrNamespaceDbchange

  fromEnum SubscrNamespaceAq = 1
  fromEnum SubscrNamespaceDbchange = 2

  toEnum 1 = SubscrNamespaceAq
  toEnum 2 = SubscrNamespaceDbchange
  toEnum unmatched = error ("SubscrNamespace.toEnum: Cannot match " ++ show unmatched)

{-# LINE 51 "src/Database/Dpi/Internal.chs" #-}

data SubscrProtocol = SubscrProtoCallback
                    | SubscrProtoMail
                    | SubscrProtoPlsql
                    | SubscrProtoHttp
  deriving (Eq,Show)
instance Enum SubscrProtocol where
  succ SubscrProtoCallback = SubscrProtoMail
  succ SubscrProtoMail = SubscrProtoPlsql
  succ SubscrProtoPlsql = SubscrProtoHttp
  succ SubscrProtoHttp = error "SubscrProtocol.succ: SubscrProtoHttp has no successor"

  pred SubscrProtoMail = SubscrProtoCallback
  pred SubscrProtoPlsql = SubscrProtoMail
  pred SubscrProtoHttp = SubscrProtoPlsql
  pred SubscrProtoCallback = error "SubscrProtocol.pred: SubscrProtoCallback has no predecessor"

  enumFromTo from to = go from
    where
      end = fromEnum to
      go v = case compare (fromEnum v) end of
                 LT -> v : go (succ v)
                 EQ -> [v]
                 GT -> []

  enumFrom from = enumFromTo from SubscrProtoHttp

  fromEnum SubscrProtoCallback = 0
  fromEnum SubscrProtoMail = 1
  fromEnum SubscrProtoPlsql = 2
  fromEnum SubscrProtoHttp = 3

  toEnum 0 = SubscrProtoCallback
  toEnum 1 = SubscrProtoMail
  toEnum 2 = SubscrProtoPlsql
  toEnum 3 = SubscrProtoHttp
  toEnum unmatched = error ("SubscrProtocol.toEnum: Cannot match " ++ show unmatched)

{-# LINE 52 "src/Database/Dpi/Internal.chs" #-}

data SubscrQOS = SubscrQosReliable
               | SubscrQosDeregNfy
               | SubscrQosRowids
               | SubscrQosQuery
               | SubscrQosBestEffort
  deriving (Eq,Show)
instance Enum SubscrQOS where
  succ SubscrQosReliable = SubscrQosDeregNfy
  succ SubscrQosDeregNfy = SubscrQosRowids
  succ SubscrQosRowids = SubscrQosQuery
  succ SubscrQosQuery = SubscrQosBestEffort
  succ SubscrQosBestEffort = error "SubscrQOS.succ: SubscrQosBestEffort has no successor"

  pred SubscrQosDeregNfy = SubscrQosReliable
  pred SubscrQosRowids = SubscrQosDeregNfy
  pred SubscrQosQuery = SubscrQosRowids
  pred SubscrQosBestEffort = SubscrQosQuery
  pred SubscrQosReliable = error "SubscrQOS.pred: SubscrQosReliable has no predecessor"

  enumFromTo from to = go from
    where
      end = fromEnum to
      go v = case compare (fromEnum v) end of
                 LT -> v : go (succ v)
                 EQ -> [v]
                 GT -> []

  enumFrom from = enumFromTo from SubscrQosBestEffort

  fromEnum SubscrQosReliable = 1
  fromEnum SubscrQosDeregNfy = 2
  fromEnum SubscrQosRowids = 4
  fromEnum SubscrQosQuery = 8
  fromEnum SubscrQosBestEffort = 16

  toEnum 1 = SubscrQosReliable
  toEnum 2 = SubscrQosDeregNfy
  toEnum 4 = SubscrQosRowids
  toEnum 8 = SubscrQosQuery
  toEnum 16 = SubscrQosBestEffort
  toEnum unmatched = error ("SubscrQOS.toEnum: Cannot match " ++ show unmatched)

{-# LINE 53 "src/Database/Dpi/Internal.chs" #-}

data Visibility = VisibilityImmediate
                | VisibilityOnCommit
  deriving (Eq,Show)
instance Enum Visibility where
  succ VisibilityImmediate = VisibilityOnCommit
  succ VisibilityOnCommit = error "Visibility.succ: VisibilityOnCommit has no successor"

  pred VisibilityOnCommit = VisibilityImmediate
  pred VisibilityImmediate = error "Visibility.pred: VisibilityImmediate has no predecessor"

  enumFromTo from to = go from
    where
      end = fromEnum to
      go v = case compare (fromEnum v) end of
                 LT -> v : go (succ v)
                 EQ -> [v]
                 GT -> []

  enumFrom from = enumFromTo from VisibilityOnCommit

  fromEnum VisibilityImmediate = 1
  fromEnum VisibilityOnCommit = 2

  toEnum 1 = VisibilityImmediate
  toEnum 2 = VisibilityOnCommit
  toEnum unmatched = error ("Visibility.toEnum: Cannot match " ++ show unmatched)

{-# LINE 54 "src/Database/Dpi/Internal.chs" #-}


-- Handler 
newtype DPI_Conn = DPI_Conn (C2HSImp.ForeignPtr (DPI_Conn))
withDPI_Conn :: DPI_Conn -> (C2HSImp.Ptr DPI_Conn -> IO b) -> IO b
withDPI_Conn (DPI_Conn fptr) = C2HSImp.withForeignPtr fptr
{-# LINE 57 "src/Database/Dpi/Internal.chs" #-}

newtype DPI_Pool = DPI_Pool (C2HSImp.ForeignPtr (DPI_Pool))
withDPI_Pool :: DPI_Pool -> (C2HSImp.Ptr DPI_Pool -> IO b) -> IO b
withDPI_Pool (DPI_Pool fptr) = C2HSImp.withForeignPtr fptr
{-# LINE 58 "src/Database/Dpi/Internal.chs" #-}

newtype DPI_Stmt = DPI_Stmt (C2HSImp.ForeignPtr (DPI_Stmt))
withDPI_Stmt :: DPI_Stmt -> (C2HSImp.Ptr DPI_Stmt -> IO b) -> IO b
withDPI_Stmt (DPI_Stmt fptr) = C2HSImp.withForeignPtr fptr
{-# LINE 59 "src/Database/Dpi/Internal.chs" #-}

newtype DPI_Var = DPI_Var (C2HSImp.ForeignPtr (DPI_Var))
withDPI_Var :: DPI_Var -> (C2HSImp.Ptr DPI_Var -> IO b) -> IO b
withDPI_Var (DPI_Var fptr) = C2HSImp.withForeignPtr fptr
{-# LINE 60 "src/Database/Dpi/Internal.chs" #-}

newtype DPI_Lob = DPI_Lob (C2HSImp.ForeignPtr (DPI_Lob))
withDPI_Lob :: DPI_Lob -> (C2HSImp.Ptr DPI_Lob -> IO b) -> IO b
withDPI_Lob (DPI_Lob fptr) = C2HSImp.withForeignPtr fptr
{-# LINE 61 "src/Database/Dpi/Internal.chs" #-}

newtype DPI_Object = DPI_Object (C2HSImp.ForeignPtr (DPI_Object))
withDPI_Object :: DPI_Object -> (C2HSImp.Ptr DPI_Object -> IO b) -> IO b
withDPI_Object (DPI_Object fptr) = C2HSImp.withForeignPtr fptr
{-# LINE 62 "src/Database/Dpi/Internal.chs" #-}

newtype DPI_ObjectAttr = DPI_ObjectAttr (C2HSImp.ForeignPtr (DPI_ObjectAttr))
withDPI_ObjectAttr :: DPI_ObjectAttr -> (C2HSImp.Ptr DPI_ObjectAttr -> IO b) -> IO b
withDPI_ObjectAttr (DPI_ObjectAttr fptr) = C2HSImp.withForeignPtr fptr
{-# LINE 63 "src/Database/Dpi/Internal.chs" #-}

newtype DPI_ObjectType = DPI_ObjectType (C2HSImp.ForeignPtr (DPI_ObjectType))
withDPI_ObjectType :: DPI_ObjectType -> (C2HSImp.Ptr DPI_ObjectType -> IO b) -> IO b
withDPI_ObjectType (DPI_ObjectType fptr) = C2HSImp.withForeignPtr fptr
{-# LINE 64 "src/Database/Dpi/Internal.chs" #-}

newtype DPI_Rowid = DPI_Rowid (C2HSImp.ForeignPtr (DPI_Rowid))
withDPI_Rowid :: DPI_Rowid -> (C2HSImp.Ptr DPI_Rowid -> IO b) -> IO b
withDPI_Rowid (DPI_Rowid fptr) = C2HSImp.withForeignPtr fptr
{-# LINE 65 "src/Database/Dpi/Internal.chs" #-}

newtype DPI_Subscr = DPI_Subscr (C2HSImp.ForeignPtr (DPI_Subscr))
withDPI_Subscr :: DPI_Subscr -> (C2HSImp.Ptr DPI_Subscr -> IO b) -> IO b
withDPI_Subscr (DPI_Subscr fptr) = C2HSImp.withForeignPtr fptr
{-# LINE 66 "src/Database/Dpi/Internal.chs" #-}

newtype DPI_DeqOptions = DPI_DeqOptions (C2HSImp.ForeignPtr (DPI_DeqOptions))
withDPI_DeqOptions :: DPI_DeqOptions -> (C2HSImp.Ptr DPI_DeqOptions -> IO b) -> IO b
withDPI_DeqOptions (DPI_DeqOptions fptr) = C2HSImp.withForeignPtr fptr
{-# LINE 67 "src/Database/Dpi/Internal.chs" #-}

newtype DPI_EnqOptions = DPI_EnqOptions (C2HSImp.ForeignPtr (DPI_EnqOptions))
withDPI_EnqOptions :: DPI_EnqOptions -> (C2HSImp.Ptr DPI_EnqOptions -> IO b) -> IO b
withDPI_EnqOptions (DPI_EnqOptions fptr) = C2HSImp.withForeignPtr fptr
{-# LINE 68 "src/Database/Dpi/Internal.chs" #-}

newtype DPI_MsgProps = DPI_MsgProps (C2HSImp.ForeignPtr (DPI_MsgProps))
withDPI_MsgProps :: DPI_MsgProps -> (C2HSImp.Ptr DPI_MsgProps -> IO b) -> IO b
withDPI_MsgProps (DPI_MsgProps fptr) = C2HSImp.withForeignPtr fptr
{-# LINE 69 "src/Database/Dpi/Internal.chs" #-}


newtype DPI_Context = DPI_Context (C2HSImp.ForeignPtr (DPI_Context))
withDPI_Context :: DPI_Context -> (C2HSImp.Ptr DPI_Context -> IO b) -> IO b
withDPI_Context (DPI_Context fptr) = C2HSImp.withForeignPtr fptr
{-# LINE 71 "src/Database/Dpi/Internal.chs" #-}


type HasCxtPtr a   = (PtrContext, Ptr a) 
type PtrConn       = HasCxtPtr DPI_Conn
type PtrPool       = HasCxtPtr DPI_Pool
type PtrStmt       = HasCxtPtr DPI_Stmt
type PtrVar        = HasCxtPtr DPI_Var
type PtrLob        = HasCxtPtr DPI_Lob
type PtrObject     = HasCxtPtr DPI_Object
type PtrObjectAttr = HasCxtPtr DPI_ObjectAttr
type PtrObjectType = HasCxtPtr DPI_ObjectType
type PtrRowid      = HasCxtPtr DPI_Rowid
type PtrSubscr     = HasCxtPtr DPI_Subscr
type PtrDeqOptions = HasCxtPtr DPI_DeqOptions
type PtrEnqOptions = HasCxtPtr DPI_EnqOptions
type PtrMsgProps   = HasCxtPtr DPI_MsgProps
type PtrContext    = Ptr DPI_Context

--        Inner               Data
type Ptr_Bytes = C2HSImp.Ptr (Data_Bytes)
{-# LINE 90 "src/Database/Dpi/Internal.chs" #-}

type Ptr_IntervalDS = C2HSImp.Ptr (Data_IntervalDS)
{-# LINE 91 "src/Database/Dpi/Internal.chs" #-}

type Ptr_IntervalYM = C2HSImp.Ptr (Data_IntervalYM)
{-# LINE 92 "src/Database/Dpi/Internal.chs" #-}

type Ptr_Timestamp = C2HSImp.Ptr (Data_Timestamp)
{-# LINE 93 "src/Database/Dpi/Internal.chs" #-}


data Data_Bytes = Data_Bytes
  { bytes    :: L.Text
  , encoding :: Text
  } deriving Show

instance Storable Data_Bytes where
  sizeOf    _ = 24
{-# LINE 101 "src/Database/Dpi/Internal.chs" #-}

  alignment _ = 8
{-# LINE 102 "src/Database/Dpi/Internal.chs" #-}

  poke      _ = noImplement
  peek      p = do
    ptr      <- (\ptr -> do {C2HSImp.peekByteOff ptr 0 :: IO (C2HSImp.Ptr C2HSImp.CChar)}) p
    length   <- (\ptr -> do {C2HSImp.peekByteOff ptr 8 :: IO C2HSImp.CUInt}) p
    encoding <- (\ptr -> do {C2HSImp.peekByteOff ptr 16 :: IO (C2HSImp.Ptr C2HSImp.CChar)}) p >>= tb
    bytes    <- L.pack <$> peekCStringLen (ptr, fromIntegral length)
    return Data_Bytes {..}

data Data_IntervalDS = Data_IntervalDS
  { days     :: !CInt
  , hours    :: !CInt
  , minutes  :: !CInt
  , seconds  :: !CInt
  , fseconds :: !CInt
  } deriving Show

instance Storable Data_IntervalDS where
  sizeOf    _ = 20
{-# LINE 120 "src/Database/Dpi/Internal.chs" #-}

  alignment _ = 4
{-# LINE 121 "src/Database/Dpi/Internal.chs" #-}

  poke      _ = noImplement
  peek      p = do
    days     <- (\ptr -> do {C2HSImp.peekByteOff ptr 0 :: IO C2HSImp.CInt}) p
    hours    <- (\ptr -> do {C2HSImp.peekByteOff ptr 4 :: IO C2HSImp.CInt}) p
    minutes  <- (\ptr -> do {C2HSImp.peekByteOff ptr 8 :: IO C2HSImp.CInt}) p
    seconds  <- (\ptr -> do {C2HSImp.peekByteOff ptr 12 :: IO C2HSImp.CInt}) p
    fseconds <- (\ptr -> do {C2HSImp.peekByteOff ptr 16 :: IO C2HSImp.CInt}) p
    return Data_IntervalDS {..}

data Data_IntervalYM = Data_IntervalYM
  { years    :: !CInt
  , months   :: !CInt
  } deriving Show

instance Storable Data_IntervalYM where
  sizeOf    _ = 8
{-# LINE 137 "src/Database/Dpi/Internal.chs" #-}

  alignment _ = 4
{-# LINE 138 "src/Database/Dpi/Internal.chs" #-}

  poke      _ = noImplement
  peek      p = do
    years    <- (\ptr -> do {C2HSImp.peekByteOff ptr 0 :: IO C2HSImp.CInt}) p
    months   <- (\ptr -> do {C2HSImp.peekByteOff ptr 4 :: IO C2HSImp.CInt}) p
    return Data_IntervalYM {..}

data Data_Timestamp  = Data_Timestamp
  { year           :: !CShort
  , month          :: !CUChar
  , day            :: !CUChar
  , hour           :: !CUChar
  , minute         :: !CUChar
  , second         :: !CUChar
  , fsecond        :: !CUInt
  , tzHourOffset   :: !CSChar
  , tzMinuteOffset :: !CSChar
  } deriving Show

instance Storable Data_Timestamp where
  sizeOf    _ = 16
{-# LINE 158 "src/Database/Dpi/Internal.chs" #-}

  alignment _ = 4
{-# LINE 159 "src/Database/Dpi/Internal.chs" #-}

  poke      _ = noImplement
  peek      p = do
    year           <- (\ptr -> do {C2HSImp.peekByteOff ptr 0 :: IO C2HSImp.CShort}) p
    month          <- (\ptr -> do {C2HSImp.peekByteOff ptr 2 :: IO C2HSImp.CUChar}) p
    day            <- (\ptr -> do {C2HSImp.peekByteOff ptr 3 :: IO C2HSImp.CUChar}) p
    hour           <- (\ptr -> do {C2HSImp.peekByteOff ptr 4 :: IO C2HSImp.CUChar}) p
    minute         <- (\ptr -> do {C2HSImp.peekByteOff ptr 5 :: IO C2HSImp.CUChar}) p
    second         <- (\ptr -> do {C2HSImp.peekByteOff ptr 6 :: IO C2HSImp.CUChar}) p
    fsecond        <- (\ptr -> do {C2HSImp.peekByteOff ptr 8 :: IO C2HSImp.CUInt}) p
    tzHourOffset   <- (\ptr -> do {C2HSImp.peekByteOff ptr 12 :: IO C2HSImp.CSChar}) p
    tzMinuteOffset <- (\ptr -> do {C2HSImp.peekByteOff ptr 13 :: IO C2HSImp.CSChar}) p
    return Data_Timestamp {..}

--        Data
type PtrAppContext = C2HSImp.Ptr (Data_AppContext)
{-# LINE 174 "src/Database/Dpi/Internal.chs" #-}

type PtrCommonCreateParams = C2HSImp.Ptr (Data_CommonCreateParams)
{-# LINE 175 "src/Database/Dpi/Internal.chs" #-}

type PtrConnCreateParams = C2HSImp.Ptr (Data_ConnCreateParams)
{-# LINE 176 "src/Database/Dpi/Internal.chs" #-}

type PtrData = C2HSImp.Ptr (Data)
{-# LINE 177 "src/Database/Dpi/Internal.chs" #-}

type PtrDataTypeInfo = C2HSImp.Ptr (Data_DataTypeInfo)
{-# LINE 178 "src/Database/Dpi/Internal.chs" #-}

type PtrEncodingInfo = C2HSImp.Ptr (Data_EncodingInfo)
{-# LINE 179 "src/Database/Dpi/Internal.chs" #-}

type PtrErrorInfo = C2HSImp.Ptr (Data_ErrorInfo)
{-# LINE 180 "src/Database/Dpi/Internal.chs" #-}

type PtrObjectAttrInfo = C2HSImp.Ptr (Data_ObjectAttrInfo)
{-# LINE 181 "src/Database/Dpi/Internal.chs" #-}

type PtrObjectTypeInfo = C2HSImp.Ptr (Data_ObjectTypeInfo)
{-# LINE 182 "src/Database/Dpi/Internal.chs" #-}

type PtrPoolCreateParams = C2HSImp.Ptr (Data_PoolCreateParams)
{-# LINE 183 "src/Database/Dpi/Internal.chs" #-}

type PtrQueryInfo = C2HSImp.Ptr (Data_QueryInfo)
{-# LINE 184 "src/Database/Dpi/Internal.chs" #-}

type PtrShardingKeyColumn = C2HSImp.Ptr (Data_ShardingKeyColumn)
{-# LINE 185 "src/Database/Dpi/Internal.chs" #-}

type PtrStmtInfo = C2HSImp.Ptr (Data_StmtInfo)
{-# LINE 186 "src/Database/Dpi/Internal.chs" #-}

type PtrSubscrCreateParams = C2HSImp.Ptr (Data_SubscrCreateParams)
{-# LINE 187 "src/Database/Dpi/Internal.chs" #-}

type PtrSubscrMessage = C2HSImp.Ptr (Data_SubscrMessage)
{-# LINE 188 "src/Database/Dpi/Internal.chs" #-}

type PtrSubscrMessageQuery = C2HSImp.Ptr (Data_SubscrMessageQuery)
{-# LINE 189 "src/Database/Dpi/Internal.chs" #-}

type PtrSubscrMessageRow = C2HSImp.Ptr (Data_SubscrMessageRow)
{-# LINE 190 "src/Database/Dpi/Internal.chs" #-}

type PtrSubscrMessageTable = C2HSImp.Ptr (Data_SubscrMessageTable)
{-# LINE 191 "src/Database/Dpi/Internal.chs" #-}

type PtrVersionInfo = C2HSImp.Ptr (Data_VersionInfo)
{-# LINE 192 "src/Database/Dpi/Internal.chs" #-}


data Data_AppContext  = Data_AppContext
  { namespaceName       :: !Text
  , name                :: !Text
  , value               :: !Text
  } deriving Show

instance Storable Data_AppContext where
  sizeOf    _ = 48
{-# LINE 201 "src/Database/Dpi/Internal.chs" #-}

  alignment _ = 8
{-# LINE 202 "src/Database/Dpi/Internal.chs" #-}

  poke      _ = noImplement
  peek      p = do
    namespaceName'      <- (\ptr -> do {C2HSImp.peekByteOff ptr 0 :: IO (C2HSImp.Ptr C2HSImp.CChar)}) p
    namespaceNameLength <- (\ptr -> do {C2HSImp.peekByteOff ptr 8 :: IO C2HSImp.CUInt}) p
    name'               <- (\ptr -> do {C2HSImp.peekByteOff ptr 16 :: IO (C2HSImp.Ptr C2HSImp.CChar)}) p
    nameLength          <- (\ptr -> do {C2HSImp.peekByteOff ptr 24 :: IO C2HSImp.CUInt}) p
    value'              <- (\ptr -> do {C2HSImp.peekByteOff ptr 32 :: IO (C2HSImp.Ptr C2HSImp.CChar)}) p
    valueLength         <- (\ptr -> do {C2HSImp.peekByteOff ptr 40 :: IO C2HSImp.CUInt}) p
    namespaceName <- ts namespaceName' namespaceNameLength
    name          <- ts name'          nameLength
    value         <- ts value'         valueLength
    return Data_AppContext {..}

data Data_CommonCreateParams  = Data_CommonCreateParams
  { createMode       :: !CreateMode
  , encoding         :: !Text
  , nencoding        :: !Text
  , edition          :: !Text
  , driverName       :: !Text
  } deriving Show

instance Storable Data_CommonCreateParams where
  sizeOf    _ = 56
{-# LINE 225 "src/Database/Dpi/Internal.chs" #-}

  alignment _ = 8
{-# LINE 226 "src/Database/Dpi/Internal.chs" #-}

  poke    p Data_CommonCreateParams{..} = do
    pe       <- fs encoding  
    pn       <- fs nencoding 
    (e,elen) <- fb edition   
    (d,dlen) <- fb driverName
    (\ptr val -> do {C2HSImp.pokeByteOff ptr 0 (val :: C2HSImp.CInt)}) p (fe createMode)
    (\ptr val -> do {C2HSImp.pokeByteOff ptr 8 (val :: (C2HSImp.Ptr C2HSImp.CChar))}) p pe
    (\ptr val -> do {C2HSImp.pokeByteOff ptr 16 (val :: (C2HSImp.Ptr C2HSImp.CChar))}) p pn
    (\ptr val -> do {C2HSImp.pokeByteOff ptr 24 (val :: (C2HSImp.Ptr C2HSImp.CChar))}) p e
    (\ptr val -> do {C2HSImp.pokeByteOff ptr 32 (val :: C2HSImp.CUInt)}) p (fromIntegral elen)
    (\ptr val -> do {C2HSImp.pokeByteOff ptr 40 (val :: (C2HSImp.Ptr C2HSImp.CChar))}) p d
    (\ptr val -> do {C2HSImp.pokeByteOff ptr 48 (val :: C2HSImp.CUInt)}) p (fromIntegral dlen)
  peek      p = do
    createMode       <- te <$> (\ptr -> do {C2HSImp.peekByteOff ptr 0 :: IO C2HSImp.CInt}) p
    encoding         <- (\ptr -> do {C2HSImp.peekByteOff ptr 8 :: IO (C2HSImp.Ptr C2HSImp.CChar)}) p >>= tb
    nencoding        <- (\ptr -> do {C2HSImp.peekByteOff ptr 16 :: IO (C2HSImp.Ptr C2HSImp.CChar)}) p >>= tb
    edition'         <- (\ptr -> do {C2HSImp.peekByteOff ptr 24 :: IO (C2HSImp.Ptr C2HSImp.CChar)}) p
    editionLength    <- (\ptr -> do {C2HSImp.peekByteOff ptr 32 :: IO C2HSImp.CUInt}) p
    driverName'      <- (\ptr -> do {C2HSImp.peekByteOff ptr 40 :: IO (C2HSImp.Ptr C2HSImp.CChar)}) p
    driverNameLength <- (\ptr -> do {C2HSImp.peekByteOff ptr 48 :: IO C2HSImp.CUInt}) p
    edition    <- ts edition'    editionLength
    driverName <- ts driverName' driverNameLength
    return Data_CommonCreateParams {..}

data Data_ConnCreateParams  = Data_ConnCreateParams
  { authMode                   :: !AuthMode
  , connectionClass            :: !Text
  , purity                     :: !Purity
  , newPassword                :: !Text
  , appContext                 :: !PtrAppContext
  , numAppContext              :: !CUInt
  , externalAuth               :: !CInt
  , externalHandle             :: !(Ptr ())
  , pool                       :: !(Ptr DPI_Pool)
  , tag                        :: !Text
  , matchAnyTag                :: !CInt
  , outTag                     :: !Text
  , outTagFound                :: !CInt
  , shardingKeyColumns         :: !PtrShardingKeyColumn
  , numShardingKeyColumns      :: !CUChar
  , superShardingKeyColumns    :: !PtrShardingKeyColumn
  , numSuperShardingKeyColumns :: !CUChar
  } deriving Show

instance Storable Data_ConnCreateParams where
  sizeOf    _ = 136
{-# LINE 272 "src/Database/Dpi/Internal.chs" #-}

  alignment _ = 8
{-# LINE 273 "src/Database/Dpi/Internal.chs" #-}

  poke    p Data_ConnCreateParams{..} = do
    (cc,cclen) <- fb connectionClass
    (np,nplen) <- fb newPassword
    (tg,tglen) <- fb tag
    (og,oglen) <- fb outTag
    (\ptr val -> do {C2HSImp.pokeByteOff ptr 0 (val :: C2HSImp.CInt)}) p (fe authMode)                 
    (\ptr val -> do {C2HSImp.pokeByteOff ptr 8 (val :: (C2HSImp.Ptr C2HSImp.CChar))}) p cc           
    (\ptr val -> do {C2HSImp.pokeByteOff ptr 16 (val :: C2HSImp.CUInt)}) p (fromIntegral cclen)     
    (\ptr val -> do {C2HSImp.pokeByteOff ptr 20 (val :: C2HSImp.CInt)}) p (fe purity)                    
    (\ptr val -> do {C2HSImp.pokeByteOff ptr 24 (val :: (C2HSImp.Ptr C2HSImp.CChar))}) p np               
    (\ptr val -> do {C2HSImp.pokeByteOff ptr 32 (val :: C2HSImp.CUInt)}) p (fromIntegral nplen)         
    (\ptr val -> do {C2HSImp.pokeByteOff ptr 40 (val :: (PtrAppContext))}) p appContext                
    (\ptr val -> do {C2HSImp.pokeByteOff ptr 48 (val :: C2HSImp.CUInt)}) p numAppContext             
    (\ptr val -> do {C2HSImp.pokeByteOff ptr 52 (val :: C2HSImp.CInt)}) p externalAuth              
    (\ptr val -> do {C2HSImp.pokeByteOff ptr 56 (val :: (C2HSImp.Ptr ()))}) p externalHandle            
    (\ptr val -> do {C2HSImp.pokeByteOff ptr 64 (val :: (C2HSImp.Ptr (DPI_Pool)))}) p pool                      
    (\ptr val -> do {C2HSImp.pokeByteOff ptr 72 (val :: (C2HSImp.Ptr C2HSImp.CChar))}) p tg                       
    (\ptr val -> do {C2HSImp.pokeByteOff ptr 80 (val :: C2HSImp.CUInt)}) p (fromIntegral tglen)                 
    (\ptr val -> do {C2HSImp.pokeByteOff ptr 84 (val :: C2HSImp.CInt)}) p matchAnyTag               
    (\ptr val -> do {C2HSImp.pokeByteOff ptr 88 (val :: (C2HSImp.Ptr C2HSImp.CChar))}) p og                    
    (\ptr val -> do {C2HSImp.pokeByteOff ptr 96 (val :: C2HSImp.CUInt)}) p (fromIntegral oglen)              
    (\ptr val -> do {C2HSImp.pokeByteOff ptr 100 (val :: C2HSImp.CInt)}) p outTagFound               
    (\ptr val -> do {C2HSImp.pokeByteOff ptr 104 (val :: (PtrShardingKeyColumn))}) p shardingKeyColumns        
    (\ptr val -> do {C2HSImp.pokeByteOff ptr 112 (val :: C2HSImp.CUChar)}) p numShardingKeyColumns     
    (\ptr val -> do {C2HSImp.pokeByteOff ptr 120 (val :: (PtrShardingKeyColumn))}) p superShardingKeyColumns   
    (\ptr val -> do {C2HSImp.pokeByteOff ptr 128 (val :: C2HSImp.CUChar)}) p numSuperShardingKeyColumns
  peek      p = do
    authMode                   <- te <$> (\ptr -> do {C2HSImp.peekByteOff ptr 0 :: IO C2HSImp.CInt}) p
    connectionClass'           <- (\ptr -> do {C2HSImp.peekByteOff ptr 8 :: IO (C2HSImp.Ptr C2HSImp.CChar)}) p
    connectionClassLength      <- (\ptr -> do {C2HSImp.peekByteOff ptr 16 :: IO C2HSImp.CUInt}) p
    purity                     <- te <$> (\ptr -> do {C2HSImp.peekByteOff ptr 20 :: IO C2HSImp.CInt}) p
    newPassword'               <- (\ptr -> do {C2HSImp.peekByteOff ptr 24 :: IO (C2HSImp.Ptr C2HSImp.CChar)}) p
    newPasswordLength          <- (\ptr -> do {C2HSImp.peekByteOff ptr 32 :: IO C2HSImp.CUInt}) p
    appContext                 <- (\ptr -> do {C2HSImp.peekByteOff ptr 40 :: IO (PtrAppContext)}) p
    numAppContext              <- (\ptr -> do {C2HSImp.peekByteOff ptr 48 :: IO C2HSImp.CUInt}) p
    externalAuth               <- (\ptr -> do {C2HSImp.peekByteOff ptr 52 :: IO C2HSImp.CInt}) p
    externalHandle             <- (\ptr -> do {C2HSImp.peekByteOff ptr 56 :: IO (C2HSImp.Ptr ())}) p
    pool                       <- (\ptr -> do {C2HSImp.peekByteOff ptr 64 :: IO (C2HSImp.Ptr (DPI_Pool))}) p
    tag'                       <- (\ptr -> do {C2HSImp.peekByteOff ptr 72 :: IO (C2HSImp.Ptr C2HSImp.CChar)}) p
    tagLength                  <- (\ptr -> do {C2HSImp.peekByteOff ptr 80 :: IO C2HSImp.CUInt}) p
    matchAnyTag                <- (\ptr -> do {C2HSImp.peekByteOff ptr 84 :: IO C2HSImp.CInt}) p
    outTag'                    <- (\ptr -> do {C2HSImp.peekByteOff ptr 88 :: IO (C2HSImp.Ptr C2HSImp.CChar)}) p
    outTagLength               <- (\ptr -> do {C2HSImp.peekByteOff ptr 96 :: IO C2HSImp.CUInt}) p
    outTagFound                <- (\ptr -> do {C2HSImp.peekByteOff ptr 100 :: IO C2HSImp.CInt}) p
    shardingKeyColumns         <- (\ptr -> do {C2HSImp.peekByteOff ptr 104 :: IO (PtrShardingKeyColumn)}) p
    numShardingKeyColumns      <- (\ptr -> do {C2HSImp.peekByteOff ptr 112 :: IO C2HSImp.CUChar}) p
    superShardingKeyColumns    <- (\ptr -> do {C2HSImp.peekByteOff ptr 120 :: IO (PtrShardingKeyColumn)}) p
    numSuperShardingKeyColumns <- (\ptr -> do {C2HSImp.peekByteOff ptr 128 :: IO C2HSImp.CUChar}) p
    connectionClass <- ts connectionClass' connectionClassLength
    newPassword     <- ts newPassword'     newPasswordLength
    tag             <- ts tag'             tagLength
    outTag          <- ts outTag'          outTagLength
    return Data_ConnCreateParams {..}

data DataValue
  = DataNull           !NativeTypeNum
  | DataBFile          !(Ptr DPI_Lob)
  | DataBoolean        !Bool
  | DataBlob           !(Ptr DPI_Lob)
  | DataChar           !Text
  | DataClob           !(Ptr DPI_Lob)
  | DataDate           !UTCTime
  | DataIntervalDs     !DiffTime
  | DataIntervalYm     !Data_IntervalYM
  | DataLongRaw        !Text
  | DataLongVarchar    !Text
  | DataDouble         !CDouble
  | DataFloat          !CFloat
  | DataInt            !Int64
  | DataUint           !Word64
  | DataNChar          !Text
  | DataNClob          !(Ptr DPI_Lob)
  | DataNumDouble      !CDouble
  | DataNumBytes       !Text
  | DataNumInt         !Int64
  | DataNumUint        !Word64
  | DataNVarchar       !Text
  | DataObject         !(Ptr DPI_Object)
  | DataRaw            !Text
  | DataRowid          !(Ptr DPI_Rowid)
  | DataStmt           !(Ptr DPI_Stmt)
  | DataTimestamp      !UTCTime
  | DataTimestampD     !CDouble
  | DataTimestampLtz   !UTCTime
  | DataTimestampLtzD  !CDouble
  | DataTimestampTz    !UTCTime
  | DataTimestampTzD   !CDouble
  | DataVarchar        !Text
  deriving Show

{-# INLINE newData #-}
newData :: DataValue -> IO (NativeTypeNum, OracleTypeNum, PtrData)
newData d = do
  pd <- malloc
  let (tp,ot) = go d
  poke pd (Data $ \_ _ -> return d)
  return (tp, ot, pd)
  where
    {-# INLINE go #-}
    go (DataNull          t) = (t,                    OracleTypeNone         )
    go (DataBFile         _) = (NativeTypeLob,        OracleTypeBfile        )
    go (DataBoolean       _) = (NativeTypeBoolean,    OracleTypeBoolean      )
    go (DataBlob          _) = (NativeTypeLob,        OracleTypeBlob         )
    go (DataChar          _) = (NativeTypeBytes,      OracleTypeChar         )
    go (DataClob          _) = (NativeTypeLob,        OracleTypeClob         )
    go (DataDate          _) = (NativeTypeTimestamp,  OracleTypeDate         )
    go (DataIntervalDs    _) = (NativeTypeIntervalDs, OracleTypeIntervalDs   )
    go (DataIntervalYm    _) = (NativeTypeIntervalYm, OracleTypeIntervalYm   )
    go (DataLongRaw       _) = (NativeTypeBytes,      OracleTypeLongRaw      )
    go (DataLongVarchar   _) = (NativeTypeBytes,      OracleTypeLongVarchar  )
    go (DataDouble        _) = (NativeTypeDouble,     OracleTypeNativeDouble )
    go (DataFloat         _) = (NativeTypeFloat,      OracleTypeNativeFloat  )
    go (DataInt           _) = (NativeTypeInt64,      OracleTypeNativeInt    )
    go (DataUint          _) = (NativeTypeUint64,     OracleTypeNativeUint   )
    go (DataNChar         _) = (NativeTypeBytes,      OracleTypeNchar        )
    go (DataNClob         _) = (NativeTypeLob,        OracleTypeNclob        )
    go (DataNumDouble     _) = (NativeTypeDouble,     OracleTypeNumber       )
    go (DataNumBytes      _) = (NativeTypeBytes,      OracleTypeNumber       )
    go (DataNumInt        _) = (NativeTypeInt64,      OracleTypeNumber       )
    go (DataNumUint       _) = (NativeTypeUint64,     OracleTypeNumber       )
    go (DataNVarchar      _) = (NativeTypeBytes,      OracleTypeNvarchar     )
    go (DataObject        _) = (NativeTypeObject,     OracleTypeObject       )
    go (DataRaw           _) = (NativeTypeBytes,      OracleTypeRaw          )
    go (DataRowid         _) = (NativeTypeRowid,      OracleTypeRowid        )
    go (DataStmt          _) = (NativeTypeStmt,       OracleTypeStmt         )
    go (DataTimestamp     _) = (NativeTypeTimestamp,  OracleTypeTimestamp    )
    go (DataTimestampD    _) = (NativeTypeDouble,     OracleTypeTimestamp    )
    go (DataTimestampLtz  _) = (NativeTypeTimestamp,  OracleTypeTimestampLtz )
    go (DataTimestampLtzD _) = (NativeTypeDouble,     OracleTypeTimestampLtz )
    go (DataTimestampTz   _) = (NativeTypeTimestamp,  OracleTypeTimestampTz  )
    go (DataTimestampTzD  _) = (NativeTypeDouble,     OracleTypeTimestampTz  )
    go (DataVarchar       _) = (NativeTypeBytes,      OracleTypeVarchar      )

newtype Data = Data (NativeTypeNum -> OracleTypeNum -> IO DataValue)

picoResolution :: Integer
picoResolution = 10 ^ 12

instance Storable Data where
  sizeOf    _ = 32
{-# LINE 413 "src/Database/Dpi/Internal.chs" #-}

  alignment _ = 8
{-# LINE 414 "src/Database/Dpi/Internal.chs" #-}

  poke      p (Data f) = do
    f NativeTypeDouble OracleTypeNone >>=  go p
    where
      sLob p1 v1 = (\ptr val -> do {C2HSImp.pokeByteOff ptr 8 (val :: (C2HSImp.Ptr (DPI_Lob)))}) p1 v1
      sByt p2 v2 = do
        (b,bl) <- newCStringLen $ T.unpack v2
        e      <- fs "UTF-8"
        (\ptr val -> do {C2HSImp.pokeByteOff ptr 8 (val :: (C2HSImp.Ptr C2HSImp.CChar))}) p2 b
        (\ptr val -> do {C2HSImp.pokeByteOff ptr 16 (val :: C2HSImp.CUInt)}) p2 (fromIntegral bl)
        (\ptr val -> do {C2HSImp.pokeByteOff ptr 24 (val :: (C2HSImp.Ptr C2HSImp.CChar))}) p2 e
      sTmp p3 UTCTime{..} = do
        let (year, month, day) = toGregorian utctDay
            fs                 = diffTimeToPicoseconds utctDayTime
            (t1,fsecond)       = fs `divMod` picoResolution
            (t2,second)        = t1 `divMod` 60
            (hour,minute)      = t2 `divMod` 60
        (\ptr val -> do {C2HSImp.pokeByteOff ptr 8 (val :: C2HSImp.CShort)}) p3 $ fromIntegral year
        (\ptr val -> do {C2HSImp.pokeByteOff ptr 10 (val :: C2HSImp.CUChar)}) p3 $ fromIntegral month
        (\ptr val -> do {C2HSImp.pokeByteOff ptr 11 (val :: C2HSImp.CUChar)}) p3 $ fromIntegral day
        (\ptr val -> do {C2HSImp.pokeByteOff ptr 12 (val :: C2HSImp.CUChar)}) p3 $ fromIntegral hour
        (\ptr val -> do {C2HSImp.pokeByteOff ptr 13 (val :: C2HSImp.CUChar)}) p3 $ fromIntegral minute
        (\ptr val -> do {C2HSImp.pokeByteOff ptr 14 (val :: C2HSImp.CUChar)}) p3 $ fromIntegral second
        (\ptr val -> do {C2HSImp.pokeByteOff ptr 16 (val :: C2HSImp.CUInt)}) p3 $ fromIntegral fsecond
        (\ptr val -> do {C2HSImp.pokeByteOff ptr 20 (val :: C2HSImp.CSChar)}) p3 0
        (\ptr val -> do {C2HSImp.pokeByteOff ptr 21 (val :: C2HSImp.CSChar)}) p3 0
      go p (DataNull          _) = (\ptr val -> do {C2HSImp.pokeByteOff ptr 0 (val :: C2HSImp.CInt)}) p 1
      go p (DataBFile         v) = sLob p v
      go p (DataBoolean       v) = (\ptr val -> do {C2HSImp.pokeByteOff ptr 8 (val :: C2HSImp.CInt)}) p (fromBool v)
      go p (DataBlob          v) = sLob p v
      go p (DataChar          v) = sByt p v
      go p (DataClob          v) = sLob p v
      go p (DataDate          v) = sTmp p v
      go p (DataIntervalDs    v) = do
        let fs                 = diffTimeToPicoseconds v
            (t1,fseconds)      = fs `divMod` picoResolution
            (t2,seconds)       = t1 `divMod` 60
            (t3,minutes)       = t2 `divMod` 60
            (days,hours)       = t3 `divMod` 24
        (\ptr val -> do {C2HSImp.pokeByteOff ptr 8 (val :: C2HSImp.CInt)}) p $ fromIntegral days    
        (\ptr val -> do {C2HSImp.pokeByteOff ptr 12 (val :: C2HSImp.CInt)}) p $ fromIntegral hours   
        (\ptr val -> do {C2HSImp.pokeByteOff ptr 16 (val :: C2HSImp.CInt)}) p $ fromIntegral minutes 
        (\ptr val -> do {C2HSImp.pokeByteOff ptr 20 (val :: C2HSImp.CInt)}) p $ fromIntegral seconds 
        (\ptr val -> do {C2HSImp.pokeByteOff ptr 24 (val :: C2HSImp.CInt)}) p $ fromIntegral fseconds
      go p (DataIntervalYm    (Data_IntervalYM {..})) = do
        (\ptr val -> do {C2HSImp.pokeByteOff ptr 8 (val :: C2HSImp.CInt)}) p  years 
        (\ptr val -> do {C2HSImp.pokeByteOff ptr 12 (val :: C2HSImp.CInt)}) p  months
      go p (DataLongRaw       v) = sByt p v
      go p (DataLongVarchar   v) = sByt p v
      go p (DataDouble        v) = (\ptr val -> do {C2HSImp.pokeByteOff ptr 8 (val :: C2HSImp.CDouble)}) p v
      go p (DataFloat         v) = (\ptr val -> do {C2HSImp.pokeByteOff ptr 8 (val :: C2HSImp.CFloat)}) p v
      go p (DataInt           v) = (\ptr val -> do {C2HSImp.pokeByteOff ptr 8 (val :: C2HSImp.CLLong)}) p (fromIntegral v)
      go p (DataUint          v) = (\ptr val -> do {C2HSImp.pokeByteOff ptr 8 (val :: C2HSImp.CULLong)}) p (fromIntegral v)
      go p (DataNChar         v) = sByt p v
      go p (DataNClob         v) = sLob p v
      go p (DataNumDouble     v) = (\ptr val -> do {C2HSImp.pokeByteOff ptr 8 (val :: C2HSImp.CDouble)}) p v
      go p (DataNumBytes      v) = sByt p v
      go p (DataNumInt        v) = (\ptr val -> do {C2HSImp.pokeByteOff ptr 8 (val :: C2HSImp.CLLong)}) p (fromIntegral v)
      go p (DataNumUint       v) = (\ptr val -> do {C2HSImp.pokeByteOff ptr 8 (val :: C2HSImp.CULLong)}) p (fromIntegral v)
      go p (DataNVarchar      v) = sByt p v
      go p (DataObject        v) = (\ptr val -> do {C2HSImp.pokeByteOff ptr 8 (val :: (C2HSImp.Ptr (DPI_Object)))})   p  v
      go p (DataRaw           v) = sByt p v
      go p (DataRowid         v) = (\ptr val -> do {C2HSImp.pokeByteOff ptr 8 (val :: (C2HSImp.Ptr (DPI_Rowid)))}) p v
      go p (DataStmt          v) = (\ptr val -> do {C2HSImp.pokeByteOff ptr 8 (val :: (C2HSImp.Ptr (DPI_Stmt)))}) p v
      go p (DataTimestamp     v) = sTmp p v
      go p (DataTimestampD    v) = (\ptr val -> do {C2HSImp.pokeByteOff ptr 8 (val :: C2HSImp.CDouble)}) p v
      go p (DataTimestampLtz  v) = sTmp p v
      go p (DataTimestampLtzD v) = (\ptr val -> do {C2HSImp.pokeByteOff ptr 8 (val :: C2HSImp.CDouble)}) p v
      go p (DataTimestampTz   v) = sTmp p v
      go p (DataTimestampTzD  v) = (\ptr val -> do {C2HSImp.pokeByteOff ptr 8 (val :: C2HSImp.CDouble)}) p v
      go p (DataVarchar       v) = sByt p v
  peek      p = return $ Data $ go p
    where
      go p NativeTypeBoolean    _ = (DataBoolean .toBool)<$> (\ptr -> do {C2HSImp.peekByteOff ptr 8 :: IO C2HSImp.CInt}) p
      go p NativeTypeInt64      o = (gInt o .fromInteger.toInteger) <$> (\ptr -> do {C2HSImp.peekByteOff ptr 8 :: IO C2HSImp.CLLong}) p
      go p NativeTypeUint64     o = (gUnt o .fromInteger.toInteger) <$> (\ptr -> do {C2HSImp.peekByteOff ptr 8 :: IO C2HSImp.CULLong}) p
      go p NativeTypeFloat      _ = DataFloat      <$> (\ptr -> do {C2HSImp.peekByteOff ptr 8 :: IO C2HSImp.CFloat}) p
      go p NativeTypeDouble     _ = DataDouble     <$> (\ptr -> do {C2HSImp.peekByteOff ptr 8 :: IO C2HSImp.CDouble}) p
      go p NativeTypeBytes      o = gByt o         <$> do
        ptr      <- (\ptr -> do {C2HSImp.peekByteOff ptr 8 :: IO (C2HSImp.Ptr C2HSImp.CChar)}) p
        length   <- (\ptr -> do {C2HSImp.peekByteOff ptr 16 :: IO C2HSImp.CUInt}) p
        encoding <- (\ptr -> do {C2HSImp.peekByteOff ptr 24 :: IO (C2HSImp.Ptr C2HSImp.CChar)}) p >>= tb
        T.pack <$> peekCStringLen (ptr, fromIntegral length)
      go p NativeTypeTimestamp  o = do
        year           <- (\ptr -> do {C2HSImp.peekByteOff ptr 8 :: IO C2HSImp.CShort}) p
        month          <- (\ptr -> do {C2HSImp.peekByteOff ptr 10 :: IO C2HSImp.CUChar}) p
        day            <- (\ptr -> do {C2HSImp.peekByteOff ptr 11 :: IO C2HSImp.CUChar}) p
        hour           <- (\ptr -> do {C2HSImp.peekByteOff ptr 12 :: IO C2HSImp.CUChar}) p
        minute         <- (\ptr -> do {C2HSImp.peekByteOff ptr 13 :: IO C2HSImp.CUChar}) p
        second         <- (\ptr -> do {C2HSImp.peekByteOff ptr 14 :: IO C2HSImp.CUChar}) p
        fsecond        <- (\ptr -> do {C2HSImp.peekByteOff ptr 16 :: IO C2HSImp.CUInt}) p
        tzHourOffset   <- (\ptr -> do {C2HSImp.peekByteOff ptr 20 :: IO C2HSImp.CSChar}) p
        tzMinuteOffset <- (\ptr -> do {C2HSImp.peekByteOff ptr 21 :: IO C2HSImp.CSChar}) p
        return $ toTime o Data_Timestamp{..}
      go p NativeTypeIntervalDs _ = DataIntervalDs <$> do
        days     <- (\ptr -> do {C2HSImp.peekByteOff ptr 8 :: IO C2HSImp.CInt}) p
        hours    <- (\ptr -> do {C2HSImp.peekByteOff ptr 12 :: IO C2HSImp.CInt}) p
        minutes  <- (\ptr -> do {C2HSImp.peekByteOff ptr 16 :: IO C2HSImp.CInt}) p
        seconds  <- (\ptr -> do {C2HSImp.peekByteOff ptr 20 :: IO C2HSImp.CInt}) p
        fseconds <- (\ptr -> do {C2HSImp.peekByteOff ptr 24 :: IO C2HSImp.CInt}) p
        return $ picosecondsToDiffTime $ (fromIntegral days * 24 * 3600 + fromIntegral hours * 3600 + fromIntegral minutes * 60 + fromIntegral seconds) * picoResolution + fromIntegral fseconds
      go p NativeTypeIntervalYm _ = DataIntervalYm <$> do
        years    <- (\ptr -> do {C2HSImp.peekByteOff ptr 8 :: IO C2HSImp.CInt}) p
        months   <- (\ptr -> do {C2HSImp.peekByteOff ptr 12 :: IO C2HSImp.CInt}) p
        return Data_IntervalYM {..}
      go p NativeTypeLob        o = gLob o         <$> (\ptr -> do {C2HSImp.peekByteOff ptr 8 :: IO (C2HSImp.Ptr (DPI_Lob))}) p
      go p NativeTypeObject     _ = DataObject     <$> (\ptr -> do {C2HSImp.peekByteOff ptr 8 :: IO (C2HSImp.Ptr (DPI_Object))}) p
      go p NativeTypeStmt       _ = DataStmt       <$> (\ptr -> do {C2HSImp.peekByteOff ptr 8 :: IO (C2HSImp.Ptr (DPI_Stmt))}) p
      go p NativeTypeRowid      _ = DataRowid      <$> (\ptr -> do {C2HSImp.peekByteOff ptr 8 :: IO (C2HSImp.Ptr (DPI_Rowid))}) p


gByt OracleTypeChar         = DataChar
gByt OracleTypeLongRaw      = DataLongRaw
gByt OracleTypeLongVarchar  = DataLongVarchar
gByt OracleTypeNchar        = DataNChar
gByt OracleTypeNumber       = DataNumBytes
gByt OracleTypeNvarchar     = DataNVarchar
gByt OracleTypeRaw          = DataRaw
gByt OracleTypeVarchar      = DataVarchar
gByt _                      = DataVarchar
gInt OracleTypeNumber       = DataNumInt
gInt OracleTypeNativeInt    = DataInt
gInt _                      = DataInt
gUnt OracleTypeNumber       = DataNumUint
gUnt OracleTypeNativeUint   = DataUint
gUnt _                      = DataUint
gDbl OracleTypeNumber       = DataNumDouble
gDbl OracleTypeTimestamp    = DataTimestampD
gDbl OracleTypeTimestampLtz = DataTimestampLtzD
gDbl OracleTypeTimestampTz  = DataTimestampTzD
gDbl OracleTypeNativeDouble = DataTimestampTzD
gDbl _                      = DataDouble
gLob OracleTypeBfile        = DataBFile
gLob OracleTypeBlob         = DataBlob
gLob OracleTypeClob         = DataClob
gLob OracleTypeNclob        = DataNClob
gLob _                      = DataBlob
gTmp OracleTypeDate         = DataDate
gTmp OracleTypeTimestamp    = DataTimestamp
gTmp OracleTypeTimestampLtz = DataTimestampLtz
gTmp OracleTypeTimestampTz  = DataTimestampTz
gTmp _                      = DataTimestamp

data Data_DataTypeInfo  = Data_DataTypeInfo
  { oracleTypeNum        :: !OracleTypeNum
  , defaultNativeTypeNum :: !NativeTypeNum
  , ociTypeCode          :: !CUShort
  , dbSizeInBytes        :: !CUInt
  , clientSizeInBytes    :: !CUInt
  , sizeInChars          :: !CUInt
  , precision            :: !CShort
  , scale                :: !CSChar
  , fsPrecision          :: !CUChar
  , objectType           :: !(Ptr DPI_ObjectType)
  } deriving Show

instance Storable Data_DataTypeInfo where
  sizeOf    _ = 40
{-# LINE 571 "src/Database/Dpi/Internal.chs" #-}

  alignment _ = 8
{-# LINE 572 "src/Database/Dpi/Internal.chs" #-}

  poke    _ _ = noImplement
  peek      p = do
    oracleTypeNum        <- te <$> (\ptr -> do {C2HSImp.peekByteOff ptr 0 :: IO C2HSImp.CInt}) p
    defaultNativeTypeNum <- te <$> (\ptr -> do {C2HSImp.peekByteOff ptr 4 :: IO C2HSImp.CInt}) p
    ociTypeCode          <- (\ptr -> do {C2HSImp.peekByteOff ptr 8 :: IO C2HSImp.CUShort}) p
    dbSizeInBytes        <- (\ptr -> do {C2HSImp.peekByteOff ptr 12 :: IO C2HSImp.CUInt}) p
    clientSizeInBytes    <- (\ptr -> do {C2HSImp.peekByteOff ptr 16 :: IO C2HSImp.CUInt}) p
    sizeInChars          <- (\ptr -> do {C2HSImp.peekByteOff ptr 20 :: IO C2HSImp.CUInt}) p
    precision            <- (\ptr -> do {C2HSImp.peekByteOff ptr 24 :: IO C2HSImp.CShort}) p
    scale                <- (\ptr -> do {C2HSImp.peekByteOff ptr 26 :: IO C2HSImp.CSChar}) p
    fsPrecision          <- (\ptr -> do {C2HSImp.peekByteOff ptr 27 :: IO C2HSImp.CUChar}) p
    objectType           <- (\ptr -> do {C2HSImp.peekByteOff ptr 32 :: IO (C2HSImp.Ptr (DPI_ObjectType))}) p
    return Data_DataTypeInfo {..}

{-# INLINE toTime #-}
toTime :: OracleTypeNum -> Data_Timestamp -> DataValue
toTime t Data_Timestamp{..} 
  = let utctDay     = fromGregorian (fromIntegral year) (fromIntegral month) (fromIntegral day)
        utctDayTime = picosecondsToDiffTime $ ((fromIntegral hour - fromIntegral tzHourOffset) * 3600 + (fromIntegral minute - fromIntegral tzMinuteOffset) * 60 + fromIntegral second) * picoResolution + fromIntegral fsecond
        go OracleTypeDate         = DataDate
        go OracleTypeTimestamp    = DataTimestamp
        go OracleTypeTimestampLtz = DataTimestampLtz
        go OracleTypeTimestampTz  = DataTimestampTz
        go _                      = DataTimestamp
    in go t $ UTCTime {..}


data Data_EncodingInfo  = Data_EncodingInfo
  { encoding              :: !Text
  , maxBytesPerCharacter  :: !CInt
  , nencoding             :: !Text
  , nmaxBytesPerCharacter :: !CInt
  } deriving Show

instance Storable Data_EncodingInfo where
  sizeOf    _ = 32
{-# LINE 608 "src/Database/Dpi/Internal.chs" #-}

  alignment _ = 8
{-# LINE 609 "src/Database/Dpi/Internal.chs" #-}

  poke   _  _ = noImplement
  peek      p = do
    encoding              <- (\ptr -> do {C2HSImp.peekByteOff ptr 0 :: IO (C2HSImp.Ptr C2HSImp.CChar)}) p >>= tb
    maxBytesPerCharacter  <- (\ptr -> do {C2HSImp.peekByteOff ptr 8 :: IO C2HSImp.CInt}) p
    nencoding             <- (\ptr -> do {C2HSImp.peekByteOff ptr 16 :: IO (C2HSImp.Ptr C2HSImp.CChar)}) p >>= tb
    nmaxBytesPerCharacter <- (\ptr -> do {C2HSImp.peekByteOff ptr 24 :: IO C2HSImp.CInt}) p
    return Data_EncodingInfo {..}

data Data_ErrorInfo  = Data_ErrorInfo
  { code          :: !CInt
  , offset        :: !CUShort
  , message       :: !Text
  , encoding      :: !Text
  , fnName        :: !Text
  , action        :: !Text
  , sqlState      :: !Text
  , isRecoverable :: !Bool
  } deriving Show

instance Storable Data_ErrorInfo where
  sizeOf    _ = 64
{-# LINE 630 "src/Database/Dpi/Internal.chs" #-}

  alignment _ = 8
{-# LINE 631 "src/Database/Dpi/Internal.chs" #-}

  poke    _ _ = noImplement
  peek      p = do
    code          <- (\ptr -> do {C2HSImp.peekByteOff ptr 0 :: IO C2HSImp.CInt}) p
    offset        <- (\ptr -> do {C2HSImp.peekByteOff ptr 4 :: IO C2HSImp.CUShort}) p
    message'      <- (\ptr -> do {C2HSImp.peekByteOff ptr 8 :: IO (C2HSImp.Ptr C2HSImp.CChar)}) p
    messageLength <- (\ptr -> do {C2HSImp.peekByteOff ptr 16 :: IO C2HSImp.CUInt}) p
    encoding      <- (\ptr -> do {C2HSImp.peekByteOff ptr 24 :: IO (C2HSImp.Ptr C2HSImp.CChar)}) p >>= tb
    fnName        <- (\ptr -> do {C2HSImp.peekByteOff ptr 32 :: IO (C2HSImp.Ptr C2HSImp.CChar)}) p >>= tb
    action        <- (\ptr -> do {C2HSImp.peekByteOff ptr 40 :: IO (C2HSImp.Ptr C2HSImp.CChar)}) p >>= tb
    sqlState      <- (\ptr -> do {C2HSImp.peekByteOff ptr 48 :: IO (C2HSImp.Ptr C2HSImp.CChar)}) p >>= tb
    isRecoverable <- toBool <$> (\ptr -> do {C2HSImp.peekByteOff ptr 56 :: IO C2HSImp.CInt}) p
    message       <- ts message' messageLength
    return Data_ErrorInfo {..}

data Data_ObjectAttrInfo  = Data_ObjectAttrInfo
  { name       :: !Text
  , typeInfo   :: !Data_DataTypeInfo
  } deriving Show

instance Storable Data_ObjectAttrInfo where
  sizeOf    _ = 56
{-# LINE 652 "src/Database/Dpi/Internal.chs" #-}

  alignment _ = 8
{-# LINE 653 "src/Database/Dpi/Internal.chs" #-}

  poke    _ _ = noImplement
  peek      p = do
    name'      <- (\ptr -> do {C2HSImp.peekByteOff ptr 0 :: IO (C2HSImp.Ptr C2HSImp.CChar)}) p
    nameLength <- (\ptr -> do {C2HSImp.peekByteOff ptr 8 :: IO C2HSImp.CUInt}) p
    typeInfo   <- do
      oracleTypeNum        <- te <$> (\ptr -> do {C2HSImp.peekByteOff ptr 16 :: IO C2HSImp.CInt}) p
      defaultNativeTypeNum <- te <$> (\ptr -> do {C2HSImp.peekByteOff ptr 20 :: IO C2HSImp.CInt}) p
      ociTypeCode          <-        (\ptr -> do {C2HSImp.peekByteOff ptr 24 :: IO C2HSImp.CUShort}) p
      dbSizeInBytes        <-        (\ptr -> do {C2HSImp.peekByteOff ptr 28 :: IO C2HSImp.CUInt}) p
      clientSizeInBytes    <-        (\ptr -> do {C2HSImp.peekByteOff ptr 32 :: IO C2HSImp.CUInt}) p
      sizeInChars          <-        (\ptr -> do {C2HSImp.peekByteOff ptr 36 :: IO C2HSImp.CUInt}) p
      precision            <-        (\ptr -> do {C2HSImp.peekByteOff ptr 40 :: IO C2HSImp.CShort}) p
      scale                <-        (\ptr -> do {C2HSImp.peekByteOff ptr 42 :: IO C2HSImp.CSChar}) p
      fsPrecision          <-        (\ptr -> do {C2HSImp.peekByteOff ptr 43 :: IO C2HSImp.CUChar}) p
      objectType           <-        (\ptr -> do {C2HSImp.peekByteOff ptr 48 :: IO (C2HSImp.Ptr (DPI_ObjectType))}) p
      return Data_DataTypeInfo {..}
    name       <- ts name' nameLength
    return Data_ObjectAttrInfo {..}

data Data_ObjectTypeInfo  = Data_ObjectTypeInfo
  { schema          :: !Text
  , name            :: !Text
  , isCollection    :: !Bool
  , elementTypeInfo :: !Data_DataTypeInfo
  , numAttributes   :: !CUShort
  } deriving Show

instance Storable Data_ObjectTypeInfo where
  sizeOf    _ = 56
{-# LINE 682 "src/Database/Dpi/Internal.chs" #-}

  alignment _ = 8
{-# LINE 683 "src/Database/Dpi/Internal.chs" #-}

  poke    _ _ = noImplement
  peek      p = do
    schema'         <- (\ptr -> do {C2HSImp.peekByteOff ptr 0 :: IO (C2HSImp.Ptr C2HSImp.CChar)}) p
    schemaLength    <- (\ptr -> do {C2HSImp.peekByteOff ptr 8 :: IO C2HSImp.CUInt}) p
    name'           <- (\ptr -> do {C2HSImp.peekByteOff ptr 16 :: IO (C2HSImp.Ptr C2HSImp.CChar)}) p
    nameLength      <- (\ptr -> do {C2HSImp.peekByteOff ptr 24 :: IO C2HSImp.CUInt}) p
    isCollection    <- toBool  <$> (\ptr -> do {C2HSImp.peekByteOff ptr 28 :: IO C2HSImp.CInt}) p
    elementTypeInfo <- do
      oracleTypeNum        <- te <$> (\ptr -> do {C2HSImp.peekByteOff ptr 32 :: IO C2HSImp.CInt}) p
      defaultNativeTypeNum <- te <$> (\ptr -> do {C2HSImp.peekByteOff ptr 36 :: IO C2HSImp.CInt}) p
      ociTypeCode          <-        (\ptr -> do {C2HSImp.peekByteOff ptr 40 :: IO C2HSImp.CUShort}) p
      dbSizeInBytes        <-        (\ptr -> do {C2HSImp.peekByteOff ptr 44 :: IO C2HSImp.CUInt}) p
      clientSizeInBytes    <-        (\ptr -> do {C2HSImp.peekByteOff ptr 48 :: IO C2HSImp.CUInt}) p
      sizeInChars          <-        (\ptr -> do {C2HSImp.peekByteOff ptr 52 :: IO C2HSImp.CUInt}) p
      precision            <-        (\ptr -> do {C2HSImp.peekByteOff ptr 56 :: IO C2HSImp.CShort}) p
      scale                <-        (\ptr -> do {C2HSImp.peekByteOff ptr 58 :: IO C2HSImp.CSChar}) p
      fsPrecision          <-        (\ptr -> do {C2HSImp.peekByteOff ptr 59 :: IO C2HSImp.CUChar}) p
      objectType           <-        (\ptr -> do {C2HSImp.peekByteOff ptr 64 :: IO (C2HSImp.Ptr (DPI_ObjectType))}) p
      return Data_DataTypeInfo {..}
    numAttributes   <- (\ptr -> do {C2HSImp.peekByteOff ptr 72 :: IO C2HSImp.CUShort}) p
    schema          <- ts schema' schemaLength
    name            <- ts name'   nameLength
    return Data_ObjectTypeInfo {..}

data Data_PoolCreateParams  = Data_PoolCreateParams
  { minSessions       :: !CUInt
  , maxSessions       :: !CUInt
  , sessionIncrement  :: !CUInt
  , pingInterval      :: !CInt
  , pingTimeout       :: !CInt
  , homogeneous       :: !CInt
  , externalAuth      :: !CInt
  , getMode           :: !PoolGetMode
  , outPoolName       :: !Text
  } deriving Show

instance Storable Data_PoolCreateParams where
  sizeOf    _ = 56
{-# LINE 721 "src/Database/Dpi/Internal.chs" #-}

  alignment _ = 8
{-# LINE 722 "src/Database/Dpi/Internal.chs" #-}

  poke      p Data_PoolCreateParams{..} = do
    (e,elen) <- fb outPoolName   
    (\ptr val -> do {C2HSImp.pokeByteOff ptr 0 (val :: C2HSImp.CUInt)}) p minSessions
    (\ptr val -> do {C2HSImp.pokeByteOff ptr 4 (val :: C2HSImp.CUInt)}) p maxSessions
    (\ptr val -> do {C2HSImp.pokeByteOff ptr 8 (val :: C2HSImp.CUInt)}) p sessionIncrement
    (\ptr val -> do {C2HSImp.pokeByteOff ptr 12 (val :: C2HSImp.CInt)}) p pingInterval
    (\ptr val -> do {C2HSImp.pokeByteOff ptr 16 (val :: C2HSImp.CInt)}) p pingTimeout
    (\ptr val -> do {C2HSImp.pokeByteOff ptr 20 (val :: C2HSImp.CInt)}) p homogeneous
    (\ptr val -> do {C2HSImp.pokeByteOff ptr 24 (val :: C2HSImp.CInt)}) p externalAuth
    (\ptr val -> do {C2HSImp.pokeByteOff ptr 28 (val :: C2HSImp.CInt)}) p (fe              getMode)
    (\ptr val -> do {C2HSImp.pokeByteOff ptr 32 (val :: (C2HSImp.Ptr C2HSImp.CChar))}) p e
    (\ptr val -> do {C2HSImp.pokeByteOff ptr 40 (val :: C2HSImp.CUInt)}) p (fromIntegral    elen)
  peek      p = do
    minSessions       <- (\ptr -> do {C2HSImp.peekByteOff ptr 0 :: IO C2HSImp.CUInt}) p
    maxSessions       <- (\ptr -> do {C2HSImp.peekByteOff ptr 4 :: IO C2HSImp.CUInt}) p
    sessionIncrement  <- (\ptr -> do {C2HSImp.peekByteOff ptr 8 :: IO C2HSImp.CUInt}) p
    pingInterval      <- (\ptr -> do {C2HSImp.peekByteOff ptr 12 :: IO C2HSImp.CInt}) p
    pingTimeout       <- (\ptr -> do {C2HSImp.peekByteOff ptr 16 :: IO C2HSImp.CInt}) p
    homogeneous       <- (\ptr -> do {C2HSImp.peekByteOff ptr 20 :: IO C2HSImp.CInt}) p
    externalAuth      <- (\ptr -> do {C2HSImp.peekByteOff ptr 24 :: IO C2HSImp.CInt}) p
    getMode           <- te <$> (\ptr -> do {C2HSImp.peekByteOff ptr 28 :: IO C2HSImp.CInt}) p
    outPoolName'      <- (\ptr -> do {C2HSImp.peekByteOff ptr 32 :: IO (C2HSImp.Ptr C2HSImp.CChar)}) p
    outPoolNameLength <- (\ptr -> do {C2HSImp.peekByteOff ptr 40 :: IO C2HSImp.CUInt}) p
    outPoolName       <- ts outPoolName' outPoolNameLength
    return Data_PoolCreateParams {..}

data Data_QueryInfo = Data_QueryInfo
  { name       :: !Text
  , typeInfo   :: !Data_DataTypeInfo
  , nullOk     :: !Bool
  } deriving Show

instance Storable Data_QueryInfo where
  sizeOf    _ = 64
{-# LINE 756 "src/Database/Dpi/Internal.chs" #-}

  alignment _ = 8
{-# LINE 757 "src/Database/Dpi/Internal.chs" #-}

  poke    _ _ = noImplement
  peek      p = do
    name'      <- (\ptr -> do {C2HSImp.peekByteOff ptr 0 :: IO (C2HSImp.Ptr C2HSImp.CChar)}) p
    nameLength <- (\ptr -> do {C2HSImp.peekByteOff ptr 8 :: IO C2HSImp.CUInt}) p
    typeInfo   <- do
      oracleTypeNum        <- te <$> (\ptr -> do {C2HSImp.peekByteOff ptr 16 :: IO C2HSImp.CInt}) p
      defaultNativeTypeNum <- te <$> (\ptr -> do {C2HSImp.peekByteOff ptr 20 :: IO C2HSImp.CInt}) p
      ociTypeCode          <-        (\ptr -> do {C2HSImp.peekByteOff ptr 24 :: IO C2HSImp.CUShort}) p
      dbSizeInBytes        <-        (\ptr -> do {C2HSImp.peekByteOff ptr 28 :: IO C2HSImp.CUInt}) p
      clientSizeInBytes    <-        (\ptr -> do {C2HSImp.peekByteOff ptr 32 :: IO C2HSImp.CUInt}) p
      sizeInChars          <-        (\ptr -> do {C2HSImp.peekByteOff ptr 36 :: IO C2HSImp.CUInt}) p
      precision            <-        (\ptr -> do {C2HSImp.peekByteOff ptr 40 :: IO C2HSImp.CShort}) p
      scale                <-        (\ptr -> do {C2HSImp.peekByteOff ptr 42 :: IO C2HSImp.CSChar}) p
      fsPrecision          <-        (\ptr -> do {C2HSImp.peekByteOff ptr 43 :: IO C2HSImp.CUChar}) p
      objectType           <-        (\ptr -> do {C2HSImp.peekByteOff ptr 48 :: IO (C2HSImp.Ptr (DPI_ObjectType))}) p
      return Data_DataTypeInfo {..}
    nullOk     <- toBool  <$> (\ptr -> do {C2HSImp.peekByteOff ptr 56 :: IO C2HSImp.CInt}) p
    name       <- ts name' nameLength
    return Data_QueryInfo {..}

data Data_ShardingKeyColumn  = Data_ShardingKeyColumn
  { oracleTypeNum :: !OracleTypeNum
  , nativeTypeNum :: !NativeTypeNum
  , value         :: !DataValue
  } deriving Show

instance Storable Data_ShardingKeyColumn where
  sizeOf    _ = 32
{-# LINE 785 "src/Database/Dpi/Internal.chs" #-}

  alignment _ = 8
{-# LINE 786 "src/Database/Dpi/Internal.chs" #-}

  poke    _ _ = noImplement
  peek      p = do
    oracleTypeNum <- te      <$> (\ptr -> do {C2HSImp.peekByteOff ptr 0 :: IO C2HSImp.CInt}) p
    nativeTypeNum <- te      <$> (\ptr -> do {C2HSImp.peekByteOff ptr 4 :: IO C2HSImp.CInt}) p
    value         <- go p nativeTypeNum oracleTypeNum
    return Data_ShardingKeyColumn {..}
    where
      go p NativeTypeInt64      o = (gInt o  .fromInteger.toInteger) <$> (\ptr -> do {C2HSImp.peekByteOff ptr 8 :: IO C2HSImp.CLLong}) p
      go p NativeTypeUint64     o = (gUnt o .fromInteger.toInteger) <$> (\ptr -> do {C2HSImp.peekByteOff ptr 8 :: IO C2HSImp.CULLong}) p
      go p NativeTypeFloat      _ = DataFloat      <$> (\ptr -> do {C2HSImp.peekByteOff ptr 8 :: IO C2HSImp.CFloat}) p
      go p NativeTypeDouble     o = gDbl o     <$> (\ptr -> do {C2HSImp.peekByteOff ptr 8 :: IO C2HSImp.CDouble}) p
      go p NativeTypeBytes      o = gByt o       <$> do
        ptr      <- (\ptr -> do {C2HSImp.peekByteOff ptr 8 :: IO (C2HSImp.Ptr C2HSImp.CChar)}) p
        length   <- (\ptr -> do {C2HSImp.peekByteOff ptr 16 :: IO C2HSImp.CUInt}) p
        encoding <- (\ptr -> do {C2HSImp.peekByteOff ptr 24 :: IO (C2HSImp.Ptr C2HSImp.CChar)}) p >>= tb
        T.pack <$> peekCStringLen (ptr, fromIntegral length)
      go p NativeTypeTimestamp  t = do
        year           <- (\ptr -> do {C2HSImp.peekByteOff ptr 8 :: IO C2HSImp.CShort}) p
        month          <- (\ptr -> do {C2HSImp.peekByteOff ptr 10 :: IO C2HSImp.CUChar}) p
        day            <- (\ptr -> do {C2HSImp.peekByteOff ptr 11 :: IO C2HSImp.CUChar}) p
        hour           <- (\ptr -> do {C2HSImp.peekByteOff ptr 12 :: IO C2HSImp.CUChar}) p
        minute         <- (\ptr -> do {C2HSImp.peekByteOff ptr 13 :: IO C2HSImp.CUChar}) p
        second         <- (\ptr -> do {C2HSImp.peekByteOff ptr 14 :: IO C2HSImp.CUChar}) p
        fsecond        <- (\ptr -> do {C2HSImp.peekByteOff ptr 16 :: IO C2HSImp.CUInt}) p
        tzHourOffset   <- (\ptr -> do {C2HSImp.peekByteOff ptr 20 :: IO C2HSImp.CSChar}) p
        tzMinuteOffset <- (\ptr -> do {C2HSImp.peekByteOff ptr 21 :: IO C2HSImp.CSChar}) p
        return $ toTime t Data_Timestamp{..}
      go p NativeTypeIntervalDs _ = DataIntervalDs <$> do
        days     <- (\ptr -> do {C2HSImp.peekByteOff ptr 8 :: IO C2HSImp.CInt}) p
        hours    <- (\ptr -> do {C2HSImp.peekByteOff ptr 12 :: IO C2HSImp.CInt}) p
        minutes  <- (\ptr -> do {C2HSImp.peekByteOff ptr 16 :: IO C2HSImp.CInt}) p
        seconds  <- (\ptr -> do {C2HSImp.peekByteOff ptr 20 :: IO C2HSImp.CInt}) p
        fseconds <- (\ptr -> do {C2HSImp.peekByteOff ptr 24 :: IO C2HSImp.CInt}) p
        return $ picosecondsToDiffTime $ (fromIntegral days * 24 * 3600 + fromIntegral hours * 3600 + fromIntegral minutes * 60 + fromIntegral seconds) * picoResolution + fromIntegral fseconds
      go p NativeTypeIntervalYm _ = DataIntervalYm <$> do
        years    <- (\ptr -> do {C2HSImp.peekByteOff ptr 8 :: IO C2HSImp.CInt}) p
        months   <- (\ptr -> do {C2HSImp.peekByteOff ptr 12 :: IO C2HSImp.CInt}) p
        return Data_IntervalYM {..}
      go p NativeTypeLob        o = gLob o         <$> (\ptr -> do {C2HSImp.peekByteOff ptr 8 :: IO (C2HSImp.Ptr (DPI_Lob))}) p
      go p NativeTypeObject     _ = DataObject     <$> (\ptr -> do {C2HSImp.peekByteOff ptr 8 :: IO (C2HSImp.Ptr (DPI_Object))}) p
      go p NativeTypeStmt       _ = DataStmt       <$> (\ptr -> do {C2HSImp.peekByteOff ptr 8 :: IO (C2HSImp.Ptr (DPI_Stmt))}) p
      go p NativeTypeRowid      _ = DataRowid      <$> (\ptr -> do {C2HSImp.peekByteOff ptr 8 :: IO (C2HSImp.Ptr (DPI_Rowid))}) p
      go p NativeTypeBoolean    _ = (DataBoolean .toBool)<$> (\ptr -> do {C2HSImp.peekByteOff ptr 8 :: IO C2HSImp.CInt}) p

data Data_StmtInfo = Data_StmtInfo
  { isQuery       :: !Bool
  , isPLSQL       :: !Bool
  , isDDL         :: !Bool
  , isDML         :: !Bool
  , statementType :: !StatementType
  , isReturning   :: !Bool
  } deriving Show

instance Storable Data_StmtInfo where
  sizeOf    _ = 24
{-# LINE 841 "src/Database/Dpi/Internal.chs" #-}

  alignment _ = 4
{-# LINE 842 "src/Database/Dpi/Internal.chs" #-}

  poke    _ _ = noImplement
  peek      p = do
    isQuery       <- toBool <$> (\ptr -> do {C2HSImp.peekByteOff ptr 0 :: IO C2HSImp.CInt}) p
    isPLSQL       <- toBool <$> (\ptr -> do {C2HSImp.peekByteOff ptr 4 :: IO C2HSImp.CInt}) p
    isDDL         <- toBool <$> (\ptr -> do {C2HSImp.peekByteOff ptr 8 :: IO C2HSImp.CInt}) p
    isDML         <- toBool <$> (\ptr -> do {C2HSImp.peekByteOff ptr 12 :: IO C2HSImp.CInt}) p
    statementType <- te     <$> (\ptr -> do {C2HSImp.peekByteOff ptr 16 :: IO C2HSImp.CInt}) p
    isReturning   <- toBool <$> (\ptr -> do {C2HSImp.peekByteOff ptr 20 :: IO C2HSImp.CInt}) p
    return Data_StmtInfo {..}

data Data_SubscrCreateParams = Data_SubscrCreateParams
  { subscrNamespace     :: !SubscrNamespace
  , protocol            :: !SubscrProtocol
  , qos                 :: !SubscrQOS
  , operations          :: !CInt
  , portNumber          :: !CUInt
  , timeout             :: !CUInt
  , name                :: !Text
  , callback            :: !(FunPtr (Ptr () -> PtrSubscrMessage -> IO ()))
  , callbackContext     :: !(Ptr ())
  , recipientName       :: !Text
  } deriving Show

instance Storable Data_SubscrCreateParams where
  sizeOf    _ = 96
{-# LINE 867 "src/Database/Dpi/Internal.chs" #-}

  alignment _ = 8
{-# LINE 868 "src/Database/Dpi/Internal.chs" #-}

  poke   _  _ = noImplement
  peek      p = do
    subscrNamespace     <- te    <$>                (\ptr -> do {C2HSImp.peekByteOff ptr 0 :: IO C2HSImp.CInt}) p
    protocol            <- te    <$>                (\ptr -> do {C2HSImp.peekByteOff ptr 4 :: IO C2HSImp.CInt}) p
    qos                 <- te    <$>                (\ptr -> do {C2HSImp.peekByteOff ptr 8 :: IO C2HSImp.CInt}) p
    operations          <- (\ptr -> do {C2HSImp.peekByteOff ptr 12 :: IO C2HSImp.CInt}) p
    portNumber          <- (\ptr -> do {C2HSImp.peekByteOff ptr 16 :: IO C2HSImp.CUInt}) p
    timeout             <- (\ptr -> do {C2HSImp.peekByteOff ptr 20 :: IO C2HSImp.CUInt}) p
    name'               <- (\ptr -> do {C2HSImp.peekByteOff ptr 24 :: IO (C2HSImp.Ptr C2HSImp.CChar)}) p
    nameLength          <- (\ptr -> do {C2HSImp.peekByteOff ptr 32 :: IO C2HSImp.CUInt}) p
    callback            <- (\ptr -> do {C2HSImp.peekByteOff ptr 40 :: IO (C2HSImp.FunPtr ((C2HSImp.Ptr ()) -> ((PtrSubscrMessage) -> (IO ()))))}) p
    callbackContext     <- (\ptr -> do {C2HSImp.peekByteOff ptr 48 :: IO (C2HSImp.Ptr ())}) p
    recipientName'      <- (\ptr -> do {C2HSImp.peekByteOff ptr 56 :: IO (C2HSImp.Ptr C2HSImp.CChar)}) p
    recipientNameLength <- (\ptr -> do {C2HSImp.peekByteOff ptr 64 :: IO C2HSImp.CUInt}) p
    name                <- ts name'          nameLength
    recipientName       <- ts recipientName' recipientNameLength
    return Data_SubscrCreateParams {..}

data Data_SubscrMessage = Data_SubscrMessage
  { eventType    :: !EventType
  , dbName       :: !Text
  , tables       :: !PtrSubscrMessageTable
  , numTables    :: !CUInt
  , queries      :: !PtrSubscrMessageQuery
  , numQueries   :: !CUInt
  , errorInfo    :: !PtrErrorInfo
  , txId         :: !(Ptr ())
  , txIdLength   :: !CUInt
  } deriving Show

instance Storable Data_SubscrMessage where
  sizeOf    _ = 112
{-# LINE 900 "src/Database/Dpi/Internal.chs" #-}

  alignment _ = 8
{-# LINE 901 "src/Database/Dpi/Internal.chs" #-}

  poke    _ _ = noImplement
  peek      p = do
    eventType    <- te <$> (\ptr -> do {C2HSImp.peekByteOff ptr 0 :: IO C2HSImp.CInt}) p
    dbName'      <- (\ptr -> do {C2HSImp.peekByteOff ptr 8 :: IO (C2HSImp.Ptr C2HSImp.CChar)}) p
    dbNameLength <- (\ptr -> do {C2HSImp.peekByteOff ptr 16 :: IO C2HSImp.CUInt}) p
    tables       <- (\ptr -> do {C2HSImp.peekByteOff ptr 24 :: IO (PtrSubscrMessageTable)}) p
    numTables    <- (\ptr -> do {C2HSImp.peekByteOff ptr 32 :: IO C2HSImp.CUInt}) p
    queries      <- (\ptr -> do {C2HSImp.peekByteOff ptr 40 :: IO (PtrSubscrMessageQuery)}) p
    numQueries   <- (\ptr -> do {C2HSImp.peekByteOff ptr 48 :: IO C2HSImp.CUInt}) p
    errorInfo    <- (\ptr -> do {C2HSImp.peekByteOff ptr 56 :: IO (PtrErrorInfo)}) p
    txId         <- (\ptr -> do {C2HSImp.peekByteOff ptr 64 :: IO (C2HSImp.Ptr ())}) p
    txIdLength   <- (\ptr -> do {C2HSImp.peekByteOff ptr 72 :: IO C2HSImp.CUInt}) p
    dbName       <- ts dbName' dbNameLength
    return Data_SubscrMessage {..}

data Data_SubscrMessageQuery = Data_SubscrMessageQuery
  { mid       :: !Int64
  , operation :: !OpCode
  , tables    :: !PtrSubscrMessageTable
  , numTables :: !CUInt
  } deriving Show

instance Storable Data_SubscrMessageQuery where
  sizeOf    _ = 32
{-# LINE 925 "src/Database/Dpi/Internal.chs" #-}

  alignment _ = 8
{-# LINE 926 "src/Database/Dpi/Internal.chs" #-}

  poke    _ _ = noImplement
  peek      p = do
    mid       <- fromInteger.toInteger <$> (\ptr -> do {C2HSImp.peekByteOff ptr 0 :: IO C2HSImp.CULLong}) p
    operation <- te <$> (\ptr -> do {C2HSImp.peekByteOff ptr 8 :: IO C2HSImp.CInt}) p
    tables    <- (\ptr -> do {C2HSImp.peekByteOff ptr 16 :: IO (PtrSubscrMessageTable)}) p
    numTables <- (\ptr -> do {C2HSImp.peekByteOff ptr 24 :: IO C2HSImp.CUInt}) p
    return Data_SubscrMessageQuery {..}

data Data_SubscrMessageRow = Data_SubscrMessageRow
  { operation   :: !OpCode
  , rowid       :: !Text
  } deriving Show

instance Storable Data_SubscrMessageRow where
  sizeOf    _ = 24
{-# LINE 941 "src/Database/Dpi/Internal.chs" #-}

  alignment _ = 8
{-# LINE 942 "src/Database/Dpi/Internal.chs" #-}

  poke    _ _ = noImplement
  peek      p = do
    operation   <- te <$> (\ptr -> do {C2HSImp.peekByteOff ptr 0 :: IO C2HSImp.CInt}) p
    rowid'      <- (\ptr -> do {C2HSImp.peekByteOff ptr 8 :: IO (C2HSImp.Ptr C2HSImp.CChar)}) p
    rowidLength <- (\ptr -> do {C2HSImp.peekByteOff ptr 16 :: IO C2HSImp.CUInt}) p
    rowid       <- ts rowid' rowidLength
    return Data_SubscrMessageRow {..}

data Data_SubscrMessageTable = Data_SubscrMessageTable
  { operation  :: !OpCode
  , name       :: !Text
  , rows       :: !PtrSubscrMessageRow
  , numRows    :: !CUInt
  } deriving Show

instance Storable Data_SubscrMessageTable where
  sizeOf    _ = 40
{-# LINE 959 "src/Database/Dpi/Internal.chs" #-}

  alignment _ = 8
{-# LINE 960 "src/Database/Dpi/Internal.chs" #-}

  poke    _ _ = noImplement
  peek      p = do
    operation  <- te <$> (\ptr -> do {C2HSImp.peekByteOff ptr 0 :: IO C2HSImp.CInt}) p
    name'      <- (\ptr -> do {C2HSImp.peekByteOff ptr 8 :: IO (C2HSImp.Ptr C2HSImp.CChar)}) p
    nameLength <- (\ptr -> do {C2HSImp.peekByteOff ptr 16 :: IO C2HSImp.CUInt}) p
    rows       <- (\ptr -> do {C2HSImp.peekByteOff ptr 24 :: IO (PtrSubscrMessageRow)}) p
    numRows    <- (\ptr -> do {C2HSImp.peekByteOff ptr 32 :: IO C2HSImp.CUInt}) p
    name       <- ts name' nameLength
    return Data_SubscrMessageTable {..}

data Data_VersionInfo = Data_VersionInfo
  { versionNum     :: !CInt
  , releaseNum     :: !CInt
  , updateNum      :: !CInt
  , portReleaseNum :: !CInt
  , portUpdateNum  :: !CInt
  , fullVersionNum :: !CUInt
  } deriving Show

instance Storable Data_VersionInfo where
  sizeOf    _ = 24
{-# LINE 981 "src/Database/Dpi/Internal.chs" #-}

  alignment _ = 4
{-# LINE 982 "src/Database/Dpi/Internal.chs" #-}

  poke    _ _ = noImplement
  peek      p = do
    versionNum     <- (\ptr -> do {C2HSImp.peekByteOff ptr 0 :: IO C2HSImp.CInt}) p
    releaseNum     <- (\ptr -> do {C2HSImp.peekByteOff ptr 4 :: IO C2HSImp.CInt}) p
    updateNum      <- (\ptr -> do {C2HSImp.peekByteOff ptr 8 :: IO C2HSImp.CInt}) p
    portReleaseNum <- (\ptr -> do {C2HSImp.peekByteOff ptr 12 :: IO C2HSImp.CInt}) p
    portUpdateNum  <- (\ptr -> do {C2HSImp.peekByteOff ptr 16 :: IO C2HSImp.CInt}) p
    fullVersionNum <- (\ptr -> do {C2HSImp.peekByteOff ptr 20 :: IO C2HSImp.CUInt}) p
    return Data_VersionInfo {..}

-- Context 
{-# INLINE libContextCreate                 #-}
{-# INLINE libContextDestroy                #-}
{-# INLINE libContextGetClientVersion       #-}
{-# INLINE libContextInitCommonCreateParams #-}
{-# INLINE libContextInitConnCreateParams   #-}
{-# INLINE libContextInitPoolCreateParams   #-}
{-# INLINE libContextInitSubscrCreateParams #-}
{-# INLINE libContextGetError               #-}
libContextCreate                 = dpiContext_create
{-# LINE 1002 "src/Database/Dpi/Internal.chs" #-}

libContextDestroy                = dpiContext_destroy
{-# LINE 1003 "src/Database/Dpi/Internal.chs" #-}

libContextGetClientVersion       = dpiContext_getClientVersion
{-# LINE 1004 "src/Database/Dpi/Internal.chs" #-}

libContextInitCommonCreateParams = dpiContext_initCommonCreateParams
{-# LINE 1005 "src/Database/Dpi/Internal.chs" #-}

libContextInitConnCreateParams   = dpiContext_initConnCreateParams
{-# LINE 1006 "src/Database/Dpi/Internal.chs" #-}

libContextInitPoolCreateParams   = dpiContext_initPoolCreateParams
{-# LINE 1007 "src/Database/Dpi/Internal.chs" #-}

libContextInitSubscrCreateParams = dpiContext_initSubscrCreateParams
{-# LINE 1008 "src/Database/Dpi/Internal.chs" #-}

libContextGetError               = dpiContext_getError
{-# LINE 1009 "src/Database/Dpi/Internal.chs" #-}


-- Conn
{-# INLINE libConnAddRef              #-}
{-# INLINE libConnBeginDistribTrans   #-}
{-# INLINE libConnBreakExecution      #-}
{-# INLINE libConnChangePassword      #-}
{-# INLINE libConnClose               #-}
{-# INLINE libConnCommit              #-}
{-# INLINE libConnCreate              #-}
{-# INLINE libConnDeqObject           #-}
{-# INLINE libConnEnqObject           #-}
{-# INLINE libConnGetCurrentSchema    #-}
{-# INLINE libConnGetEdition          #-}
{-# INLINE libConnGetEncodingInfo     #-}
{-# INLINE libConnGetExternalName     #-}
{-# INLINE libConnGetHandle           #-}
{-# INLINE libConnGetInternalName     #-}
{-# INLINE libConnGetLTXID            #-}
{-# INLINE libConnGetObjectType       #-}
{-# INLINE libConnGetServerVersion    #-}
{-# INLINE libConnGetStmtCacheSize    #-}
{-# INLINE libConnNewDeqOptions       #-}
{-# INLINE libConnNewEnqOptions       #-}
{-# INLINE libConnNewMsgProps         #-}
{-# INLINE libConnNewSubscription     #-}
{-# INLINE libConnNewTempLob          #-}
{-# INLINE libConnNewVar              #-}
{-# INLINE libConnPing                #-}
{-# INLINE libConnPrepareDistribTrans #-}
{-# INLINE libConnPrepareStmt         #-}
{-# INLINE libConnRelease             #-}
{-# INLINE libConnRollback            #-}
{-# INLINE libConnSetAction           #-}
{-# INLINE libConnSetClientIdentifier #-}
{-# INLINE libConnSetClientInfo       #-}
{-# INLINE libConnSetCurrentSchema    #-}
{-# INLINE libConnSetDbOp             #-}
{-# INLINE libConnSetExternalName     #-}
{-# INLINE libConnSetInternalName     #-}
{-# INLINE libConnSetModule           #-}
{-# INLINE libConnSetStmtCacheSize    #-}
{-# INLINE libConnShutdownDatabase    #-}
{-# INLINE libConnStartupDatabase     #-}
libConnAddRef              = dpiConn_addRef
{-# LINE 1053 "src/Database/Dpi/Internal.chs" #-}

libConnBeginDistribTrans   = dpiConn_beginDistribTrans
{-# LINE 1054 "src/Database/Dpi/Internal.chs" #-}

libConnBreakExecution      = dpiConn_breakExecution
{-# LINE 1055 "src/Database/Dpi/Internal.chs" #-}

libConnChangePassword      = dpiConn_changePassword
{-# LINE 1056 "src/Database/Dpi/Internal.chs" #-}

libConnClose               = dpiConn_close
{-# LINE 1057 "src/Database/Dpi/Internal.chs" #-}

libConnCommit              = dpiConn_commit
{-# LINE 1058 "src/Database/Dpi/Internal.chs" #-}

libConnCreate              = dpiConn_create
{-# LINE 1059 "src/Database/Dpi/Internal.chs" #-}

libConnDeqObject           = dpiConn_deqObject
{-# LINE 1060 "src/Database/Dpi/Internal.chs" #-}

libConnEnqObject           = dpiConn_enqObject
{-# LINE 1061 "src/Database/Dpi/Internal.chs" #-}

libConnGetCurrentSchema    = dpiConn_getCurrentSchema
{-# LINE 1062 "src/Database/Dpi/Internal.chs" #-}

libConnGetEdition          = dpiConn_getEdition
{-# LINE 1063 "src/Database/Dpi/Internal.chs" #-}

libConnGetEncodingInfo     = dpiConn_getEncodingInfo
{-# LINE 1064 "src/Database/Dpi/Internal.chs" #-}

libConnGetExternalName     = dpiConn_getExternalName
{-# LINE 1065 "src/Database/Dpi/Internal.chs" #-}

libConnGetHandle           = dpiConn_getHandle
{-# LINE 1066 "src/Database/Dpi/Internal.chs" #-}

libConnGetInternalName     = dpiConn_getInternalName
{-# LINE 1067 "src/Database/Dpi/Internal.chs" #-}

libConnGetLTXID            = dpiConn_getLTXID
{-# LINE 1068 "src/Database/Dpi/Internal.chs" #-}

libConnGetObjectType       = dpiConn_getObjectType
{-# LINE 1069 "src/Database/Dpi/Internal.chs" #-}

libConnGetServerVersion    = dpiConn_getServerVersion
{-# LINE 1070 "src/Database/Dpi/Internal.chs" #-}

libConnGetStmtCacheSize    = dpiConn_getStmtCacheSize
{-# LINE 1071 "src/Database/Dpi/Internal.chs" #-}

libConnNewDeqOptions       = dpiConn_newDeqOptions
{-# LINE 1072 "src/Database/Dpi/Internal.chs" #-}

libConnNewEnqOptions       = dpiConn_newEnqOptions
{-# LINE 1073 "src/Database/Dpi/Internal.chs" #-}

libConnNewMsgProps         = dpiConn_newMsgProps
{-# LINE 1074 "src/Database/Dpi/Internal.chs" #-}

libConnNewSubscription     = dpiConn_newSubscription
{-# LINE 1075 "src/Database/Dpi/Internal.chs" #-}

libConnNewTempLob          = dpiConn_newTempLob
{-# LINE 1076 "src/Database/Dpi/Internal.chs" #-}

libConnNewVar              = dpiConn_newVar
{-# LINE 1077 "src/Database/Dpi/Internal.chs" #-}

libConnPing                = dpiConn_ping
{-# LINE 1078 "src/Database/Dpi/Internal.chs" #-}

libConnPrepareDistribTrans = dpiConn_prepareDistribTrans
{-# LINE 1079 "src/Database/Dpi/Internal.chs" #-}

libConnPrepareStmt         = dpiConn_prepareStmt
{-# LINE 1080 "src/Database/Dpi/Internal.chs" #-}

libConnRelease             = dpiConn_release
{-# LINE 1081 "src/Database/Dpi/Internal.chs" #-}

libConnRollback            = dpiConn_rollback
{-# LINE 1082 "src/Database/Dpi/Internal.chs" #-}

libConnSetAction           = dpiConn_setAction
{-# LINE 1083 "src/Database/Dpi/Internal.chs" #-}

libConnSetClientIdentifier = dpiConn_setClientIdentifier
{-# LINE 1084 "src/Database/Dpi/Internal.chs" #-}

libConnSetClientInfo       = dpiConn_setClientInfo
{-# LINE 1085 "src/Database/Dpi/Internal.chs" #-}

libConnSetCurrentSchema    = dpiConn_setCurrentSchema
{-# LINE 1086 "src/Database/Dpi/Internal.chs" #-}

libConnSetDbOp             = dpiConn_setDbOp
{-# LINE 1087 "src/Database/Dpi/Internal.chs" #-}

libConnSetExternalName     = dpiConn_setExternalName
{-# LINE 1088 "src/Database/Dpi/Internal.chs" #-}

libConnSetInternalName     = dpiConn_setInternalName
{-# LINE 1089 "src/Database/Dpi/Internal.chs" #-}

libConnSetModule           = dpiConn_setModule
{-# LINE 1090 "src/Database/Dpi/Internal.chs" #-}

libConnSetStmtCacheSize    = dpiConn_setStmtCacheSize
{-# LINE 1091 "src/Database/Dpi/Internal.chs" #-}

libConnShutdownDatabase    = dpiConn_shutdownDatabase
{-# LINE 1092 "src/Database/Dpi/Internal.chs" #-}

libConnStartupDatabase     = dpiConn_startupDatabase
{-# LINE 1093 "src/Database/Dpi/Internal.chs" #-}


-- Data 
{-# INLINE libDataGetDouble     #-}
{-# INLINE libDataGetBytes      #-}
{-# INLINE libDataGetIntervalDS #-}
{-# INLINE libDataGetIntervalYM #-}
{-# INLINE libDataGetLOB        #-}
{-# INLINE libDataGetObject     #-}
{-# INLINE libDataGetStmt       #-}
{-# INLINE libDataGetTimestamp  #-}
{-# INLINE libDataGetFloat      #-}
{-# INLINE libDataGetBool       #-}
{-# INLINE libDataGetInt64      #-}
{-# INLINE libDataGetUint64     #-}
{-# INLINE libDataSetBool       #-}
{-# INLINE libDataSetBytes      #-}
{-# INLINE libDataSetDouble     #-}
{-# INLINE libDataSetFloat      #-}
{-# INLINE libDataSetInt64      #-}
{-# INLINE libDataSetIntervalDS #-}
{-# INLINE libDataSetIntervalYM #-}
{-# INLINE libDataSetLOB        #-}
{-# INLINE libDataSetObject     #-}
{-# INLINE libDataSetStmt       #-}
{-# INLINE libDataSetTimestamp  #-}
{-# INLINE libDataSetUint64     #-}
libDataGetDouble     = dpiData_getDouble
{-# LINE 1120 "src/Database/Dpi/Internal.chs" #-}

libDataGetBytes      = dpiData_getBytes
{-# LINE 1121 "src/Database/Dpi/Internal.chs" #-}

libDataGetIntervalDS = dpiData_getIntervalDS
{-# LINE 1122 "src/Database/Dpi/Internal.chs" #-}

libDataGetIntervalYM = dpiData_getIntervalYM
{-# LINE 1123 "src/Database/Dpi/Internal.chs" #-}

libDataGetLOB        = dpiData_getLOB
{-# LINE 1124 "src/Database/Dpi/Internal.chs" #-}

libDataGetObject     = dpiData_getObject
{-# LINE 1125 "src/Database/Dpi/Internal.chs" #-}

libDataGetStmt       = dpiData_getStmt
{-# LINE 1126 "src/Database/Dpi/Internal.chs" #-}

libDataGetTimestamp  = dpiData_getTimestamp
{-# LINE 1127 "src/Database/Dpi/Internal.chs" #-}

libDataGetFloat      = dpiData_getFloat
{-# LINE 1128 "src/Database/Dpi/Internal.chs" #-}

libDataGetBool       = dpiData_getBool
{-# LINE 1129 "src/Database/Dpi/Internal.chs" #-}

libDataGetInt64      = dpiData_getInt64
{-# LINE 1130 "src/Database/Dpi/Internal.chs" #-}

libDataGetUint64     = dpiData_getUint64
{-# LINE 1131 "src/Database/Dpi/Internal.chs" #-}

libDataSetBool       = dpiData_setBool
{-# LINE 1132 "src/Database/Dpi/Internal.chs" #-}

libDataSetBytes      = dpiData_setBytes
{-# LINE 1133 "src/Database/Dpi/Internal.chs" #-}

libDataSetDouble     = dpiData_setDouble
{-# LINE 1134 "src/Database/Dpi/Internal.chs" #-}

libDataSetFloat      = dpiData_setFloat
{-# LINE 1135 "src/Database/Dpi/Internal.chs" #-}

libDataSetInt64      = dpiData_setInt64
{-# LINE 1136 "src/Database/Dpi/Internal.chs" #-}

libDataSetIntervalDS = dpiData_setIntervalDS
{-# LINE 1137 "src/Database/Dpi/Internal.chs" #-}

libDataSetIntervalYM = dpiData_setIntervalYM
{-# LINE 1138 "src/Database/Dpi/Internal.chs" #-}

libDataSetLOB        = dpiData_setLOB
{-# LINE 1139 "src/Database/Dpi/Internal.chs" #-}

libDataSetObject     = dpiData_setObject
{-# LINE 1140 "src/Database/Dpi/Internal.chs" #-}

libDataSetStmt       = dpiData_setStmt
{-# LINE 1141 "src/Database/Dpi/Internal.chs" #-}

libDataSetTimestamp  = dpiData_setTimestamp
{-# LINE 1142 "src/Database/Dpi/Internal.chs" #-}

libDataSetUint64     = dpiData_setUint64
{-# LINE 1143 "src/Database/Dpi/Internal.chs" #-}



-- DeqOptions
{-# INLINE libDeqOptionsAddRef            #-}
{-# INLINE libDeqOptionsGetCondition      #-}
{-# INLINE libDeqOptionsGetConsumerName   #-}
{-# INLINE libDeqOptionsGetCorrelation    #-}
{-# INLINE libDeqOptionsGetMode           #-}
{-# INLINE libDeqOptionsGetMsgId          #-}
{-# INLINE libDeqOptionsGetNavigation     #-}
{-# INLINE libDeqOptionsGetTransformation #-}
{-# INLINE libDeqOptionsGetVisibility     #-}
{-# INLINE libDeqOptionsGetWait           #-}
{-# INLINE libDeqOptionsRelease           #-}
{-# INLINE libDeqOptionsSetCondition      #-}
{-# INLINE libDeqOptionsSetConsumerName   #-}
{-# INLINE libDeqOptionsSetCorrelation    #-}
{-# INLINE libDeqOptionsSetDeliveryMode   #-}
{-# INLINE libDeqOptionsSetMode           #-}
{-# INLINE libDeqOptionsSetMsgId          #-}
{-# INLINE libDeqOptionsSetNavigation     #-}
{-# INLINE libDeqOptionsSetTransformation #-}
{-# INLINE libDeqOptionsSetVisibility     #-}
{-# INLINE libDeqOptionsSetWait           #-}
libDeqOptionsAddRef            = dpiDeqOptions_addRef
{-# LINE 1168 "src/Database/Dpi/Internal.chs" #-}

libDeqOptionsGetCondition      = dpiDeqOptions_getCondition
{-# LINE 1169 "src/Database/Dpi/Internal.chs" #-}

libDeqOptionsGetConsumerName   = dpiDeqOptions_getConsumerName
{-# LINE 1170 "src/Database/Dpi/Internal.chs" #-}

libDeqOptionsGetCorrelation    = dpiDeqOptions_getCorrelation
{-# LINE 1171 "src/Database/Dpi/Internal.chs" #-}

libDeqOptionsGetMode           = dpiDeqOptions_getMode
{-# LINE 1172 "src/Database/Dpi/Internal.chs" #-}

libDeqOptionsGetMsgId          = dpiDeqOptions_getMsgId
{-# LINE 1173 "src/Database/Dpi/Internal.chs" #-}

libDeqOptionsGetNavigation     = dpiDeqOptions_getNavigation
{-# LINE 1174 "src/Database/Dpi/Internal.chs" #-}

libDeqOptionsGetTransformation = dpiDeqOptions_getTransformation
{-# LINE 1175 "src/Database/Dpi/Internal.chs" #-}

libDeqOptionsGetVisibility     = dpiDeqOptions_getVisibility
{-# LINE 1176 "src/Database/Dpi/Internal.chs" #-}

libDeqOptionsGetWait           = dpiDeqOptions_getWait
{-# LINE 1177 "src/Database/Dpi/Internal.chs" #-}

libDeqOptionsRelease           = dpiDeqOptions_release
{-# LINE 1178 "src/Database/Dpi/Internal.chs" #-}

libDeqOptionsSetCondition      = dpiDeqOptions_setCondition
{-# LINE 1179 "src/Database/Dpi/Internal.chs" #-}

libDeqOptionsSetConsumerName   = dpiDeqOptions_setConsumerName
{-# LINE 1180 "src/Database/Dpi/Internal.chs" #-}

libDeqOptionsSetCorrelation    = dpiDeqOptions_setCorrelation
{-# LINE 1181 "src/Database/Dpi/Internal.chs" #-}

libDeqOptionsSetDeliveryMode   = dpiDeqOptions_setDeliveryMode
{-# LINE 1182 "src/Database/Dpi/Internal.chs" #-}

libDeqOptionsSetMode           = dpiDeqOptions_setMode
{-# LINE 1183 "src/Database/Dpi/Internal.chs" #-}

libDeqOptionsSetMsgId          = dpiDeqOptions_setMsgId
{-# LINE 1184 "src/Database/Dpi/Internal.chs" #-}

libDeqOptionsSetNavigation     = dpiDeqOptions_setNavigation
{-# LINE 1185 "src/Database/Dpi/Internal.chs" #-}

libDeqOptionsSetTransformation = dpiDeqOptions_setTransformation
{-# LINE 1186 "src/Database/Dpi/Internal.chs" #-}

libDeqOptionsSetVisibility     = dpiDeqOptions_setVisibility
{-# LINE 1187 "src/Database/Dpi/Internal.chs" #-}

libDeqOptionsSetWait           = dpiDeqOptions_setWait
{-# LINE 1188 "src/Database/Dpi/Internal.chs" #-}


-- EnqOptions
{-# INLINE libEnqOptionsAddRef            #-}
{-# INLINE libEnqOptionsGetTransformation #-}
{-# INLINE libEnqOptionsGetVisibility     #-}
{-# INLINE libEnqOptionsRelease           #-}
{-# INLINE libEnqOptionsSetDeliveryMode   #-}
{-# INLINE libEnqOptionsSetTransformation #-}
{-# INLINE libEnqOptionsSetVisibility     #-}
libEnqOptionsAddRef            = dpiEnqOptions_addRef
{-# LINE 1198 "src/Database/Dpi/Internal.chs" #-}

libEnqOptionsGetTransformation = dpiEnqOptions_getTransformation
{-# LINE 1199 "src/Database/Dpi/Internal.chs" #-}

libEnqOptionsGetVisibility     = dpiEnqOptions_getVisibility
{-# LINE 1200 "src/Database/Dpi/Internal.chs" #-}

libEnqOptionsRelease           = dpiEnqOptions_release
{-# LINE 1201 "src/Database/Dpi/Internal.chs" #-}

libEnqOptionsSetDeliveryMode   = dpiEnqOptions_setDeliveryMode
{-# LINE 1202 "src/Database/Dpi/Internal.chs" #-}

libEnqOptionsSetTransformation = dpiEnqOptions_setTransformation
{-# LINE 1203 "src/Database/Dpi/Internal.chs" #-}

libEnqOptionsSetVisibility     = dpiEnqOptions_setVisibility
{-# LINE 1204 "src/Database/Dpi/Internal.chs" #-}


-- Lob
{-# INLINE libLobAddRef                  #-}
{-# INLINE libLobClose                   #-}
{-# INLINE libLobCloseResource           #-}
{-# INLINE libLobCopy                    #-}
{-# INLINE libLobFlushBuffer             #-}
{-# INLINE libLobGetBufferSize           #-}
{-# INLINE libLobGetChunkSize            #-}
{-# INLINE libLobGetDirectoryAndFileName #-}
{-# INLINE libLobGetFileExists           #-}
{-# INLINE libLobGetIsResourceOpen       #-}
{-# INLINE libLobGetSize                 #-}
{-# INLINE libLobOpenResource            #-}
{-# INLINE libLobReadBytes               #-}
{-# INLINE libLobRelease                 #-}
{-# INLINE libLobSetDirectoryAndFileName #-}
{-# INLINE libLobSetFromBytes            #-}
{-# INLINE libLobTrim                    #-}
{-# INLINE libLobWriteBytes              #-}
libLobAddRef                  = dpiLob_addRef
{-# LINE 1225 "src/Database/Dpi/Internal.chs" #-}

libLobClose                   = dpiLob_close
{-# LINE 1226 "src/Database/Dpi/Internal.chs" #-}

libLobCloseResource           = dpiLob_closeResource
{-# LINE 1227 "src/Database/Dpi/Internal.chs" #-}

libLobCopy                    = dpiLob_copy
{-# LINE 1228 "src/Database/Dpi/Internal.chs" #-}

libLobFlushBuffer             = dpiLob_flushBuffer
{-# LINE 1229 "src/Database/Dpi/Internal.chs" #-}

libLobGetBufferSize           = dpiLob_getBufferSize
{-# LINE 1230 "src/Database/Dpi/Internal.chs" #-}

libLobGetChunkSize            = dpiLob_getChunkSize
{-# LINE 1231 "src/Database/Dpi/Internal.chs" #-}

libLobGetDirectoryAndFileName = dpiLob_getDirectoryAndFileName
{-# LINE 1232 "src/Database/Dpi/Internal.chs" #-}

libLobGetFileExists           = dpiLob_getFileExists
{-# LINE 1233 "src/Database/Dpi/Internal.chs" #-}

libLobGetIsResourceOpen       = dpiLob_getIsResourceOpen
{-# LINE 1234 "src/Database/Dpi/Internal.chs" #-}

libLobGetSize                 = dpiLob_getSize
{-# LINE 1235 "src/Database/Dpi/Internal.chs" #-}

libLobOpenResource            = dpiLob_openResource
{-# LINE 1236 "src/Database/Dpi/Internal.chs" #-}

libLobReadBytes               = dpiLob_readBytes
{-# LINE 1237 "src/Database/Dpi/Internal.chs" #-}

libLobRelease                 = dpiLob_release
{-# LINE 1238 "src/Database/Dpi/Internal.chs" #-}

libLobSetDirectoryAndFileName = dpiLob_setDirectoryAndFileName
{-# LINE 1239 "src/Database/Dpi/Internal.chs" #-}

libLobSetFromBytes            = dpiLob_setFromBytes
{-# LINE 1240 "src/Database/Dpi/Internal.chs" #-}

libLobTrim                    = dpiLob_trim
{-# LINE 1241 "src/Database/Dpi/Internal.chs" #-}

libLobWriteBytes              = dpiLob_writeBytes
{-# LINE 1242 "src/Database/Dpi/Internal.chs" #-}


-- MsgProps
{-# INLINE libMsgPropsAddRef           #-}
{-# INLINE libMsgPropsGetCorrelation   #-}
{-# INLINE libMsgPropsGetDelay         #-}
{-# INLINE libMsgPropsGetDeliveryMode  #-}
{-# INLINE libMsgPropsGetEnqTime       #-}
{-# INLINE libMsgPropsGetExceptionQ    #-}
{-# INLINE libMsgPropsGetExpiration    #-}
{-# INLINE libMsgPropsGetNumAttempts   #-}
{-# INLINE libMsgPropsGetOriginalMsgId #-}
{-# INLINE libMsgPropsGetPriority      #-}
{-# INLINE libMsgPropsGetState         #-}
{-# INLINE libMsgPropsRelease          #-}
{-# INLINE libMsgPropsSetCorrelation   #-}
{-# INLINE libMsgPropsSetDelay         #-}
{-# INLINE libMsgPropsSetExceptionQ    #-}
{-# INLINE libMsgPropsSetExpiration    #-}
{-# INLINE libMsgPropsSetOriginalMsgId #-}
{-# INLINE libMsgPropsSetPriority      #-}
libMsgPropsAddRef           = dpiMsgProps_addRef
{-# LINE 1263 "src/Database/Dpi/Internal.chs" #-}

libMsgPropsGetCorrelation   = dpiMsgProps_getCorrelation
{-# LINE 1264 "src/Database/Dpi/Internal.chs" #-}

libMsgPropsGetDelay         = dpiMsgProps_getDelay
{-# LINE 1265 "src/Database/Dpi/Internal.chs" #-}

libMsgPropsGetDeliveryMode  = dpiMsgProps_getDeliveryMode
{-# LINE 1266 "src/Database/Dpi/Internal.chs" #-}

libMsgPropsGetEnqTime       = dpiMsgProps_getEnqTime
{-# LINE 1267 "src/Database/Dpi/Internal.chs" #-}

libMsgPropsGetExceptionQ    = dpiMsgProps_getExceptionQ
{-# LINE 1268 "src/Database/Dpi/Internal.chs" #-}

libMsgPropsGetExpiration    = dpiMsgProps_getExpiration
{-# LINE 1269 "src/Database/Dpi/Internal.chs" #-}

libMsgPropsGetNumAttempts   = dpiMsgProps_getNumAttempts
{-# LINE 1270 "src/Database/Dpi/Internal.chs" #-}

libMsgPropsGetOriginalMsgId = dpiMsgProps_getOriginalMsgId
{-# LINE 1271 "src/Database/Dpi/Internal.chs" #-}

libMsgPropsGetPriority      = dpiMsgProps_getPriority
{-# LINE 1272 "src/Database/Dpi/Internal.chs" #-}

libMsgPropsGetState         = dpiMsgProps_getState
{-# LINE 1273 "src/Database/Dpi/Internal.chs" #-}

libMsgPropsRelease          = dpiMsgProps_release
{-# LINE 1274 "src/Database/Dpi/Internal.chs" #-}

libMsgPropsSetCorrelation   = dpiMsgProps_setCorrelation
{-# LINE 1275 "src/Database/Dpi/Internal.chs" #-}

libMsgPropsSetDelay         = dpiMsgProps_setDelay
{-# LINE 1276 "src/Database/Dpi/Internal.chs" #-}

libMsgPropsSetExceptionQ    = dpiMsgProps_setExceptionQ
{-# LINE 1277 "src/Database/Dpi/Internal.chs" #-}

libMsgPropsSetExpiration    = dpiMsgProps_setExpiration
{-# LINE 1278 "src/Database/Dpi/Internal.chs" #-}

libMsgPropsSetOriginalMsgId = dpiMsgProps_setOriginalMsgId
{-# LINE 1279 "src/Database/Dpi/Internal.chs" #-}

libMsgPropsSetPriority      = dpiMsgProps_setPriority
{-# LINE 1280 "src/Database/Dpi/Internal.chs" #-}


-- Object
{-# INLINE libObjectAddRef                  #-}
{-# INLINE libObjectAppendElement           #-}
{-# INLINE libObjectCopy                    #-}
{-# INLINE libObjectDeleteElementByIndex    #-}
{-# INLINE libObjectGetAttributeValue       #-}
{-# INLINE libObjectGetElementExistsByIndex #-}
{-# INLINE libObjectGetElementValueByIndex  #-}
{-# INLINE libObjectGetFirstIndex           #-}
{-# INLINE libObjectGetLastIndex            #-}
{-# INLINE libObjectGetNextIndex            #-}
{-# INLINE libObjectGetPrevIndex            #-}
{-# INLINE libObjectGetSize                 #-}
{-# INLINE libObjectRelease                 #-}
{-# INLINE libObjectSetAttributeValue       #-}
{-# INLINE libObjectSetElementValueByIndex  #-}
{-# INLINE libObjectTrim                    #-}
libObjectAddRef                  = dpiObject_addRef
{-# LINE 1299 "src/Database/Dpi/Internal.chs" #-}

libObjectAppendElement           = dpiObject_appendElement
{-# LINE 1300 "src/Database/Dpi/Internal.chs" #-}

libObjectCopy                    = dpiObject_copy
{-# LINE 1301 "src/Database/Dpi/Internal.chs" #-}

libObjectDeleteElementByIndex    = dpiObject_deleteElementByIndex
{-# LINE 1302 "src/Database/Dpi/Internal.chs" #-}

libObjectGetAttributeValue       = dpiObject_getAttributeValue
{-# LINE 1303 "src/Database/Dpi/Internal.chs" #-}

libObjectGetElementExistsByIndex = dpiObject_getElementExistsByIndex
{-# LINE 1304 "src/Database/Dpi/Internal.chs" #-}

libObjectGetElementValueByIndex  = dpiObject_getElementValueByIndex
{-# LINE 1305 "src/Database/Dpi/Internal.chs" #-}

libObjectGetFirstIndex           = dpiObject_getFirstIndex
{-# LINE 1306 "src/Database/Dpi/Internal.chs" #-}

libObjectGetLastIndex            = dpiObject_getLastIndex
{-# LINE 1307 "src/Database/Dpi/Internal.chs" #-}

libObjectGetNextIndex            = dpiObject_getNextIndex
{-# LINE 1308 "src/Database/Dpi/Internal.chs" #-}

libObjectGetPrevIndex            = dpiObject_getPrevIndex
{-# LINE 1309 "src/Database/Dpi/Internal.chs" #-}

libObjectGetSize                 = dpiObject_getSize
{-# LINE 1310 "src/Database/Dpi/Internal.chs" #-}

libObjectRelease                 = dpiObject_release
{-# LINE 1311 "src/Database/Dpi/Internal.chs" #-}

libObjectSetAttributeValue       = dpiObject_setAttributeValue
{-# LINE 1312 "src/Database/Dpi/Internal.chs" #-}

libObjectSetElementValueByIndex  = dpiObject_setElementValueByIndex
{-# LINE 1313 "src/Database/Dpi/Internal.chs" #-}

libObjectTrim                    = dpiObject_trim
{-# LINE 1314 "src/Database/Dpi/Internal.chs" #-}


-- ObjectAttr
{-# INLINE libObjectAttrAddRef  #-}
{-# INLINE libObjectAttrGetInfo #-}
{-# INLINE libObjectAttrRelease #-}
libObjectAttrAddRef  = dpiObjectAttr_addRef
{-# LINE 1320 "src/Database/Dpi/Internal.chs" #-}

libObjectAttrGetInfo = dpiObjectAttr_getInfo
{-# LINE 1321 "src/Database/Dpi/Internal.chs" #-}

libObjectAttrRelease = dpiObjectAttr_release
{-# LINE 1322 "src/Database/Dpi/Internal.chs" #-}


-- ObjectType
{-# INLINE libObjectTypeAddRef        #-}
{-# INLINE libObjectTypeCreateObject  #-}
{-# INLINE libObjectTypeGetAttributes #-}
{-# INLINE libObjectTypeGetInfo       #-}
{-# INLINE libObjectTypeRelease       #-}
libObjectTypeAddRef        = dpiObjectType_addRef
{-# LINE 1330 "src/Database/Dpi/Internal.chs" #-}

libObjectTypeCreateObject  = dpiObjectType_createObject
{-# LINE 1331 "src/Database/Dpi/Internal.chs" #-}

libObjectTypeGetAttributes = dpiObjectType_getAttributes
{-# LINE 1332 "src/Database/Dpi/Internal.chs" #-}

libObjectTypeGetInfo       = dpiObjectType_getInfo
{-# LINE 1333 "src/Database/Dpi/Internal.chs" #-}

libObjectTypeRelease       = dpiObjectType_release
{-# LINE 1334 "src/Database/Dpi/Internal.chs" #-}


-- Pool
{-# INLINE libPoolAcquireConnection     #-}
{-# INLINE libPoolAddRef                #-}
{-# INLINE libPoolClose                 #-}
{-# INLINE libPoolCreate                #-}
{-# INLINE libPoolGetBusyCount          #-}
{-# INLINE libPoolGetEncodingInfo       #-}
{-# INLINE libPoolGetGetMode            #-}
{-# INLINE libPoolGetMaxLifetimeSession #-}
{-# INLINE libPoolGetOpenCount          #-}
{-# INLINE libPoolGetStmtCacheSize      #-}
{-# INLINE libPoolGetTimeout            #-}
{-# INLINE libPoolRelease               #-}
{-# INLINE libPoolSetGetMode            #-}
{-# INLINE libPoolSetMaxLifetimeSession #-}
{-# INLINE libPoolSetStmtCacheSize      #-}
{-# INLINE libPoolSetTimeout            #-}
libPoolAcquireConnection     = dpiPool_acquireConnection
{-# LINE 1353 "src/Database/Dpi/Internal.chs" #-}

libPoolAddRef                = dpiPool_addRef
{-# LINE 1354 "src/Database/Dpi/Internal.chs" #-}

libPoolClose                 = dpiPool_close
{-# LINE 1355 "src/Database/Dpi/Internal.chs" #-}

libPoolCreate                = dpiPool_create
{-# LINE 1356 "src/Database/Dpi/Internal.chs" #-}

libPoolGetBusyCount          = dpiPool_getBusyCount
{-# LINE 1357 "src/Database/Dpi/Internal.chs" #-}

libPoolGetEncodingInfo       = dpiPool_getEncodingInfo
{-# LINE 1358 "src/Database/Dpi/Internal.chs" #-}

libPoolGetGetMode            = dpiPool_getGetMode
{-# LINE 1359 "src/Database/Dpi/Internal.chs" #-}

libPoolGetMaxLifetimeSession = dpiPool_getMaxLifetimeSession
{-# LINE 1360 "src/Database/Dpi/Internal.chs" #-}

libPoolGetOpenCount          = dpiPool_getOpenCount
{-# LINE 1361 "src/Database/Dpi/Internal.chs" #-}

libPoolGetStmtCacheSize      = dpiPool_getStmtCacheSize
{-# LINE 1362 "src/Database/Dpi/Internal.chs" #-}

libPoolGetTimeout            = dpiPool_getTimeout
{-# LINE 1363 "src/Database/Dpi/Internal.chs" #-}

libPoolRelease               = dpiPool_release
{-# LINE 1364 "src/Database/Dpi/Internal.chs" #-}

libPoolSetGetMode            = dpiPool_setGetMode
{-# LINE 1365 "src/Database/Dpi/Internal.chs" #-}

libPoolSetMaxLifetimeSession = dpiPool_setMaxLifetimeSession
{-# LINE 1366 "src/Database/Dpi/Internal.chs" #-}

libPoolSetStmtCacheSize      = dpiPool_setStmtCacheSize
{-# LINE 1367 "src/Database/Dpi/Internal.chs" #-}

libPoolSetTimeout            = dpiPool_setTimeout
{-# LINE 1368 "src/Database/Dpi/Internal.chs" #-}


-- Stmt
{-# INLINE libStmtAddRef             #-}
{-# INLINE libStmtBindByName         #-}
{-# INLINE libStmtBindByPos          #-}
{-# INLINE libStmtBindValueByName    #-}
{-# INLINE libStmtBindValueByPos     #-}
{-# INLINE libStmtClose              #-}
{-# INLINE libStmtDefine             #-}
{-# INLINE libStmtDefineValue        #-}
{-# INLINE libStmtExecute            #-}
{-# INLINE libStmtExecuteMany        #-}
{-# INLINE libStmtFetch              #-}
{-# INLINE libStmtFetchRows          #-}
{-# INLINE libStmtGetBatchErrorCount #-}
{-# INLINE libStmtGetBatchErrors     #-}
{-# INLINE libStmtGetBindCount       #-}
{-# INLINE libStmtGetBindNames       #-}
{-# INLINE libStmtGetFetchArraySize  #-}
{-# INLINE libStmtGetImplicitResult  #-}
{-# INLINE libStmtGetInfo            #-}
{-# INLINE libStmtGetNumQueryColumns #-}
{-# INLINE libStmtGetQueryInfo       #-}
{-# INLINE libStmtGetQueryValue      #-}
{-# INLINE libStmtGetRowCount        #-}
{-# INLINE libStmtGetRowCounts       #-}
{-# INLINE libStmtGetSubscrQueryId   #-}
{-# INLINE libStmtRelease            #-}
{-# INLINE libStmtScroll             #-}
{-# INLINE libStmtSetFetchArraySize  #-}
libStmtAddRef             = dpiStmt_addRef
{-# LINE 1399 "src/Database/Dpi/Internal.chs" #-}

libStmtBindByName         = dpiStmt_bindByName
{-# LINE 1400 "src/Database/Dpi/Internal.chs" #-}

libStmtBindByPos          = dpiStmt_bindByPos
{-# LINE 1401 "src/Database/Dpi/Internal.chs" #-}

libStmtBindValueByName    = dpiStmt_bindValueByName
{-# LINE 1402 "src/Database/Dpi/Internal.chs" #-}

libStmtBindValueByPos     = dpiStmt_bindValueByPos
{-# LINE 1403 "src/Database/Dpi/Internal.chs" #-}

libStmtClose              = dpiStmt_close
{-# LINE 1404 "src/Database/Dpi/Internal.chs" #-}

libStmtDefine             = dpiStmt_define
{-# LINE 1405 "src/Database/Dpi/Internal.chs" #-}

libStmtDefineValue        = dpiStmt_defineValue
{-# LINE 1406 "src/Database/Dpi/Internal.chs" #-}

libStmtExecute            = dpiStmt_execute
{-# LINE 1407 "src/Database/Dpi/Internal.chs" #-}

libStmtExecuteMany        = dpiStmt_executeMany
{-# LINE 1408 "src/Database/Dpi/Internal.chs" #-}

libStmtFetch              = dpiStmt_fetch
{-# LINE 1409 "src/Database/Dpi/Internal.chs" #-}

libStmtFetchRows          = dpiStmt_fetchRows
{-# LINE 1410 "src/Database/Dpi/Internal.chs" #-}

libStmtGetBatchErrorCount = dpiStmt_getBatchErrorCount
{-# LINE 1411 "src/Database/Dpi/Internal.chs" #-}

libStmtGetBatchErrors     = dpiStmt_getBatchErrors
{-# LINE 1412 "src/Database/Dpi/Internal.chs" #-}

libStmtGetBindCount       = dpiStmt_getBindCount
{-# LINE 1413 "src/Database/Dpi/Internal.chs" #-}

libStmtGetBindNames       = dpiStmt_getBindNames
{-# LINE 1414 "src/Database/Dpi/Internal.chs" #-}

libStmtGetFetchArraySize  = dpiStmt_getFetchArraySize
{-# LINE 1415 "src/Database/Dpi/Internal.chs" #-}

libStmtGetImplicitResult  = dpiStmt_getImplicitResult
{-# LINE 1416 "src/Database/Dpi/Internal.chs" #-}

libStmtGetInfo            = dpiStmt_getInfo
{-# LINE 1417 "src/Database/Dpi/Internal.chs" #-}

libStmtGetNumQueryColumns = dpiStmt_getNumQueryColumns
{-# LINE 1418 "src/Database/Dpi/Internal.chs" #-}

libStmtGetQueryInfo       = dpiStmt_getQueryInfo
{-# LINE 1419 "src/Database/Dpi/Internal.chs" #-}

libStmtGetQueryValue      = dpiStmt_getQueryValue
{-# LINE 1420 "src/Database/Dpi/Internal.chs" #-}

libStmtGetRowCount        = dpiStmt_getRowCount
{-# LINE 1421 "src/Database/Dpi/Internal.chs" #-}

libStmtGetRowCounts       = dpiStmt_getRowCounts
{-# LINE 1422 "src/Database/Dpi/Internal.chs" #-}

libStmtGetSubscrQueryId   = dpiStmt_getSubscrQueryId
{-# LINE 1423 "src/Database/Dpi/Internal.chs" #-}

libStmtRelease            = dpiStmt_release
{-# LINE 1424 "src/Database/Dpi/Internal.chs" #-}

libStmtScroll             = dpiStmt_scroll
{-# LINE 1425 "src/Database/Dpi/Internal.chs" #-}

libStmtSetFetchArraySize  = dpiStmt_setFetchArraySize
{-# LINE 1426 "src/Database/Dpi/Internal.chs" #-}


-- RowId
{-# INLINE libRowidAddRef         #-}
{-# INLINE libRowidGetStringValue #-}
{-# INLINE libRowidRelease        #-}
libRowidAddRef         = dpiRowid_addRef
{-# LINE 1432 "src/Database/Dpi/Internal.chs" #-}

libRowidGetStringValue = dpiRowid_getStringValue
{-# LINE 1433 "src/Database/Dpi/Internal.chs" #-}

libRowidRelease        = dpiRowid_release
{-# LINE 1434 "src/Database/Dpi/Internal.chs" #-}


-- Subscr
{-# INLINE libSubscrAddRef      #-}
{-# INLINE libSubscrClose       #-}
{-# INLINE libSubscrPrepareStmt #-}
{-# INLINE libSubscrRelease     #-}
libSubscrAddRef      = dpiSubscr_addRef
{-# LINE 1441 "src/Database/Dpi/Internal.chs" #-}

libSubscrClose       = dpiSubscr_close
{-# LINE 1442 "src/Database/Dpi/Internal.chs" #-}

libSubscrPrepareStmt = dpiSubscr_prepareStmt
{-# LINE 1443 "src/Database/Dpi/Internal.chs" #-}

libSubscrRelease     = dpiSubscr_release
{-# LINE 1444 "src/Database/Dpi/Internal.chs" #-}


-- Var
{-# INLINE libVarAddRef                #-}
{-# INLINE libVarCopyData              #-}
{-# INLINE libVarGetData               #-}
{-# INLINE libVarGetNumElementsInArray #-}
{-# INLINE libVarGetSizeInBytes        #-}
{-# INLINE libVarRelease               #-}
{-# INLINE libVarSetFromBytes          #-}
{-# INLINE libVarSetFromLob            #-}
{-# INLINE libVarSetFromObject         #-}
{-# INLINE libVarSetFromRowid          #-}
{-# INLINE libVarSetFromStmt           #-}
{-# INLINE libVarSetNumElementsInArray #-}
libVarAddRef                = dpiVar_addRef
{-# LINE 1459 "src/Database/Dpi/Internal.chs" #-}

libVarCopyData              = dpiVar_copyData
{-# LINE 1460 "src/Database/Dpi/Internal.chs" #-}

libVarGetData               = dpiVar_getData
{-# LINE 1461 "src/Database/Dpi/Internal.chs" #-}

libVarGetNumElementsInArray = dpiVar_getNumElementsInArray
{-# LINE 1462 "src/Database/Dpi/Internal.chs" #-}

libVarGetSizeInBytes        = dpiVar_getSizeInBytes
{-# LINE 1463 "src/Database/Dpi/Internal.chs" #-}

libVarRelease               = dpiVar_release
{-# LINE 1464 "src/Database/Dpi/Internal.chs" #-}

libVarSetFromBytes          = dpiVar_setFromBytes
{-# LINE 1465 "src/Database/Dpi/Internal.chs" #-}

libVarSetFromLob            = dpiVar_setFromLob
{-# LINE 1466 "src/Database/Dpi/Internal.chs" #-}

libVarSetFromObject         = dpiVar_setFromObject
{-# LINE 1467 "src/Database/Dpi/Internal.chs" #-}

libVarSetFromRowid          = dpiVar_setFromRowid
{-# LINE 1468 "src/Database/Dpi/Internal.chs" #-}

libVarSetFromStmt           = dpiVar_setFromStmt
{-# LINE 1469 "src/Database/Dpi/Internal.chs" #-}

libVarSetNumElementsInArray = dpiVar_setNumElementsInArray
{-# LINE 1002 "src/Database/Dpi/Internal.chs" #-}

foreign import ccall safe "Database/Dpi/Internal.chs.h dpiContext_create"
  dpiContext_create :: (C2HSImp.CUInt -> (C2HSImp.CUInt -> ((C2HSImp.Ptr (C2HSImp.Ptr (DPI_Context))) -> ((PtrErrorInfo) -> (IO C2HSImp.CInt)))))

foreign import ccall safe "Database/Dpi/Internal.chs.h dpiContext_destroy"
  dpiContext_destroy :: ((C2HSImp.Ptr (DPI_Context)) -> (IO C2HSImp.CInt))

foreign import ccall safe "Database/Dpi/Internal.chs.h dpiContext_getClientVersion"
  dpiContext_getClientVersion :: ((C2HSImp.Ptr (DPI_Context)) -> ((PtrVersionInfo) -> (IO C2HSImp.CInt)))

foreign import ccall safe "Database/Dpi/Internal.chs.h dpiContext_initCommonCreateParams"
  dpiContext_initCommonCreateParams :: ((C2HSImp.Ptr (DPI_Context)) -> ((PtrCommonCreateParams) -> (IO C2HSImp.CInt)))

foreign import ccall safe "Database/Dpi/Internal.chs.h dpiContext_initConnCreateParams"
  dpiContext_initConnCreateParams :: ((C2HSImp.Ptr (DPI_Context)) -> ((PtrConnCreateParams) -> (IO C2HSImp.CInt)))

foreign import ccall safe "Database/Dpi/Internal.chs.h dpiContext_initPoolCreateParams"
  dpiContext_initPoolCreateParams :: ((C2HSImp.Ptr (DPI_Context)) -> ((PtrPoolCreateParams) -> (IO C2HSImp.CInt)))

foreign import ccall safe "Database/Dpi/Internal.chs.h dpiContext_initSubscrCreateParams"
  dpiContext_initSubscrCreateParams :: ((C2HSImp.Ptr (DPI_Context)) -> ((PtrSubscrCreateParams) -> (IO C2HSImp.CInt)))

foreign import ccall safe "Database/Dpi/Internal.chs.h dpiContext_getError"
  dpiContext_getError :: ((C2HSImp.Ptr (DPI_Context)) -> ((PtrErrorInfo) -> (IO ())))

foreign import ccall safe "Database/Dpi/Internal.chs.h dpiConn_addRef"
  dpiConn_addRef :: ((C2HSImp.Ptr (DPI_Conn)) -> (IO C2HSImp.CInt))

foreign import ccall safe "Database/Dpi/Internal.chs.h dpiConn_beginDistribTrans"
  dpiConn_beginDistribTrans :: ((C2HSImp.Ptr (DPI_Conn)) -> (C2HSImp.CLong -> ((C2HSImp.Ptr C2HSImp.CChar) -> (C2HSImp.CUInt -> ((C2HSImp.Ptr C2HSImp.CChar) -> (C2HSImp.CUInt -> (IO C2HSImp.CInt)))))))

foreign import ccall safe "Database/Dpi/Internal.chs.h dpiConn_breakExecution"
  dpiConn_breakExecution :: ((C2HSImp.Ptr (DPI_Conn)) -> (IO C2HSImp.CInt))

foreign import ccall safe "Database/Dpi/Internal.chs.h dpiConn_changePassword"
  dpiConn_changePassword :: ((C2HSImp.Ptr (DPI_Conn)) -> ((C2HSImp.Ptr C2HSImp.CChar) -> (C2HSImp.CUInt -> ((C2HSImp.Ptr C2HSImp.CChar) -> (C2HSImp.CUInt -> ((C2HSImp.Ptr C2HSImp.CChar) -> (C2HSImp.CUInt -> (IO C2HSImp.CInt))))))))

foreign import ccall safe "Database/Dpi/Internal.chs.h dpiConn_close"
  dpiConn_close :: ((C2HSImp.Ptr (DPI_Conn)) -> (C2HSImp.CInt -> ((C2HSImp.Ptr C2HSImp.CChar) -> (C2HSImp.CUInt -> (IO C2HSImp.CInt)))))

foreign import ccall safe "Database/Dpi/Internal.chs.h dpiConn_commit"
  dpiConn_commit :: ((C2HSImp.Ptr (DPI_Conn)) -> (IO C2HSImp.CInt))

foreign import ccall safe "Database/Dpi/Internal.chs.h dpiConn_create"
  dpiConn_create :: ((C2HSImp.Ptr (DPI_Context)) -> ((C2HSImp.Ptr C2HSImp.CChar) -> (C2HSImp.CUInt -> ((C2HSImp.Ptr C2HSImp.CChar) -> (C2HSImp.CUInt -> ((C2HSImp.Ptr C2HSImp.CChar) -> (C2HSImp.CUInt -> ((PtrCommonCreateParams) -> ((PtrConnCreateParams) -> ((C2HSImp.Ptr (C2HSImp.Ptr (DPI_Conn))) -> (IO C2HSImp.CInt)))))))))))

foreign import ccall safe "Database/Dpi/Internal.chs.h dpiConn_deqObject"
  dpiConn_deqObject :: ((C2HSImp.Ptr (DPI_Conn)) -> ((C2HSImp.Ptr C2HSImp.CChar) -> (C2HSImp.CUInt -> ((C2HSImp.Ptr (DPI_DeqOptions)) -> ((C2HSImp.Ptr (DPI_MsgProps)) -> ((C2HSImp.Ptr (DPI_Object)) -> ((C2HSImp.Ptr (C2HSImp.Ptr C2HSImp.CChar)) -> ((C2HSImp.Ptr C2HSImp.CUInt) -> (IO C2HSImp.CInt)))))))))

foreign import ccall safe "Database/Dpi/Internal.chs.h dpiConn_enqObject"
  dpiConn_enqObject :: ((C2HSImp.Ptr (DPI_Conn)) -> ((C2HSImp.Ptr C2HSImp.CChar) -> (C2HSImp.CUInt -> ((C2HSImp.Ptr (DPI_EnqOptions)) -> ((C2HSImp.Ptr (DPI_MsgProps)) -> ((C2HSImp.Ptr (DPI_Object)) -> ((C2HSImp.Ptr (C2HSImp.Ptr C2HSImp.CChar)) -> ((C2HSImp.Ptr C2HSImp.CUInt) -> (IO C2HSImp.CInt)))))))))

foreign import ccall safe "Database/Dpi/Internal.chs.h dpiConn_getCurrentSchema"
  dpiConn_getCurrentSchema :: ((C2HSImp.Ptr (DPI_Conn)) -> ((C2HSImp.Ptr (C2HSImp.Ptr C2HSImp.CChar)) -> ((C2HSImp.Ptr C2HSImp.CUInt) -> (IO C2HSImp.CInt))))

foreign import ccall safe "Database/Dpi/Internal.chs.h dpiConn_getEdition"
  dpiConn_getEdition :: ((C2HSImp.Ptr (DPI_Conn)) -> ((C2HSImp.Ptr (C2HSImp.Ptr C2HSImp.CChar)) -> ((C2HSImp.Ptr C2HSImp.CUInt) -> (IO C2HSImp.CInt))))

foreign import ccall safe "Database/Dpi/Internal.chs.h dpiConn_getEncodingInfo"
  dpiConn_getEncodingInfo :: ((C2HSImp.Ptr (DPI_Conn)) -> ((PtrEncodingInfo) -> (IO C2HSImp.CInt)))

foreign import ccall safe "Database/Dpi/Internal.chs.h dpiConn_getExternalName"
  dpiConn_getExternalName :: ((C2HSImp.Ptr (DPI_Conn)) -> ((C2HSImp.Ptr (C2HSImp.Ptr C2HSImp.CChar)) -> ((C2HSImp.Ptr C2HSImp.CUInt) -> (IO C2HSImp.CInt))))

foreign import ccall safe "Database/Dpi/Internal.chs.h dpiConn_getHandle"
  dpiConn_getHandle :: ((C2HSImp.Ptr (DPI_Conn)) -> ((C2HSImp.Ptr (C2HSImp.Ptr ())) -> (IO C2HSImp.CInt)))

foreign import ccall safe "Database/Dpi/Internal.chs.h dpiConn_getInternalName"
  dpiConn_getInternalName :: ((C2HSImp.Ptr (DPI_Conn)) -> ((C2HSImp.Ptr (C2HSImp.Ptr C2HSImp.CChar)) -> ((C2HSImp.Ptr C2HSImp.CUInt) -> (IO C2HSImp.CInt))))

foreign import ccall safe "Database/Dpi/Internal.chs.h dpiConn_getLTXID"
  dpiConn_getLTXID :: ((C2HSImp.Ptr (DPI_Conn)) -> ((C2HSImp.Ptr (C2HSImp.Ptr C2HSImp.CChar)) -> ((C2HSImp.Ptr C2HSImp.CUInt) -> (IO C2HSImp.CInt))))

foreign import ccall safe "Database/Dpi/Internal.chs.h dpiConn_getObjectType"
  dpiConn_getObjectType :: ((C2HSImp.Ptr (DPI_Conn)) -> ((C2HSImp.Ptr C2HSImp.CChar) -> (C2HSImp.CUInt -> ((C2HSImp.Ptr (C2HSImp.Ptr (DPI_ObjectType))) -> (IO C2HSImp.CInt)))))

foreign import ccall safe "Database/Dpi/Internal.chs.h dpiConn_getServerVersion"
  dpiConn_getServerVersion :: ((C2HSImp.Ptr (DPI_Conn)) -> ((C2HSImp.Ptr (C2HSImp.Ptr C2HSImp.CChar)) -> ((C2HSImp.Ptr C2HSImp.CUInt) -> ((PtrVersionInfo) -> (IO C2HSImp.CInt)))))

foreign import ccall safe "Database/Dpi/Internal.chs.h dpiConn_getStmtCacheSize"
  dpiConn_getStmtCacheSize :: ((C2HSImp.Ptr (DPI_Conn)) -> ((C2HSImp.Ptr C2HSImp.CUInt) -> (IO C2HSImp.CInt)))

foreign import ccall safe "Database/Dpi/Internal.chs.h dpiConn_newDeqOptions"
  dpiConn_newDeqOptions :: ((C2HSImp.Ptr (DPI_Conn)) -> ((C2HSImp.Ptr (C2HSImp.Ptr (DPI_DeqOptions))) -> (IO C2HSImp.CInt)))

foreign import ccall safe "Database/Dpi/Internal.chs.h dpiConn_newEnqOptions"
  dpiConn_newEnqOptions :: ((C2HSImp.Ptr (DPI_Conn)) -> ((C2HSImp.Ptr (C2HSImp.Ptr (DPI_EnqOptions))) -> (IO C2HSImp.CInt)))

foreign import ccall safe "Database/Dpi/Internal.chs.h dpiConn_newMsgProps"
  dpiConn_newMsgProps :: ((C2HSImp.Ptr (DPI_Conn)) -> ((C2HSImp.Ptr (C2HSImp.Ptr (DPI_MsgProps))) -> (IO C2HSImp.CInt)))

foreign import ccall safe "Database/Dpi/Internal.chs.h dpiConn_newSubscription"
  dpiConn_newSubscription :: ((C2HSImp.Ptr (DPI_Conn)) -> ((PtrSubscrCreateParams) -> ((C2HSImp.Ptr (C2HSImp.Ptr (DPI_Subscr))) -> ((C2HSImp.Ptr C2HSImp.CULLong) -> (IO C2HSImp.CInt)))))

foreign import ccall safe "Database/Dpi/Internal.chs.h dpiConn_newTempLob"
  dpiConn_newTempLob :: ((C2HSImp.Ptr (DPI_Conn)) -> (C2HSImp.CInt -> ((C2HSImp.Ptr (C2HSImp.Ptr (DPI_Lob))) -> (IO C2HSImp.CInt))))

foreign import ccall safe "Database/Dpi/Internal.chs.h dpiConn_newVar"
  dpiConn_newVar :: ((C2HSImp.Ptr (DPI_Conn)) -> (C2HSImp.CInt -> (C2HSImp.CInt -> (C2HSImp.CUInt -> (C2HSImp.CUInt -> (C2HSImp.CInt -> (C2HSImp.CInt -> ((C2HSImp.Ptr (DPI_ObjectType)) -> ((C2HSImp.Ptr (C2HSImp.Ptr (DPI_Var))) -> ((C2HSImp.Ptr (PtrData)) -> (IO C2HSImp.CInt)))))))))))

foreign import ccall safe "Database/Dpi/Internal.chs.h dpiConn_ping"
  dpiConn_ping :: ((C2HSImp.Ptr (DPI_Conn)) -> (IO C2HSImp.CInt))

foreign import ccall safe "Database/Dpi/Internal.chs.h dpiConn_prepareDistribTrans"
  dpiConn_prepareDistribTrans :: ((C2HSImp.Ptr (DPI_Conn)) -> ((C2HSImp.Ptr C2HSImp.CInt) -> (IO C2HSImp.CInt)))

foreign import ccall safe "Database/Dpi/Internal.chs.h dpiConn_prepareStmt"
  dpiConn_prepareStmt :: ((C2HSImp.Ptr (DPI_Conn)) -> (C2HSImp.CInt -> ((C2HSImp.Ptr C2HSImp.CChar) -> (C2HSImp.CUInt -> ((C2HSImp.Ptr C2HSImp.CChar) -> (C2HSImp.CUInt -> ((C2HSImp.Ptr (C2HSImp.Ptr (DPI_Stmt))) -> (IO C2HSImp.CInt))))))))

foreign import ccall safe "Database/Dpi/Internal.chs.h dpiConn_release"
  dpiConn_release :: ((C2HSImp.Ptr (DPI_Conn)) -> (IO C2HSImp.CInt))

foreign import ccall safe "Database/Dpi/Internal.chs.h dpiConn_rollback"
  dpiConn_rollback :: ((C2HSImp.Ptr (DPI_Conn)) -> (IO C2HSImp.CInt))

foreign import ccall safe "Database/Dpi/Internal.chs.h dpiConn_setAction"
  dpiConn_setAction :: ((C2HSImp.Ptr (DPI_Conn)) -> ((C2HSImp.Ptr C2HSImp.CChar) -> (C2HSImp.CUInt -> (IO C2HSImp.CInt))))

foreign import ccall safe "Database/Dpi/Internal.chs.h dpiConn_setClientIdentifier"
  dpiConn_setClientIdentifier :: ((C2HSImp.Ptr (DPI_Conn)) -> ((C2HSImp.Ptr C2HSImp.CChar) -> (C2HSImp.CUInt -> (IO C2HSImp.CInt))))

foreign import ccall safe "Database/Dpi/Internal.chs.h dpiConn_setClientInfo"
  dpiConn_setClientInfo :: ((C2HSImp.Ptr (DPI_Conn)) -> ((C2HSImp.Ptr C2HSImp.CChar) -> (C2HSImp.CUInt -> (IO C2HSImp.CInt))))

foreign import ccall safe "Database/Dpi/Internal.chs.h dpiConn_setCurrentSchema"
  dpiConn_setCurrentSchema :: ((C2HSImp.Ptr (DPI_Conn)) -> ((C2HSImp.Ptr C2HSImp.CChar) -> (C2HSImp.CUInt -> (IO C2HSImp.CInt))))

foreign import ccall safe "Database/Dpi/Internal.chs.h dpiConn_setDbOp"
  dpiConn_setDbOp :: ((C2HSImp.Ptr (DPI_Conn)) -> ((C2HSImp.Ptr C2HSImp.CChar) -> (C2HSImp.CUInt -> (IO C2HSImp.CInt))))

foreign import ccall safe "Database/Dpi/Internal.chs.h dpiConn_setExternalName"
  dpiConn_setExternalName :: ((C2HSImp.Ptr (DPI_Conn)) -> ((C2HSImp.Ptr C2HSImp.CChar) -> (C2HSImp.CUInt -> (IO C2HSImp.CInt))))

foreign import ccall safe "Database/Dpi/Internal.chs.h dpiConn_setInternalName"
  dpiConn_setInternalName :: ((C2HSImp.Ptr (DPI_Conn)) -> ((C2HSImp.Ptr C2HSImp.CChar) -> (C2HSImp.CUInt -> (IO C2HSImp.CInt))))

foreign import ccall safe "Database/Dpi/Internal.chs.h dpiConn_setModule"
  dpiConn_setModule :: ((C2HSImp.Ptr (DPI_Conn)) -> ((C2HSImp.Ptr C2HSImp.CChar) -> (C2HSImp.CUInt -> (IO C2HSImp.CInt))))

foreign import ccall safe "Database/Dpi/Internal.chs.h dpiConn_setStmtCacheSize"
  dpiConn_setStmtCacheSize :: ((C2HSImp.Ptr (DPI_Conn)) -> (C2HSImp.CUInt -> (IO C2HSImp.CInt)))

foreign import ccall safe "Database/Dpi/Internal.chs.h dpiConn_shutdownDatabase"
  dpiConn_shutdownDatabase :: ((C2HSImp.Ptr (DPI_Conn)) -> (C2HSImp.CInt -> (IO C2HSImp.CInt)))

foreign import ccall safe "Database/Dpi/Internal.chs.h dpiConn_startupDatabase"
  dpiConn_startupDatabase :: ((C2HSImp.Ptr (DPI_Conn)) -> (C2HSImp.CInt -> (IO C2HSImp.CInt)))

foreign import ccall safe "Database/Dpi/Internal.chs.h dpiData_getDouble"
  dpiData_getDouble :: ((PtrData) -> (IO C2HSImp.CDouble))

foreign import ccall safe "Database/Dpi/Internal.chs.h dpiData_getBytes"
  dpiData_getBytes :: ((PtrData) -> (IO (Ptr_Bytes)))

foreign import ccall safe "Database/Dpi/Internal.chs.h dpiData_getIntervalDS"
  dpiData_getIntervalDS :: ((PtrData) -> (IO (Ptr_IntervalDS)))

foreign import ccall safe "Database/Dpi/Internal.chs.h dpiData_getIntervalYM"
  dpiData_getIntervalYM :: ((PtrData) -> (IO (Ptr_IntervalYM)))

foreign import ccall safe "Database/Dpi/Internal.chs.h dpiData_getLOB"
  dpiData_getLOB :: ((PtrData) -> (IO (C2HSImp.Ptr (DPI_Lob))))

foreign import ccall safe "Database/Dpi/Internal.chs.h dpiData_getObject"
  dpiData_getObject :: ((PtrData) -> (IO (C2HSImp.Ptr (DPI_Object))))

foreign import ccall safe "Database/Dpi/Internal.chs.h dpiData_getStmt"
  dpiData_getStmt :: ((PtrData) -> (IO (C2HSImp.Ptr (DPI_Stmt))))

foreign import ccall safe "Database/Dpi/Internal.chs.h dpiData_getTimestamp"
  dpiData_getTimestamp :: ((PtrData) -> (IO (Ptr_Timestamp)))

foreign import ccall safe "Database/Dpi/Internal.chs.h dpiData_getFloat"
  dpiData_getFloat :: ((PtrData) -> (IO C2HSImp.CFloat))

foreign import ccall safe "Database/Dpi/Internal.chs.h dpiData_getBool"
  dpiData_getBool :: ((PtrData) -> (IO C2HSImp.CInt))

foreign import ccall safe "Database/Dpi/Internal.chs.h dpiData_getInt64"
  dpiData_getInt64 :: ((PtrData) -> (IO C2HSImp.CLLong))

foreign import ccall safe "Database/Dpi/Internal.chs.h dpiData_getUint64"
  dpiData_getUint64 :: ((PtrData) -> (IO C2HSImp.CULLong))

foreign import ccall safe "Database/Dpi/Internal.chs.h dpiData_setBool"
  dpiData_setBool :: ((PtrData) -> (C2HSImp.CInt -> (IO ())))

foreign import ccall safe "Database/Dpi/Internal.chs.h dpiData_setBytes"
  dpiData_setBytes :: ((PtrData) -> ((C2HSImp.Ptr C2HSImp.CChar) -> (C2HSImp.CUInt -> (IO ()))))

foreign import ccall safe "Database/Dpi/Internal.chs.h dpiData_setDouble"
  dpiData_setDouble :: ((PtrData) -> (C2HSImp.CDouble -> (IO ())))

foreign import ccall safe "Database/Dpi/Internal.chs.h dpiData_setFloat"
  dpiData_setFloat :: ((PtrData) -> (C2HSImp.CFloat -> (IO ())))

foreign import ccall safe "Database/Dpi/Internal.chs.h dpiData_setInt64"
  dpiData_setInt64 :: ((PtrData) -> (C2HSImp.CLLong -> (IO ())))

foreign import ccall safe "Database/Dpi/Internal.chs.h dpiData_setIntervalDS"
  dpiData_setIntervalDS :: ((PtrData) -> (C2HSImp.CInt -> (C2HSImp.CInt -> (C2HSImp.CInt -> (C2HSImp.CInt -> (C2HSImp.CInt -> (IO ())))))))

foreign import ccall safe "Database/Dpi/Internal.chs.h dpiData_setIntervalYM"
  dpiData_setIntervalYM :: ((PtrData) -> (C2HSImp.CInt -> (C2HSImp.CInt -> (IO ()))))

foreign import ccall safe "Database/Dpi/Internal.chs.h dpiData_setLOB"
  dpiData_setLOB :: ((PtrData) -> ((C2HSImp.Ptr (DPI_Lob)) -> (IO ())))

foreign import ccall safe "Database/Dpi/Internal.chs.h dpiData_setObject"
  dpiData_setObject :: ((PtrData) -> ((C2HSImp.Ptr (DPI_Object)) -> (IO ())))

foreign import ccall safe "Database/Dpi/Internal.chs.h dpiData_setStmt"
  dpiData_setStmt :: ((PtrData) -> ((C2HSImp.Ptr (DPI_Stmt)) -> (IO ())))

foreign import ccall safe "Database/Dpi/Internal.chs.h dpiData_setTimestamp"
  dpiData_setTimestamp :: ((PtrData) -> (C2HSImp.CShort -> (C2HSImp.CUChar -> (C2HSImp.CUChar -> (C2HSImp.CUChar -> (C2HSImp.CUChar -> (C2HSImp.CUChar -> (C2HSImp.CUInt -> (C2HSImp.CSChar -> (C2HSImp.CSChar -> (IO ())))))))))))

foreign import ccall safe "Database/Dpi/Internal.chs.h dpiData_setUint64"
  dpiData_setUint64 :: ((PtrData) -> (C2HSImp.CULLong -> (IO ())))

foreign import ccall safe "Database/Dpi/Internal.chs.h dpiDeqOptions_addRef"
  dpiDeqOptions_addRef :: ((C2HSImp.Ptr (DPI_DeqOptions)) -> (IO C2HSImp.CInt))

foreign import ccall safe "Database/Dpi/Internal.chs.h dpiDeqOptions_getCondition"
  dpiDeqOptions_getCondition :: ((C2HSImp.Ptr (DPI_DeqOptions)) -> ((C2HSImp.Ptr (C2HSImp.Ptr C2HSImp.CChar)) -> ((C2HSImp.Ptr C2HSImp.CUInt) -> (IO C2HSImp.CInt))))

foreign import ccall safe "Database/Dpi/Internal.chs.h dpiDeqOptions_getConsumerName"
  dpiDeqOptions_getConsumerName :: ((C2HSImp.Ptr (DPI_DeqOptions)) -> ((C2HSImp.Ptr (C2HSImp.Ptr C2HSImp.CChar)) -> ((C2HSImp.Ptr C2HSImp.CUInt) -> (IO C2HSImp.CInt))))

foreign import ccall safe "Database/Dpi/Internal.chs.h dpiDeqOptions_getCorrelation"
  dpiDeqOptions_getCorrelation :: ((C2HSImp.Ptr (DPI_DeqOptions)) -> ((C2HSImp.Ptr (C2HSImp.Ptr C2HSImp.CChar)) -> ((C2HSImp.Ptr C2HSImp.CUInt) -> (IO C2HSImp.CInt))))

foreign import ccall safe "Database/Dpi/Internal.chs.h dpiDeqOptions_getMode"
  dpiDeqOptions_getMode :: ((C2HSImp.Ptr (DPI_DeqOptions)) -> ((C2HSImp.Ptr C2HSImp.CInt) -> (IO C2HSImp.CInt)))

foreign import ccall safe "Database/Dpi/Internal.chs.h dpiDeqOptions_getMsgId"
  dpiDeqOptions_getMsgId :: ((C2HSImp.Ptr (DPI_DeqOptions)) -> ((C2HSImp.Ptr (C2HSImp.Ptr C2HSImp.CChar)) -> ((C2HSImp.Ptr C2HSImp.CUInt) -> (IO C2HSImp.CInt))))

foreign import ccall safe "Database/Dpi/Internal.chs.h dpiDeqOptions_getNavigation"
  dpiDeqOptions_getNavigation :: ((C2HSImp.Ptr (DPI_DeqOptions)) -> ((C2HSImp.Ptr C2HSImp.CInt) -> (IO C2HSImp.CInt)))

foreign import ccall safe "Database/Dpi/Internal.chs.h dpiDeqOptions_getTransformation"
  dpiDeqOptions_getTransformation :: ((C2HSImp.Ptr (DPI_DeqOptions)) -> ((C2HSImp.Ptr (C2HSImp.Ptr C2HSImp.CChar)) -> ((C2HSImp.Ptr C2HSImp.CUInt) -> (IO C2HSImp.CInt))))

foreign import ccall safe "Database/Dpi/Internal.chs.h dpiDeqOptions_getVisibility"
  dpiDeqOptions_getVisibility :: ((C2HSImp.Ptr (DPI_DeqOptions)) -> ((C2HSImp.Ptr C2HSImp.CInt) -> (IO C2HSImp.CInt)))

foreign import ccall safe "Database/Dpi/Internal.chs.h dpiDeqOptions_getWait"
  dpiDeqOptions_getWait :: ((C2HSImp.Ptr (DPI_DeqOptions)) -> ((C2HSImp.Ptr C2HSImp.CUInt) -> (IO C2HSImp.CInt)))

foreign import ccall safe "Database/Dpi/Internal.chs.h dpiDeqOptions_release"
  dpiDeqOptions_release :: ((C2HSImp.Ptr (DPI_DeqOptions)) -> (IO C2HSImp.CInt))

foreign import ccall safe "Database/Dpi/Internal.chs.h dpiDeqOptions_setCondition"
  dpiDeqOptions_setCondition :: ((C2HSImp.Ptr (DPI_DeqOptions)) -> ((C2HSImp.Ptr C2HSImp.CChar) -> (C2HSImp.CUInt -> (IO C2HSImp.CInt))))

foreign import ccall safe "Database/Dpi/Internal.chs.h dpiDeqOptions_setConsumerName"
  dpiDeqOptions_setConsumerName :: ((C2HSImp.Ptr (DPI_DeqOptions)) -> ((C2HSImp.Ptr C2HSImp.CChar) -> (C2HSImp.CUInt -> (IO C2HSImp.CInt))))

foreign import ccall safe "Database/Dpi/Internal.chs.h dpiDeqOptions_setCorrelation"
  dpiDeqOptions_setCorrelation :: ((C2HSImp.Ptr (DPI_DeqOptions)) -> ((C2HSImp.Ptr C2HSImp.CChar) -> (C2HSImp.CUInt -> (IO C2HSImp.CInt))))

foreign import ccall safe "Database/Dpi/Internal.chs.h dpiDeqOptions_setDeliveryMode"
  dpiDeqOptions_setDeliveryMode :: ((C2HSImp.Ptr (DPI_DeqOptions)) -> (C2HSImp.CInt -> (IO C2HSImp.CInt)))

foreign import ccall safe "Database/Dpi/Internal.chs.h dpiDeqOptions_setMode"
  dpiDeqOptions_setMode :: ((C2HSImp.Ptr (DPI_DeqOptions)) -> (C2HSImp.CInt -> (IO C2HSImp.CInt)))

foreign import ccall safe "Database/Dpi/Internal.chs.h dpiDeqOptions_setMsgId"
  dpiDeqOptions_setMsgId :: ((C2HSImp.Ptr (DPI_DeqOptions)) -> ((C2HSImp.Ptr C2HSImp.CChar) -> (C2HSImp.CUInt -> (IO C2HSImp.CInt))))

foreign import ccall safe "Database/Dpi/Internal.chs.h dpiDeqOptions_setNavigation"
  dpiDeqOptions_setNavigation :: ((C2HSImp.Ptr (DPI_DeqOptions)) -> (C2HSImp.CInt -> (IO C2HSImp.CInt)))

foreign import ccall safe "Database/Dpi/Internal.chs.h dpiDeqOptions_setTransformation"
  dpiDeqOptions_setTransformation :: ((C2HSImp.Ptr (DPI_DeqOptions)) -> ((C2HSImp.Ptr C2HSImp.CChar) -> (C2HSImp.CUInt -> (IO C2HSImp.CInt))))

foreign import ccall safe "Database/Dpi/Internal.chs.h dpiDeqOptions_setVisibility"
  dpiDeqOptions_setVisibility :: ((C2HSImp.Ptr (DPI_DeqOptions)) -> (C2HSImp.CInt -> (IO C2HSImp.CInt)))

foreign import ccall safe "Database/Dpi/Internal.chs.h dpiDeqOptions_setWait"
  dpiDeqOptions_setWait :: ((C2HSImp.Ptr (DPI_DeqOptions)) -> (C2HSImp.CUInt -> (IO C2HSImp.CInt)))

foreign import ccall safe "Database/Dpi/Internal.chs.h dpiEnqOptions_addRef"
  dpiEnqOptions_addRef :: ((C2HSImp.Ptr (DPI_EnqOptions)) -> (IO C2HSImp.CInt))

foreign import ccall safe "Database/Dpi/Internal.chs.h dpiEnqOptions_getTransformation"
  dpiEnqOptions_getTransformation :: ((C2HSImp.Ptr (DPI_EnqOptions)) -> ((C2HSImp.Ptr (C2HSImp.Ptr C2HSImp.CChar)) -> ((C2HSImp.Ptr C2HSImp.CUInt) -> (IO C2HSImp.CInt))))

foreign import ccall safe "Database/Dpi/Internal.chs.h dpiEnqOptions_getVisibility"
  dpiEnqOptions_getVisibility :: ((C2HSImp.Ptr (DPI_EnqOptions)) -> ((C2HSImp.Ptr C2HSImp.CInt) -> (IO C2HSImp.CInt)))

foreign import ccall safe "Database/Dpi/Internal.chs.h dpiEnqOptions_release"
  dpiEnqOptions_release :: ((C2HSImp.Ptr (DPI_EnqOptions)) -> (IO C2HSImp.CInt))

foreign import ccall safe "Database/Dpi/Internal.chs.h dpiEnqOptions_setDeliveryMode"
  dpiEnqOptions_setDeliveryMode :: ((C2HSImp.Ptr (DPI_EnqOptions)) -> (C2HSImp.CInt -> (IO C2HSImp.CInt)))

foreign import ccall safe "Database/Dpi/Internal.chs.h dpiEnqOptions_setTransformation"
  dpiEnqOptions_setTransformation :: ((C2HSImp.Ptr (DPI_EnqOptions)) -> ((C2HSImp.Ptr C2HSImp.CChar) -> (C2HSImp.CUInt -> (IO C2HSImp.CInt))))

foreign import ccall safe "Database/Dpi/Internal.chs.h dpiEnqOptions_setVisibility"
  dpiEnqOptions_setVisibility :: ((C2HSImp.Ptr (DPI_EnqOptions)) -> (C2HSImp.CInt -> (IO C2HSImp.CInt)))

foreign import ccall safe "Database/Dpi/Internal.chs.h dpiLob_addRef"
  dpiLob_addRef :: ((C2HSImp.Ptr (DPI_Lob)) -> (IO C2HSImp.CInt))

foreign import ccall safe "Database/Dpi/Internal.chs.h dpiLob_close"
  dpiLob_close :: ((C2HSImp.Ptr (DPI_Lob)) -> (IO C2HSImp.CInt))

foreign import ccall safe "Database/Dpi/Internal.chs.h dpiLob_closeResource"
  dpiLob_closeResource :: ((C2HSImp.Ptr (DPI_Lob)) -> (IO C2HSImp.CInt))

foreign import ccall safe "Database/Dpi/Internal.chs.h dpiLob_copy"
  dpiLob_copy :: ((C2HSImp.Ptr (DPI_Lob)) -> ((C2HSImp.Ptr (C2HSImp.Ptr (DPI_Lob))) -> (IO C2HSImp.CInt)))

foreign import ccall safe "Database/Dpi/Internal.chs.h dpiLob_flushBuffer"
  dpiLob_flushBuffer :: ((C2HSImp.Ptr (DPI_Lob)) -> (IO C2HSImp.CInt))

foreign import ccall safe "Database/Dpi/Internal.chs.h dpiLob_getBufferSize"
  dpiLob_getBufferSize :: ((C2HSImp.Ptr (DPI_Lob)) -> (C2HSImp.CULLong -> ((C2HSImp.Ptr C2HSImp.CULLong) -> (IO C2HSImp.CInt))))

foreign import ccall safe "Database/Dpi/Internal.chs.h dpiLob_getChunkSize"
  dpiLob_getChunkSize :: ((C2HSImp.Ptr (DPI_Lob)) -> ((C2HSImp.Ptr C2HSImp.CUInt) -> (IO C2HSImp.CInt)))

foreign import ccall safe "Database/Dpi/Internal.chs.h dpiLob_getDirectoryAndFileName"
  dpiLob_getDirectoryAndFileName :: ((C2HSImp.Ptr (DPI_Lob)) -> ((C2HSImp.Ptr (C2HSImp.Ptr C2HSImp.CChar)) -> ((C2HSImp.Ptr C2HSImp.CUInt) -> ((C2HSImp.Ptr (C2HSImp.Ptr C2HSImp.CChar)) -> ((C2HSImp.Ptr C2HSImp.CUInt) -> (IO C2HSImp.CInt))))))

foreign import ccall safe "Database/Dpi/Internal.chs.h dpiLob_getFileExists"
  dpiLob_getFileExists :: ((C2HSImp.Ptr (DPI_Lob)) -> ((C2HSImp.Ptr C2HSImp.CInt) -> (IO C2HSImp.CInt)))

foreign import ccall safe "Database/Dpi/Internal.chs.h dpiLob_getIsResourceOpen"
  dpiLob_getIsResourceOpen :: ((C2HSImp.Ptr (DPI_Lob)) -> ((C2HSImp.Ptr C2HSImp.CInt) -> (IO C2HSImp.CInt)))

foreign import ccall safe "Database/Dpi/Internal.chs.h dpiLob_getSize"
  dpiLob_getSize :: ((C2HSImp.Ptr (DPI_Lob)) -> ((C2HSImp.Ptr C2HSImp.CULLong) -> (IO C2HSImp.CInt)))

foreign import ccall safe "Database/Dpi/Internal.chs.h dpiLob_openResource"
  dpiLob_openResource :: ((C2HSImp.Ptr (DPI_Lob)) -> (IO C2HSImp.CInt))

foreign import ccall safe "Database/Dpi/Internal.chs.h dpiLob_readBytes"
  dpiLob_readBytes :: ((C2HSImp.Ptr (DPI_Lob)) -> (C2HSImp.CULLong -> (C2HSImp.CULLong -> ((C2HSImp.Ptr C2HSImp.CChar) -> ((C2HSImp.Ptr C2HSImp.CULLong) -> (IO C2HSImp.CInt))))))

foreign import ccall safe "Database/Dpi/Internal.chs.h dpiLob_release"
  dpiLob_release :: ((C2HSImp.Ptr (DPI_Lob)) -> (IO C2HSImp.CInt))

foreign import ccall safe "Database/Dpi/Internal.chs.h dpiLob_setDirectoryAndFileName"
  dpiLob_setDirectoryAndFileName :: ((C2HSImp.Ptr (DPI_Lob)) -> ((C2HSImp.Ptr C2HSImp.CChar) -> (C2HSImp.CUInt -> ((C2HSImp.Ptr C2HSImp.CChar) -> (C2HSImp.CUInt -> (IO C2HSImp.CInt))))))

foreign import ccall safe "Database/Dpi/Internal.chs.h dpiLob_setFromBytes"
  dpiLob_setFromBytes :: ((C2HSImp.Ptr (DPI_Lob)) -> ((C2HSImp.Ptr C2HSImp.CChar) -> (C2HSImp.CULLong -> (IO C2HSImp.CInt))))

foreign import ccall safe "Database/Dpi/Internal.chs.h dpiLob_trim"
  dpiLob_trim :: ((C2HSImp.Ptr (DPI_Lob)) -> (C2HSImp.CULLong -> (IO C2HSImp.CInt)))

foreign import ccall safe "Database/Dpi/Internal.chs.h dpiLob_writeBytes"
  dpiLob_writeBytes :: ((C2HSImp.Ptr (DPI_Lob)) -> (C2HSImp.CULLong -> ((C2HSImp.Ptr C2HSImp.CChar) -> (C2HSImp.CULLong -> (IO C2HSImp.CInt)))))

foreign import ccall safe "Database/Dpi/Internal.chs.h dpiMsgProps_addRef"
  dpiMsgProps_addRef :: ((C2HSImp.Ptr (DPI_MsgProps)) -> (IO C2HSImp.CInt))

foreign import ccall safe "Database/Dpi/Internal.chs.h dpiMsgProps_getCorrelation"
  dpiMsgProps_getCorrelation :: ((C2HSImp.Ptr (DPI_MsgProps)) -> ((C2HSImp.Ptr (C2HSImp.Ptr C2HSImp.CChar)) -> ((C2HSImp.Ptr C2HSImp.CUInt) -> (IO C2HSImp.CInt))))

foreign import ccall safe "Database/Dpi/Internal.chs.h dpiMsgProps_getDelay"
  dpiMsgProps_getDelay :: ((C2HSImp.Ptr (DPI_MsgProps)) -> ((C2HSImp.Ptr C2HSImp.CInt) -> (IO C2HSImp.CInt)))

foreign import ccall safe "Database/Dpi/Internal.chs.h dpiMsgProps_getDeliveryMode"
  dpiMsgProps_getDeliveryMode :: ((C2HSImp.Ptr (DPI_MsgProps)) -> ((C2HSImp.Ptr C2HSImp.CInt) -> (IO C2HSImp.CInt)))

foreign import ccall safe "Database/Dpi/Internal.chs.h dpiMsgProps_getEnqTime"
  dpiMsgProps_getEnqTime :: ((C2HSImp.Ptr (DPI_MsgProps)) -> ((Ptr_Timestamp) -> (IO C2HSImp.CInt)))

foreign import ccall safe "Database/Dpi/Internal.chs.h dpiMsgProps_getExceptionQ"
  dpiMsgProps_getExceptionQ :: ((C2HSImp.Ptr (DPI_MsgProps)) -> ((C2HSImp.Ptr (C2HSImp.Ptr C2HSImp.CChar)) -> ((C2HSImp.Ptr C2HSImp.CUInt) -> (IO C2HSImp.CInt))))

foreign import ccall safe "Database/Dpi/Internal.chs.h dpiMsgProps_getExpiration"
  dpiMsgProps_getExpiration :: ((C2HSImp.Ptr (DPI_MsgProps)) -> ((C2HSImp.Ptr C2HSImp.CInt) -> (IO C2HSImp.CInt)))

foreign import ccall safe "Database/Dpi/Internal.chs.h dpiMsgProps_getNumAttempts"
  dpiMsgProps_getNumAttempts :: ((C2HSImp.Ptr (DPI_MsgProps)) -> ((C2HSImp.Ptr C2HSImp.CInt) -> (IO C2HSImp.CInt)))

foreign import ccall safe "Database/Dpi/Internal.chs.h dpiMsgProps_getOriginalMsgId"
  dpiMsgProps_getOriginalMsgId :: ((C2HSImp.Ptr (DPI_MsgProps)) -> ((C2HSImp.Ptr (C2HSImp.Ptr C2HSImp.CChar)) -> ((C2HSImp.Ptr C2HSImp.CUInt) -> (IO C2HSImp.CInt))))

foreign import ccall safe "Database/Dpi/Internal.chs.h dpiMsgProps_getPriority"
  dpiMsgProps_getPriority :: ((C2HSImp.Ptr (DPI_MsgProps)) -> ((C2HSImp.Ptr C2HSImp.CInt) -> (IO C2HSImp.CInt)))

foreign import ccall safe "Database/Dpi/Internal.chs.h dpiMsgProps_getState"
  dpiMsgProps_getState :: ((C2HSImp.Ptr (DPI_MsgProps)) -> ((C2HSImp.Ptr C2HSImp.CInt) -> (IO C2HSImp.CInt)))

foreign import ccall safe "Database/Dpi/Internal.chs.h dpiMsgProps_release"
  dpiMsgProps_release :: ((C2HSImp.Ptr (DPI_MsgProps)) -> (IO C2HSImp.CInt))

foreign import ccall safe "Database/Dpi/Internal.chs.h dpiMsgProps_setCorrelation"
  dpiMsgProps_setCorrelation :: ((C2HSImp.Ptr (DPI_MsgProps)) -> ((C2HSImp.Ptr C2HSImp.CChar) -> (C2HSImp.CUInt -> (IO C2HSImp.CInt))))

foreign import ccall safe "Database/Dpi/Internal.chs.h dpiMsgProps_setDelay"
  dpiMsgProps_setDelay :: ((C2HSImp.Ptr (DPI_MsgProps)) -> (C2HSImp.CInt -> (IO C2HSImp.CInt)))

foreign import ccall safe "Database/Dpi/Internal.chs.h dpiMsgProps_setExceptionQ"
  dpiMsgProps_setExceptionQ :: ((C2HSImp.Ptr (DPI_MsgProps)) -> ((C2HSImp.Ptr C2HSImp.CChar) -> (C2HSImp.CUInt -> (IO C2HSImp.CInt))))

foreign import ccall safe "Database/Dpi/Internal.chs.h dpiMsgProps_setExpiration"
  dpiMsgProps_setExpiration :: ((C2HSImp.Ptr (DPI_MsgProps)) -> (C2HSImp.CInt -> (IO C2HSImp.CInt)))

foreign import ccall safe "Database/Dpi/Internal.chs.h dpiMsgProps_setOriginalMsgId"
  dpiMsgProps_setOriginalMsgId :: ((C2HSImp.Ptr (DPI_MsgProps)) -> ((C2HSImp.Ptr C2HSImp.CChar) -> (C2HSImp.CUInt -> (IO C2HSImp.CInt))))

foreign import ccall safe "Database/Dpi/Internal.chs.h dpiMsgProps_setPriority"
  dpiMsgProps_setPriority :: ((C2HSImp.Ptr (DPI_MsgProps)) -> (C2HSImp.CInt -> (IO C2HSImp.CInt)))

foreign import ccall safe "Database/Dpi/Internal.chs.h dpiObject_addRef"
  dpiObject_addRef :: ((C2HSImp.Ptr (DPI_Object)) -> (IO C2HSImp.CInt))

foreign import ccall safe "Database/Dpi/Internal.chs.h dpiObject_appendElement"
  dpiObject_appendElement :: ((C2HSImp.Ptr (DPI_Object)) -> (C2HSImp.CInt -> ((PtrData) -> (IO C2HSImp.CInt))))

foreign import ccall safe "Database/Dpi/Internal.chs.h dpiObject_copy"
  dpiObject_copy :: ((C2HSImp.Ptr (DPI_Object)) -> ((C2HSImp.Ptr (C2HSImp.Ptr (DPI_Object))) -> (IO C2HSImp.CInt)))

foreign import ccall safe "Database/Dpi/Internal.chs.h dpiObject_deleteElementByIndex"
  dpiObject_deleteElementByIndex :: ((C2HSImp.Ptr (DPI_Object)) -> (C2HSImp.CInt -> (IO C2HSImp.CInt)))

foreign import ccall safe "Database/Dpi/Internal.chs.h dpiObject_getAttributeValue"
  dpiObject_getAttributeValue :: ((C2HSImp.Ptr (DPI_Object)) -> ((C2HSImp.Ptr (DPI_ObjectAttr)) -> (C2HSImp.CInt -> ((PtrData) -> (IO C2HSImp.CInt)))))

foreign import ccall safe "Database/Dpi/Internal.chs.h dpiObject_getElementExistsByIndex"
  dpiObject_getElementExistsByIndex :: ((C2HSImp.Ptr (DPI_Object)) -> (C2HSImp.CInt -> ((C2HSImp.Ptr C2HSImp.CInt) -> (IO C2HSImp.CInt))))

foreign import ccall safe "Database/Dpi/Internal.chs.h dpiObject_getElementValueByIndex"
  dpiObject_getElementValueByIndex :: ((C2HSImp.Ptr (DPI_Object)) -> (C2HSImp.CInt -> (C2HSImp.CInt -> ((PtrData) -> (IO C2HSImp.CInt)))))

foreign import ccall safe "Database/Dpi/Internal.chs.h dpiObject_getFirstIndex"
  dpiObject_getFirstIndex :: ((C2HSImp.Ptr (DPI_Object)) -> ((C2HSImp.Ptr C2HSImp.CInt) -> ((C2HSImp.Ptr C2HSImp.CInt) -> (IO C2HSImp.CInt))))

foreign import ccall safe "Database/Dpi/Internal.chs.h dpiObject_getLastIndex"
  dpiObject_getLastIndex :: ((C2HSImp.Ptr (DPI_Object)) -> ((C2HSImp.Ptr C2HSImp.CInt) -> ((C2HSImp.Ptr C2HSImp.CInt) -> (IO C2HSImp.CInt))))

foreign import ccall safe "Database/Dpi/Internal.chs.h dpiObject_getNextIndex"
  dpiObject_getNextIndex :: ((C2HSImp.Ptr (DPI_Object)) -> (C2HSImp.CInt -> ((C2HSImp.Ptr C2HSImp.CInt) -> ((C2HSImp.Ptr C2HSImp.CInt) -> (IO C2HSImp.CInt)))))

foreign import ccall safe "Database/Dpi/Internal.chs.h dpiObject_getPrevIndex"
  dpiObject_getPrevIndex :: ((C2HSImp.Ptr (DPI_Object)) -> (C2HSImp.CInt -> ((C2HSImp.Ptr C2HSImp.CInt) -> ((C2HSImp.Ptr C2HSImp.CInt) -> (IO C2HSImp.CInt)))))

foreign import ccall safe "Database/Dpi/Internal.chs.h dpiObject_getSize"
  dpiObject_getSize :: ((C2HSImp.Ptr (DPI_Object)) -> ((C2HSImp.Ptr C2HSImp.CInt) -> (IO C2HSImp.CInt)))

foreign import ccall safe "Database/Dpi/Internal.chs.h dpiObject_release"
  dpiObject_release :: ((C2HSImp.Ptr (DPI_Object)) -> (IO C2HSImp.CInt))

foreign import ccall safe "Database/Dpi/Internal.chs.h dpiObject_setAttributeValue"
  dpiObject_setAttributeValue :: ((C2HSImp.Ptr (DPI_Object)) -> ((C2HSImp.Ptr (DPI_ObjectAttr)) -> (C2HSImp.CInt -> ((PtrData) -> (IO C2HSImp.CInt)))))

foreign import ccall safe "Database/Dpi/Internal.chs.h dpiObject_setElementValueByIndex"
  dpiObject_setElementValueByIndex :: ((C2HSImp.Ptr (DPI_Object)) -> (C2HSImp.CInt -> (C2HSImp.CInt -> ((PtrData) -> (IO C2HSImp.CInt)))))

foreign import ccall safe "Database/Dpi/Internal.chs.h dpiObject_trim"
  dpiObject_trim :: ((C2HSImp.Ptr (DPI_Object)) -> (C2HSImp.CUInt -> (IO C2HSImp.CInt)))

foreign import ccall safe "Database/Dpi/Internal.chs.h dpiObjectAttr_addRef"
  dpiObjectAttr_addRef :: ((C2HSImp.Ptr (DPI_ObjectAttr)) -> (IO C2HSImp.CInt))

foreign import ccall safe "Database/Dpi/Internal.chs.h dpiObjectAttr_getInfo"
  dpiObjectAttr_getInfo :: ((C2HSImp.Ptr (DPI_ObjectAttr)) -> ((PtrObjectAttrInfo) -> (IO C2HSImp.CInt)))

foreign import ccall safe "Database/Dpi/Internal.chs.h dpiObjectAttr_release"
  dpiObjectAttr_release :: ((C2HSImp.Ptr (DPI_ObjectAttr)) -> (IO C2HSImp.CInt))

foreign import ccall safe "Database/Dpi/Internal.chs.h dpiObjectType_addRef"
  dpiObjectType_addRef :: ((C2HSImp.Ptr (DPI_ObjectType)) -> (IO C2HSImp.CInt))

foreign import ccall safe "Database/Dpi/Internal.chs.h dpiObjectType_createObject"
  dpiObjectType_createObject :: ((C2HSImp.Ptr (DPI_ObjectType)) -> ((C2HSImp.Ptr (C2HSImp.Ptr (DPI_Object))) -> (IO C2HSImp.CInt)))

foreign import ccall safe "Database/Dpi/Internal.chs.h dpiObjectType_getAttributes"
  dpiObjectType_getAttributes :: ((C2HSImp.Ptr (DPI_ObjectType)) -> (C2HSImp.CUShort -> ((C2HSImp.Ptr (C2HSImp.Ptr (DPI_ObjectAttr))) -> (IO C2HSImp.CInt))))

foreign import ccall safe "Database/Dpi/Internal.chs.h dpiObjectType_getInfo"
  dpiObjectType_getInfo :: ((C2HSImp.Ptr (DPI_ObjectType)) -> ((PtrObjectTypeInfo) -> (IO C2HSImp.CInt)))

foreign import ccall safe "Database/Dpi/Internal.chs.h dpiObjectType_release"
  dpiObjectType_release :: ((C2HSImp.Ptr (DPI_ObjectType)) -> (IO C2HSImp.CInt))

foreign import ccall safe "Database/Dpi/Internal.chs.h dpiPool_acquireConnection"
  dpiPool_acquireConnection :: ((C2HSImp.Ptr (DPI_Pool)) -> ((C2HSImp.Ptr C2HSImp.CChar) -> (C2HSImp.CUInt -> ((C2HSImp.Ptr C2HSImp.CChar) -> (C2HSImp.CUInt -> ((PtrConnCreateParams) -> ((C2HSImp.Ptr (C2HSImp.Ptr (DPI_Conn))) -> (IO C2HSImp.CInt))))))))

foreign import ccall safe "Database/Dpi/Internal.chs.h dpiPool_addRef"
  dpiPool_addRef :: ((C2HSImp.Ptr (DPI_Pool)) -> (IO C2HSImp.CInt))

foreign import ccall safe "Database/Dpi/Internal.chs.h dpiPool_close"
  dpiPool_close :: ((C2HSImp.Ptr (DPI_Pool)) -> (C2HSImp.CInt -> (IO C2HSImp.CInt)))

foreign import ccall safe "Database/Dpi/Internal.chs.h dpiPool_create"
  dpiPool_create :: ((C2HSImp.Ptr (DPI_Context)) -> ((C2HSImp.Ptr C2HSImp.CChar) -> (C2HSImp.CUInt -> ((C2HSImp.Ptr C2HSImp.CChar) -> (C2HSImp.CUInt -> ((C2HSImp.Ptr C2HSImp.CChar) -> (C2HSImp.CUInt -> ((PtrCommonCreateParams) -> ((PtrPoolCreateParams) -> ((C2HSImp.Ptr (C2HSImp.Ptr (DPI_Pool))) -> (IO C2HSImp.CInt)))))))))))

foreign import ccall safe "Database/Dpi/Internal.chs.h dpiPool_getBusyCount"
  dpiPool_getBusyCount :: ((C2HSImp.Ptr (DPI_Pool)) -> ((C2HSImp.Ptr C2HSImp.CUInt) -> (IO C2HSImp.CInt)))

foreign import ccall safe "Database/Dpi/Internal.chs.h dpiPool_getEncodingInfo"
  dpiPool_getEncodingInfo :: ((C2HSImp.Ptr (DPI_Pool)) -> ((PtrEncodingInfo) -> (IO C2HSImp.CInt)))

foreign import ccall safe "Database/Dpi/Internal.chs.h dpiPool_getGetMode"
  dpiPool_getGetMode :: ((C2HSImp.Ptr (DPI_Pool)) -> ((C2HSImp.Ptr C2HSImp.CInt) -> (IO C2HSImp.CInt)))

foreign import ccall safe "Database/Dpi/Internal.chs.h dpiPool_getMaxLifetimeSession"
  dpiPool_getMaxLifetimeSession :: ((C2HSImp.Ptr (DPI_Pool)) -> ((C2HSImp.Ptr C2HSImp.CUInt) -> (IO C2HSImp.CInt)))

foreign import ccall safe "Database/Dpi/Internal.chs.h dpiPool_getOpenCount"
  dpiPool_getOpenCount :: ((C2HSImp.Ptr (DPI_Pool)) -> ((C2HSImp.Ptr C2HSImp.CUInt) -> (IO C2HSImp.CInt)))

foreign import ccall safe "Database/Dpi/Internal.chs.h dpiPool_getStmtCacheSize"
  dpiPool_getStmtCacheSize :: ((C2HSImp.Ptr (DPI_Pool)) -> ((C2HSImp.Ptr C2HSImp.CUInt) -> (IO C2HSImp.CInt)))

foreign import ccall safe "Database/Dpi/Internal.chs.h dpiPool_getTimeout"
  dpiPool_getTimeout :: ((C2HSImp.Ptr (DPI_Pool)) -> ((C2HSImp.Ptr C2HSImp.CUInt) -> (IO C2HSImp.CInt)))

foreign import ccall safe "Database/Dpi/Internal.chs.h dpiPool_release"
  dpiPool_release :: ((C2HSImp.Ptr (DPI_Pool)) -> (IO C2HSImp.CInt))

foreign import ccall safe "Database/Dpi/Internal.chs.h dpiPool_setGetMode"
  dpiPool_setGetMode :: ((C2HSImp.Ptr (DPI_Pool)) -> (C2HSImp.CInt -> (IO C2HSImp.CInt)))

foreign import ccall safe "Database/Dpi/Internal.chs.h dpiPool_setMaxLifetimeSession"
  dpiPool_setMaxLifetimeSession :: ((C2HSImp.Ptr (DPI_Pool)) -> (C2HSImp.CUInt -> (IO C2HSImp.CInt)))

foreign import ccall safe "Database/Dpi/Internal.chs.h dpiPool_setStmtCacheSize"
  dpiPool_setStmtCacheSize :: ((C2HSImp.Ptr (DPI_Pool)) -> (C2HSImp.CUInt -> (IO C2HSImp.CInt)))

foreign import ccall safe "Database/Dpi/Internal.chs.h dpiPool_setTimeout"
  dpiPool_setTimeout :: ((C2HSImp.Ptr (DPI_Pool)) -> (C2HSImp.CUInt -> (IO C2HSImp.CInt)))

foreign import ccall safe "Database/Dpi/Internal.chs.h dpiStmt_addRef"
  dpiStmt_addRef :: ((C2HSImp.Ptr (DPI_Stmt)) -> (IO C2HSImp.CInt))

foreign import ccall safe "Database/Dpi/Internal.chs.h dpiStmt_bindByName"
  dpiStmt_bindByName :: ((C2HSImp.Ptr (DPI_Stmt)) -> ((C2HSImp.Ptr C2HSImp.CChar) -> (C2HSImp.CUInt -> ((C2HSImp.Ptr (DPI_Var)) -> (IO C2HSImp.CInt)))))

foreign import ccall safe "Database/Dpi/Internal.chs.h dpiStmt_bindByPos"
  dpiStmt_bindByPos :: ((C2HSImp.Ptr (DPI_Stmt)) -> (C2HSImp.CUInt -> ((C2HSImp.Ptr (DPI_Var)) -> (IO C2HSImp.CInt))))

foreign import ccall safe "Database/Dpi/Internal.chs.h dpiStmt_bindValueByName"
  dpiStmt_bindValueByName :: ((C2HSImp.Ptr (DPI_Stmt)) -> ((C2HSImp.Ptr C2HSImp.CChar) -> (C2HSImp.CUInt -> (C2HSImp.CInt -> ((PtrData) -> (IO C2HSImp.CInt))))))

foreign import ccall safe "Database/Dpi/Internal.chs.h dpiStmt_bindValueByPos"
  dpiStmt_bindValueByPos :: ((C2HSImp.Ptr (DPI_Stmt)) -> (C2HSImp.CUInt -> (C2HSImp.CInt -> ((PtrData) -> (IO C2HSImp.CInt)))))

foreign import ccall safe "Database/Dpi/Internal.chs.h dpiStmt_close"
  dpiStmt_close :: ((C2HSImp.Ptr (DPI_Stmt)) -> ((C2HSImp.Ptr C2HSImp.CChar) -> (C2HSImp.CUInt -> (IO C2HSImp.CInt))))

foreign import ccall safe "Database/Dpi/Internal.chs.h dpiStmt_define"
  dpiStmt_define :: ((C2HSImp.Ptr (DPI_Stmt)) -> (C2HSImp.CUInt -> ((C2HSImp.Ptr (DPI_Var)) -> (IO C2HSImp.CInt))))

foreign import ccall safe "Database/Dpi/Internal.chs.h dpiStmt_defineValue"
  dpiStmt_defineValue :: ((C2HSImp.Ptr (DPI_Stmt)) -> (C2HSImp.CUInt -> (C2HSImp.CInt -> (C2HSImp.CInt -> (C2HSImp.CUInt -> (C2HSImp.CInt -> ((C2HSImp.Ptr (DPI_ObjectType)) -> (IO C2HSImp.CInt))))))))

foreign import ccall safe "Database/Dpi/Internal.chs.h dpiStmt_execute"
  dpiStmt_execute :: ((C2HSImp.Ptr (DPI_Stmt)) -> (C2HSImp.CInt -> ((C2HSImp.Ptr C2HSImp.CUInt) -> (IO C2HSImp.CInt))))

foreign import ccall safe "Database/Dpi/Internal.chs.h dpiStmt_executeMany"
  dpiStmt_executeMany :: ((C2HSImp.Ptr (DPI_Stmt)) -> (C2HSImp.CInt -> (C2HSImp.CUInt -> (IO C2HSImp.CInt))))

foreign import ccall safe "Database/Dpi/Internal.chs.h dpiStmt_fetch"
  dpiStmt_fetch :: ((C2HSImp.Ptr (DPI_Stmt)) -> ((C2HSImp.Ptr C2HSImp.CInt) -> ((C2HSImp.Ptr C2HSImp.CUInt) -> (IO C2HSImp.CInt))))

foreign import ccall safe "Database/Dpi/Internal.chs.h dpiStmt_fetchRows"
  dpiStmt_fetchRows :: ((C2HSImp.Ptr (DPI_Stmt)) -> (C2HSImp.CUInt -> ((C2HSImp.Ptr C2HSImp.CUInt) -> ((C2HSImp.Ptr C2HSImp.CUInt) -> ((C2HSImp.Ptr C2HSImp.CInt) -> (IO C2HSImp.CInt))))))

foreign import ccall safe "Database/Dpi/Internal.chs.h dpiStmt_getBatchErrorCount"
  dpiStmt_getBatchErrorCount :: ((C2HSImp.Ptr (DPI_Stmt)) -> ((C2HSImp.Ptr C2HSImp.CUInt) -> (IO C2HSImp.CInt)))

foreign import ccall safe "Database/Dpi/Internal.chs.h dpiStmt_getBatchErrors"
  dpiStmt_getBatchErrors :: ((C2HSImp.Ptr (DPI_Stmt)) -> (C2HSImp.CUInt -> ((PtrErrorInfo) -> (IO C2HSImp.CInt))))

foreign import ccall safe "Database/Dpi/Internal.chs.h dpiStmt_getBindCount"
  dpiStmt_getBindCount :: ((C2HSImp.Ptr (DPI_Stmt)) -> ((C2HSImp.Ptr C2HSImp.CUInt) -> (IO C2HSImp.CInt)))

foreign import ccall safe "Database/Dpi/Internal.chs.h dpiStmt_getBindNames"
  dpiStmt_getBindNames :: ((C2HSImp.Ptr (DPI_Stmt)) -> ((C2HSImp.Ptr C2HSImp.CUInt) -> ((C2HSImp.Ptr (C2HSImp.Ptr C2HSImp.CChar)) -> ((C2HSImp.Ptr C2HSImp.CUInt) -> (IO C2HSImp.CInt)))))

foreign import ccall safe "Database/Dpi/Internal.chs.h dpiStmt_getFetchArraySize"
  dpiStmt_getFetchArraySize :: ((C2HSImp.Ptr (DPI_Stmt)) -> ((C2HSImp.Ptr C2HSImp.CUInt) -> (IO C2HSImp.CInt)))

foreign import ccall safe "Database/Dpi/Internal.chs.h dpiStmt_getImplicitResult"
  dpiStmt_getImplicitResult :: ((C2HSImp.Ptr (DPI_Stmt)) -> ((C2HSImp.Ptr (C2HSImp.Ptr (DPI_Stmt))) -> (IO C2HSImp.CInt)))

foreign import ccall safe "Database/Dpi/Internal.chs.h dpiStmt_getInfo"
  dpiStmt_getInfo :: ((C2HSImp.Ptr (DPI_Stmt)) -> ((PtrStmtInfo) -> (IO C2HSImp.CInt)))

foreign import ccall safe "Database/Dpi/Internal.chs.h dpiStmt_getNumQueryColumns"
  dpiStmt_getNumQueryColumns :: ((C2HSImp.Ptr (DPI_Stmt)) -> ((C2HSImp.Ptr C2HSImp.CUInt) -> (IO C2HSImp.CInt)))

foreign import ccall safe "Database/Dpi/Internal.chs.h dpiStmt_getQueryInfo"
  dpiStmt_getQueryInfo :: ((C2HSImp.Ptr (DPI_Stmt)) -> (C2HSImp.CUInt -> ((PtrQueryInfo) -> (IO C2HSImp.CInt))))

foreign import ccall safe "Database/Dpi/Internal.chs.h dpiStmt_getQueryValue"
  dpiStmt_getQueryValue :: ((C2HSImp.Ptr (DPI_Stmt)) -> (C2HSImp.CUInt -> ((C2HSImp.Ptr C2HSImp.CInt) -> ((C2HSImp.Ptr (PtrData)) -> (IO C2HSImp.CInt)))))

foreign import ccall safe "Database/Dpi/Internal.chs.h dpiStmt_getRowCount"
  dpiStmt_getRowCount :: ((C2HSImp.Ptr (DPI_Stmt)) -> ((C2HSImp.Ptr C2HSImp.CULLong) -> (IO C2HSImp.CInt)))

foreign import ccall safe "Database/Dpi/Internal.chs.h dpiStmt_getRowCounts"
  dpiStmt_getRowCounts :: ((C2HSImp.Ptr (DPI_Stmt)) -> ((C2HSImp.Ptr C2HSImp.CUInt) -> ((C2HSImp.Ptr (C2HSImp.Ptr C2HSImp.CULLong)) -> (IO C2HSImp.CInt))))

foreign import ccall safe "Database/Dpi/Internal.chs.h dpiStmt_getSubscrQueryId"
  dpiStmt_getSubscrQueryId :: ((C2HSImp.Ptr (DPI_Stmt)) -> ((C2HSImp.Ptr C2HSImp.CULLong) -> (IO C2HSImp.CInt)))

foreign import ccall safe "Database/Dpi/Internal.chs.h dpiStmt_release"
  dpiStmt_release :: ((C2HSImp.Ptr (DPI_Stmt)) -> (IO C2HSImp.CInt))

foreign import ccall safe "Database/Dpi/Internal.chs.h dpiStmt_scroll"
  dpiStmt_scroll :: ((C2HSImp.Ptr (DPI_Stmt)) -> (C2HSImp.CInt -> (C2HSImp.CInt -> (C2HSImp.CInt -> (IO C2HSImp.CInt)))))

foreign import ccall safe "Database/Dpi/Internal.chs.h dpiStmt_setFetchArraySize"
  dpiStmt_setFetchArraySize :: ((C2HSImp.Ptr (DPI_Stmt)) -> (C2HSImp.CUInt -> (IO C2HSImp.CInt)))

foreign import ccall safe "Database/Dpi/Internal.chs.h dpiRowid_addRef"
  dpiRowid_addRef :: ((C2HSImp.Ptr (DPI_Rowid)) -> (IO C2HSImp.CInt))

foreign import ccall safe "Database/Dpi/Internal.chs.h dpiRowid_getStringValue"
  dpiRowid_getStringValue :: ((C2HSImp.Ptr (DPI_Rowid)) -> ((C2HSImp.Ptr (C2HSImp.Ptr C2HSImp.CChar)) -> ((C2HSImp.Ptr C2HSImp.CUInt) -> (IO C2HSImp.CInt))))

foreign import ccall safe "Database/Dpi/Internal.chs.h dpiRowid_release"
  dpiRowid_release :: ((C2HSImp.Ptr (DPI_Rowid)) -> (IO C2HSImp.CInt))

foreign import ccall safe "Database/Dpi/Internal.chs.h dpiSubscr_addRef"
  dpiSubscr_addRef :: ((C2HSImp.Ptr (DPI_Subscr)) -> (IO C2HSImp.CInt))

foreign import ccall safe "Database/Dpi/Internal.chs.h dpiSubscr_close"
  dpiSubscr_close :: ((C2HSImp.Ptr (DPI_Subscr)) -> (IO C2HSImp.CInt))

foreign import ccall safe "Database/Dpi/Internal.chs.h dpiSubscr_prepareStmt"
  dpiSubscr_prepareStmt :: ((C2HSImp.Ptr (DPI_Subscr)) -> ((C2HSImp.Ptr C2HSImp.CChar) -> (C2HSImp.CUInt -> ((C2HSImp.Ptr (C2HSImp.Ptr (DPI_Stmt))) -> (IO C2HSImp.CInt)))))

foreign import ccall safe "Database/Dpi/Internal.chs.h dpiSubscr_release"
  dpiSubscr_release :: ((C2HSImp.Ptr (DPI_Subscr)) -> (IO C2HSImp.CInt))

foreign import ccall safe "Database/Dpi/Internal.chs.h dpiVar_addRef"
  dpiVar_addRef :: ((C2HSImp.Ptr (DPI_Var)) -> (IO C2HSImp.CInt))

foreign import ccall safe "Database/Dpi/Internal.chs.h dpiVar_copyData"
  dpiVar_copyData :: ((C2HSImp.Ptr (DPI_Var)) -> (C2HSImp.CUInt -> ((C2HSImp.Ptr (DPI_Var)) -> (C2HSImp.CUInt -> (IO C2HSImp.CInt)))))

foreign import ccall safe "Database/Dpi/Internal.chs.h dpiVar_getData"
  dpiVar_getData :: ((C2HSImp.Ptr (DPI_Var)) -> ((C2HSImp.Ptr C2HSImp.CUInt) -> ((C2HSImp.Ptr (PtrData)) -> (IO C2HSImp.CInt))))

foreign import ccall safe "Database/Dpi/Internal.chs.h dpiVar_getNumElementsInArray"
  dpiVar_getNumElementsInArray :: ((C2HSImp.Ptr (DPI_Var)) -> ((C2HSImp.Ptr C2HSImp.CUInt) -> (IO C2HSImp.CInt)))

foreign import ccall safe "Database/Dpi/Internal.chs.h dpiVar_getSizeInBytes"
  dpiVar_getSizeInBytes :: ((C2HSImp.Ptr (DPI_Var)) -> ((C2HSImp.Ptr C2HSImp.CUInt) -> (IO C2HSImp.CInt)))

foreign import ccall safe "Database/Dpi/Internal.chs.h dpiVar_release"
  dpiVar_release :: ((C2HSImp.Ptr (DPI_Var)) -> (IO C2HSImp.CInt))

foreign import ccall safe "Database/Dpi/Internal.chs.h dpiVar_setFromBytes"
  dpiVar_setFromBytes :: ((C2HSImp.Ptr (DPI_Var)) -> (C2HSImp.CUInt -> ((C2HSImp.Ptr C2HSImp.CChar) -> (C2HSImp.CUInt -> (IO C2HSImp.CInt)))))

foreign import ccall safe "Database/Dpi/Internal.chs.h dpiVar_setFromLob"
  dpiVar_setFromLob :: ((C2HSImp.Ptr (DPI_Var)) -> (C2HSImp.CUInt -> ((C2HSImp.Ptr (DPI_Lob)) -> (IO C2HSImp.CInt))))

foreign import ccall safe "Database/Dpi/Internal.chs.h dpiVar_setFromObject"
  dpiVar_setFromObject :: ((C2HSImp.Ptr (DPI_Var)) -> (C2HSImp.CUInt -> ((C2HSImp.Ptr (DPI_Object)) -> (IO C2HSImp.CInt))))

foreign import ccall safe "Database/Dpi/Internal.chs.h dpiVar_setFromRowid"
  dpiVar_setFromRowid :: ((C2HSImp.Ptr (DPI_Var)) -> (C2HSImp.CUInt -> ((C2HSImp.Ptr (DPI_Rowid)) -> (IO C2HSImp.CInt))))

foreign import ccall safe "Database/Dpi/Internal.chs.h dpiVar_setFromStmt"
  dpiVar_setFromStmt :: ((C2HSImp.Ptr (DPI_Var)) -> (C2HSImp.CUInt -> ((C2HSImp.Ptr (DPI_Stmt)) -> (IO C2HSImp.CInt))))

foreign import ccall safe "Database/Dpi/Internal.chs.h dpiVar_setNumElementsInArray"
  dpiVar_setNumElementsInArray :: ((C2HSImp.Ptr (DPI_Var)) -> (C2HSImp.CUInt -> (IO C2HSImp.CInt)))