Add errno to the IOError type
[ghc-base.git] / System / Posix / Internals.hs
1 {-# OPTIONS_GHC -XNoImplicitPrelude #-}
2 {-# OPTIONS_GHC -fno-warn-unused-binds #-}
3 {-# OPTIONS_HADDOCK hide #-}
4
5 -----------------------------------------------------------------------------
6 -- |
7 -- Module      :  System.Posix.Internals
8 -- Copyright   :  (c) The University of Glasgow, 1992-2002
9 -- License     :  see libraries/base/LICENSE
10 -- 
11 -- Maintainer  :  cvs-ghc@haskell.org
12 -- Stability   :  internal
13 -- Portability :  non-portable (requires POSIX)
14 --
15 -- POSIX support layer for the standard libraries.
16 -- This library is built on *every* platform, including Win32.
17 --
18 -- Non-posix compliant in order to support the following features:
19 --      * S_ISSOCK (no sockets in POSIX)
20 --
21 -----------------------------------------------------------------------------
22
23 -- #hide
24 module System.Posix.Internals where
25
26 #include "HsBaseConfig.h"
27
28 #if ! (defined(mingw32_HOST_OS) || defined(__MINGW32__))
29 import Control.Monad
30 #endif
31 import System.Posix.Types
32
33 import Foreign
34 import Foreign.C
35
36 import Data.Bits
37 import Data.Maybe
38
39 #if __GLASGOW_HASKELL__
40 import GHC.Base
41 import GHC.Num
42 import GHC.Real
43 import GHC.IOBase
44 #elif __HUGS__
45 import Hugs.Prelude (IOException(..), IOErrorType(..))
46 import Hugs.IO (IOMode(..))
47 #else
48 import System.IO
49 #endif
50
51 #ifdef __HUGS__
52 {-# CFILES cbits/PrelIOUtils.c cbits/dirUtils.c cbits/consUtils.c #-}
53 #endif
54
55 -- ---------------------------------------------------------------------------
56 -- Types
57
58 type CDir       = ()
59 type CDirent    = ()
60 type CFLock     = ()
61 type CGroup     = ()
62 type CLconv     = ()
63 type CPasswd    = ()
64 type CSigaction = ()
65 type CSigset    = ()
66 type CStat      = ()
67 type CTermios   = ()
68 type CTm        = ()
69 type CTms       = ()
70 type CUtimbuf   = ()
71 type CUtsname   = ()
72
73 #ifndef __GLASGOW_HASKELL__
74 type FD = CInt
75 #endif
76
77 -- ---------------------------------------------------------------------------
78 -- stat()-related stuff
79
80 fdFileSize :: FD -> IO Integer
81 fdFileSize fd = 
82   allocaBytes sizeof_stat $ \ p_stat -> do
83     throwErrnoIfMinus1Retry "fileSize" $
84         c_fstat fd p_stat
85     c_mode <- st_mode p_stat :: IO CMode 
86     if not (s_isreg c_mode)
87         then return (-1)
88         else do
89     c_size <- st_size p_stat
90     return (fromIntegral c_size)
91
92 data FDType  = Directory | Stream | RegularFile | RawDevice
93                deriving (Eq)
94
95 fileType :: FilePath -> IO FDType
96 fileType file =
97   allocaBytes sizeof_stat $ \ p_stat -> do
98   withCString file $ \p_file -> do
99     throwErrnoIfMinus1Retry "fileType" $
100       c_stat p_file p_stat
101     statGetType p_stat
102
103 -- NOTE: On Win32 platforms, this will only work with file descriptors
104 -- referring to file handles. i.e., it'll fail for socket FDs.
105 fdStat :: FD -> IO (FDType, CDev, CIno)
106 fdStat fd = 
107   allocaBytes sizeof_stat $ \ p_stat -> do
108     throwErrnoIfMinus1Retry "fdType" $
109         c_fstat fd p_stat
110     ty <- statGetType p_stat
111     dev <- st_dev p_stat
112     ino <- st_ino p_stat
113     return (ty,dev,ino)
114     
115 fdType :: FD -> IO FDType
116 fdType fd = do (ty,_,_) <- fdStat fd; return ty
117
118 statGetType :: Ptr CStat -> IO FDType
119 statGetType p_stat = do
120   c_mode <- st_mode p_stat :: IO CMode
121   case () of
122       _ | s_isdir c_mode        -> return Directory
123         | s_isfifo c_mode || s_issock c_mode || s_ischr  c_mode
124                                 -> return Stream
125         | s_isreg c_mode        -> return RegularFile
126          -- Q: map char devices to RawDevice too?
127         | s_isblk c_mode        -> return RawDevice
128         | otherwise             -> ioError ioe_unknownfiletype
129     
130 ioe_unknownfiletype :: IOException
131 ioe_unknownfiletype = IOError Nothing UnsupportedOperation "fdType"
132                         "unknown file type"
133 #if __GLASGOW_HASKELL__
134                         Nothing
135 #endif
136                         Nothing
137
138 #if __GLASGOW_HASKELL__ && (defined(mingw32_HOST_OS) || defined(__MINGW32__))
139 closeFd :: Bool -> CInt -> IO CInt
140 closeFd isStream fd 
141   | isStream  = c_closesocket fd
142   | otherwise = c_close fd
143
144 foreign import stdcall unsafe "HsBase.h closesocket"
145    c_closesocket :: CInt -> IO CInt
146 #endif
147
148 fdGetMode :: FD -> IO IOMode
149 #if defined(mingw32_HOST_OS) || defined(__MINGW32__)
150 fdGetMode _ = do
151     -- We don't have a way of finding out which flags are set on FDs
152     -- on Windows, so make a handle that thinks that anything goes.
153     let flags = o_RDWR
154 #else
155 fdGetMode fd = do
156     flags <- throwErrnoIfMinus1Retry "fdGetMode" 
157                 (c_fcntl_read fd const_f_getfl)
158 #endif
159     let
160        wH  = (flags .&. o_WRONLY) /= 0
161        aH  = (flags .&. o_APPEND) /= 0
162        rwH = (flags .&. o_RDWR) /= 0
163
164        mode
165          | wH && aH  = AppendMode
166          | wH        = WriteMode
167          | rwH       = ReadWriteMode
168          | otherwise = ReadMode
169           
170     return mode
171
172 -- ---------------------------------------------------------------------------
173 -- Terminal-related stuff
174
175 fdIsTTY :: FD -> IO Bool
176 fdIsTTY fd = c_isatty fd >>= return.toBool
177
178 #if defined(HTYPE_TCFLAG_T)
179
180 setEcho :: FD -> Bool -> IO ()
181 setEcho fd on = do
182   tcSetAttr fd $ \ p_tios -> do
183     lflag <- c_lflag p_tios :: IO CTcflag
184     let new_lflag
185          | on        = lflag .|. fromIntegral const_echo
186          | otherwise = lflag .&. complement (fromIntegral const_echo)
187     poke_c_lflag p_tios (new_lflag :: CTcflag)
188
189 getEcho :: FD -> IO Bool
190 getEcho fd = do
191   tcSetAttr fd $ \ p_tios -> do
192     lflag <- c_lflag p_tios :: IO CTcflag
193     return ((lflag .&. fromIntegral const_echo) /= 0)
194
195 setCooked :: FD -> Bool -> IO ()
196 setCooked fd cooked = 
197   tcSetAttr fd $ \ p_tios -> do
198
199     -- turn on/off ICANON
200     lflag <- c_lflag p_tios :: IO CTcflag
201     let new_lflag | cooked    = lflag .|. (fromIntegral const_icanon)
202                   | otherwise = lflag .&. complement (fromIntegral const_icanon)
203     poke_c_lflag p_tios (new_lflag :: CTcflag)
204
205     -- set VMIN & VTIME to 1/0 respectively
206     when (not cooked) $ do
207             c_cc <- ptr_c_cc p_tios
208             let vmin  = (c_cc `plusPtr` (fromIntegral const_vmin))  :: Ptr Word8
209                 vtime = (c_cc `plusPtr` (fromIntegral const_vtime)) :: Ptr Word8
210             poke vmin  1
211             poke vtime 0
212
213 tcSetAttr :: FD -> (Ptr CTermios -> IO a) -> IO a
214 tcSetAttr fd fun = do
215      allocaBytes sizeof_termios  $ \p_tios -> do
216         throwErrnoIfMinus1Retry "tcSetAttr"
217            (c_tcgetattr fd p_tios)
218
219 #ifdef __GLASGOW_HASKELL__
220         -- Save a copy of termios, if this is a standard file descriptor.
221         -- These terminal settings are restored in hs_exit().
222         when (fd <= 2) $ do
223           p <- get_saved_termios fd
224           when (p == nullPtr) $ do
225              saved_tios <- mallocBytes sizeof_termios
226              copyBytes saved_tios p_tios sizeof_termios
227              set_saved_termios fd saved_tios
228 #endif
229
230         -- tcsetattr() when invoked by a background process causes the process
231         -- to be sent SIGTTOU regardless of whether the process has TOSTOP set
232         -- in its terminal flags (try it...).  This function provides a
233         -- wrapper which temporarily blocks SIGTTOU around the call, making it
234         -- transparent.
235         allocaBytes sizeof_sigset_t $ \ p_sigset -> do
236         allocaBytes sizeof_sigset_t $ \ p_old_sigset -> do
237              c_sigemptyset p_sigset
238              c_sigaddset   p_sigset const_sigttou
239              c_sigprocmask const_sig_block p_sigset p_old_sigset
240              r <- fun p_tios  -- do the business
241              throwErrnoIfMinus1Retry_ "tcSetAttr" $
242                  c_tcsetattr fd const_tcsanow p_tios
243              c_sigprocmask const_sig_setmask p_old_sigset nullPtr
244              return r
245
246 #ifdef __GLASGOW_HASKELL__
247 foreign import ccall unsafe "HsBase.h __hscore_get_saved_termios"
248    get_saved_termios :: CInt -> IO (Ptr CTermios)
249
250 foreign import ccall unsafe "HsBase.h __hscore_set_saved_termios"
251    set_saved_termios :: CInt -> (Ptr CTermios) -> IO ()
252 #endif
253
254 #else
255
256 -- 'raw' mode for Win32 means turn off 'line input' (=> buffering and
257 -- character translation for the console.) The Win32 API for doing
258 -- this is GetConsoleMode(), which also requires echoing to be disabled
259 -- when turning off 'line input' processing. Notice that turning off
260 -- 'line input' implies enter/return is reported as '\r' (and it won't
261 -- report that character until another character is input..odd.) This
262 -- latter feature doesn't sit too well with IO actions like IO.hGetLine..
263 -- consider yourself warned.
264 setCooked :: FD -> Bool -> IO ()
265 setCooked fd cooked = do
266   x <- set_console_buffering fd (if cooked then 1 else 0)
267   if (x /= 0)
268    then ioError (ioe_unk_error "setCooked" "failed to set buffering")
269    else return ()
270
271 ioe_unk_error :: String -> String -> IOException
272 ioe_unk_error loc msg 
273  = IOError Nothing OtherError loc msg Nothing
274
275 -- Note: echoing goes hand in hand with enabling 'line input' / raw-ness
276 -- for Win32 consoles, hence setEcho ends up being the inverse of setCooked.
277 setEcho :: FD -> Bool -> IO ()
278 setEcho fd on = do
279   x <- set_console_echo fd (if on then 1 else 0)
280   if (x /= 0)
281    then ioError (ioe_unk_error "setEcho" "failed to set echoing")
282    else return ()
283
284 getEcho :: FD -> IO Bool
285 getEcho fd = do
286   r <- get_console_echo fd
287   if (r == (-1))
288    then ioError (ioe_unk_error "getEcho" "failed to get echoing")
289    else return (r == 1)
290
291 foreign import ccall unsafe "consUtils.h set_console_buffering__"
292    set_console_buffering :: CInt -> CInt -> IO CInt
293
294 foreign import ccall unsafe "consUtils.h set_console_echo__"
295    set_console_echo :: CInt -> CInt -> IO CInt
296
297 foreign import ccall unsafe "consUtils.h get_console_echo__"
298    get_console_echo :: CInt -> IO CInt
299
300 #endif
301
302 -- ---------------------------------------------------------------------------
303 -- Turning on non-blocking for a file descriptor
304
305 setNonBlockingFD :: FD -> IO ()
306 #if !defined(mingw32_HOST_OS) && !defined(__MINGW32__)
307 setNonBlockingFD fd = do
308   flags <- throwErrnoIfMinus1Retry "setNonBlockingFD"
309                  (c_fcntl_read fd const_f_getfl)
310   -- An error when setting O_NONBLOCK isn't fatal: on some systems 
311   -- there are certain file handles on which this will fail (eg. /dev/null
312   -- on FreeBSD) so we throw away the return code from fcntl_write.
313   unless (testBit flags (fromIntegral o_NONBLOCK)) $ do
314     c_fcntl_write fd const_f_setfl (fromIntegral (flags .|. o_NONBLOCK))
315     return ()
316 #else
317
318 -- bogus defns for win32
319 setNonBlockingFD _ = return ()
320
321 #endif
322
323 -- -----------------------------------------------------------------------------
324 -- foreign imports
325
326 foreign import ccall unsafe "HsBase.h access"
327    c_access :: CString -> CInt -> IO CInt
328
329 foreign import ccall unsafe "HsBase.h chmod"
330    c_chmod :: CString -> CMode -> IO CInt
331
332 foreign import ccall unsafe "HsBase.h close"
333    c_close :: CInt -> IO CInt
334
335 foreign import ccall unsafe "HsBase.h closedir" 
336    c_closedir :: Ptr CDir -> IO CInt
337
338 foreign import ccall unsafe "HsBase.h creat"
339    c_creat :: CString -> CMode -> IO CInt
340
341 foreign import ccall unsafe "HsBase.h dup"
342    c_dup :: CInt -> IO CInt
343
344 foreign import ccall unsafe "HsBase.h dup2"
345    c_dup2 :: CInt -> CInt -> IO CInt
346
347 foreign import ccall unsafe "HsBase.h __hscore_fstat"
348    c_fstat :: CInt -> Ptr CStat -> IO CInt
349
350 foreign import ccall unsafe "HsBase.h isatty"
351    c_isatty :: CInt -> IO CInt
352
353 #if defined(mingw32_HOST_OS) || defined(__MINGW32__)
354 foreign import ccall unsafe "HsBase.h __hscore_lseek"
355    c_lseek :: CInt -> Int64 -> CInt -> IO Int64
356 #else
357 foreign import ccall unsafe "HsBase.h __hscore_lseek"
358    c_lseek :: CInt -> COff -> CInt -> IO COff
359 #endif
360
361 foreign import ccall unsafe "HsBase.h __hscore_lstat"
362    lstat :: CString -> Ptr CStat -> IO CInt
363
364 foreign import ccall unsafe "HsBase.h __hscore_open"
365    c_open :: CString -> CInt -> CMode -> IO CInt
366
367 foreign import ccall unsafe "HsBase.h opendir" 
368    c_opendir :: CString  -> IO (Ptr CDir)
369
370 foreign import ccall unsafe "HsBase.h __hscore_mkdir"
371    mkdir :: CString -> CInt -> IO CInt
372
373 foreign import ccall unsafe "HsBase.h read" 
374    c_read :: CInt -> Ptr CChar -> CSize -> IO CSsize
375
376 foreign import ccall unsafe "HsBase.h rewinddir"
377    c_rewinddir :: Ptr CDir -> IO ()
378
379 foreign import ccall unsafe "HsBase.h __hscore_stat"
380    c_stat :: CString -> Ptr CStat -> IO CInt
381
382 foreign import ccall unsafe "HsBase.h umask"
383    c_umask :: CMode -> IO CMode
384
385 foreign import ccall unsafe "HsBase.h write" 
386    c_write :: CInt -> Ptr CChar -> CSize -> IO CSsize
387
388 foreign import ccall unsafe "HsBase.h __hscore_ftruncate"
389    c_ftruncate :: CInt -> COff -> IO CInt
390
391 foreign import ccall unsafe "HsBase.h unlink"
392    c_unlink :: CString -> IO CInt
393
394 foreign import ccall unsafe "HsBase.h getpid"
395    c_getpid :: IO CPid
396
397 #if !defined(mingw32_HOST_OS) && !defined(__MINGW32__)
398 foreign import ccall unsafe "HsBase.h fcntl"
399    c_fcntl_read  :: CInt -> CInt -> IO CInt
400
401 foreign import ccall unsafe "HsBase.h fcntl"
402    c_fcntl_write :: CInt -> CInt -> CLong -> IO CInt
403
404 foreign import ccall unsafe "HsBase.h fcntl"
405    c_fcntl_lock  :: CInt -> CInt -> Ptr CFLock -> IO CInt
406
407 foreign import ccall unsafe "HsBase.h fork"
408    c_fork :: IO CPid 
409
410 foreign import ccall unsafe "HsBase.h link"
411    c_link :: CString -> CString -> IO CInt
412
413 foreign import ccall unsafe "HsBase.h mkfifo"
414    c_mkfifo :: CString -> CMode -> IO CInt
415
416 foreign import ccall unsafe "HsBase.h pipe"
417    c_pipe :: Ptr CInt -> IO CInt
418
419 foreign import ccall unsafe "HsBase.h __hscore_sigemptyset"
420    c_sigemptyset :: Ptr CSigset -> IO CInt
421
422 foreign import ccall unsafe "HsBase.h __hscore_sigaddset"
423    c_sigaddset :: Ptr CSigset -> CInt -> IO CInt
424
425 foreign import ccall unsafe "HsBase.h sigprocmask"
426    c_sigprocmask :: CInt -> Ptr CSigset -> Ptr CSigset -> IO CInt
427
428 foreign import ccall unsafe "HsBase.h tcgetattr"
429    c_tcgetattr :: CInt -> Ptr CTermios -> IO CInt
430
431 foreign import ccall unsafe "HsBase.h tcsetattr"
432    c_tcsetattr :: CInt -> CInt -> Ptr CTermios -> IO CInt
433
434 foreign import ccall unsafe "HsBase.h utime"
435    c_utime :: CString -> Ptr CUtimbuf -> IO CInt
436
437 foreign import ccall unsafe "HsBase.h waitpid"
438    c_waitpid :: CPid -> Ptr CInt -> CInt -> IO CPid
439 #endif
440
441 -- traversing directories
442 foreign import ccall unsafe "dirUtils.h __hscore_readdir"
443   readdir  :: Ptr CDir -> Ptr (Ptr CDirent) -> IO CInt
444  
445 foreign import ccall unsafe "HsBase.h __hscore_free_dirent"
446   freeDirEnt  :: Ptr CDirent -> IO ()
447  
448 foreign import ccall unsafe "HsBase.h __hscore_end_of_dir"
449   end_of_dir :: CInt
450  
451 foreign import ccall unsafe "HsBase.h __hscore_d_name"
452   d_name :: Ptr CDirent -> IO CString
453
454 -- POSIX flags only:
455 foreign import ccall unsafe "HsBase.h __hscore_o_rdonly" o_RDONLY :: CInt
456 foreign import ccall unsafe "HsBase.h __hscore_o_wronly" o_WRONLY :: CInt
457 foreign import ccall unsafe "HsBase.h __hscore_o_rdwr"   o_RDWR   :: CInt
458 foreign import ccall unsafe "HsBase.h __hscore_o_append" o_APPEND :: CInt
459 foreign import ccall unsafe "HsBase.h __hscore_o_creat"  o_CREAT  :: CInt
460 foreign import ccall unsafe "HsBase.h __hscore_o_excl"   o_EXCL   :: CInt
461 foreign import ccall unsafe "HsBase.h __hscore_o_trunc"  o_TRUNC  :: CInt
462
463 -- non-POSIX flags.
464 foreign import ccall unsafe "HsBase.h __hscore_o_noctty"   o_NOCTTY   :: CInt
465 foreign import ccall unsafe "HsBase.h __hscore_o_nonblock" o_NONBLOCK :: CInt
466 foreign import ccall unsafe "HsBase.h __hscore_o_binary"   o_BINARY   :: CInt
467
468 foreign import ccall unsafe "HsBase.h __hscore_s_isreg"  c_s_isreg  :: CMode -> CInt
469 foreign import ccall unsafe "HsBase.h __hscore_s_ischr"  c_s_ischr  :: CMode -> CInt
470 foreign import ccall unsafe "HsBase.h __hscore_s_isblk"  c_s_isblk  :: CMode -> CInt
471 foreign import ccall unsafe "HsBase.h __hscore_s_isdir"  c_s_isdir  :: CMode -> CInt
472 foreign import ccall unsafe "HsBase.h __hscore_s_isfifo" c_s_isfifo :: CMode -> CInt
473
474 s_isreg  :: CMode -> Bool
475 s_isreg cm = c_s_isreg cm /= 0
476 s_ischr  :: CMode -> Bool
477 s_ischr cm = c_s_ischr cm /= 0
478 s_isblk  :: CMode -> Bool
479 s_isblk cm = c_s_isblk cm /= 0
480 s_isdir  :: CMode -> Bool
481 s_isdir cm = c_s_isdir cm /= 0
482 s_isfifo :: CMode -> Bool
483 s_isfifo cm = c_s_isfifo cm /= 0
484
485 foreign import ccall unsafe "HsBase.h __hscore_sizeof_stat" sizeof_stat :: Int
486 foreign import ccall unsafe "HsBase.h __hscore_st_mtime" st_mtime :: Ptr CStat -> IO CTime
487 #ifdef mingw32_HOST_OS
488 foreign import ccall unsafe "HsBase.h __hscore_st_size" st_size :: Ptr CStat -> IO Int64
489 #else
490 foreign import ccall unsafe "HsBase.h __hscore_st_size" st_size :: Ptr CStat -> IO COff
491 #endif
492 foreign import ccall unsafe "HsBase.h __hscore_st_mode" st_mode :: Ptr CStat -> IO CMode
493 foreign import ccall unsafe "HsBase.h __hscore_st_dev" st_dev :: Ptr CStat -> IO CDev
494 foreign import ccall unsafe "HsBase.h __hscore_st_ino" st_ino :: Ptr CStat -> IO CIno
495
496 foreign import ccall unsafe "HsBase.h __hscore_echo"         const_echo :: CInt
497 foreign import ccall unsafe "HsBase.h __hscore_tcsanow"      const_tcsanow :: CInt
498 foreign import ccall unsafe "HsBase.h __hscore_icanon"       const_icanon :: CInt
499 foreign import ccall unsafe "HsBase.h __hscore_vmin"         const_vmin   :: CInt
500 foreign import ccall unsafe "HsBase.h __hscore_vtime"        const_vtime  :: CInt
501 foreign import ccall unsafe "HsBase.h __hscore_sigttou"      const_sigttou :: CInt
502 foreign import ccall unsafe "HsBase.h __hscore_sig_block"    const_sig_block :: CInt
503 foreign import ccall unsafe "HsBase.h __hscore_sig_setmask"  const_sig_setmask :: CInt
504 foreign import ccall unsafe "HsBase.h __hscore_f_getfl"      const_f_getfl :: CInt
505 foreign import ccall unsafe "HsBase.h __hscore_f_setfl"      const_f_setfl :: CInt
506
507 #if defined(HTYPE_TCFLAG_T)
508 foreign import ccall unsafe "HsBase.h __hscore_sizeof_termios"  sizeof_termios :: Int
509 foreign import ccall unsafe "HsBase.h __hscore_sizeof_sigset_t" sizeof_sigset_t :: Int
510
511 foreign import ccall unsafe "HsBase.h __hscore_lflag" c_lflag :: Ptr CTermios -> IO CTcflag
512 foreign import ccall unsafe "HsBase.h __hscore_poke_lflag" poke_c_lflag :: Ptr CTermios -> CTcflag -> IO ()
513 foreign import ccall unsafe "HsBase.h __hscore_ptr_c_cc" ptr_c_cc  :: Ptr CTermios -> IO (Ptr Word8)
514 #endif
515
516 s_issock :: CMode -> Bool
517 #if !defined(mingw32_HOST_OS) && !defined(__MINGW32__)
518 s_issock cmode = c_s_issock cmode /= 0
519 foreign import ccall unsafe "HsBase.h __hscore_s_issock" c_s_issock :: CMode -> CInt
520 #else
521 s_issock _ = False
522 #endif