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