add GHC.HetMet.{hetmet_kappa,hetmet_kappa_app}
[ghc-base.git] / GHC / IO / Device.hs
1 {-# LANGUAGE CPP, NoImplicitPrelude, BangPatterns #-}
2
3 -----------------------------------------------------------------------------
4 -- |
5 -- Module      :  GHC.IO.Device
6 -- Copyright   :  (c) The University of Glasgow, 1994-2008
7 -- License     :  see libraries/base/LICENSE
8 -- 
9 -- Maintainer  :  libraries@haskell.org
10 -- Stability   :  internal
11 -- Portability :  non-portable
12 --
13 -- Type classes for I/O providers.
14 --
15 -----------------------------------------------------------------------------
16
17 module GHC.IO.Device (
18     RawIO(..),
19     IODevice(..),
20     IODeviceType(..),
21     SeekMode(..)
22   ) where  
23
24 #ifdef __GLASGOW_HASKELL__
25 import GHC.Base
26 import GHC.Word
27 import GHC.Arr
28 import GHC.Enum
29 import GHC.Read
30 import GHC.Show
31 import GHC.Ptr
32 import Data.Maybe
33 import GHC.Num
34 import GHC.IO
35 import {-# SOURCE #-} GHC.IO.Exception ( unsupportedOperation )
36 #endif
37 #ifdef __NHC__
38 import Foreign
39 import Ix
40 import Control.Exception.Base
41 unsupportedOperation = userError "unsupported operation"
42 #endif
43
44 -- | A low-level I/O provider where the data is bytes in memory.
45 class RawIO a where
46   -- | Read up to the specified number of bytes, returning the number
47   -- of bytes actually read.  This function should only block if there
48   -- is no data available.  If there is not enough data available,
49   -- then the function should just return the available data. A return
50   -- value of zero indicates that the end of the data stream (e.g. end
51   -- of file) has been reached.
52   read                :: a -> Ptr Word8 -> Int -> IO Int
53
54   -- | Read up to the specified number of bytes, returning the number
55   -- of bytes actually read, or 'Nothing' if the end of the stream has
56   -- been reached.
57   readNonBlocking     :: a -> Ptr Word8 -> Int -> IO (Maybe Int)
58
59   -- | Write the specified number of bytes.
60   write               :: a -> Ptr Word8 -> Int -> IO ()
61
62   -- | Write up to the specified number of bytes without blocking.  Returns
63   -- the actual number of bytes written.
64   writeNonBlocking    :: a -> Ptr Word8 -> Int -> IO Int
65
66
67 -- | I/O operations required for implementing a 'Handle'.
68 class IODevice a where
69   -- | @ready dev write msecs@ returns 'True' if the device has data
70   -- to read (if @write@ is 'False') or space to write new data (if
71   -- @write@ is 'True').  @msecs@ specifies how long to wait, in
72   -- milliseconds.
73   -- 
74   ready :: a -> Bool -> Int -> IO Bool
75
76   -- | closes the device.  Further operations on the device should
77   -- produce exceptions.
78   close :: a -> IO ()
79
80   -- | returns 'True' if the device is a terminal or console.
81   isTerminal :: a -> IO Bool
82   isTerminal _ = return False
83
84   -- | returns 'True' if the device supports 'seek' operations.
85   isSeekable :: a -> IO Bool
86   isSeekable _ = return False
87
88   -- | seek to the specified position in the data.
89   seek :: a -> SeekMode -> Integer -> IO ()
90   seek _ _ _ = ioe_unsupportedOperation
91
92   -- | return the current position in the data.
93   tell :: a -> IO Integer
94   tell _ = ioe_unsupportedOperation
95
96   -- | return the size of the data.
97   getSize :: a -> IO Integer
98   getSize _ = ioe_unsupportedOperation
99
100   -- | change the size of the data.
101   setSize :: a -> Integer -> IO () 
102   setSize _ _ = ioe_unsupportedOperation
103
104   -- | for terminal devices, changes whether characters are echoed on
105   -- the device.
106   setEcho :: a -> Bool -> IO ()
107   setEcho _ _ = ioe_unsupportedOperation
108
109   -- | returns the current echoing status.
110   getEcho :: a -> IO Bool
111   getEcho _ = ioe_unsupportedOperation
112
113   -- | some devices (e.g. terminals) support a "raw" mode where
114   -- characters entered are immediately made available to the program.
115   -- If available, this operations enables raw mode.
116   setRaw :: a -> Bool -> IO ()
117   setRaw _ _ = ioe_unsupportedOperation
118
119   -- | returns the 'IODeviceType' corresponding to this device.
120   devType :: a -> IO IODeviceType
121
122   -- | duplicates the device, if possible.  The new device is expected
123   -- to share a file pointer with the original device (like Unix @dup@).
124   dup :: a -> IO a
125   dup _ = ioe_unsupportedOperation
126
127   -- | @dup2 source target@ replaces the target device with the source
128   -- device.  The target device is closed first, if necessary, and then
129   -- it is made into a duplicate of the first device (like Unix @dup2@).
130   dup2 :: a -> a -> IO a
131   dup2 _ _ = ioe_unsupportedOperation
132
133 ioe_unsupportedOperation :: IO a
134 ioe_unsupportedOperation = throwIO unsupportedOperation
135
136 -- | Type of a device that can be used to back a
137 -- 'GHC.IO.Handle.Handle' (see also 'GHC.IO.Handle.mkFileHandle'). The
138 -- standard libraries provide creation of 'GHC.IO.Handle.Handle's via
139 -- Posix file operations with file descriptors (see
140 -- 'GHC.IO.Handle.FD.mkHandleFromFD') with FD being the underlying
141 -- 'GHC.IO.Device.IODevice' instance.
142 --
143 -- Users may provide custom instances of 'GHC.IO.Device.IODevice'
144 -- which are expected to conform the following rules:
145
146 data IODeviceType
147   = Directory -- ^ The standard libraries do not have direct support
148               -- for this device type, but a user implementation is
149               -- expected to provide a list of file names in
150               -- the directory, in any order, separated by @'\0'@
151               -- characters, excluding the @"."@ and @".."@ names. See
152               -- also 'System.Directory.getDirectoryContents'.  Seek
153               -- operations are not supported on directories (other
154               -- than to the zero position).
155   | Stream    -- ^ A duplex communications channel (results in
156               -- creation of a duplex 'GHC.IO.Handle.Handle'). The
157               -- standard libraries use this device type when
158               -- creating 'GHC.IO.Handle.Handle's for open sockets.
159   | RegularFile -- ^ A file that may be read or written, and also
160                 -- may be seekable.
161   | RawDevice -- ^ A "raw" (disk) device which supports block binary
162               -- read and write operations and may be seekable only
163               -- to positions of certain granularity (block-
164               -- aligned).
165   deriving (Eq)
166
167 -- -----------------------------------------------------------------------------
168 -- SeekMode type
169
170 -- | A mode that determines the effect of 'hSeek' @hdl mode i@.
171 data SeekMode
172   = AbsoluteSeek        -- ^ the position of @hdl@ is set to @i@.
173   | RelativeSeek        -- ^ the position of @hdl@ is set to offset @i@
174                         -- from the current position.
175   | SeekFromEnd         -- ^ the position of @hdl@ is set to offset @i@
176                         -- from the end of the file.
177     deriving (Eq, Ord, Ix, Enum, Read, Show)