File: Types.hs

package info (click to toggle)
haskell-hsql 1.7-2
  • links: PTS, VCS
  • area: main
  • in suites: lenny
  • size: 84 kB
  • sloc: haskell: 132; makefile: 50; sh: 12
file content (153 lines) | stat: -rwxr-xr-x 6,419 bytes parent folder | download | duplicates (2)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
134
135
136
137
138
139
140
141
142
143
144
145
146
147
148
149
150
151
152
153
-- #hide
module Database.HSQL.Types where

import Control.Concurrent.MVar
import Control.Exception
import Data.Dynamic
import Foreign
import Foreign.C

type FieldDef = (String, SqlType, Bool)

data SqlType
	= SqlChar          Int               -- ODBC, MySQL, PostgreSQL
	| SqlVarChar       Int               -- ODBC, MySQL, PostgreSQL, MSI
	| SqlLongVarChar   Int               -- ODBC
	| SqlText                            --     ,      , PostgreSQL, MSI
	| SqlWChar         Int               -- ODBC
	| SqlWVarChar      Int               -- ODBC
	| SqlWLongVarChar  Int               -- ODBC
	| SqlDecimal       Int Int           -- ODBC
	| SqlNumeric       Int Int           -- ODBC, MySQL, PostgreSQL
	| SqlSmallInt                        -- ODBC, MySQL, PostgreSQL
	| SqlMedInt                          --     , MySQL,           
	| SqlInteger                         -- ODBC, MySQL, PostgreSQL, MSI
	| SqlReal                            -- ODBC, MySQL, PostgreSQL
	| SqlFloat                           -- ODBC
	| SqlDouble                          -- ODBC, MySQL, PostgreSQL
	| SqlBit                             -- ODBC,      , PostgreSQL
	| SqlTinyInt                         -- ODBC, MySQL, PostgreSQL
	| SqlBigInt                          -- ODBC, MySQL, PostgreSQL, MSI
	| SqlBinary        Int               -- ODBC,      , PostgreSQL
	| SqlVarBinary     Int               -- ODBC,      , PostgreSQL
	| SqlLongVarBinary Int               -- ODBC
	| SqlDate                            -- ODBC, MySQL, PostgreSQL
	| SqlTime                            -- ODBC, MySQL, PostgreSQL
	| SqlTimeTZ                          --     ,      , PostgreSQL
	| SqlAbsTime                         --     ,      , PostgreSQL
	| SqlRelTime                         --     ,      , PostgreSQL
	| SqlTimeInterval                    --     ,      , PostgreSQL
	| SqlAbsTimeInterval                 --     ,      , PostgreSQL
	| SqlTimeStamp                       -- ODBC, MySQL
	| SqlDateTime                        --     , MySQL
	| SqlDateTimeTZ                      --     , MySQL, PostgreSQL
	| SqlYear                            --     , MySQL
	| SqlSET                             --     , MySQL
	| SqlENUM                            --     , MySQL
	| SqlBLOB                            --     , MySQL,           , MSI
	| SqlMoney                           --     ,      , PostgreSQL
	| SqlINetAddr                        --     ,      , PostgreSQL
	| SqlCIDRAddr                        --     ,      , PostgreSQL
	| SqlMacAddr                         --     ,      , PostgreSQL
	| SqlPoint                           --     ,      , PostgreSQL
	| SqlLSeg                            --     ,      , PostgreSQL
	| SqlPath                            --     ,      , PostgreSQL
	| SqlBox                             --     ,      , PostgreSQL
	| SqlPolygon                         --     ,      , PostgreSQL
	| SqlLine                            --     ,      , PostgreSQL
	| SqlCircle                          --     ,      , PostgreSQL
	| SqlUnknown Int                     -- ^ HSQL returns @SqlUnknown tp@ for all
	                                     -- columns for which it cannot determine
	                                     -- the right type. The @tp@ here is the
	                                     -- internal type code returned from the
	                                     -- backend library
	deriving (Eq, Show)

data SqlError
   = SqlError
		{ seState       :: String
		, seNativeError :: Int
		, seErrorMsg    :: String
		}
   | SqlNoData
   | SqlInvalidHandle
   | SqlStillExecuting
   | SqlNeedData
   | SqlBadTypeCast
   		{ seFieldName :: String
   		, seFieldType :: SqlType
   		}
   | SqlFetchNull
   		{ seFieldName :: String
		}
   | SqlUnknownField
		{ seFieldName :: String
		}
   | SqlUnsupportedOperation
   | SqlClosedHandle
#ifdef __GLASGOW_HASKELL__
   deriving Typeable
#endif

sqlErrorTc :: TyCon
sqlErrorTc = mkTyCon "Database.HSQL.SqlError"

#ifndef __GLASGOW_HASKELL__
instance Typeable SqlError where
	typeOf _ = mkAppTy sqlErrorTc []
#endif

instance Show SqlError where
	showsPrec _ (SqlError{seErrorMsg=msg}) = showString msg
	showsPrec _ SqlNoData                  = showString "No data"
	showsPrec _ SqlInvalidHandle           = showString "Invalid handle"
	showsPrec _ SqlStillExecuting          = showString "Stlll executing"
	showsPrec _ SqlNeedData                = showString "Need data"
	showsPrec _ (SqlBadTypeCast name tp)   = showString ("The type of " ++ name ++ " field can't be converted to " ++ show tp ++ " type")
	showsPrec _ (SqlFetchNull name)        = showString ("The value of " ++ name ++ " field is null")
	showsPrec _ (SqlUnknownField name)     = showString ("Unknown field name: " ++ name)
	showsPrec _ SqlUnsupportedOperation    = showString "Unsupported operation"
	showsPrec _ SqlClosedHandle            = showString "The referenced handle is already closed"

-- | A 'Connection' type represents a connection to a database, through which you can operate on the it.
-- In order to create the connection you need to use the @connect@ function from the module for
-- your prefered backend.
data Connection
  =  Connection
		{ connDisconnect :: IO ()
		, connExecute :: String -> IO ()
		, connQuery :: String -> IO Statement
		, connTables :: IO [String]
		, connDescribe :: String -> IO [FieldDef]
		, connBeginTransaction :: IO ()
		, connCommitTransaction :: IO ()
		, connRollbackTransaction :: IO ()
		, connClosed :: MVar Bool
		}

-- | The 'Statement' type represents a result from the execution of given SQL query.
data Statement
  =  Statement
		{ stmtConn   :: Connection
		, stmtClose  :: IO ()
		, stmtFetch  :: IO Bool
		, stmtGetCol :: forall a . Int -> FieldDef -> (FieldDef -> CString -> Int -> IO a) -> IO a
		, stmtFields :: [FieldDef]
		, stmtClosed :: MVar Bool
		}


class SqlBind a where
	-- This allows for faster conversion for eq. integral numeric types, etc.
	-- Default version uses fromSqlValue.
	fromSqlCStringLen :: FieldDef -> CString -> Int -> IO a
	fromSqlCStringLen (name,sqlType,_) cstr cstrLen
	  | cstr == nullPtr = throwDyn (SqlFetchNull name)
	  | otherwise       = do 
	      str <- peekCStringLen (cstr, cstrLen)
	      case fromSqlValue sqlType str of
	        Nothing -> throwDyn (SqlBadTypeCast name sqlType)
	        Just v  -> return v

	fromSqlValue :: SqlType -> String -> Maybe a
	toSqlValue   :: a -> String