{-# LINE 1 "Database/SQLite3/Bindings/Types.hsc" #-}
{-# LANGUAGE EmptyDataDecls #-}
{-# LANGUAGE FunctionalDependencies #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
module Database.SQLite3.Bindings.Types (
    -- * Objects
    -- | <https://www.sqlite.org/c3ref/objlist.html>
    CDatabase,
    CStatement,
    CValue,
    CContext,
    CBlob,
    CBackup,

    -- * Enumerations

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

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

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

    -- ** Indices (FFI)
    CParamIndex(..),
    CColumnIndex(..),
    CColumnCount,

    -- * Miscellaneous
    CNumBytes(..),
    CDestructor,
    c_SQLITE_STATIC,
    c_SQLITE_TRANSIENT,
    c_SQLITE_UTF8,

    -- * Custom functions
    ArgCount(..),
    ArgIndex,
    CArgCount(..),
    c_SQLITE_DETERMINISTIC,

    -- * Conversion to and from FFI types
    FFIType(..),
) where


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


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

import Foreign.C.Types
import Foreign.Ptr

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

-- | <https://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
           | ErrorNotice                 -- ^ Notifications from sqlite3_log()
           | ErrorWarning                -- ^ Warnings from sqlite3_log()
           | ErrorRow                    -- ^ @sqlite3_step()@ has another row ready
           | ErrorDone                   -- ^ @sqlite3_step()@ has finished executing
             deriving (Eq, Show)

-- | <https://www.sqlite.org/c3ref/c_blob.html>
data ColumnType = IntegerColumn
                | FloatColumn
                | TextColumn
                | BlobColumn
                | NullColumn
                  deriving (Eq, Show)

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

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

-- | <https://www.sqlite.org/c3ref/value.html>
--
-- @CValue@ = @sqlite3_value@
data CValue

-- | <https://www.sqlite.org/c3ref/context.html>
--
-- @CContext@ = @sqlite3_context@
data CContext

-- | <https://www.sqlite.org/c3ref/blob.html>
--
-- @CBlob@ = @sqlite3_blob@
data CBlob

-- | <https://www.sqlite.org/c3ref/backup.html>
--
-- @CBackup@ = @sqlite3_backup@
data CBackup

-- | 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 <https://www.sqlite.org/lang_expr.html#varparam> for the syntax of
-- parameter placeholders, and how parameter indices are assigned.
newtype ParamIndex = ParamIndex Int
    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

-- | Limit min/max bounds to fit into SQLite's native parameter ranges.
instance Bounded ParamIndex where
    minBound = ParamIndex (fromIntegral (minBound :: CInt))
    maxBound = ParamIndex (fromIntegral (maxBound :: CInt))

-- | Index of a column in a result set.  Column indices start from 0.
newtype ColumnIndex = ColumnIndex Int
    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

-- | Limit min/max bounds to fit into SQLite's native parameter ranges.
instance Bounded ColumnIndex where
    minBound = ColumnIndex (fromIntegral (minBound :: CInt))
    maxBound = ColumnIndex (fromIntegral (maxBound :: CInt))

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

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

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

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

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

type CColumnCount = CColumnIndex

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

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

-- | Tells SQLite3 that the content pointer is constant and will never change
c_SQLITE_STATIC :: Ptr CDestructor
c_SQLITE_STATIC = intPtrToPtr 0

-- | Tells SQLite3 to make its own private copy of the data
c_SQLITE_TRANSIENT :: Ptr CDestructor
c_SQLITE_TRANSIENT = intPtrToPtr (-1)

c_SQLITE_UTF8 :: CInt
c_SQLITE_UTF8 = 1
{-# LINE 218 "Database/SQLite3/Bindings/Types.hsc" #-}

-- | Number of arguments of a user defined SQL function.
newtype ArgCount = ArgCount Int
    deriving (Eq, Ord, Enum, Num, Real, Integral)

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

instance Bounded ArgCount where
    minBound = ArgCount 0
    maxBound = ArgCount (6)
{-# LINE 230 "Database/SQLite3/Bindings/Types.hsc" #-}

-- | Index of an argument to a custom function. Indices start from 0.
type ArgIndex = ArgCount

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

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

instance Bounded CArgCount where
    minBound = CArgCount (-1)
    maxBound = CArgCount 6
{-# LINE 244 "Database/SQLite3/Bindings/Types.hsc" #-}

-- | Tells SQLite3 that the defined custom SQL function is deterministic.
c_SQLITE_DETERMINISTIC :: CInt
c_SQLITE_DETERMINISTIC = 2048
{-# LINE 248 "Database/SQLite3/Bindings/Types.hsc" #-}

-- | <https://www.sqlite.org/c3ref/c_abort.html>
newtype CError = CError CInt
    deriving (Eq, 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.24.0).  If you do, ensure that 'decodeError'
-- and 'decodeColumnType' are still exhaustive.
decodeError :: CError -> Error
decodeError (CError n) = case n of
    0         -> ErrorOK
{-# LINE 266 "Database/SQLite3/Bindings/Types.hsc" #-}
    1      -> ErrorError
{-# LINE 267 "Database/SQLite3/Bindings/Types.hsc" #-}
    2   -> ErrorInternal
{-# LINE 268 "Database/SQLite3/Bindings/Types.hsc" #-}
    3       -> ErrorPermission
{-# LINE 269 "Database/SQLite3/Bindings/Types.hsc" #-}
    4      -> ErrorAbort
{-# LINE 270 "Database/SQLite3/Bindings/Types.hsc" #-}
    5       -> ErrorBusy
{-# LINE 271 "Database/SQLite3/Bindings/Types.hsc" #-}
    6     -> ErrorLocked
{-# LINE 272 "Database/SQLite3/Bindings/Types.hsc" #-}
    7      -> ErrorNoMemory
{-# LINE 273 "Database/SQLite3/Bindings/Types.hsc" #-}
    8   -> ErrorReadOnly
{-# LINE 274 "Database/SQLite3/Bindings/Types.hsc" #-}
    9  -> ErrorInterrupt
{-# LINE 275 "Database/SQLite3/Bindings/Types.hsc" #-}
    10      -> ErrorIO
{-# LINE 276 "Database/SQLite3/Bindings/Types.hsc" #-}
    11    -> ErrorCorrupt
{-# LINE 277 "Database/SQLite3/Bindings/Types.hsc" #-}
    12   -> ErrorNotFound
{-# LINE 278 "Database/SQLite3/Bindings/Types.hsc" #-}
    13       -> ErrorFull
{-# LINE 279 "Database/SQLite3/Bindings/Types.hsc" #-}
    14   -> ErrorCan'tOpen
{-# LINE 280 "Database/SQLite3/Bindings/Types.hsc" #-}
    15   -> ErrorProtocol
{-# LINE 281 "Database/SQLite3/Bindings/Types.hsc" #-}
    16      -> ErrorEmpty
{-# LINE 282 "Database/SQLite3/Bindings/Types.hsc" #-}
    17     -> ErrorSchema
{-# LINE 283 "Database/SQLite3/Bindings/Types.hsc" #-}
    18     -> ErrorTooBig
{-# LINE 284 "Database/SQLite3/Bindings/Types.hsc" #-}
    19 -> ErrorConstraint
{-# LINE 285 "Database/SQLite3/Bindings/Types.hsc" #-}
    20   -> ErrorMismatch
{-# LINE 286 "Database/SQLite3/Bindings/Types.hsc" #-}
    21     -> ErrorMisuse
{-# LINE 287 "Database/SQLite3/Bindings/Types.hsc" #-}
    22      -> ErrorNoLargeFileSupport
{-# LINE 288 "Database/SQLite3/Bindings/Types.hsc" #-}
    23       -> ErrorAuthorization
{-# LINE 289 "Database/SQLite3/Bindings/Types.hsc" #-}
    24     -> ErrorFormat
{-# LINE 290 "Database/SQLite3/Bindings/Types.hsc" #-}
    25      -> ErrorRange
{-# LINE 291 "Database/SQLite3/Bindings/Types.hsc" #-}
    26     -> ErrorNotADatabase
{-# LINE 292 "Database/SQLite3/Bindings/Types.hsc" #-}
    27     -> ErrorNotice
{-# LINE 293 "Database/SQLite3/Bindings/Types.hsc" #-}
    28    -> ErrorWarning
{-# LINE 294 "Database/SQLite3/Bindings/Types.hsc" #-}
    100        -> ErrorRow
{-# LINE 295 "Database/SQLite3/Bindings/Types.hsc" #-}
    101       -> ErrorDone
{-# LINE 296 "Database/SQLite3/Bindings/Types.hsc" #-}
    _                          -> error $ "decodeError " ++ show n

encodeError :: Error -> CError
encodeError err = CError $ case err of
    ErrorOK                 -> 0
{-# LINE 301 "Database/SQLite3/Bindings/Types.hsc" #-}
    ErrorError              -> 1
{-# LINE 302 "Database/SQLite3/Bindings/Types.hsc" #-}
    ErrorInternal           -> 2
{-# LINE 303 "Database/SQLite3/Bindings/Types.hsc" #-}
    ErrorPermission         -> 3
{-# LINE 304 "Database/SQLite3/Bindings/Types.hsc" #-}
    ErrorAbort              -> 4
{-# LINE 305 "Database/SQLite3/Bindings/Types.hsc" #-}
    ErrorBusy               -> 5
{-# LINE 306 "Database/SQLite3/Bindings/Types.hsc" #-}
    ErrorLocked             -> 6
{-# LINE 307 "Database/SQLite3/Bindings/Types.hsc" #-}
    ErrorNoMemory           -> 7
{-# LINE 308 "Database/SQLite3/Bindings/Types.hsc" #-}
    ErrorReadOnly           -> 8
{-# LINE 309 "Database/SQLite3/Bindings/Types.hsc" #-}
    ErrorInterrupt          -> 9
{-# LINE 310 "Database/SQLite3/Bindings/Types.hsc" #-}
    ErrorIO                 -> 10
{-# LINE 311 "Database/SQLite3/Bindings/Types.hsc" #-}
    ErrorCorrupt            -> 11
{-# LINE 312 "Database/SQLite3/Bindings/Types.hsc" #-}
    ErrorNotFound           -> 12
{-# LINE 313 "Database/SQLite3/Bindings/Types.hsc" #-}
    ErrorFull               -> 13
{-# LINE 314 "Database/SQLite3/Bindings/Types.hsc" #-}
    ErrorCan'tOpen          -> 14
{-# LINE 315 "Database/SQLite3/Bindings/Types.hsc" #-}
    ErrorProtocol           -> 15
{-# LINE 316 "Database/SQLite3/Bindings/Types.hsc" #-}
    ErrorEmpty              -> 16
{-# LINE 317 "Database/SQLite3/Bindings/Types.hsc" #-}
    ErrorSchema             -> 17
{-# LINE 318 "Database/SQLite3/Bindings/Types.hsc" #-}
    ErrorTooBig             -> 18
{-# LINE 319 "Database/SQLite3/Bindings/Types.hsc" #-}
    ErrorConstraint         -> 19
{-# LINE 320 "Database/SQLite3/Bindings/Types.hsc" #-}
    ErrorMismatch           -> 20
{-# LINE 321 "Database/SQLite3/Bindings/Types.hsc" #-}
    ErrorMisuse             -> 21
{-# LINE 322 "Database/SQLite3/Bindings/Types.hsc" #-}
    ErrorNoLargeFileSupport -> 22
{-# LINE 323 "Database/SQLite3/Bindings/Types.hsc" #-}
    ErrorAuthorization      -> 23
{-# LINE 324 "Database/SQLite3/Bindings/Types.hsc" #-}
    ErrorFormat             -> 24
{-# LINE 325 "Database/SQLite3/Bindings/Types.hsc" #-}
    ErrorRange              -> 25
{-# LINE 326 "Database/SQLite3/Bindings/Types.hsc" #-}
    ErrorNotADatabase       -> 26
{-# LINE 327 "Database/SQLite3/Bindings/Types.hsc" #-}
    ErrorNotice             -> 27
{-# LINE 328 "Database/SQLite3/Bindings/Types.hsc" #-}
    ErrorWarning            -> 28
{-# LINE 329 "Database/SQLite3/Bindings/Types.hsc" #-}
    ErrorRow                -> 100
{-# LINE 330 "Database/SQLite3/Bindings/Types.hsc" #-}
    ErrorDone               -> 101
{-# LINE 331 "Database/SQLite3/Bindings/Types.hsc" #-}

-- | <https://www.sqlite.org/c3ref/c_blob.html>
newtype CColumnType = CColumnType CInt
    deriving (Eq, 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 341 "Database/SQLite3/Bindings/Types.hsc" #-}
    2   -> FloatColumn
{-# LINE 342 "Database/SQLite3/Bindings/Types.hsc" #-}
    3    -> TextColumn
{-# LINE 343 "Database/SQLite3/Bindings/Types.hsc" #-}
    4    -> BlobColumn
{-# LINE 344 "Database/SQLite3/Bindings/Types.hsc" #-}
    5    -> NullColumn
{-# LINE 345 "Database/SQLite3/Bindings/Types.hsc" #-}
    _                       -> error $ "decodeColumnType " ++ show n

encodeColumnType :: ColumnType -> CColumnType
encodeColumnType t = CColumnType $ case t of
    IntegerColumn -> 1
{-# LINE 350 "Database/SQLite3/Bindings/Types.hsc" #-}
    FloatColumn   -> 2
{-# LINE 351 "Database/SQLite3/Bindings/Types.hsc" #-}
    TextColumn    -> 3
{-# LINE 352 "Database/SQLite3/Bindings/Types.hsc" #-}
    BlobColumn    -> 4
{-# LINE 353 "Database/SQLite3/Bindings/Types.hsc" #-}
    NullColumn    -> 5
{-# LINE 354 "Database/SQLite3/Bindings/Types.hsc" #-}

------------------------------------------------------------------------
-- Conversion to and from FFI types

-- | The "Database.SQLite3" and "Database.SQLite3.Direct" modules use
-- higher-level representations of some types than those used in the
-- FFI signatures ("Database.SQLite3.Bindings").  This typeclass
-- helps with the conversions.
class FFIType public ffi | public -> ffi, ffi -> public where
    toFFI   :: public -> ffi
    fromFFI :: ffi -> public

instance FFIType ParamIndex CParamIndex where
    toFFI (ParamIndex n) = CParamIndex (fromIntegral n)
    fromFFI (CParamIndex n) = ParamIndex (fromIntegral n)

instance FFIType ColumnIndex CColumnIndex where
    toFFI (ColumnIndex n) = CColumnIndex (fromIntegral n)
    fromFFI (CColumnIndex n) = ColumnIndex (fromIntegral n)

instance FFIType Error CError where
    toFFI = encodeError
    fromFFI = decodeError

instance FFIType ColumnType CColumnType where
    toFFI = encodeColumnType
    fromFFI = decodeColumnType

instance FFIType ArgCount CArgCount where
    toFFI (ArgCount n)  = CArgCount (fromIntegral n)
    fromFFI (CArgCount n) = ArgCount (fromIntegral n)