[Haskell-cafe] Re: Handling custom types in Takusen
Benjamin Franksen
benjamin.franksen at bessy.de
Fri Jul 27 13:56:05 EDT 2007
Salvatore Insalaco wrote:
> I noticed that in Takusen there're just two instances to implement to
> make any Haskell type db-serializable: DBBind / SqliteBind for
> serialization and DBType for deserialization.
FWIW, I have two patches lying around (attached) that I wanted to send to
the Takusen maintainers anyway. They (the patches) implement (only)
instance DBType Data.ByteString for Oracle and Sqlite backends. They are
rudimentarily tested ("hey, seems to work!"), anyway a review might be in
order because I am not sure I understand the internals good enough -- for
all I know I might have introduced space leaks or whatnot.
Cheers
Ben
-------------- next part --------------
New patches:
[added ByteString support to Database/Oracle
benjamin.franksen at bessy.de**20070714222517] {
hunk ./Database/Oracle/Enumerator.lhs 41
+> import qualified Data.ByteString.Char8 as B
hunk ./Database/Oracle/Enumerator.lhs 948
+> bufferToByteString :: ColumnBuffer -> IO (Maybe B.ByteString)
+> bufferToByteString buffer = OCI.bufferToByteString (undefined, colBufBufferFPtr buffer, colBufNullFPtr buffer, colBufSizeFPtr buffer)
+
hunk ./Database/Oracle/Enumerator.lhs 1010
+> instance DBType (Maybe B.ByteString) Query ColumnBuffer where
+> allocBufferFor _ q n = allocBuffer q (16000, oci_SQLT_CHR) n
+> fetchCol q buffer = bufferToByteString buffer
+
hunk ./Database/Oracle/OCIFunctions.lhs 39
+> import qualified Data.ByteString.Base as B
hunk ./Database/Oracle/OCIFunctions.lhs 676
+
+> bufferToByteString :: ColumnInfo -> IO (Maybe B.ByteString)
+> bufferToByteString (_, bufFPtr, nullFPtr, sizeFPtr) =
+> withForeignPtr nullFPtr $ \nullIndPtr -> do
+> nullInd <- liftM cShort2Int (peek nullIndPtr)
+> if (nullInd == -1) -- -1 == null, 0 == value
+> then return Nothing
+> else do
+> -- Given a column buffer, extract a string of variable length
+> withForeignPtr bufFPtr $ \bufferPtr ->
+> withForeignPtr sizeFPtr $ \retSizePtr -> do
+> retsize <- liftM cUShort2Int (peek retSizePtr)
+> --create :: Int -> (Ptr Word8 -> IO ()) -> IO ByteString
+> val <- B.create retsize (\p -> copyBytes (castPtr p) bufferPtr retsize)
+> return (Just val)
}
[added ByteString support to Database/Sqlite
Ben Franksen <benjamin.franksen at bessy.de>**20070714230837] {
hunk ./Database/Sqlite/Enumerator.lhs 38
+> import qualified Data.ByteString.Char8 as B
hunk ./Database/Sqlite/Enumerator.lhs 366
+> bufferToByteString query buffer =
+> DBAPI.colValByteString (stmtHandle (queryStmt query)) (colPos buffer)
+
hunk ./Database/Sqlite/Enumerator.lhs 414
+> instance DBType (Maybe B.ByteString) Query ColumnBuffer where
+> allocBufferFor _ q n = allocBuffer q n
+> fetchCol q buffer = bufferToByteString q buffer
+
hunk ./Database/Sqlite/SqliteFunctions.lhs 22
+> import qualified Data.ByteString.Char8 as B
hunk ./Database/Sqlite/SqliteFunctions.lhs 278
+
+> colValByteString :: StmtHandle -> Int -> IO (Maybe B.ByteString)
+> colValByteString stmt colnum = do
+> cstrptr <- sqliteColumnText stmt (fromIntegral (colnum - 1))
+> if cstrptr == nullPtr
+> then return Nothing
+> else do
+> str <- B.copyCString cstrptr
+> return (Just str)
}
Context:
[added Functor and MonadFix instances to DBM
Ben Franksen <benjamin.franksen at bessy.de>**20070714112112]
[TAG 0.6
oleg at okmij.org**20070202102428]
Patch bundle hash:
3bd78e14633d172cbabf4fd716fc0bcf3b32fa8c
More information about the Haskell-Cafe
mailing list