Use explicit language extensions & remove extension fields from base.cabal
[ghc-base.git] / GHC / IO / Handle / Types.hs
1 {-# LANGUAGE CPP
2            , NoImplicitPrelude
3            , ExistentialQuantification
4            , DeriveDataTypeable
5   #-}
6 {-# OPTIONS_GHC -funbox-strict-fields #-}
7 {-# OPTIONS_HADDOCK hide #-}
8
9 -----------------------------------------------------------------------------
10 -- |
11 -- Module      :  GHC.IO.Handle.Types
12 -- Copyright   :  (c) The University of Glasgow, 1994-2009
13 -- License     :  see libraries/base/LICENSE
14 -- 
15 -- Maintainer  :  libraries@haskell.org
16 -- Stability   :  internal
17 -- Portability :  non-portable
18 --
19 -- Basic types for the implementation of IO Handles.
20 --
21 -----------------------------------------------------------------------------
22
23 module GHC.IO.Handle.Types (
24       Handle(..), Handle__(..), showHandle,
25       checkHandleInvariants,
26       BufferList(..),
27       HandleType(..),
28       isReadableHandleType, isWritableHandleType, isReadWriteHandleType,
29       BufferMode(..),
30       BufferCodec(..),
31       NewlineMode(..), Newline(..), nativeNewline,
32       universalNewlineMode, noNewlineTranslation, nativeNewlineMode
33   ) where
34
35 #undef DEBUG
36
37 import GHC.Base
38 import GHC.MVar
39 import GHC.IO
40 import GHC.IO.Buffer
41 import GHC.IO.BufferedIO
42 import GHC.IO.Encoding.Types
43 import GHC.IORef
44 import Data.Maybe
45 import GHC.Show
46 import GHC.Read
47 import GHC.Word
48 import GHC.IO.Device
49 import Data.Typeable
50 #ifdef DEBUG
51 import Control.Monad
52 #endif
53
54 -- ---------------------------------------------------------------------------
55 -- Handle type
56
57 --  A Handle is represented by (a reference to) a record 
58 --  containing the state of the I/O port/device. We record
59 --  the following pieces of info:
60
61 --    * type (read,write,closed etc.)
62 --    * the underlying file descriptor
63 --    * buffering mode 
64 --    * buffer, and spare buffers
65 --    * user-friendly name (usually the
66 --      FilePath used when IO.openFile was called)
67
68 -- Note: when a Handle is garbage collected, we want to flush its buffer
69 -- and close the OS file handle, so as to free up a (precious) resource.
70
71 -- | Haskell defines operations to read and write characters from and to files,
72 -- represented by values of type @Handle@.  Each value of this type is a
73 -- /handle/: a record used by the Haskell run-time system to /manage/ I\/O
74 -- with file system objects.  A handle has at least the following properties:
75 -- 
76 --  * whether it manages input or output or both;
77 --
78 --  * whether it is /open/, /closed/ or /semi-closed/;
79 --
80 --  * whether the object is seekable;
81 --
82 --  * whether buffering is disabled, or enabled on a line or block basis;
83 --
84 --  * a buffer (whose length may be zero).
85 --
86 -- Most handles will also have a current I\/O position indicating where the next
87 -- input or output operation will occur.  A handle is /readable/ if it
88 -- manages only input or both input and output; likewise, it is /writable/ if
89 -- it manages only output or both input and output.  A handle is /open/ when
90 -- first allocated.
91 -- Once it is closed it can no longer be used for either input or output,
92 -- though an implementation cannot re-use its storage while references
93 -- remain to it.  Handles are in the 'Show' and 'Eq' classes.  The string
94 -- produced by showing a handle is system dependent; it should include
95 -- enough information to identify the handle for debugging.  A handle is
96 -- equal according to '==' only to itself; no attempt
97 -- is made to compare the internal state of different handles for equality.
98
99 data Handle 
100   = FileHandle                          -- A normal handle to a file
101         FilePath                        -- the file (used for error messages
102                                         -- only)
103         !(MVar Handle__)
104
105   | DuplexHandle                        -- A handle to a read/write stream
106         FilePath                        -- file for a FIFO, otherwise some
107                                         --   descriptive string (used for error
108                                         --   messages only)
109         !(MVar Handle__)                -- The read side
110         !(MVar Handle__)                -- The write side
111
112   deriving Typeable
113
114 -- NOTES:
115 --    * A 'FileHandle' is seekable.  A 'DuplexHandle' may or may not be
116 --      seekable.
117
118 instance Eq Handle where
119  (FileHandle _ h1)     == (FileHandle _ h2)     = h1 == h2
120  (DuplexHandle _ h1 _) == (DuplexHandle _ h2 _) = h1 == h2
121  _ == _ = False 
122
123 data Handle__
124   = forall dev enc_state dec_state . (IODevice dev, BufferedIO dev, Typeable dev) =>
125     Handle__ {
126       haDevice      :: !dev,
127       haType        :: HandleType,           -- type (read/write/append etc.)
128       haByteBuffer  :: !(IORef (Buffer Word8)),
129       haBufferMode  :: BufferMode,
130       haLastDecode  :: !(IORef (dec_state, Buffer Word8)),
131       haCharBuffer  :: !(IORef (Buffer CharBufElem)), -- the current buffer
132       haBuffers     :: !(IORef (BufferList CharBufElem)),  -- spare buffers
133       haEncoder     :: Maybe (TextEncoder enc_state),
134       haDecoder     :: Maybe (TextDecoder dec_state),
135       haCodec       :: Maybe TextEncoding,
136       haInputNL     :: Newline,
137       haOutputNL    :: Newline,
138       haOtherSide   :: Maybe (MVar Handle__) -- ptr to the write side of a 
139                                              -- duplex handle.
140     }
141     deriving Typeable
142
143 -- we keep a few spare buffers around in a handle to avoid allocating
144 -- a new one for each hPutStr.  These buffers are *guaranteed* to be the
145 -- same size as the main buffer.
146 data BufferList e
147   = BufferListNil 
148   | BufferListCons (RawBuffer e) (BufferList e)
149
150 --  Internally, we classify handles as being one
151 --  of the following:
152
153 data HandleType
154  = ClosedHandle
155  | SemiClosedHandle
156  | ReadHandle
157  | WriteHandle
158  | AppendHandle
159  | ReadWriteHandle
160
161 isReadableHandleType :: HandleType -> Bool
162 isReadableHandleType ReadHandle         = True
163 isReadableHandleType ReadWriteHandle    = True
164 isReadableHandleType _                  = False
165
166 isWritableHandleType :: HandleType -> Bool
167 isWritableHandleType AppendHandle    = True
168 isWritableHandleType WriteHandle     = True
169 isWritableHandleType ReadWriteHandle = True
170 isWritableHandleType _               = False
171
172 isReadWriteHandleType :: HandleType -> Bool
173 isReadWriteHandleType ReadWriteHandle{} = True
174 isReadWriteHandleType _                 = False
175
176 -- INVARIANTS on Handles:
177 --
178 --   * A handle *always* has a buffer, even if it is only 1 character long
179 --     (an unbuffered handle needs a 1 character buffer in order to support
180 --      hLookAhead and hIsEOF).
181 --   * In a read Handle, the byte buffer is always empty (we decode when reading)
182 --   * In a wriite Handle, the Char buffer is always empty (we encode when writing)
183 --
184 checkHandleInvariants :: Handle__ -> IO ()
185 #ifdef DEBUG
186 checkHandleInvariants h_ = do
187  bbuf <- readIORef (haByteBuffer h_)
188  checkBuffer bbuf
189  cbuf <- readIORef (haCharBuffer h_)
190  checkBuffer cbuf
191  when (isWriteBuffer cbuf && not (isEmptyBuffer cbuf)) $
192    error ("checkHandleInvariants: char write buffer non-empty: " ++
193           summaryBuffer bbuf ++ ", " ++ summaryBuffer cbuf)
194  when (isWriteBuffer bbuf /= isWriteBuffer cbuf) $
195    error ("checkHandleInvariants: buffer modes differ: " ++
196           summaryBuffer bbuf ++ ", " ++ summaryBuffer cbuf)
197
198 #else
199 checkHandleInvariants _ = return ()
200 #endif
201
202 -- ---------------------------------------------------------------------------
203 -- Buffering modes
204
205 -- | Three kinds of buffering are supported: line-buffering, 
206 -- block-buffering or no-buffering.  These modes have the following
207 -- effects. For output, items are written out, or /flushed/,
208 -- from the internal buffer according to the buffer mode:
209 --
210 --  * /line-buffering/: the entire output buffer is flushed
211 --    whenever a newline is output, the buffer overflows, 
212 --    a 'System.IO.hFlush' is issued, or the handle is closed.
213 --
214 --  * /block-buffering/: the entire buffer is written out whenever it
215 --    overflows, a 'System.IO.hFlush' is issued, or the handle is closed.
216 --
217 --  * /no-buffering/: output is written immediately, and never stored
218 --    in the buffer.
219 --
220 -- An implementation is free to flush the buffer more frequently,
221 -- but not less frequently, than specified above.
222 -- The output buffer is emptied as soon as it has been written out.
223 --
224 -- Similarly, input occurs according to the buffer mode for the handle:
225 --
226 --  * /line-buffering/: when the buffer for the handle is not empty,
227 --    the next item is obtained from the buffer; otherwise, when the
228 --    buffer is empty, characters up to and including the next newline
229 --    character are read into the buffer.  No characters are available
230 --    until the newline character is available or the buffer is full.
231 --
232 --  * /block-buffering/: when the buffer for the handle becomes empty,
233 --    the next block of data is read into the buffer.
234 --
235 --  * /no-buffering/: the next input item is read and returned.
236 --    The 'System.IO.hLookAhead' operation implies that even a no-buffered
237 --    handle may require a one-character buffer.
238 --
239 -- The default buffering mode when a handle is opened is
240 -- implementation-dependent and may depend on the file system object
241 -- which is attached to that handle.
242 -- For most implementations, physical files will normally be block-buffered 
243 -- and terminals will normally be line-buffered.
244
245 data BufferMode  
246  = NoBuffering  -- ^ buffering is disabled if possible.
247  | LineBuffering
248                 -- ^ line-buffering should be enabled if possible.
249  | BlockBuffering (Maybe Int)
250                 -- ^ block-buffering should be enabled if possible.
251                 -- The size of the buffer is @n@ items if the argument
252                 -- is 'Just' @n@ and is otherwise implementation-dependent.
253    deriving (Eq, Ord, Read, Show)
254
255 {-
256 [note Buffering Implementation]
257
258 Each Handle has two buffers: a byte buffer (haByteBuffer) and a Char
259 buffer (haCharBuffer).  
260
261 [note Buffered Reading]
262
263 For read Handles, bytes are read into the byte buffer, and immediately
264 decoded into the Char buffer (see
265 GHC.IO.Handle.Internals.readTextDevice).  The only way there might be
266 some data left in the byte buffer is if there is a partial multi-byte
267 character sequence that cannot be decoded into a full character.
268
269 Note that the buffering mode (haBufferMode) makes no difference when
270 reading data into a Handle.  When reading, we can always just read all
271 the data there is available without blocking, decode it into the Char
272 buffer, and then provide it immediately to the caller.
273
274 [note Buffered Writing]
275
276 Characters are written into the Char buffer by e.g. hPutStr.  At the
277 end of the operation, or when the char buffer is full, the buffer is
278 decoded to the byte buffer (see writeCharBuffer).  This is so that we
279 can detect encoding errors at the right point.
280
281 Hence, the Char buffer is always empty between Handle operations.
282
283 [note Buffer Sizing]
284
285 The char buffer is always a default size (dEFAULT_CHAR_BUFFER_SIZE).
286 The byte buffer size is chosen by the underlying device (via its
287 IODevice.newBuffer).  Hence the size of these buffers is not under
288 user control.
289
290 There are certain minimum sizes for these buffers imposed by the
291 library (but not checked):
292
293  - we must be able to buffer at least one character, so that
294    hLookAhead can work
295
296  - the byte buffer must be able to store at least one encoded
297    character in the current encoding (6 bytes?)
298
299  - when reading, the char buffer must have room for two characters, so
300    that we can spot the \r\n sequence.
301
302 How do we implement hSetBuffering?
303
304 For reading, we have never used the user-supplied buffer size, because
305 there's no point: we always pass all available data to the reader
306 immediately.  Buffering would imply waiting until a certain amount of
307 data is available, which has no advantages.  So hSetBuffering is
308 essentially a no-op for read handles, except that it turns on/off raw
309 mode for the underlying device if necessary.
310
311 For writing, the buffering mode is handled by the write operations
312 themselves (hPutChar and hPutStr).  Every write ends with
313 writeCharBuffer, which checks whether the buffer should be flushed
314 according to the current buffering mode.  Additionally, we look for
315 newlines and flush if the mode is LineBuffering.
316
317 [note Buffer Flushing]
318
319 ** Flushing the Char buffer
320
321 We must be able to flush the Char buffer, in order to implement
322 hSetEncoding, and things like hGetBuf which want to read raw bytes.
323
324 Flushing the Char buffer on a write Handle is easy: it is always empty.
325
326 Flushing the Char buffer on a read Handle involves rewinding the byte
327 buffer to the point representing the next Char in the Char buffer.
328 This is done by
329
330  - remembering the state of the byte buffer *before* the last decode
331
332  - re-decoding the bytes that represent the chars already read from the
333    Char buffer.  This gives us the point in the byte buffer that
334    represents the *next* Char to be read.
335
336 In order for this to work, after readTextHandle we must NOT MODIFY THE
337 CONTENTS OF THE BYTE OR CHAR BUFFERS, except to remove characters from
338 the Char buffer.
339
340 ** Flushing the byte buffer
341
342 The byte buffer can be flushed if the Char buffer has already been
343 flushed (see above).  For a read Handle, flushing the byte buffer
344 means seeking the device back by the number of bytes in the buffer,
345 and hence it is only possible on a seekable Handle.
346
347 -}
348
349 -- ---------------------------------------------------------------------------
350 -- Newline translation
351
352 -- | The representation of a newline in the external file or stream.
353 data Newline = LF    -- ^ '\n'
354              | CRLF  -- ^ '\r\n'
355              deriving (Eq, Ord, Read, Show)
356
357 -- | Specifies the translation, if any, of newline characters between
358 -- internal Strings and the external file or stream.  Haskell Strings
359 -- are assumed to represent newlines with the '\n' character; the
360 -- newline mode specifies how to translate '\n' on output, and what to
361 -- translate into '\n' on input.
362 data NewlineMode 
363   = NewlineMode { inputNL :: Newline,
364                     -- ^ the representation of newlines on input
365                   outputNL :: Newline
366                     -- ^ the representation of newlines on output
367                  }
368              deriving (Eq, Ord, Read, Show)
369
370 -- | The native newline representation for the current platform: 'LF'
371 -- on Unix systems, 'CRLF' on Windows.
372 nativeNewline :: Newline
373 #ifdef mingw32_HOST_OS
374 nativeNewline = CRLF
375 #else
376 nativeNewline = LF
377 #endif
378
379 -- | Map '\r\n' into '\n' on input, and '\n' to the native newline
380 -- represetnation on output.  This mode can be used on any platform, and
381 -- works with text files using any newline convention.  The downside is
382 -- that @readFile >>= writeFile@ might yield a different file.
383 -- 
384 -- > universalNewlineMode  = NewlineMode { inputNL  = CRLF, 
385 -- >                                       outputNL = nativeNewline }
386 --
387 universalNewlineMode :: NewlineMode
388 universalNewlineMode  = NewlineMode { inputNL  = CRLF, 
389                                       outputNL = nativeNewline }
390
391 -- | Use the native newline representation on both input and output
392 -- 
393 -- > nativeNewlineMode  = NewlineMode { inputNL  = nativeNewline
394 -- >                                    outputNL = nativeNewline }
395 --
396 nativeNewlineMode    :: NewlineMode
397 nativeNewlineMode     = NewlineMode { inputNL  = nativeNewline, 
398                                       outputNL = nativeNewline }
399
400 -- | Do no newline translation at all.
401 -- 
402 -- > noNewlineTranslation  = NewlineMode { inputNL  = LF, outputNL = LF }
403 --
404 noNewlineTranslation :: NewlineMode
405 noNewlineTranslation  = NewlineMode { inputNL  = LF, outputNL = LF }
406
407 -- ---------------------------------------------------------------------------
408 -- Show instance for Handles
409
410 -- handle types are 'show'n when printing error msgs, so
411 -- we provide a more user-friendly Show instance for it
412 -- than the derived one.
413
414 instance Show HandleType where
415   showsPrec _ t =
416     case t of
417       ClosedHandle      -> showString "closed"
418       SemiClosedHandle  -> showString "semi-closed"
419       ReadHandle        -> showString "readable"
420       WriteHandle       -> showString "writable"
421       AppendHandle      -> showString "writable (append)"
422       ReadWriteHandle   -> showString "read-writable"
423
424 instance Show Handle where 
425   showsPrec _ (FileHandle   file _)   = showHandle file
426   showsPrec _ (DuplexHandle file _ _) = showHandle file
427
428 showHandle :: FilePath -> String -> String
429 showHandle file = showString "{handle: " . showString file . showString "}"