| 
      
      
      From: <kr_...@us...> - 2003-09-27 09:10:25
      
     | 
| Update of /cvsroot/htoolkit/HSQL/MySQL
In directory sc8-pr-cvs1:/tmp/cvs-serv24891
Modified Files:
	HSQL.hsc 
Log Message:
formatting
Index: HSQL.hsc
===================================================================
RCS file: /cvsroot/htoolkit/HSQL/MySQL/HSQL.hsc,v
retrieving revision 1.6
retrieving revision 1.7
diff -C2 -d -r1.6 -r1.7
*** HSQL.hsc	25 Sep 2003 17:51:32 -0000	1.6
--- HSQL.hsc	27 Sep 2003 09:10:09 -0000	1.7
***************
*** 3,25 ****
  module Database.MySQL.HSQL
  		( SqlBind(..), SqlError(..), SqlType(..), Connection, Statement
! 		, catchSql		-- :: IO a -> (SqlError -> IO a) -> IO a
! 		, handleSql		-- :: (SqlError -> IO a) -> IO a -> IO a
! 		, sqlExceptions		-- :: Exception -> Maybe SqlError
! 		, connect		-- :: String -> String -> String -> IO Connection
! 		, disconnect		-- :: Connection -> IO ()
! 		, execute		-- :: Connection -> String -> IO ()
! 		, query			-- :: Connection -> String -> IO Statement
! 		, closeStatement	-- :: Statement -> IO ()
! 		, fetch			-- :: Statement -> IO Bool
! 		, inTransaction		-- :: Connection -> (Connection -> IO a) -> IO a
! 		, getFieldValueMB	-- :: SqlBind a => Statement -> String -> IO (Maybe a)
! 		, getFieldValue		-- :: SqlBind a => Statement -> String -> IO a
! 		, getFieldValue'	-- :: SqlBind a => Statement -> String -> a -> IO a
! 		, getFieldValueType	-- :: Statement -> String -> (SqlType, Bool)
! 		, getFieldsTypes	-- :: Statement -> [(String, SqlType, Bool)]
! 		, forEachRow		-- :: (Statement -> s -> IO s) -> Statement -> s -> IO s
! 		, forEachRow'		-- :: (Statement -> IO ()) -> Statement -> IO ()
! 		, collectRows		-- :: (Statement -> IO s) -> Statement -> IO [s]
! 		)	where
  
  
--- 3,25 ----
  module Database.MySQL.HSQL
  		( SqlBind(..), SqlError(..), SqlType(..), Connection, Statement
! 		, catchSql          -- :: IO a -> (SqlError -> IO a) -> IO a
! 		, handleSql         -- :: (SqlError -> IO a) -> IO a -> IO a
! 		, sqlExceptions     -- :: Exception -> Maybe SqlError
! 		, connect           -- :: String -> String -> String -> IO Connection
! 		, disconnect        -- :: Connection -> IO ()
! 		, execute           -- :: Connection -> String -> IO ()
! 		, query             -- :: Connection -> String -> IO Statement
! 		, closeStatement    -- :: Statement -> IO ()
! 		, fetch             -- :: Statement -> IO Bool
! 		, inTransaction     -- :: Connection -> (Connection -> IO a) -> IO a
! 		, getFieldValueMB   -- :: SqlBind a => Statement -> String -> IO (Maybe a)
! 		, getFieldValue     -- :: SqlBind a => Statement -> String -> IO a
! 		, getFieldValue'    -- :: SqlBind a => Statement -> String -> a -> IO a
! 		, getFieldValueType -- :: Statement -> String -> (SqlType, Bool)
! 		, getFieldsTypes    -- :: Statement -> [(String, SqlType, Bool)]
! 		, forEachRow        -- :: (Statement -> s -> IO s) -> Statement -> s -> IO s
! 		, forEachRow'       -- :: (Statement -> IO ()) -> Statement -> IO ()
! 		, collectRows       -- :: (Statement -> IO s) -> Statement -> IO [s]
! 		) where
  
  
***************
*** 65,72 ****
  data Statement
    =  Statement
! 		{ pRes 				:: !MYSQL_RES
! 		, connection			:: !Connection
! 		, fields			:: ![FieldDef]
! 		, currRow			:: IORef (MYSQL_ROW, MYSQL_LENGTHS)
  		}
  
--- 65,72 ----
  data Statement
    =  Statement
! 		{ pRes       :: !MYSQL_RES
! 		, connection :: !Connection
! 		, fields     :: ![FieldDef]
! 		, currRow    :: IORef (MYSQL_ROW, MYSQL_LENGTHS)
  		}
  
