[project @ 2003-04-16 15:12:02 by sof]
[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 || count > rangeSize (l,u)
145   = illegalBufferSize handle "hGetArray" count
146   | otherwise = do
147       wantReadableHandle "hGetArray" handle $ 
148         \ handle_@Handle__{ haFD=fd, haBuffer=ref, haIsStream=is_stream } -> do
149         buf@Buffer{ bufBuf=raw, bufWPtr=w, bufRPtr=r } <- readIORef ref
150         if bufferEmpty buf
151            then readChunk fd is_stream ptr 0 count
152            else do 
153                 let avail = w - r
154                 copied <- if (count >= avail)
155                             then do 
156                                 memcpy_ba_baoff ptr raw r (fromIntegral avail)
157                                 writeIORef ref buf{ bufWPtr=0, bufRPtr=0 }
158                                 return avail
159                             else do 
160                                 memcpy_ba_baoff ptr raw r (fromIntegral count)
161                                 writeIORef ref buf{ bufRPtr = r + count }
162                                 return count
163
164                 let remaining = count - copied
165                 if remaining > 0 
166                    then do rest <- readChunk fd is_stream ptr copied remaining
167                            return (rest + copied)
168                    else return count
169
170 readChunk :: FD -> Bool -> RawBuffer -> Int -> Int -> IO Int
171 readChunk fd is_stream ptr init_off bytes = loop init_off bytes 
172  where
173   loop :: Int -> Int -> IO Int
174   loop off bytes | bytes <= 0 = return (off - init_off)
175   loop off bytes = do
176     r' <- readRawBuffer "readChunk" (fromIntegral fd) is_stream ptr
177                                     (fromIntegral off) (fromIntegral bytes)
178     let r = fromIntegral r'
179     if r == 0
180         then return (off - init_off)
181         else loop (off + r) (bytes - r)
182
183 -- ---------------------------------------------------------------------------
184 -- hPutArray
185
186 -- | Writes an array of 'Word8' to the specified 'Handle'.
187 hPutArray
188         :: Handle                       -- ^ Handle to write to
189         -> IOUArray Int Word8           -- ^ Array to write from
190         -> Int                          -- ^ Number of 'Word8's to write
191         -> IO ()
192
193 hPutArray handle (IOUArray (STUArray l u raw)) count
194   | count <= 0 || count > rangeSize (l,u)
195   = illegalBufferSize handle "hPutArray" count
196   | otherwise
197    = do wantWritableHandle "hPutArray" handle $ 
198           \ handle_@Handle__{ haFD=fd, haBuffer=ref, haIsStream=stream } -> do
199
200           old_buf@Buffer{ bufBuf=old_raw, bufRPtr=r, bufWPtr=w, bufSize=size }
201             <- readIORef ref
202
203           -- enough room in handle buffer?
204           if (size - w > count)
205                 -- There's enough room in the buffer:
206                 -- just copy the data in and update bufWPtr.
207             then do memcpy_baoff_ba old_raw w raw (fromIntegral count)
208                     writeIORef ref old_buf{ bufWPtr = w + count }
209                     return ()
210
211                 -- else, we have to flush
212             else do flushed_buf <- flushWriteBuffer fd stream old_buf
213                     writeIORef ref flushed_buf
214                     let this_buf = 
215                             Buffer{ bufBuf=raw, bufState=WriteBuffer, 
216                                     bufRPtr=0, bufWPtr=count, bufSize=count }
217                     flushWriteBuffer fd stream this_buf
218                     return ()
219
220 -- ---------------------------------------------------------------------------
221 -- Internal Utils
222
223 foreign import ccall unsafe "__hscore_memcpy_dst_off"
224    memcpy_baoff_ba :: RawBuffer -> Int -> RawBuffer -> CSize -> IO (Ptr ())
225 foreign import ccall unsafe "__hscore_memcpy_src_off"
226    memcpy_ba_baoff :: RawBuffer -> RawBuffer -> Int -> CSize -> IO (Ptr ())
227
228 illegalBufferSize :: Handle -> String -> Int -> IO a
229 illegalBufferSize handle fn sz = 
230         ioException (IOError (Just handle)
231                             InvalidArgument  fn
232                             ("illegal buffer size " ++ showsPrec 9 (sz::Int) [])
233                             Nothing)
234
235 #endif /* __GLASGOW_HASKELL__ */