{-# LANGUAGE MagicHash, UnliftedFFITypes #-}------------------------------------------------------------------------------- |-- Module : Data.Array.IO-- Copyright : (c) The University of Glasgow 2001-- License : BSD-style (see the file libraries/base/LICENSE)---- Maintainer : libraries@haskell.org-- Stability : experimental-- Portability : non-portable (uses Data.Array.MArray)---- Mutable boxed and unboxed arrays in the IO monad.-------------------------------------------------------------------------------moduleData.Array.IO(-- * @IO@ arrays with boxed elementsIOArray,-- instance of: Eq, Typeable-- * @IO@ arrays with unboxed elementsIOUArray ,-- instance of: Eq, Typeable-- * Overloaded mutable array interfacemoduleData.Array.MArray ,-- * Doing I\/O with @IOUArray@shGetArray ,-- :: Handle -> IOUArray Int Word8 -> Int -> IO InthPutArray ,-- :: Handle -> IOUArray Int Word8 -> Int -> IO ())whereimportData.Array.Base importData.Array.IO.Internals importData.Array.MArray importSystem.IO.ErrorimportForeignimportForeign.CimportGHC.Exts(MutableByteArray#,RealWorld)importGHC.IO.HandleimportGHC.IO.Exception-- ----------------------------------------------------------------------------- hGetArray-- | Reads a number of 'Word8's from the specified 'Handle' directly-- into an array.hGetArray ::Handle-- ^ Handle to read from->IOUArray IntWord8-- ^ Array in which to place the values->Int-- ^ Number of 'Word8's to read->IOInt-- ^ Returns: the number of 'Word8's actually-- read, which might be smaller than the number requested-- if the end of file was reached.hGetArray :: Handle -> IOUArray Int Word8 -> Int -> IO Int
hGetArray Handle
handle (IOUArray (STUArray Int
_l Int
_u Int
n MutableByteArray# RealWorld
ptr ))Int
count |Int
count forall a. Eq a => a -> a -> Bool
==Int
0=forall (m :: * -> *) a. Monad m => a -> m a
returnInt
0|Int
count forall a. Ord a => a -> a -> Bool
<Int
0Bool -> Bool -> Bool
||Int
count forall a. Ord a => a -> a -> Bool
>Int
n =forall a. Handle -> String -> Int -> IO a
illegalBufferSize Handle
handle String
"hGetArray"Int
count |Bool
otherwise=do-- we would like to read directly into the buffer, but we can't-- be sure that the MutableByteArray# is pinned, so we have to-- allocate a separate area of memory and copy.forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytesInt
count forall a b. (a -> b) -> a -> b
$\Ptr Any
p ->doInt
r <-forall a. Handle -> Ptr a -> Int -> IO Int
hGetBufHandle
handle Ptr Any
p Int
count Ptr ()
_<-forall a.
MutableByteArray# RealWorld -> Ptr a -> CSize -> IO (Ptr ())
memcpy_ba_ptr MutableByteArray# RealWorld
ptr Ptr Any
p (forall a b. (Integral a, Num b) => a -> b
fromIntegralInt
r )forall (m :: * -> *) a. Monad m => a -> m a
returnInt
r foreignimportccallunsafe"memcpy"memcpy_ba_ptr ::MutableByteArray#RealWorld->Ptra ->CSize->IO(Ptr())-- ----------------------------------------------------------------------------- hPutArray-- | Writes an array of 'Word8' to the specified 'Handle'.hPutArray ::Handle-- ^ Handle to write to->IOUArray IntWord8-- ^ Array to write from->Int-- ^ Number of 'Word8's to write->IO()hPutArray :: Handle -> IOUArray Int Word8 -> Int -> IO ()
hPutArray Handle
handle (IOUArray (STUArray Int
_l Int
_u Int
n MutableByteArray# RealWorld
raw ))Int
count |Int
count forall a. Eq a => a -> a -> Bool
==Int
0=forall (m :: * -> *) a. Monad m => a -> m a
return()|Int
count forall a. Ord a => a -> a -> Bool
<Int
0Bool -> Bool -> Bool
||Int
count forall a. Ord a => a -> a -> Bool
>Int
n =forall a. Handle -> String -> Int -> IO a
illegalBufferSize Handle
handle String
"hPutArray"Int
count |Bool
otherwise=do-- as in hGetArray, we would like to use the array directly, but-- we can't be sure that the MutableByteArray# is pinned.forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytesInt
count forall a b. (a -> b) -> a -> b
$\Ptr Any
p ->doPtr ()
_<-forall a.
Ptr a -> MutableByteArray# RealWorld -> CSize -> IO (Ptr ())
memcpy_ptr_ba Ptr Any
p MutableByteArray# RealWorld
raw (forall a b. (Integral a, Num b) => a -> b
fromIntegralInt
count )forall a. Handle -> Ptr a -> Int -> IO ()
hPutBufHandle
handle Ptr Any
p Int
count foreignimportccallunsafe"memcpy"memcpy_ptr_ba ::Ptra ->MutableByteArray#RealWorld->CSize->IO(Ptr())-- ----------------------------------------------------------------------------- Internal UtilsillegalBufferSize ::Handle->String->Int->IOa illegalBufferSize :: forall a. Handle -> String -> Int -> IO a
illegalBufferSize Handle
handle String
fn Int
sz =forall a. IOException -> IO a
ioException(IOException -> String -> IOException
ioeSetErrorString(IOErrorType
-> String -> Maybe Handle -> Maybe String -> IOException
mkIOErrorIOErrorType
InvalidArgumentString
fn (forall a. a -> Maybe a
JustHandle
handle )forall a. Maybe a
Nothing)(String
"illegal buffer size "forall a. [a] -> [a] -> [a]
++forall a. Show a => Int -> a -> ShowS
showsPrecInt
9(Int
sz ::Int)[]))

AltStyle によって変換されたページ (->オリジナル) /