{-# 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.
--
-----------------------------------------------------------------------------

module Data.Array.IO (
    -- * @IO@ arrays with boxed elements
    IOArray,             -- instance of: Eq, Typeable

    -- * @IO@ arrays with unboxed elements
    IOUArray,            -- instance of: Eq, Typeable

    -- * Overloaded mutable array interface
    module Data.Array.MArray,

    -- * Doing I\/O with @IOUArray@s
    hGetArray,           -- :: Handle -> IOUArray Int Word8 -> Int -> IO Int
    hPutArray,           -- :: Handle -> IOUArray Int Word8 -> Int -> IO ()
  ) where

import Data.Array.Base
import Data.Array.IO.Internals
import Data.Array.MArray
import System.IO.Error

import Foreign
import Foreign.C

import GHC.Exts  (MutableByteArray#, RealWorld)
import GHC.IO.Handle
import GHC.IO.Exception

-- ---------------------------------------------------------------------------
-- hGetArray

-- | Reads a number of 'Word8's from the specified 'Handle' directly
-- into an array.
hGetArray
        :: Handle               -- ^ Handle to read from
        -> IOUArray Int Word8   -- ^ Array in which to place the values
        -> Int                  -- ^ Number of 'Word8's to read
        -> IO Int
                -- ^ 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 Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
0              = Int -> IO Int
forall (m :: * -> *) a. Monad m => a -> m a
return Int
0
  | Int
count Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
0 Bool -> Bool -> Bool
|| Int
count Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
n  = Handle -> String -> Int -> IO Int
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.
      Int -> (Ptr Any -> IO Int) -> IO Int
forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
count ((Ptr Any -> IO Int) -> IO Int) -> (Ptr Any -> IO Int) -> IO Int
forall a b. (a -> b) -> a -> b
$ \Ptr Any
p -> do
        Int
r <- Handle -> Ptr Any -> Int -> IO Int
forall a. Handle -> Ptr a -> Int -> IO Int
hGetBuf Handle
handle Ptr Any
p Int
count
        Ptr ()
_ <- MutableByteArray# RealWorld -> Ptr Any -> CSize -> IO (Ptr ())
forall a.
MutableByteArray# RealWorld -> Ptr a -> CSize -> IO (Ptr ())
memcpy_ba_ptr MutableByteArray# RealWorld
ptr Ptr Any
p (Int -> CSize
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
r)
        Int -> IO Int
forall (m :: * -> *) a. Monad m => a -> m a
return Int
r

foreign import ccall unsafe "memcpy"
   memcpy_ba_ptr :: MutableByteArray# RealWorld -> Ptr a -> CSize -> IO (Ptr ())

-- ---------------------------------------------------------------------------
-- hPutArray

-- | Writes an array of 'Word8' to the specified 'Handle'.
hPutArray
        :: Handle                       -- ^ Handle to write to
        -> IOUArray Int Word8           -- ^ 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 Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
0              = () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
  | Int
count Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
0 Bool -> Bool -> Bool
|| Int
count Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
n  = Handle -> String -> Int -> IO ()
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.
     Int -> (Ptr Any -> IO ()) -> IO ()
forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
count ((Ptr Any -> IO ()) -> IO ()) -> (Ptr Any -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr Any
p -> do
       Ptr ()
_ <- Ptr Any -> MutableByteArray# RealWorld -> CSize -> IO (Ptr ())
forall a.
Ptr a -> MutableByteArray# RealWorld -> CSize -> IO (Ptr ())
memcpy_ptr_ba Ptr Any
p MutableByteArray# RealWorld
raw (Int -> CSize
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
count)
       Handle -> Ptr Any -> Int -> IO ()
forall a. Handle -> Ptr a -> Int -> IO ()
hPutBuf Handle
handle Ptr Any
p Int
count

foreign import ccall unsafe "memcpy"
   memcpy_ptr_ba :: Ptr a -> MutableByteArray# RealWorld -> CSize -> IO (Ptr ())

-- ---------------------------------------------------------------------------
-- Internal Utils

illegalBufferSize :: Handle -> String -> Int -> IO a
illegalBufferSize :: Handle -> String -> Int -> IO a
illegalBufferSize Handle
handle String
fn Int
sz =
        IOException -> IO a
forall a. IOException -> IO a
ioException (IOException -> String -> IOException
ioeSetErrorString
                     (IOErrorType
-> String -> Maybe Handle -> Maybe String -> IOException
mkIOError IOErrorType
InvalidArgument String
fn (Handle -> Maybe Handle
forall a. a -> Maybe a
Just Handle
handle) Maybe String
forall a. Maybe a
Nothing)
                     (String
"illegal buffer size " String -> String -> String
forall a. [a] -> [a] -> [a]
++ Int -> Int -> String -> String
forall a. Show a => Int -> a -> String -> String
showsPrec Int
9 (Int
sz::Int) []))