add GHC.HetMet.{hetmet_kappa,hetmet_kappa_app}
[ghc-base.git] / GHC / IO / Handle / FD.hs
1 {-# LANGUAGE CPP, NoImplicitPrelude, PatternGuards, ForeignFunctionInterface #-}
2
3 -----------------------------------------------------------------------------
4 -- |
5 -- Module      :  GHC.IO.Handle.FD
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 -- Handle operations implemented by file descriptors (FDs)
14 --
15 -----------------------------------------------------------------------------
16
17 module GHC.IO.Handle.FD ( 
18   stdin, stdout, stderr,
19   openFile, openBinaryFile, openFileBlocking,
20   mkHandleFromFD, fdToHandle, fdToHandle',
21   isEOF
22  ) where
23
24 import GHC.Base
25 import GHC.Show
26 import Data.Maybe
27 -- import Control.Monad
28 import Foreign.C.Types
29 import GHC.MVar
30 import GHC.IO
31 import GHC.IO.Encoding
32 -- import GHC.IO.Exception
33 import GHC.IO.Device as IODevice
34 import GHC.IO.Exception
35 import GHC.IO.IOMode
36 import GHC.IO.Handle
37 import GHC.IO.Handle.Types
38 import GHC.IO.Handle.Internals
39 import GHC.IO.FD (FD(..))
40 import qualified GHC.IO.FD as FD
41 import qualified System.Posix.Internals as Posix
42
43 -- ---------------------------------------------------------------------------
44 -- Standard Handles
45
46 -- Three handles are allocated during program initialisation.  The first
47 -- two manage input or output from the Haskell program's standard input
48 -- or output channel respectively.  The third manages output to the
49 -- standard error channel. These handles are initially open.
50
51 -- | A handle managing input from the Haskell program's standard input channel.
52 stdin :: Handle
53 {-# NOINLINE stdin #-}
54 stdin = unsafePerformIO $ do
55    -- ToDo: acquire lock
56    setBinaryMode FD.stdin
57    mkHandle FD.stdin "<stdin>" ReadHandle True (Just localeEncoding)
58                 nativeNewlineMode{-translate newlines-}
59                 (Just stdHandleFinalizer) Nothing
60
61 -- | A handle managing output to the Haskell program's standard output channel.
62 stdout :: Handle
63 {-# NOINLINE stdout #-}
64 stdout = unsafePerformIO $ do
65    -- ToDo: acquire lock
66    setBinaryMode FD.stdout
67    mkHandle FD.stdout "<stdout>" WriteHandle True (Just localeEncoding)
68                 nativeNewlineMode{-translate newlines-}
69                 (Just stdHandleFinalizer) Nothing
70
71 -- | A handle managing output to the Haskell program's standard error channel.
72 stderr :: Handle
73 {-# NOINLINE stderr #-}
74 stderr = unsafePerformIO $ do
75     -- ToDo: acquire lock
76    setBinaryMode FD.stderr
77    mkHandle FD.stderr "<stderr>" WriteHandle False{-stderr is unbuffered-} 
78                 (Just localeEncoding)
79                 nativeNewlineMode{-translate newlines-}
80                 (Just stdHandleFinalizer) Nothing
81
82 stdHandleFinalizer :: FilePath -> MVar Handle__ -> IO ()
83 stdHandleFinalizer fp m = do
84   h_ <- takeMVar m
85   flushWriteBuffer h_
86   case haType h_ of 
87       ClosedHandle -> return ()
88       _other       -> closeTextCodecs h_
89   putMVar m (ioe_finalizedHandle fp)
90
91 -- We have to put the FDs into binary mode on Windows to avoid the newline
92 -- translation that the CRT IO library does.
93 setBinaryMode :: FD -> IO ()
94 #ifdef mingw32_HOST_OS
95 setBinaryMode fd = do _ <- setmode (fdFD fd) True
96                       return ()
97 #else
98 setBinaryMode _ = return ()
99 #endif
100
101 #ifdef mingw32_HOST_OS
102 foreign import ccall unsafe "__hscore_setmode"
103   setmode :: CInt -> Bool -> IO CInt
104 #endif
105
106 -- ---------------------------------------------------------------------------
107 -- isEOF
108
109 -- | The computation 'isEOF' is identical to 'hIsEOF',
110 -- except that it works only on 'stdin'.
111
112 isEOF :: IO Bool
113 isEOF = hIsEOF stdin
114
115 -- ---------------------------------------------------------------------------
116 -- Opening and Closing Files
117
118 addFilePathToIOError :: String -> FilePath -> IOException -> IOException
119 addFilePathToIOError fun fp ioe
120   = ioe{ ioe_location = fun, ioe_filename = Just fp }
121
122 -- | Computation 'openFile' @file mode@ allocates and returns a new, open
123 -- handle to manage the file @file@.  It manages input if @mode@
124 -- is 'ReadMode', output if @mode@ is 'WriteMode' or 'AppendMode',
125 -- and both input and output if mode is 'ReadWriteMode'.
126 --
127 -- If the file does not exist and it is opened for output, it should be
128 -- created as a new file.  If @mode@ is 'WriteMode' and the file
129 -- already exists, then it should be truncated to zero length.
130 -- Some operating systems delete empty files, so there is no guarantee
131 -- that the file will exist following an 'openFile' with @mode@
132 -- 'WriteMode' unless it is subsequently written to successfully.
133 -- The handle is positioned at the end of the file if @mode@ is
134 -- 'AppendMode', and otherwise at the beginning (in which case its
135 -- internal position is 0).
136 -- The initial buffer mode is implementation-dependent.
137 --
138 -- This operation may fail with:
139 --
140 --  * 'isAlreadyInUseError' if the file is already open and cannot be reopened;
141 --
142 --  * 'isDoesNotExistError' if the file does not exist; or
143 --
144 --  * 'isPermissionError' if the user does not have permission to open the file.
145 --
146 -- Note: if you will be working with files containing binary data, you'll want to
147 -- be using 'openBinaryFile'.
148 openFile :: FilePath -> IOMode -> IO Handle
149 openFile fp im = 
150   catchException
151     (openFile' fp im dEFAULT_OPEN_IN_BINARY_MODE True)
152     (\e -> ioError (addFilePathToIOError "openFile" fp e))
153
154 -- | Like 'openFile', but opens the file in ordinary blocking mode.
155 -- This can be useful for opening a FIFO for reading: if we open in
156 -- non-blocking mode then the open will fail if there are no writers,
157 -- whereas a blocking open will block until a writer appears.
158 openFileBlocking :: FilePath -> IOMode -> IO Handle
159 openFileBlocking fp im =
160   catchException
161     (openFile' fp im dEFAULT_OPEN_IN_BINARY_MODE False)
162     (\e -> ioError (addFilePathToIOError "openFile" fp e))
163
164 -- | Like 'openFile', but open the file in binary mode.
165 -- On Windows, reading a file in text mode (which is the default)
166 -- will translate CRLF to LF, and writing will translate LF to CRLF.
167 -- This is usually what you want with text files.  With binary files
168 -- this is undesirable; also, as usual under Microsoft operating systems,
169 -- text mode treats control-Z as EOF.  Binary mode turns off all special
170 -- treatment of end-of-line and end-of-file characters.
171 -- (See also 'hSetBinaryMode'.)
172
173 openBinaryFile :: FilePath -> IOMode -> IO Handle
174 openBinaryFile fp m =
175   catchException
176     (openFile' fp m True True)
177     (\e -> ioError (addFilePathToIOError "openBinaryFile" fp e))
178
179 openFile' :: String -> IOMode -> Bool -> Bool -> IO Handle
180 openFile' filepath iomode binary non_blocking = do
181   -- first open the file to get an FD
182   (fd, fd_type) <- FD.openFile filepath iomode non_blocking
183
184   let mb_codec = if binary then Nothing else Just localeEncoding
185
186   -- then use it to make a Handle
187   mkHandleFromFD fd fd_type filepath iomode
188                    False {- do not *set* non-blocking mode -}
189                    mb_codec
190             `onException` IODevice.close fd
191         -- NB. don't forget to close the FD if mkHandleFromFD fails, otherwise
192         -- this FD leaks.
193         -- ASSERT: if we just created the file, then fdToHandle' won't fail
194         -- (so we don't need to worry about removing the newly created file
195         --  in the event of an error).
196
197
198 -- ---------------------------------------------------------------------------
199 -- Converting file descriptors to Handles
200
201 mkHandleFromFD
202    :: FD
203    -> IODeviceType
204    -> FilePath  -- a string describing this file descriptor (e.g. the filename)
205    -> IOMode
206    -> Bool      --  *set* non-blocking mode on the FD
207    -> Maybe TextEncoding
208    -> IO Handle
209
210 mkHandleFromFD fd0 fd_type filepath iomode set_non_blocking mb_codec
211   = do
212 #ifndef mingw32_HOST_OS
213     -- turn on non-blocking mode
214     fd <- if set_non_blocking 
215              then FD.setNonBlockingMode fd0 True
216              else return fd0
217 #else
218     let _ = set_non_blocking -- warning suppression
219     fd <- return fd0
220 #endif
221
222     let nl | isJust mb_codec = nativeNewlineMode
223            | otherwise       = noNewlineTranslation
224
225     case fd_type of
226         Directory -> 
227            ioException (IOError Nothing InappropriateType "openFile"
228                            "is a directory" Nothing Nothing)
229
230         Stream
231            -- only *Streams* can be DuplexHandles.  Other read/write
232            -- Handles must share a buffer.
233            | ReadWriteMode <- iomode -> 
234                 mkDuplexHandle fd filepath mb_codec nl
235                    
236
237         _other -> 
238            mkFileHandle fd filepath iomode mb_codec nl
239
240 -- | Old API kept to avoid breaking clients
241 fdToHandle' :: CInt
242             -> Maybe IODeviceType
243             -> Bool -- is_socket on Win, non-blocking on Unix
244             -> FilePath
245             -> IOMode
246             -> Bool -- binary
247             -> IO Handle
248 fdToHandle' fdint mb_type is_socket filepath iomode binary = do
249   let mb_stat = case mb_type of
250                         Nothing          -> Nothing
251                           -- mkFD will do the stat:
252                         Just RegularFile -> Nothing
253                           -- no stat required for streams etc.:
254                         Just other       -> Just (other,0,0)
255   (fd,fd_type) <- FD.mkFD fdint iomode mb_stat
256                        is_socket
257                        is_socket
258   mkHandleFromFD fd fd_type filepath iomode is_socket
259                        (if binary then Nothing else Just localeEncoding)
260
261
262 -- | Turn an existing file descriptor into a Handle.  This is used by
263 -- various external libraries to make Handles.
264 --
265 -- Makes a binary Handle.  This is for historical reasons; it should
266 -- probably be a text Handle with the default encoding and newline
267 -- translation instead.
268 fdToHandle :: Posix.FD -> IO Handle
269 fdToHandle fdint = do
270    iomode <- Posix.fdGetMode fdint
271    (fd,fd_type) <- FD.mkFD fdint iomode Nothing
272             False{-is_socket-} 
273               -- NB. the is_socket flag is False, meaning that:
274               --  on Windows we're guessing this is not a socket (XXX)
275             False{-is_nonblock-}
276               -- file descriptors that we get from external sources are
277               -- not put into non-blocking mode, becuase that would affect
278               -- other users of the file descriptor
279    let fd_str = "<file descriptor: " ++ show fd ++ ">"
280    mkHandleFromFD fd fd_type fd_str iomode False{-non-block-} 
281                   Nothing -- bin mode
282
283 -- ---------------------------------------------------------------------------
284 -- Are files opened by default in text or binary mode, if the user doesn't
285 -- specify?
286
287 dEFAULT_OPEN_IN_BINARY_MODE :: Bool
288 dEFAULT_OPEN_IN_BINARY_MODE = False