[project @ 2002-08-30 14:19:18 by simonpj]
[ghc-base.git] / GHC / Posix.hs
1 {-# OPTIONS -fno-implicit-prelude #-}
2
3 -----------------------------------------------------------------------------
4 -- |
5 -- Module      :  GHC.Posix
6 -- Copyright   :  (c) The University of Glasgow, 1992-2002
7 -- License     :  see libraries/base/LICENSE
8 -- 
9 -- Maintainer  :  cvs-ghc@haskell.org
10 -- Stability   :  internal
11 -- Portability :  non-portable
12 --
13 -- POSIX support layer for the standard libraries.
14 -- This library is built on *every* platform, including Win32.
15 --
16 -- Non-posix compliant in order to support the following features:
17 --      * S_ISSOCK (no sockets in POSIX)
18 --
19 -----------------------------------------------------------------------------
20
21 module GHC.Posix where
22
23 #include "config.h"
24
25 import Control.Monad
26
27 import Foreign
28 import Foreign.C
29
30 import Data.Bits
31 import Data.Maybe
32
33 import GHC.Base
34 import GHC.Num
35 import GHC.Real
36 import GHC.IOBase
37
38 -- ---------------------------------------------------------------------------
39 -- Types
40
41 type CDir       = ()
42 type CDirent    = ()
43 type CFLock     = ()
44 type CGroup     = ()
45 type CLconv     = ()
46 type CPasswd    = ()
47 type CSigaction = ()
48 type CSigset    = ()
49 type CStat      = ()
50 type CTermios   = ()
51 type CTm        = ()
52 type CTms       = ()
53 type CUtimbuf   = ()
54 type CUtsname   = ()
55
56 type CDev    = HTYPE_DEV_T
57 type CIno    = HTYPE_INO_T
58 type CMode   = HTYPE_MODE_T
59 type COff    = HTYPE_OFF_T
60 type CPid    = HTYPE_PID_T
61
62 #ifdef mingw32_TARGET_OS
63 type CSsize  = HTYPE_SIZE_T
64 #else
65 type CGid    = HTYPE_GID_T
66 type CNlink  = HTYPE_NLINK_T
67 type CSsize  = HTYPE_SSIZE_T
68 type CUid    = HTYPE_UID_T
69 type CCc     = HTYPE_CC_T
70 type CSpeed  = HTYPE_SPEED_T
71 type CTcflag = HTYPE_TCFLAG_T
72 #endif
73
74 -- ---------------------------------------------------------------------------
75 -- stat()-related stuff
76
77 fdFileSize :: Int -> IO Integer
78 fdFileSize fd = 
79   allocaBytes sizeof_stat $ \ p_stat -> do
80     throwErrnoIfMinus1Retry "fileSize" $
81         c_fstat (fromIntegral 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 :: IO COff
87     return (fromIntegral c_size)
88
89 data FDType  = Directory | Stream | RegularFile
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 fdType :: Int -> IO FDType
103 fdType fd = 
104   allocaBytes sizeof_stat $ \ p_stat -> do
105     throwErrnoIfMinus1Retry "fdType" $
106         c_fstat (fromIntegral fd) p_stat
107     statGetType p_stat
108
109 statGetType p_stat = do
110   c_mode <- st_mode p_stat :: IO CMode
111   case () of
112       _ | s_isdir c_mode                     -> return Directory
113         | s_isfifo c_mode || s_issock c_mode -> return Stream
114         | s_isreg c_mode                     -> return RegularFile
115         | otherwise                          -> ioException ioe_unknownfiletype
116     
117
118 ioe_unknownfiletype = IOError Nothing UnsupportedOperation "fdType"
119                         "unknown file type" Nothing
120
121 -- It isn't clear whether ftruncate is POSIX or not (I've read several
122 -- manpages and they seem to conflict), so we truncate using open/2.
123 fileTruncate :: FilePath -> IO ()
124 fileTruncate file = do
125   let flags = o_WRONLY .|. o_TRUNC
126   withCString file $ \file_cstr -> do
127     fd <- fromIntegral `liftM`
128             throwErrnoIfMinus1Retry "fileTruncate"
129                 (c_open file_cstr (fromIntegral flags) 0o666)
130     c_close fd
131   return ()
132
133 #ifdef mingw32_TARGET_OS
134 closeFd :: Bool -> CInt -> IO CInt
135 closeFd isStream fd 
136   | isStream  = c_closesocket fd
137   | otherwise = c_close fd
138
139 foreign import stdcall unsafe "closesocket"
140    c_closesocket :: CInt -> IO CInt
141 #endif
142
143 fdGetMode :: Int -> IO IOMode
144 fdGetMode fd = do
145     flags <- throwErrnoIfMinus1Retry "fdGetMode" 
146                 (c_fcntl_read (fromIntegral fd) const_f_getfl)
147     
148     let
149        wH  = (flags .&. o_WRONLY) /= 0
150        aH  = (flags .&. o_APPEND) /= 0
151        rwH = (flags .&. o_RDWR) /= 0
152
153        mode
154          | wH && aH  = AppendMode
155          | wH        = WriteMode
156          | rwH       = ReadWriteMode
157          | otherwise = ReadMode
158           
159     return mode
160
161 -- ---------------------------------------------------------------------------
162 -- Terminal-related stuff
163
164 fdIsTTY :: Int -> IO Bool
165 fdIsTTY fd = c_isatty (fromIntegral fd) >>= return.toBool
166
167 #ifndef mingw32_TARGET_OS
168
169 setEcho :: Int -> Bool -> IO ()
170 setEcho fd on = do
171   allocaBytes sizeof_termios  $ \p_tios -> do
172     throwErrnoIfMinus1Retry "setEcho"
173         (c_tcgetattr (fromIntegral fd) p_tios)
174     c_lflag <- c_lflag p_tios :: IO CTcflag
175     let new_c_lflag
176          | on        = c_lflag .|. fromIntegral const_echo
177          | otherwise = c_lflag .&. complement (fromIntegral const_echo)
178     poke_c_lflag p_tios (new_c_lflag :: CTcflag)
179     tcSetAttr fd const_tcsanow p_tios
180
181 getEcho :: Int -> IO Bool
182 getEcho fd = do
183   allocaBytes sizeof_termios  $ \p_tios -> do
184     throwErrnoIfMinus1Retry "setEcho"
185         (c_tcgetattr (fromIntegral fd) p_tios)
186     c_lflag <- c_lflag p_tios :: IO CTcflag
187     return ((c_lflag .&. fromIntegral const_echo) /= 0)
188
189 setCooked :: Int -> Bool -> IO ()
190 setCooked fd cooked = 
191   allocaBytes sizeof_termios  $ \p_tios -> do
192     throwErrnoIfMinus1Retry "setCooked"
193         (c_tcgetattr (fromIntegral fd) p_tios)
194
195     -- turn on/off ICANON
196     c_lflag <- c_lflag p_tios :: IO CTcflag
197     let new_c_lflag | cooked    = c_lflag .|. (fromIntegral const_icanon)
198                     | otherwise = c_lflag .&. complement (fromIntegral const_icanon)
199     poke_c_lflag p_tios (new_c_lflag :: CTcflag)
200
201     -- set VMIN & VTIME to 1/0 respectively
202     when cooked $ do
203             c_cc <- ptr_c_cc p_tios
204             let vmin  = (c_cc `plusPtr` (fromIntegral const_vmin))  :: Ptr Word8
205                 vtime = (c_cc `plusPtr` (fromIntegral const_vtime)) :: Ptr Word8
206             poke vmin  1
207             poke vtime 0
208
209     tcSetAttr fd const_tcsanow p_tios
210
211 -- tcsetattr() when invoked by a background process causes the process
212 -- to be sent SIGTTOU regardless of whether the process has TOSTOP set
213 -- in its terminal flags (try it...).  This function provides a
214 -- wrapper which temporarily blocks SIGTTOU around the call, making it
215 -- transparent.
216
217 tcSetAttr :: FD -> CInt -> Ptr CTermios -> IO ()
218 tcSetAttr fd options p_tios = do
219   allocaBytes sizeof_sigset_t $ \ p_sigset -> do
220   allocaBytes sizeof_sigset_t $ \ p_old_sigset -> do
221      c_sigemptyset p_sigset
222      c_sigaddset   p_sigset const_sigttou
223      c_sigprocmask const_sig_block p_sigset p_old_sigset
224      throwErrnoIfMinus1Retry_ "tcSetAttr" $
225          c_tcsetattr (fromIntegral fd) options p_tios
226      c_sigprocmask const_sig_setmask p_old_sigset nullPtr
227
228 #else
229
230 -- bogus defns for win32
231 setCooked :: Int -> Bool -> IO ()
232 setCooked fd cooked = do
233   x <- set_console_buffering (fromIntegral fd) (if cooked then 1 else 0)
234   if (x /= 0)
235    then ioException (ioe_unk_error "setCooked" "failed to set buffering")
236    else return ()
237
238 ioe_unk_error loc msg 
239  = IOError Nothing OtherError loc msg Nothing
240
241 setEcho :: Int -> Bool -> IO ()
242 setEcho fd on = do
243   x <- set_console_echo (fromIntegral fd) (if on then 1 else 0)
244   if (x /= 0)
245    then ioException (ioe_unk_error "setEcho" "failed to set echoing")
246    else return ()
247
248 getEcho :: Int -> IO Bool
249 getEcho fd = do
250   r <- get_console_echo (fromIntegral fd)
251   if (r == (-1))
252    then ioException (ioe_unk_error "getEcho" "failed to get echoing")
253    else return (r == 1)
254
255 foreign import ccall unsafe "consUtils.h set_console_buffering__"
256    set_console_buffering :: CInt -> CInt -> IO CInt
257
258 foreign import ccall unsafe "consUtils.h set_console_echo__"
259    set_console_echo :: CInt -> CInt -> IO CInt
260
261 foreign import ccall unsafe "consUtils.h get_console_echo__"
262    get_console_echo :: CInt -> IO CInt
263
264 #endif
265
266 -- ---------------------------------------------------------------------------
267 -- Turning on non-blocking for a file descriptor
268
269 #ifndef mingw32_TARGET_OS
270
271 setNonBlockingFD fd = do
272   flags <- throwErrnoIfMinus1Retry "setNonBlockingFD"
273                  (c_fcntl_read (fromIntegral fd) const_f_getfl)
274   -- An error when setting O_NONBLOCK isn't fatal: on some systems 
275   -- there are certain file handles on which this will fail (eg. /dev/null
276   -- on FreeBSD) so we throw away the return code from fcntl_write.
277   c_fcntl_write (fromIntegral fd) const_f_setfl (flags .|. o_NONBLOCK)
278 #else
279
280 -- bogus defns for win32
281 setNonBlockingFD fd = return ()
282
283 #endif
284
285 -- -----------------------------------------------------------------------------
286 -- foreign imports
287
288 foreign import ccall unsafe "access"
289    c_access :: CString -> CMode -> IO CInt
290
291 foreign import ccall unsafe "chmod"
292    c_chmod :: CString -> CMode -> IO CInt
293
294 foreign import ccall unsafe "chdir"
295    c_chdir :: CString -> IO CInt
296
297 foreign import ccall unsafe "close"
298    c_close :: CInt -> IO CInt
299
300 foreign import ccall unsafe "closedir" 
301    c_closedir :: Ptr CDir -> IO CInt
302
303 foreign import ccall unsafe "creat"
304    c_creat :: CString -> CMode -> IO CInt
305
306 foreign import ccall unsafe "dup"
307    c_dup :: CInt -> IO CInt
308
309 foreign import ccall unsafe "dup2"
310    c_dup2 :: CInt -> CInt -> IO CInt
311
312 foreign import ccall unsafe "fstat"
313    c_fstat :: CInt -> Ptr CStat -> IO CInt
314
315 foreign import ccall unsafe "getcwd"
316    c_getcwd   :: Ptr CChar -> CInt -> IO (Ptr CChar)
317
318 foreign import ccall unsafe "isatty"
319    c_isatty :: CInt -> IO CInt
320
321 foreign import ccall unsafe "lseek"
322    c_lseek :: CInt -> COff -> CInt -> IO COff
323
324 foreign import ccall unsafe "__hscore_lstat"
325    lstat :: CString -> Ptr CStat -> IO CInt
326
327 foreign import ccall unsafe "open"
328    c_open :: CString -> CInt -> CMode -> IO CInt
329
330 foreign import ccall unsafe "opendir" 
331    c_opendir :: CString  -> IO (Ptr CDir)
332
333 foreign import ccall unsafe "__hscore_mkdir"
334    mkdir :: CString -> CInt -> IO CInt
335
336 foreign import ccall unsafe "read" 
337    c_read :: CInt -> Ptr CChar -> CSize -> IO CSsize
338
339 foreign import ccall unsafe "readdir" 
340    c_readdir :: Ptr CDir -> IO (Ptr CDirent)
341
342 foreign import ccall unsafe "rename"
343    c_rename :: CString -> CString -> IO CInt
344                      
345 foreign import ccall unsafe "rewinddir"
346    c_rewinddir :: Ptr CDir -> IO ()
347
348 foreign import ccall unsafe "rmdir"
349    c_rmdir :: CString -> IO CInt
350
351 foreign import ccall unsafe "stat"
352    c_stat :: CString -> Ptr CStat -> IO CInt
353
354 foreign import ccall unsafe "umask"
355    c_umask :: CMode -> IO CMode
356
357 foreign import ccall unsafe "write" 
358    c_write :: CInt -> Ptr CChar -> CSize -> IO CSsize
359
360 foreign import ccall unsafe "unlink"
361    c_unlink :: CString -> IO CInt
362
363 #ifndef mingw32_TARGET_OS
364 foreign import ccall unsafe "fcntl"
365    c_fcntl_read  :: CInt -> CInt -> IO CInt
366
367 foreign import ccall unsafe "fcntl"
368    c_fcntl_write :: CInt -> CInt -> CInt -> IO CInt
369
370 foreign import ccall unsafe "fcntl"
371    c_fcntl_lock  :: CInt -> CInt -> Ptr CFLock -> IO CInt
372
373 foreign import ccall unsafe "fork"
374    c_fork :: IO CPid 
375
376 foreign import ccall unsafe "fpathconf"
377    c_fpathconf :: CInt -> CInt -> IO CLong
378
379 foreign import ccall unsafe "__hscore_sigemptyset"
380    c_sigemptyset :: Ptr CSigset -> IO ()
381
382 foreign import ccall unsafe "link"
383    c_link :: CString -> CString -> IO CInt
384
385 foreign import ccall unsafe "mkfifo"
386    c_mkfifo :: CString -> CMode -> IO CInt
387
388 foreign import ccall unsafe "pathconf"
389    c_pathconf :: CString -> CInt -> IO CLong
390
391 foreign import ccall unsafe "pipe"
392    c_pipe :: Ptr CInt -> IO CInt
393
394 foreign import ccall unsafe "__hscore_sigaddset"
395    c_sigaddset :: Ptr CSigset -> CInt -> IO CInt
396
397 foreign import ccall unsafe "sigprocmask"
398    c_sigprocmask :: CInt -> Ptr CSigset -> Ptr CSigset -> IO ()
399
400 foreign import ccall unsafe "tcgetattr"
401    c_tcgetattr :: CInt -> Ptr CTermios -> IO CInt
402
403 foreign import ccall unsafe "tcsetattr"
404    c_tcsetattr :: CInt -> CInt -> Ptr CTermios -> IO CInt
405
406 foreign import ccall unsafe "uname"
407    c_uname :: Ptr CUtsname -> IO CInt
408
409 foreign import ccall unsafe "utime"
410    c_utime :: CString -> Ptr CUtimbuf -> IO CMode
411
412 foreign import ccall unsafe "waitpid"
413    c_waitpid :: CPid -> Ptr CInt -> CInt -> IO CPid
414 #endif
415
416 -- POSIX flags only:
417 foreign import ccall unsafe "__hscore_o_rdonly" o_RDONLY :: CInt
418 foreign import ccall unsafe "__hscore_o_wronly" o_WRONLY :: CInt
419 foreign import ccall unsafe "__hscore_o_rdwr"   o_RDWR   :: CInt
420 foreign import ccall unsafe "__hscore_o_append" o_APPEND :: CInt
421 foreign import ccall unsafe "__hscore_o_creat"  o_CREAT  :: CInt
422 foreign import ccall unsafe "__hscore_o_excl"   o_EXCL   :: CInt
423 foreign import ccall unsafe "__hscore_o_trunc"  o_TRUNC  :: CInt
424
425 -- non-POSIX flags.
426 foreign import ccall unsafe "__hscore_o_noctty"   o_NOCTTY   :: CInt
427 foreign import ccall unsafe "__hscore_o_nonblock" o_NONBLOCK :: CInt
428 foreign import ccall unsafe "__hscore_o_binary"   o_BINARY   :: CInt
429
430 foreign import ccall unsafe "__hscore_s_isreg"  s_isreg  :: CMode -> Bool
431 foreign import ccall unsafe "__hscore_s_ischr"  s_ischr  :: CMode -> Bool
432 foreign import ccall unsafe "__hscore_s_isblk"  s_isblk  :: CMode -> Bool
433 foreign import ccall unsafe "__hscore_s_isdir"  s_isdir  :: CMode -> Bool
434 foreign import ccall unsafe "__hscore_s_isfifo" s_isfifo :: CMode -> Bool
435
436 foreign import ccall unsafe "__hscore_sizeof_stat" sizeof_stat :: Int
437 foreign import ccall unsafe "__hscore_st_mtime" st_mtime :: Ptr CStat -> IO CTime
438 foreign import ccall unsafe "__hscore_st_size" st_size :: Ptr CStat -> IO COff
439 foreign import ccall unsafe "__hscore_st_mode" st_mode :: Ptr CStat -> IO CMode
440
441 foreign import ccall unsafe "__hscore_echo"         const_echo :: CInt
442 foreign import ccall unsafe "__hscore_tcsanow"      const_tcsanow :: CInt
443 foreign import ccall unsafe "__hscore_icanon"       const_icanon :: CInt
444 foreign import ccall unsafe "__hscore_vmin"         const_vmin   :: CInt
445 foreign import ccall unsafe "__hscore_vtime"        const_vtime  :: CInt
446 foreign import ccall unsafe "__hscore_sigttou"      const_sigttou :: CInt
447 foreign import ccall unsafe "__hscore_sig_block"    const_sig_block :: CInt
448 foreign import ccall unsafe "__hscore_sig_setmask"  const_sig_setmask :: CInt
449 foreign import ccall unsafe "__hscore_f_getfl"      const_f_getfl :: CInt
450 foreign import ccall unsafe "__hscore_f_setfl"      const_f_setfl :: CInt
451
452 #ifndef mingw32_TARGET_OS
453 foreign import ccall unsafe "__hscore_sizeof_termios"  sizeof_termios :: Int
454 foreign import ccall unsafe "__hscore_sizeof_sigset_t" sizeof_sigset_t :: Int
455
456 foreign import ccall unsafe "__hscore_lflag" c_lflag :: Ptr CTermios -> IO CTcflag
457 foreign import ccall unsafe "__hscore_poke_lflag" poke_c_lflag :: Ptr CTermios -> CTcflag -> IO ()
458 foreign import ccall unsafe "__hscore_ptr_c_cc" ptr_c_cc  :: Ptr CTermios -> IO (Ptr Word8)
459 #endif
460
461 #ifndef mingw32_TARGET_OS
462 foreign import ccall unsafe "__hscore_s_issock" s_issock :: CMode -> Bool
463 #else
464 s_issock :: CMode -> Bool
465 s_issock cmode = False
466 #endif