module Bio.Iteratee.ReadableChunk ( ReadableChunk(..) ) where
import Control.Monad.IO.Class
import Data.Word
import Foreign.C
import Foreign.Marshal.Array
import Foreign.Ptr
import Foreign.Storable
import Prelude
import qualified Data.ByteString as B
import qualified Data.ByteString.Lazy as L
class (Storable el) => ReadableChunk s el | s -> el where
readFromPtr ::
MonadIO m =>
Ptr el
-> Int
-> m s
instance ReadableChunk [Char] Char where
readFromPtr buf l = liftIO $ peekCAStringLen (castPtr buf, l)
instance ReadableChunk [Word8] Word8 where
readFromPtr buf l = liftIO $ peekArray l buf
instance ReadableChunk [Word16] Word16 where
readFromPtr buf l = liftIO $ peekArray l buf
instance ReadableChunk [Word32] Word32 where
readFromPtr buf l = liftIO $ peekArray l buf
instance ReadableChunk [Word] Word where
readFromPtr buf l = liftIO $ peekArray l buf
instance ReadableChunk B.ByteString Word8 where
readFromPtr buf l = liftIO $ B.packCStringLen (castPtr buf, l)
instance ReadableChunk L.ByteString Word8 where
readFromPtr buf l = liftIO $
return . L.fromChunks . (:[]) =<< readFromPtr buf l