***************
*** 75,81 ****
  
  data SqlType
! 	= SqlChar			Int
! 	| SqlVarChar	Int
! 	| SqlNumeric		Int Int
  	| SqlSmallInt
  	| SqlMedInt
--- 75,81 ----
  
  data SqlType
! 	= SqlChar     Int
! 	| SqlVarChar  Int
! 	| SqlNumeric  Int Int
  	| SqlSmallInt
  	| SqlMedInt
***************
*** 199,221 ****
  
  		mkSqlType :: Int -> Int -> Int -> SqlType
! 		mkSqlType (#const FIELD_TYPE_STRING )		size 	_	= SqlChar size
! 		mkSqlType (#const FIELD_TYPE_VAR_STRING) size _  = SqlVarChar size
! 		mkSqlType (#const FIELD_TYPE_DECIMAL)		size 	prec	= SqlNumeric size prec
! 		mkSqlType (#const FIELD_TYPE_SHORT)		_    	_	= SqlSmallInt
! 		mkSqlType (#const FIELD_TYPE_INT24)			_		_  = SqlMedInt
! 		mkSqlType (#const FIELD_TYPE_LONG)		_    	_	= SqlInteger
! 		mkSqlType (#const FIELD_TYPE_FLOAT)		_    	_	= SqlReal
! 		mkSqlType (#const FIELD_TYPE_DOUBLE )		_    	_	= SqlDouble
! 		mkSqlType (#const FIELD_TYPE_TINY)		_	_	= SqlTinyInt
! 		mkSqlType (#const FIELD_TYPE_LONGLONG)		_	_	= SqlBigInt
! 		mkSqlType (#const FIELD_TYPE_DATE )		_	_	= SqlDate
! 		mkSqlType (#const FIELD_TYPE_TIME )		_	_	= SqlTime
! 		mkSqlType (#const FIELD_TYPE_TIMESTAMP )	_	_	= SqlTimeStamp
! 		mkSqlType (#const FIELD_TYPE_DATETIME) _ _ = SqlDateTime
! 		mkSqlType (#const FIELD_TYPE_YEAR) _ _ = SqlYear
! 		mkSqlType (#const FIELD_TYPE_BLOB) _ _ = SqlBLOB
! 		mkSqlType (#const FIELD_TYPE_SET)  _ _ = SqlSET
! 		mkSqlType (#const FIELD_TYPE_ENUM) _ _ = SqlENUM
! 		mkSqlType (#const FIELD_TYPE_NULL) _ _ = SqlUnknown
  
  -- | 'fetch' fetches the next rowset of data from the result set.
--- 199,221 ----
  
  		mkSqlType :: Int -> Int -> Int -> SqlType
! 		mkSqlType (#const FIELD_TYPE_STRING)     size _	   = SqlChar size
! 		mkSqlType (#const FIELD_TYPE_VAR_STRING) size _    = SqlVarChar size
! 		mkSqlType (#const FIELD_TYPE_DECIMAL)    size prec = SqlNumeric size prec
! 		mkSqlType (#const FIELD_TYPE_SHORT)      _    _    = SqlSmallInt
! 		mkSqlType (#const FIELD_TYPE_INT24)      _    _    = SqlMedInt
! 		mkSqlType (#const FIELD_TYPE_LONG)       _    _    = SqlInteger
! 		mkSqlType (#const FIELD_TYPE_FLOAT)      _    _	   = SqlReal
! 		mkSqlType (#const FIELD_TYPE_DOUBLE)     _    _    = SqlDouble
! 		mkSqlType (#const FIELD_TYPE_TINY)       _    _    = SqlTinyInt
! 		mkSqlType (#const FIELD_TYPE_LONGLONG)   _    _    = SqlBigInt
! 		mkSqlType (#const FIELD_TYPE_DATE)       _    _    = SqlDate
! 		mkSqlType (#const FIELD_TYPE_TIME)       _    _    = SqlTime
! 		mkSqlType (#const FIELD_TYPE_TIMESTAMP)  _    _    = SqlTimeStamp
! 		mkSqlType (#const FIELD_TYPE_DATETIME)   _    _    = SqlDateTime
! 		mkSqlType (#const FIELD_TYPE_YEAR)       _    _    = SqlYear
! 		mkSqlType (#const FIELD_TYPE_BLOB)       _    _    = SqlBLOB
! 		mkSqlType (#const FIELD_TYPE_SET)        _    _    = SqlSET
! 		mkSqlType (#const FIELD_TYPE_ENUM)       _    _    = SqlENUM
! 		mkSqlType (#const FIELD_TYPE_NULL)       _    _    = SqlUnknown
  
  -- | 'fetch' fetches the next rowset of data from the result set.
***************
*** 312,321 ****
  	toSqlValue s = '\'' : foldr mapChar "'" s
  		where
! 			mapChar '\\' s = '\\':'\\':s
! 			mapChar '\'' s = '\\':'\'':s
! 			mapChar '\n' s = '\\':'n':s
! 			mapChar '\r' s = '\\':'r':s
! 			mapChar '\t' s = '\\':'t':s
! 			mapChar c   s = c:s
  
  instance SqlBind Double where
--- 312,321 ----
  	toSqlValue s = '\'' : foldr mapChar "'" s
  		where
! 			mapChar '\\'   s = '\\':'\\':s
! 			mapChar '\''   s = '\\':'\'':s
! 			mapChar '\n'   s = '\\':'n' :s
! 			mapChar '\r'   s = '\\':'r' :s
! 			mapChar '\t'   s = '\\':'t' :s
! 			mapChar c      s = c        :s
  
  instance SqlBind Double where
***************
*** 331,339 ****
  	unsafePerformIO $ do
  		allocaBytes (#const sizeof(struct tm)) $ \ p_tm -> do
! 			(#poke struct tm,tm_sec   ) p_tm	(fromIntegral sec  :: CInt)
! 			(#poke struct tm,tm_min   ) p_tm	(fromIntegral min  :: CInt)
  			(#poke struct tm,tm_hour ) p_tm	(fromIntegral hour :: CInt)
! 			(#poke struct tm,tm_mday) p_tm	(fromIntegral mday :: CInt)
! 			(#poke struct tm,tm_mon ) p_tm	(fromIntegral (mon-1) :: CInt)
  			(#poke struct tm,tm_year ) p_tm	(fromIntegral (year-1900) :: CInt)
  			(#poke struct tm,tm_isdst) p_tm	(-1 :: CInt)
--- 331,339 ----
  	unsafePerformIO $ do
  		allocaBytes (#const sizeof(struct tm)) $ \ p_tm -> do
! 			(#poke struct tm,tm_sec  ) p_tm	(fromIntegral sec  :: CInt)
! 			(#poke struct tm,tm_min  ) p_tm	(fromIntegral min  :: CInt)
  			(#poke struct tm,tm_hour ) p_tm	(fromIntegral hour :: CInt)
! 			(#poke struct tm,tm_mday ) p_tm	(fromIntegral mday :: CInt)
! 			(#poke struct tm,tm_mon  ) p_tm	(fromIntegral (mon-1) :: CInt)
  			(#poke struct tm,tm_year ) p_tm	(fromIntegral (year-1900) :: CInt)
  			(#poke struct tm,tm_isdst) p_tm	(-1 :: CInt)
***************
*** 427,434 ****
  		then return Nothing
  		else do
! 		    mv <- fromNonNullSqlCStringLen sqlType pValue len
! 		    case mv of
! 			Just v   -> return (Just v)
! 			Nothing -> throwDyn (SqlBadTypeCast name sqlType)
  
  -- | Retrieves the value of field with the specified name.
--- 427,434 ----
  		then return Nothing
  		else do
! 			mv <- fromNonNullSqlCStringLen sqlType pValue len
! 			case mv of
! 				Just v  -> return (Just v)
! 				Nothing -> throwDyn (SqlBadTypeCast name sqlType)
  
  -- | Retrieves the value of field with the specified name.
***************
*** 441,445 ****
  	case mb_v of
  		Nothing -> throwDyn (SqlFetchNull name)
! 		Just a -> return a
  
  -- | Retrieves the value of field with the specified name.
--- 441,445 ----
  	case mb_v of
  		Nothing -> throwDyn (SqlFetchNull name)
! 		Just a  -> return a
  
  -- | Retrieves the value of field with the specified name.
***************
*** 467,471 ****
  findFieldInfo name (fieldDef@(name',sqlType,nullable):fields) colNumber
  	| name == name' = (sqlType,nullable,colNumber)
! 	| otherwise		= findFieldInfo name fields $! (colNumber+1)
  
  -----------------------------------------------------------------------------------------
--- 467,471 ----
  findFieldInfo name (fieldDef@(name',sqlType,nullable):fields) colNumber
  	| name == name' = (sqlType,nullable,colNumber)
! 	| otherwise     = findFieldInfo name fields $! (colNumber+1)
  
  -----------------------------------------------------------------------------------------
 |