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