{------------------------------------------------------------------------------------- - - HDBC connectivity - Programmer: Leonidas Fegaras - Email: fegaras@cse.uta.edu - Web: http://lambda.uta.edu/ - Creation: 05/12/08, last update: 05/12/08 - - Copyright (c) 2008 by Leonidas Fegaras, the University of Texas at Arlington. All rights reserved. - This material is provided as is, with absolutely no warranty expressed or implied. - Any use is at your own risk. Permission is hereby granted to use or copy this program - for any purpose, provided the above notices are retained on all copies. - --------------------------------------------------------------------------------------} module XML.HXQ.DB where import Database.HDBC import XML.HXQ.XTree sql2xml :: SqlValue -> XTree sql2xml value = case value of SqlString s -> XText s SqlByteString bs -> XText (show bs) SqlWord32 n -> XInt (fromEnum n) SqlWord64 n -> XInt (fromEnum n) SqlInt32 n -> XText (show n) SqlInt64 n -> XText (show n) SqlInteger n -> XInt (fromEnum n) SqlChar c -> XText [c] SqlBool b -> XBool b SqlDouble n -> XText (show n) SqlRational n -> XText (show n) SqlEpochTime n -> XText (show n) SqlTimeDiff n -> XText (show n) SqlNull -> XText "" xml2sql :: XTree -> SqlValue xml2sql e = case e of XText s -> SqlString s XInt n -> SqlInteger (toInteger n) XFloat n -> SqlString (show n) XBool n -> SqlBool n executeSQL :: Statement -> XSeq -> IO XSeq executeSQL stmt args = do n <- handleSqlError (execute stmt (map xml2sql args)) result <- handleSqlError (fetchAllRowsAL stmt) return (map (\x -> XElem "row" [] 0 (map (\(s,v) -> XElem s [] 0 [sql2xml v]) x)) result) prepareSQL :: (IConnection conn) => conn -> String -> IO Statement prepareSQL db sql = handleSqlError (prepare db sql)