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