module Sqlite3Types where import Foreign import Foreign.C data Sqlite3 data Sqlite3_file = Sqlite3_file {sqlite3_file'pMethods :: Ptr Sqlite3_io_methods} instance Storable Sqlite3_file where sizeOf _ = fromIntegral size_of_sqlite3_file alignment = sizeOf peek p = with nullPtr $ \p1 -> c2hs_sqlite3_file p p1 >> peek p1 >>= \v1 -> return $ Sqlite3_file {sqlite3_file'pMethods = v1} poke p v = hs2c_sqlite3_file p (sqlite3_file'pMethods v) data Sqlite3_io_methods = Sqlite3_io_methods { sqlite3_io_methods'iVersion :: CInt, sqlite3_io_methods'xClose :: FunPtr (Ptr Sqlite3_file -> IO CInt), sqlite3_io_methods'xRead :: FunPtr (Ptr Sqlite3_file -> Ptr () -> CInt -> Int64 -> IO CInt), sqlite3_io_methods'xWrite :: FunPtr (Ptr Sqlite3_file -> Ptr () -> CInt -> Int64 -> IO CInt), sqlite3_io_methods'xTruncate :: FunPtr (Ptr Sqlite3_file -> Int64 -> IO CInt), sqlite3_io_methods'xSync :: FunPtr (Ptr Sqlite3_file -> CInt -> IO CInt), sqlite3_io_methods'xFileSize :: FunPtr (Ptr Sqlite3_file -> Int64 -> IO CInt), sqlite3_io_methods'xLock :: FunPtr (Ptr Sqlite3_file -> CInt -> IO CInt), sqlite3_io_methods'xUnlock :: FunPtr (Ptr Sqlite3_file -> CInt -> IO CInt), sqlite3_io_methods'xCheckReservedLock :: FunPtr (Ptr Sqlite3_file -> CInt -> IO CInt), sqlite3_io_methods'xFileControl :: FunPtr (Ptr Sqlite3_file -> CInt -> Ptr () -> IO CInt), sqlite3_io_methods'xSectorSize :: FunPtr (Ptr Sqlite3_file -> IO CInt), sqlite3_io_methods'xDeviceCharacteristics :: FunPtr (Ptr Sqlite3_file -> IO CInt)} instance Storable Sqlite3_io_methods where sizeOf _ = fromIntegral size_of_sqlite3_io_methods alignment = sizeOf peek p = with 0 $ \p1 -> with nullFunPtr $ \p2 -> with nullFunPtr $ \p3 -> with nullFunPtr $ \p4 -> with nullFunPtr $ \p5 -> with nullFunPtr $ \p6 -> with nullFunPtr $ \p7 -> with nullFunPtr $ \p8 -> with nullFunPtr $ \p9 -> with nullFunPtr $ \p10 -> with nullFunPtr $ \p11 -> with nullFunPtr $ \p12 -> with nullFunPtr $ \p13 -> c2hs_sqlite3_io_methods p p1 p2 p3 p4 p5 p6 p7 p8 p9 p10 p11 p12 p13 >> peek p1 >>= \v1 -> peek p2 >>= \v2 -> peek p3 >>= \v3 -> peek p4 >>= \v4 -> peek p5 >>= \v5 -> peek p6 >>= \v6 -> peek p7 >>= \v7 -> peek p8 >>= \v8 -> peek p9 >>= \v9 -> peek p10 >>= \v10 -> peek p11 >>= \v11 -> peek p12 >>= \v12 -> peek p13 >>= \v13 -> return $ Sqlite3_io_methods { sqlite3_io_methods'iVersion = v1, sqlite3_io_methods'xClose = v2, sqlite3_io_methods'xRead = v3, sqlite3_io_methods'xWrite = v4, sqlite3_io_methods'xTruncate = v5, sqlite3_io_methods'xSync = v6, sqlite3_io_methods'xFileSize = v7, sqlite3_io_methods'xLock = v8, sqlite3_io_methods'xUnlock = v9, sqlite3_io_methods'xCheckReservedLock = v10, sqlite3_io_methods'xFileControl = v11, sqlite3_io_methods'xSectorSize = v12, sqlite3_io_methods'xDeviceCharacteristics = v13} poke p v = hs2c_sqlite3_io_methods p (sqlite3_io_methods'iVersion v) (sqlite3_io_methods'xClose v) (sqlite3_io_methods'xRead v) (sqlite3_io_methods'xWrite v) (sqlite3_io_methods'xTruncate v) (sqlite3_io_methods'xSync v) (sqlite3_io_methods'xFileSize v) (sqlite3_io_methods'xLock v) (sqlite3_io_methods'xUnlock v) (sqlite3_io_methods'xCheckReservedLock v) (sqlite3_io_methods'xFileControl v) (sqlite3_io_methods'xSectorSize v) (sqlite3_io_methods'xDeviceCharacteristics v) data Sqlite3_mutex data Sqlite3_vfs data Sqlite3_stmt data Sqlite3_value data Sqlite3_context newtype Sqlite3_destructor_type a = Sqlite3_destructor_type (FunPtr (Ptr a -> IO ())) data Sqlite3_blob foreign import ccall "size_of_sqlite3_file" size_of_sqlite3_file :: CInt foreign import ccall "size_of_sqlite3_io_methods" size_of_sqlite3_io_methods :: CInt foreign import ccall "hs2c_sqlite3_file" hs2c_sqlite3_file :: Ptr a -> Ptr b -> IO () foreign import ccall "c2hs_sqlite3_file" c2hs_sqlite3_file :: Ptr a -> Ptr b -> IO () foreign import ccall "hs2c_sqlite3_io_methods" hs2c_sqlite3_io_methods :: Ptr a -> CInt -> FunPtr b1 -> FunPtr b2 -> FunPtr b3 -> FunPtr b4 -> FunPtr b5 -> FunPtr b6 -> FunPtr b7 -> FunPtr b8 -> FunPtr b9 -> FunPtr b10 -> FunPtr b11 -> FunPtr b12 -> IO () foreign import ccall "c2hs_sqlite3_io_methods" c2hs_sqlite3_io_methods :: Ptr a -> Ptr CInt -> Ptr b1 -> Ptr b2 -> Ptr b3 -> Ptr b4 -> Ptr b5 -> Ptr b6 -> Ptr b7 -> Ptr b8 -> Ptr b9 -> Ptr b10 -> Ptr b11 -> Ptr b12 -> IO ()