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