{-# LINE 1 "Database/SQLite3/Bindings/Types.hsc" #-}
{-# LANGUAGE EmptyDataDecls #-}
{-# LINE 2 "Database/SQLite3/Bindings/Types.hsc" #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
module Database.SQLite3.Bindings.Types (
    -- * Objects
    -- | <http://www.sqlite.org/c3ref/objlist.html>
    CDatabase,
    CStatement,

    -- * Enumerations

    -- ** Error
    CError(..),
    decodeError,
    Error(..),

    -- ** ColumnType
    CColumnType(..),
    decodeColumnType,
    ColumnType(..),

    -- * Indices
    ParamIndex(..),
    ColumnIndex(..),
    ColumnCount,

    -- * Miscellaneous
    CNumBytes(..),
    CDestructor,
    c_SQLITE_TRANSIENT,
) where


{-# LINE 35 "Database/SQLite3/Bindings/Types.hsc" #-}

{-# LINE 36 "Database/SQLite3/Bindings/Types.hsc" #-}

{-# LINE 37 "Database/SQLite3/Bindings/Types.hsc" #-}

import Foreign.C.Types
import Foreign.Ptr

-- Result code documentation copied from <http://www.sqlite.org/c3ref/c_abort.html>

data Error = ErrorOK                     -- ^ Successful result
           | ErrorError                  -- ^ SQL error or missing database
           | ErrorInternal               -- ^ Internal logic error in SQLite
           | ErrorPermission             -- ^ Access permission denied
           | ErrorAbort                  -- ^ Callback routine requested an abort
           | ErrorBusy                   -- ^ The database file is locked
           | ErrorLocked                 -- ^ A table in the database is locked
           | ErrorNoMemory               -- ^ A @malloc()@ failed
           | ErrorReadOnly               -- ^ Attempt to write a readonly database
           | ErrorInterrupt              -- ^ Operation terminated by @sqlite3_interrupt()@
           | ErrorIO                     -- ^ Some kind of disk I/O error occurred
           | ErrorCorrupt                -- ^ The database disk image is malformed
           | ErrorNotFound               -- ^ Unknown opcode in @sqlite3_file_control()@
           | ErrorFull                   -- ^ Insertion failed because database is full
           | ErrorCan'tOpen              -- ^ Unable to open the database file
           | ErrorProtocol               -- ^ Database lock protocol error
           | ErrorEmpty                  -- ^ Database is empty
           | ErrorSchema                 -- ^ The database schema changed
           | ErrorTooBig                 -- ^ String or BLOB exceeds size limit
           | ErrorConstraint             -- ^ Abort due to constraint violation
           | ErrorMismatch               -- ^ Data type mismatch
           | ErrorMisuse                 -- ^ Library used incorrectly
           | ErrorNoLargeFileSupport     -- ^ Uses OS features not supported on host
           | ErrorAuthorization          -- ^ Authorization denied
           | ErrorFormat                 -- ^ Auxiliary database format error
           | ErrorRange                  -- ^ 2nd parameter to sqlite3_bind out of range
           | ErrorNotADatabase           -- ^ File opened that is not a database file
           | ErrorRow                    -- ^ @sqlite3_step()@ has another row ready
           | ErrorDone                   -- ^ @sqlite3_step()@ has finished executing
             deriving (Eq, Show)

data ColumnType = IntegerColumn
                | FloatColumn
                | TextColumn
                | BlobColumn
                | NullColumn
                  deriving (Eq, Show)

-- | <http://www.sqlite.org/c3ref/sqlite3.html>
--
-- @CDatabase@ = @sqlite3@
data CDatabase

-- | <http://www.sqlite.org/c3ref/stmt.html>
--
-- @CStatement@ = @sqlite3_stmt@
data CStatement

-- | Index of a parameter in a parameterized query.
-- Parameter indices start from 1.
--
-- When a query is 'Database.SQLite3.prepare'd, SQLite allocates an
-- array indexed from 1 to the highest parameter index.  For example:
--
-- >>Right stmt <- prepare conn "SELECT ?1, ?5, ?3, ?"
-- >>bindParameterCount stmt
-- >ParamIndex 6
--
-- This will allocate an array indexed from 1 to 6 (@?@ takes the highest
-- preceding index plus one).  The array is initialized with null values.
-- When you bind a parameter with 'Database.SQLite3.bindSQLData', it assigns a
-- new value to one of these indices.
--
-- See <http://www.sqlite.org/lang_expr.html#varparam> for the syntax of
-- parameter placeholders, and how parameter indices are assigned.
newtype ParamIndex = ParamIndex CInt
    deriving (Eq, Ord, Enum, Num, Real, Integral)

-- | This just shows the underlying integer, without the data constructor.
instance Show ParamIndex where
    show (ParamIndex n) = show n

-- | Index of a column in a result set.  Column indices start from 0.
newtype ColumnIndex = ColumnIndex CInt
    deriving (Eq, Ord, Enum, Num, Real, Integral)

-- | This just shows the underlying integer, without the data constructor.
instance Show ColumnIndex where
    show (ColumnIndex n) = show n

-- | Number of columns in a result set.
type ColumnCount = ColumnIndex

newtype CNumBytes = CNumBytes CInt
    deriving (Eq, Ord, Show, Enum, Num, Real, Integral)

-- | <http://www.sqlite.org/c3ref/c_static.html>
--
-- @Ptr CDestructor@ = @sqlite3_destructor_type@
data CDestructor

c_SQLITE_TRANSIENT :: Ptr CDestructor
c_SQLITE_TRANSIENT = intPtrToPtr (-1)


-- | <http://www.sqlite.org/c3ref/c_abort.html>
newtype CError = CError CInt
    deriving Show

-- | Note that this is a partial function.  If the error code is invalid, or
-- perhaps introduced in a newer version of SQLite but this library has not
-- been updated to support it, the result is undefined.
--
-- To be clear, if 'decodeError' fails, it is /undefined behavior/, not an
-- exception you can handle.
--
-- Therefore, do not use direct-sqlite with a different version of SQLite than
-- the one bundled (currently, 3.7.13).  If you do, ensure that 'decodeError'
-- and 'decodeColumnType' are still exhaustive.
decodeError :: CError -> Error
decodeError (CError n) = case n of
    0         -> ErrorOK
{-# LINE 155 "Database/SQLite3/Bindings/Types.hsc" #-}
    1      -> ErrorError
{-# LINE 156 "Database/SQLite3/Bindings/Types.hsc" #-}
    2   -> ErrorInternal
{-# LINE 157 "Database/SQLite3/Bindings/Types.hsc" #-}
    3       -> ErrorPermission
{-# LINE 158 "Database/SQLite3/Bindings/Types.hsc" #-}
    4      -> ErrorAbort
{-# LINE 159 "Database/SQLite3/Bindings/Types.hsc" #-}
    5       -> ErrorBusy
{-# LINE 160 "Database/SQLite3/Bindings/Types.hsc" #-}
    6     -> ErrorLocked
{-# LINE 161 "Database/SQLite3/Bindings/Types.hsc" #-}
    7      -> ErrorNoMemory
{-# LINE 162 "Database/SQLite3/Bindings/Types.hsc" #-}
    8   -> ErrorReadOnly
{-# LINE 163 "Database/SQLite3/Bindings/Types.hsc" #-}
    9  -> ErrorInterrupt
{-# LINE 164 "Database/SQLite3/Bindings/Types.hsc" #-}
    10      -> ErrorIO
{-# LINE 165 "Database/SQLite3/Bindings/Types.hsc" #-}
    11    -> ErrorCorrupt
{-# LINE 166 "Database/SQLite3/Bindings/Types.hsc" #-}
    12   -> ErrorNotFound
{-# LINE 167 "Database/SQLite3/Bindings/Types.hsc" #-}
    13       -> ErrorFull
{-# LINE 168 "Database/SQLite3/Bindings/Types.hsc" #-}
    14   -> ErrorCan'tOpen
{-# LINE 169 "Database/SQLite3/Bindings/Types.hsc" #-}
    15   -> ErrorProtocol
{-# LINE 170 "Database/SQLite3/Bindings/Types.hsc" #-}
    16      -> ErrorEmpty
{-# LINE 171 "Database/SQLite3/Bindings/Types.hsc" #-}
    17     -> ErrorSchema
{-# LINE 172 "Database/SQLite3/Bindings/Types.hsc" #-}
    18     -> ErrorTooBig
{-# LINE 173 "Database/SQLite3/Bindings/Types.hsc" #-}
    19 -> ErrorConstraint
{-# LINE 174 "Database/SQLite3/Bindings/Types.hsc" #-}
    20   -> ErrorMismatch
{-# LINE 175 "Database/SQLite3/Bindings/Types.hsc" #-}
    21     -> ErrorMisuse
{-# LINE 176 "Database/SQLite3/Bindings/Types.hsc" #-}
    22      -> ErrorNoLargeFileSupport
{-# LINE 177 "Database/SQLite3/Bindings/Types.hsc" #-}
    23       -> ErrorAuthorization
{-# LINE 178 "Database/SQLite3/Bindings/Types.hsc" #-}
    24     -> ErrorFormat
{-# LINE 179 "Database/SQLite3/Bindings/Types.hsc" #-}
    25      -> ErrorRange
{-# LINE 180 "Database/SQLite3/Bindings/Types.hsc" #-}
    26     -> ErrorNotADatabase
{-# LINE 181 "Database/SQLite3/Bindings/Types.hsc" #-}
    100        -> ErrorRow
{-# LINE 182 "Database/SQLite3/Bindings/Types.hsc" #-}
    101       -> ErrorDone
{-# LINE 183 "Database/SQLite3/Bindings/Types.hsc" #-}
    _                          -> error $ "decodeError " ++ show n


-- | <http://www.sqlite.org/c3ref/c_blob.html>
newtype CColumnType = CColumnType CInt
    deriving Show

-- | Note that this is a partial function.
-- See 'decodeError' for more information.
decodeColumnType :: CColumnType -> ColumnType
decodeColumnType (CColumnType n) = case n of
    1 -> IntegerColumn
{-# LINE 195 "Database/SQLite3/Bindings/Types.hsc" #-}
    2   -> FloatColumn
{-# LINE 196 "Database/SQLite3/Bindings/Types.hsc" #-}
    3    -> TextColumn
{-# LINE 197 "Database/SQLite3/Bindings/Types.hsc" #-}
    4    -> BlobColumn
{-# LINE 198 "Database/SQLite3/Bindings/Types.hsc" #-}
    5    -> NullColumn
{-# LINE 199 "Database/SQLite3/Bindings/Types.hsc" #-}
    _                       -> error $ "decodeColumnType " ++ show n