[Haskell-cafe] bytestring vs. uvector
Manlio Perillo
manlio_perillo at libero.it
Fri Mar 13 12:55:30 EDT 2009
Don Stewart ha scritto:
> [...]
>> You also have to add instance for UIO:
>>
>> instance (RealFloat a, UIO a) => UIO (Complex a) where
>> hPutU h (UAComplex arr) = hPutU h arr
>> hGetU h = do arr <- hGetU h
>> return (UAComplex arr)
>>
>>
>> With Storable, this should not be required; you just have to write an
>> instance for the Storable class.
>>
>
> Though you get no IO operations with Storable... UIO is entirely
> separate.
>
Yes, but using Storable and Foreign.Ptr, IO is rather simple.
From storablevector package:
-- | Outputs a 'Vector' to the specified 'Handle'.
hPut :: (Storable a) => Handle -> Vector a -> IO ()
hPut h v =
if null v
then return ()
else
let (fptr, s, l) = toForeignPtr v
in withForeignPtr fptr $ \ ptr ->
let ptrS = advancePtr ptr s
ptrE = advancePtr ptrS l
-- use advancePtr and minusPtr in order to respect
-- alignment
in hPutBuf h ptrS (minusPtr ptrE ptrS)
-- | Read a 'Vector' directly from the specified 'Handle'. This
-- is far more efficient than reading the characters into a list
-- and then using 'pack'.
--
hGet :: (Storable a) => Handle -> Int -> IO (Vector a)
hGet _ 0 = return empty
hGet h i =
createAndTrim i $ \p ->
let elemType :: Ptr a -> a
elemType _ = undefined
sizeOfElem = sizeOf (elemType p)
in fmap (flip div sizeOfElem) $
hGetBuf h p (i * sizeOfElem)
Regards Manlio
More information about the Haskell-Cafe
mailing list