[project @ 2002-08-25 09:16:07 by panne]
[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 -- ---------------------------------------------------------------------------
144 -- Terminal-related stuff
145
146 fdIsTTY :: Int -> IO Bool
147 fdIsTTY fd = c_isatty (fromIntegral fd) >>= return.toBool
148
149 #ifndef mingw32_TARGET_OS
150
151 setEcho :: Int -> Bool -> IO ()
152 setEcho fd on = do
153   allocaBytes sizeof_termios  $ \p_tios -> do
154     throwErrnoIfMinus1Retry "setEcho"
155         (c_tcgetattr (fromIntegral fd) p_tios)
156     c_lflag <- c_lflag p_tios :: IO CTcflag
157     let new_c_lflag
158          | on        = c_lflag .|. fromIntegral const_echo
159          | otherwise = c_lflag .&. complement (fromIntegral const_echo)
160     poke_c_lflag p_tios (new_c_lflag :: CTcflag)
161     tcSetAttr fd const_tcsanow p_tios
162
163 getEcho :: Int -> IO Bool
164 getEcho fd = do
165   allocaBytes sizeof_termios  $ \p_tios -> do
166     throwErrnoIfMinus1Retry "setEcho"
167         (c_tcgetattr (fromIntegral fd) p_tios)
168     c_lflag <- c_lflag p_tios :: IO CTcflag
169     return ((c_lflag .&. fromIntegral const_echo) /= 0)
170
171 setCooked :: Int -> Bool -> IO ()
172 setCooked fd cooked = 
173   allocaBytes sizeof_termios  $ \p_tios -> do
174     throwErrnoIfMinus1Retry "setCooked"
175         (c_tcgetattr (fromIntegral fd) p_tios)
176
177     -- turn on/off ICANON
178     c_lflag <- c_lflag p_tios :: IO CTcflag
179     let new_c_lflag | cooked    = c_lflag .|. (fromIntegral const_icanon)
180                     | otherwise = c_lflag .&. complement (fromIntegral const_icanon)
181     poke_c_lflag p_tios (new_c_lflag :: CTcflag)
182
183     -- set VMIN & VTIME to 1/0 respectively
184     when cooked $ do
185             c_cc <- ptr_c_cc p_tios
186             let vmin  = (c_cc `plusPtr` (fromIntegral const_vmin))  :: Ptr Word8
187                 vtime = (c_cc `plusPtr` (fromIntegral const_vtime)) :: Ptr Word8
188             poke vmin  1
189             poke vtime 0
190
191     tcSetAttr fd const_tcsanow p_tios
192
193 -- tcsetattr() when invoked by a background process causes the process
194 -- to be sent SIGTTOU regardless of whether the process has TOSTOP set
195 -- in its terminal flags (try it...).  This function provides a
196 -- wrapper which temporarily blocks SIGTTOU around the call, making it
197 -- transparent.
198
199 tcSetAttr :: FD -> CInt -> Ptr CTermios -> IO ()
200 tcSetAttr fd options p_tios = do
201   allocaBytes sizeof_sigset_t $ \ p_sigset -> do
202   allocaBytes sizeof_sigset_t $ \ p_old_sigset -> do
203      c_sigemptyset p_sigset
204      c_sigaddset   p_sigset const_sigttou
205      c_sigprocmask const_sig_block p_sigset p_old_sigset
206      throwErrnoIfMinus1Retry_ "tcSetAttr" $
207          c_tcsetattr (fromIntegral fd) options p_tios
208      c_sigprocmask const_sig_setmask p_old_sigset nullPtr
209
210 #else
211
212 -- bogus defns for win32
213 setCooked :: Int -> Bool -> IO ()
214 setCooked fd cooked = do
215   x <- set_console_buffering (fromIntegral fd) (if cooked then 1 else 0)
216   if (x /= 0)
217    then ioException (ioe_unk_error "setCooked" "failed to set buffering")
218    else return ()
219
220 ioe_unk_error loc msg 
221  = IOError Nothing OtherError loc msg Nothing
222
223 setEcho :: Int -> Bool -> IO ()
224 setEcho fd on = do
225   x <- set_console_echo (fromIntegral fd) (if on then 1 else 0)
226   if (x /= 0)
227    then ioException (ioe_unk_error "setEcho" "failed to set echoing")
228    else return ()
229
230 getEcho :: Int -> IO Bool
231 getEcho fd = do
232   r <- get_console_echo (fromIntegral fd)
233   if (r == (-1))
234    then ioException (ioe_unk_error "getEcho" "failed to get echoing")
235    else return (r == 1)
236
237 foreign import ccall unsafe "consUtils.h set_console_buffering__"
238    set_console_buffering :: CInt -> CInt -> IO CInt
239
240 foreign import ccall unsafe "consUtils.h set_console_echo__"
241    set_console_echo :: CInt -> CInt -> IO CInt
242
243 foreign import ccall unsafe "consUtils.h get_console_echo__"
244    get_console_echo :: CInt -> IO CInt
245
246 #endif
247
248 -- ---------------------------------------------------------------------------
249 -- Turning on non-blocking for a file descriptor
250
251 #ifndef mingw32_TARGET_OS
252
253 setNonBlockingFD fd = do
254   flags <- throwErrnoIfMinus1Retry "setNonBlockingFD"
255                  (c_fcntl_read (fromIntegral fd) const_f_getfl)
256   -- An error when setting O_NONBLOCK isn't fatal: on some systems 
257   -- there are certain file handles on which this will fail (eg. /dev/null
258   -- on FreeBSD) so we throw away the return code from fcntl_write.
259   c_fcntl_write (fromIntegral fd) const_f_setfl (flags .|. o_NONBLOCK)
260 #else
261
262 -- bogus defns for win32
263 setNonBlockingFD fd = return ()
264
265 #endif
266
267 -- -----------------------------------------------------------------------------
268 -- foreign imports
269
270 foreign import ccall unsafe "access"
271    c_access :: CString -> CMode -> IO CInt
272
273 foreign import ccall unsafe "chmod"
274    c_chmod :: CString -> CMode -> IO CInt
275
276 foreign import ccall unsafe "chdir"
277    c_chdir :: CString -> IO CInt
278
279 foreign import ccall unsafe "close"
280    c_close :: CInt -> IO CInt
281
282 foreign import ccall unsafe "closedir" 
283    c_closedir :: Ptr CDir -> IO CInt
284
285 foreign import ccall unsafe "creat"
286    c_creat :: CString -> CMode -> IO CInt
287
288 foreign import ccall unsafe "dup"
289    c_dup :: CInt -> IO CInt
290
291 foreign import ccall unsafe "dup2"
292    c_dup2 :: CInt -> CInt -> IO CInt
293
294 foreign import ccall unsafe "fstat"
295    c_fstat :: CInt -> Ptr CStat -> IO CInt
296
297 foreign import ccall unsafe "getcwd"
298    c_getcwd   :: Ptr CChar -> CInt -> IO (Ptr CChar)
299
300 foreign import ccall unsafe "isatty"
301    c_isatty :: CInt -> IO CInt
302
303 foreign import ccall unsafe "lseek"
304    c_lseek :: CInt -> COff -> CInt -> IO COff
305
306 foreign import ccall unsafe "__hscore_lstat"
307    lstat :: CString -> Ptr CStat -> IO CInt
308
309 foreign import ccall unsafe "open"
310    c_open :: CString -> CInt -> CMode -> IO CInt
311
312 foreign import ccall unsafe "opendir" 
313    c_opendir :: CString  -> IO (Ptr CDir)
314
315 foreign import ccall unsafe "__hscore_mkdir"
316    mkdir :: CString -> CInt -> IO CInt
317
318 foreign import ccall unsafe "read" 
319    c_read :: CInt -> Ptr CChar -> CSize -> IO CSsize
320
321 foreign import ccall unsafe "readdir" 
322    c_readdir :: Ptr CDir -> IO (Ptr CDirent)
323
324 foreign import ccall unsafe "rename"
325    c_rename :: CString -> CString -> IO CInt
326                      
327 foreign import ccall unsafe "rewinddir"
328    c_rewinddir :: Ptr CDir -> IO ()
329
330 foreign import ccall unsafe "rmdir"
331    c_rmdir :: CString -> IO CInt
332
333 foreign import ccall unsafe "stat"
334    c_stat :: CString -> Ptr CStat -> IO CInt
335
336 foreign import ccall unsafe "umask"
337    c_umask :: CMode -> IO CMode
338
339 foreign import ccall unsafe "write" 
340    c_write :: CInt -> Ptr CChar -> CSize -> IO CSsize
341
342 foreign import ccall unsafe "unlink"
343    c_unlink :: CString -> IO CInt
344
345 #ifndef mingw32_TARGET_OS
346 foreign import ccall unsafe "fcntl"
347    c_fcntl_read  :: CInt -> CInt -> IO CInt
348
349 foreign import ccall unsafe "fcntl"
350    c_fcntl_write :: CInt -> CInt -> CInt -> IO CInt
351
352 foreign import ccall unsafe "fcntl"
353    c_fcntl_lock  :: CInt -> CInt -> Ptr CFLock -> IO CInt
354
355 foreign import ccall unsafe "fork"
356    c_fork :: IO CPid 
357
358 foreign import ccall unsafe "fpathconf"
359    c_fpathconf :: CInt -> CInt -> IO CLong
360
361 foreign import ccall unsafe "__hscore_sigemptyset"
362    c_sigemptyset :: Ptr CSigset -> IO ()
363
364 foreign import ccall unsafe "link"
365    c_link :: CString -> CString -> IO CInt
366
367 foreign import ccall unsafe "mkfifo"
368    c_mkfifo :: CString -> CMode -> IO CInt
369
370 foreign import ccall unsafe "pathconf"
371    c_pathconf :: CString -> CInt -> IO CLong
372
373 foreign import ccall unsafe "pipe"
374    c_pipe :: Ptr CInt -> IO CInt
375
376 foreign import ccall unsafe "__hscore_sigaddset"
377    c_sigaddset :: Ptr CSigset -> CInt -> IO CInt
378
379 foreign import ccall unsafe "sigprocmask"
380    c_sigprocmask :: CInt -> Ptr CSigset -> Ptr CSigset -> IO ()
381
382 foreign import ccall unsafe "tcgetattr"
383    c_tcgetattr :: CInt -> Ptr CTermios -> IO CInt
384
385 foreign import ccall unsafe "tcsetattr"
386    c_tcsetattr :: CInt -> CInt -> Ptr CTermios -> IO CInt
387
388 foreign import ccall unsafe "uname"
389    c_uname :: Ptr CUtsname -> IO CInt
390
391 foreign import ccall unsafe "utime"
392    c_utime :: CString -> Ptr CUtimbuf -> IO CMode
393
394 foreign import ccall unsafe "waitpid"
395    c_waitpid :: CPid -> Ptr CInt -> CInt -> IO CPid
396 #endif
397
398 -- POSIX flags only:
399 foreign import ccall unsafe "__hscore_o_rdonly" o_RDONLY :: CInt
400 foreign import ccall unsafe "__hscore_o_wronly" o_WRONLY :: CInt
401 foreign import ccall unsafe "__hscore_o_rdwr"   o_RDWR   :: CInt
402 foreign import ccall unsafe "__hscore_o_append" o_APPEND :: CInt
403 foreign import ccall unsafe "__hscore_o_creat"  o_CREAT  :: CInt
404 foreign import ccall unsafe "__hscore_o_excl"   o_EXCL   :: CInt
405 foreign import ccall unsafe "__hscore_o_trunc"  o_TRUNC  :: CInt
406
407 -- non-POSIX flags.
408 foreign import ccall unsafe "__hscore_o_noctty"   o_NOCTTY   :: CInt
409 foreign import ccall unsafe "__hscore_o_nonblock" o_NONBLOCK :: CInt
410 foreign import ccall unsafe "__hscore_o_binary"   o_BINARY   :: CInt
411
412 foreign import ccall unsafe "__hscore_s_isreg"  s_isreg  :: CMode -> Bool
413 foreign import ccall unsafe "__hscore_s_ischr"  s_ischr  :: CMode -> Bool
414 foreign import ccall unsafe "__hscore_s_isblk"  s_isblk  :: CMode -> Bool
415 foreign import ccall unsafe "__hscore_s_isdir"  s_isdir  :: CMode -> Bool
416 foreign import ccall unsafe "__hscore_s_isfifo" s_isfifo :: CMode -> Bool
417
418 foreign import ccall unsafe "__hscore_sizeof_stat" sizeof_stat :: Int
419 foreign import ccall unsafe "__hscore_st_mtime" st_mtime :: Ptr CStat -> IO CTime
420 foreign import ccall unsafe "__hscore_st_size" st_size :: Ptr CStat -> IO COff
421 foreign import ccall unsafe "__hscore_st_mode" st_mode :: Ptr CStat -> IO CMode
422
423 foreign import ccall unsafe "__hscore_echo"         const_echo :: CInt
424 foreign import ccall unsafe "__hscore_tcsanow"      const_tcsanow :: CInt
425 foreign import ccall unsafe "__hscore_icanon"       const_icanon :: CInt
426 foreign import ccall unsafe "__hscore_vmin"         const_vmin   :: CInt
427 foreign import ccall unsafe "__hscore_vtime"        const_vtime  :: CInt
428 foreign import ccall unsafe "__hscore_sigttou"      const_sigttou :: CInt
429 foreign import ccall unsafe "__hscore_sig_block"    const_sig_block :: CInt
430 foreign import ccall unsafe "__hscore_sig_setmask"  const_sig_setmask :: CInt
431 foreign import ccall unsafe "__hscore_f_getfl"      const_f_getfl :: CInt
432 foreign import ccall unsafe "__hscore_f_setfl"      const_f_setfl :: CInt
433
434 #ifndef mingw32_TARGET_OS
435 foreign import ccall unsafe "__hscore_sizeof_termios"  sizeof_termios :: Int
436 foreign import ccall unsafe "__hscore_sizeof_sigset_t" sizeof_sigset_t :: Int
437
438 foreign import ccall unsafe "__hscore_lflag" c_lflag :: Ptr CTermios -> IO CTcflag
439 foreign import ccall unsafe "__hscore_poke_lflag" poke_c_lflag :: Ptr CTermios -> CTcflag -> IO ()
440 foreign import ccall unsafe "__hscore_ptr_c_cc" ptr_c_cc  :: Ptr CTermios -> IO (Ptr Word8)
441 #endif
442
443 #ifndef mingw32_TARGET_OS
444 foreign import ccall unsafe "__hscore_s_issock" s_issock :: CMode -> Bool
445 #else
446 s_issock :: CMode -> Bool
447 s_issock cmode = False
448 #endif