bc82e2d42e9f476a823b01ca90d6b37cf18317c1
[ghc-base.git] / Data / Array / IO.hs
1 {-# OPTIONS -#include "HsBase.h" #-}
2 -----------------------------------------------------------------------------
3 -- |
4 -- Module      :  Data.Array.IO
5 -- Copyright   :  (c) The University of Glasgow 2001
6 -- License     :  BSD-style (see the file libraries/base/LICENSE)
7 -- 
8 -- Maintainer  :  libraries@haskell.org
9 -- Stability   :  experimental
10 -- Portability :  non-portable
11 --
12 -- Mutable boxed and unboxed arrays in the IO monad.
13 --
14 -----------------------------------------------------------------------------
15
16 module Data.Array.IO (
17    -- * @IO@ arrays with boxed elements
18    IOArray,             -- instance of: Eq, Typeable
19
20    -- * @IO@ arrays with unboxed elements
21    IOUArray,            -- instance of: Eq, Typeable
22 #ifdef __GLASGOW_HASKELL__
23    castIOUArray,        -- :: IOUArray i a -> IO (IOUArray i b)
24 #endif
25
26    -- * Overloaded mutable array interface
27    module Data.Array.MArray,
28
29 #ifdef __GLASGOW_HASKELL__
30    -- * Doing I\/O with @IOUArray@s
31    hGetArray,           -- :: Handle -> IOUArray Int Word8 -> Int -> IO Int
32    hPutArray,           -- :: Handle -> IOUArray Int Word8 -> Int -> IO ()
33 #endif
34  ) where
35
36 import Prelude
37
38 import Data.Array.IO.Internals
39 import Data.Array               ( Array )
40 import Data.Array.MArray
41 import Data.Int
42 import Data.Word
43
44 #ifdef __GLASGOW_HASKELL__
45 import Foreign
46 import Foreign.C
47 import Data.Array.Base
48
49 import GHC.Arr
50 import GHC.ST           ( ST(..) )
51 import GHC.IOBase
52 import GHC.Handle
53 #endif
54
55 #ifdef __GLASGOW_HASKELL__
56 -----------------------------------------------------------------------------
57 -- Freezing
58
59 freezeIOArray :: Ix ix => IOArray ix e -> IO (Array ix e)
60 freezeIOArray (IOArray marr) = stToIO (freezeSTArray marr)
61
62 freezeIOUArray :: Ix ix => IOUArray ix e -> IO (UArray ix e)
63 freezeIOUArray (IOUArray marr) = stToIO (freezeSTUArray marr)
64
65 {-# RULES
66 "freeze/IOArray"  freeze = freezeIOArray
67 "freeze/IOUArray" freeze = freezeIOUArray
68     #-}
69
70 {-# INLINE unsafeFreezeIOArray #-}
71 unsafeFreezeIOArray :: Ix ix => IOArray ix e -> IO (Array ix e)
72 unsafeFreezeIOArray (IOArray marr) = stToIO (unsafeFreezeSTArray marr)
73
74 {-# INLINE unsafeFreezeIOUArray #-}
75 unsafeFreezeIOUArray :: Ix ix => IOUArray ix e -> IO (UArray ix e)
76 unsafeFreezeIOUArray (IOUArray marr) = stToIO (unsafeFreezeSTUArray marr)
77
78 {-# RULES
79 "unsafeFreeze/IOArray"  unsafeFreeze = unsafeFreezeIOArray
80 "unsafeFreeze/IOUArray" unsafeFreeze = unsafeFreezeIOUArray
81     #-}
82
83 -----------------------------------------------------------------------------
84 -- Thawing
85
86 thawIOArray :: Ix ix => Array ix e -> IO (IOArray ix e)
87 thawIOArray arr = stToIO $ do
88     marr <- thawSTArray arr
89     return (IOArray marr)
90
91 thawIOUArray :: Ix ix => UArray ix e -> IO (IOUArray ix e)
92 thawIOUArray arr = stToIO $ do
93     marr <- thawSTUArray arr
94     return (IOUArray marr)
95
96 {-# RULES
97 "thaw/IOArray"  thaw = thawIOArray
98 "thaw/IOUArray" thaw = thawIOUArray
99     #-}
100
101 {-# INLINE unsafeThawIOArray #-}
102 unsafeThawIOArray :: Ix ix => Array ix e -> IO (IOArray ix e)
103 unsafeThawIOArray arr = stToIO $ do
104     marr <- unsafeThawSTArray arr
105     return (IOArray marr)
106
107 {-# INLINE unsafeThawIOUArray #-}
108 unsafeThawIOUArray :: Ix ix => UArray ix e -> IO (IOUArray ix e)
109 unsafeThawIOUArray arr = stToIO $ do
110     marr <- unsafeThawSTUArray arr
111     return (IOUArray marr)
112
113 {-# RULES
114 "unsafeThaw/IOArray"  unsafeThaw = unsafeThawIOArray
115 "unsafeThaw/IOUArray" unsafeThaw = unsafeThawIOUArray
116     #-}
117
118 castSTUArray :: STUArray s ix a -> ST s (STUArray s ix b)
119 castSTUArray (STUArray l u marr#) = return (STUArray l u marr#)
120
121 -- | Casts an 'IOUArray' with one element type into one with a
122 -- different element type.  All the elements of the resulting array
123 -- are undefined (unless you know what you\'re doing...).
124 castIOUArray :: IOUArray ix a -> IO (IOUArray ix b)
125 castIOUArray (IOUArray marr) = stToIO $ do
126     marr' <- castSTUArray marr
127     return (IOUArray marr')
128
129 -- ---------------------------------------------------------------------------
130 -- hGetArray
131
132 -- | Reads a number of 'Word8's from the specified 'Handle' directly
133 -- into an array.
134 hGetArray
135         :: Handle               -- ^ Handle to read from
136         -> IOUArray Int Word8   -- ^ Array in which to place the values
137         -> Int                  -- ^ Number of 'Word8's to read
138         -> IO Int
139                 -- ^ Returns: the number of 'Word8's actually 
140                 -- read, which might be smaller than the number requested
141                 -- if the end of file was reached.
142
143 hGetArray handle (IOUArray (STUArray l u ptr)) count
144   | count == 0
145   = return 0
146   | count < 0 || count > rangeSize (l,u)
147   = illegalBufferSize handle "hGetArray" count
148   | otherwise = do
149       wantReadableHandle "hGetArray" handle $ 
150         \ handle_@Handle__{ haFD=fd, haBuffer=ref, haIsStream=is_stream } -> do
151         buf@Buffer{ bufBuf=raw, bufWPtr=w, bufRPtr=r } <- readIORef ref
152         if bufferEmpty buf
153            then readChunk fd is_stream ptr 0 count
154            else do 
155                 let avail = w - r
156                 copied <- if (count >= avail)
157                             then do 
158                                 memcpy_ba_baoff ptr raw r (fromIntegral avail)
159                                 writeIORef ref buf{ bufWPtr=0, bufRPtr=0 }
160                                 return avail
161                             else do 
162                                 memcpy_ba_baoff ptr raw r (fromIntegral count)
163                                 writeIORef ref buf{ bufRPtr = r + count }
164                                 return count
165
166                 let remaining = count - copied
167                 if remaining > 0 
168                    then do rest <- readChunk fd is_stream ptr copied remaining
169                            return (rest + copied)
170                    else return count
171
172 readChunk :: FD -> Bool -> RawBuffer -> Int -> Int -> IO Int
173 readChunk fd is_stream ptr init_off bytes = loop init_off bytes 
174  where
175   loop :: Int -> Int -> IO Int
176   loop off bytes | bytes <= 0 = return (off - init_off)
177   loop off bytes = do
178     r' <- readRawBuffer "readChunk" (fromIntegral fd) is_stream ptr
179                                     (fromIntegral off) (fromIntegral bytes)
180     let r = fromIntegral r'
181     if r == 0
182         then return (off - init_off)
183         else loop (off + r) (bytes - r)
184
185 -- ---------------------------------------------------------------------------
186 -- hPutArray
187
188 -- | Writes an array of 'Word8' to the specified 'Handle'.
189 hPutArray
190         :: Handle                       -- ^ Handle to write to
191         -> IOUArray Int Word8           -- ^ Array to write from
192         -> Int                          -- ^ Number of 'Word8's to write
193         -> IO ()
194
195 hPutArray handle (IOUArray (STUArray l u raw)) count
196   | count == 0
197   = return ()
198   | count < 0 || count > rangeSize (l,u)
199   = illegalBufferSize handle "hPutArray" count
200   | otherwise
201    = do wantWritableHandle "hPutArray" handle $ 
202           \ handle_@Handle__{ haFD=fd, haBuffer=ref, haIsStream=stream } -> do
203
204           old_buf@Buffer{ bufBuf=old_raw, bufRPtr=r, bufWPtr=w, bufSize=size }
205             <- readIORef ref
206
207           -- enough room in handle buffer?
208           if (size - w > count)
209                 -- There's enough room in the buffer:
210                 -- just copy the data in and update bufWPtr.
211             then do memcpy_baoff_ba old_raw w raw (fromIntegral count)
212                     writeIORef ref old_buf{ bufWPtr = w + count }
213                     return ()
214
215                 -- else, we have to flush
216             else do flushed_buf <- flushWriteBuffer fd stream old_buf
217                     writeIORef ref flushed_buf
218                     let this_buf = 
219                             Buffer{ bufBuf=raw, bufState=WriteBuffer, 
220                                     bufRPtr=0, bufWPtr=count, bufSize=count }
221                     flushWriteBuffer fd stream this_buf
222                     return ()
223
224 -- ---------------------------------------------------------------------------
225 -- Internal Utils
226
227 foreign import ccall unsafe "__hscore_memcpy_dst_off"
228    memcpy_baoff_ba :: RawBuffer -> Int -> RawBuffer -> CSize -> IO (Ptr ())
229 foreign import ccall unsafe "__hscore_memcpy_src_off"
230    memcpy_ba_baoff :: RawBuffer -> RawBuffer -> Int -> CSize -> IO (Ptr ())
231
232 illegalBufferSize :: Handle -> String -> Int -> IO a
233 illegalBufferSize handle fn sz = 
234         ioException (IOError (Just handle)
235                             InvalidArgument  fn
236                             ("illegal buffer size " ++ showsPrec 9 (sz::Int) [])
237                             Nothing)
238
239 #endif /* __GLASGOW_HASKELL__ */