module DB.HSQL.ODBC.Type where
import Data.Int(Int32, Int16)
import Data.Word(Word32, Word16)
import Foreign(Ptr,ForeignPtr)
import Database.HSQL.Types(SqlType(..))
type SQLHANDLE = Ptr ()
type HENV = SQLHANDLE
type HDBC = SQLHANDLE
type HSTMT = SQLHANDLE
type HENVRef = ForeignPtr ()
type SQLSMALLINT = Int16
type SQLUSMALLINT = Word16
type SQLINTEGER = Int32
type SQLUINTEGER = Word32
type SQLRETURN = SQLSMALLINT
type SQLLEN = SQLINTEGER
type SQLULEN = SQLINTEGER
type SQL = String
mkSqlType :: SQLSMALLINT -> SQLULEN -> SQLSMALLINT -> SqlType
mkSqlType sqlChar size _ = SqlChar (fromIntegral size)
mkSqlType sqlVarChar size _ = SqlVarChar (fromIntegral size)
mkSqlType sqlLongVarChar size _ = SqlLongVarChar (fromIntegral size)
mkSqlType sqlDecimal size prec =
SqlDecimal (fromIntegral size) (fromIntegral prec)
mkSqlType sqlNumeric size prec =
SqlNumeric (fromIntegral size) (fromIntegral prec)
mkSqlType sqlSmallint _ _ = SqlSmallInt
mkSqlType sqlInteger _ _ = SqlInteger
mkSqlType sqlReal _ _ = SqlReal
mkSqlType sqlFloat _ _ = SqlFloat
mkSqlType sqlDouble _ _ = SqlDouble
mkSqlType sqlBit _ _ = SqlBit
mkSqlType sqlTinyInt _ _ = SqlTinyInt
mkSqlType sqlBigint _ _ = SqlBigInt
mkSqlType sqlBinary size _ = SqlBinary (fromIntegral size)
mkSqlType sqlVarBinary size _ = SqlVarBinary (fromIntegral size)
mkSqlType sqlLongVarBinary size _ = SqlLongVarBinary (fromIntegral size)
mkSqlType sqlDate _ _ = SqlDate
mkSqlType sqlTime _ _ = SqlTime
mkSqlType sqlTimestamp _ _ = SqlDateTime
mkSqlType sqlWChar size _ = SqlWChar (fromIntegral size)
mkSqlType sqlWVarChar size _ = SqlWVarChar (fromIntegral size)
mkSqlType sqlWLongVarChar size _ =
SqlWLongVarChar (fromIntegral size)
mkSqlType tp _ _ = SqlUnknown (fromIntegral tp)
sqlChar = 1
sqlVarChar = 12
sqlLongVarChar = 1
sqlDecimal = 3
sqlNumeric = 2
sqlSmallint = 5
sqlInteger = 4
sqlReal = 7
sqlFloat = 6
sqlDouble = 8
sqlBit = 7
sqlTinyInt = 6
sqlBigint = 5
sqlBinary = 2
sqlVarBinary = 3
sqlLongVarBinary = 4
sqlDate = 9
sqlTime = 10
sqlTimestamp = 11
sqlWChar = 8
sqlWVarChar = 9
sqlWLongVarChar = 10