[project @ 2004-12-02 15:57:02 by ross]
[ghc-base.git] / System / Posix / Internals.hs
1 {-# OPTIONS -fno-implicit-prelude #-}
2
3 -----------------------------------------------------------------------------
4 -- |
5 -- Module      :  System.Posix.Internals
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 -- #hide
22 module System.Posix.Internals where
23
24 #include "ghcconfig.h"
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 #ifdef __GLASGOW_HASKELL__
37 import GHC.Base
38 import GHC.Num
39 import GHC.Real
40 import GHC.IOBase
41 #else
42 import System.IO
43 #endif
44
45 #ifdef __HUGS__
46 import Hugs.Prelude (IOException(..), IOErrorType(..))
47
48 {-# CFILES cbits/PrelIOUtils.c cbits/dirUtils.c cbits/consUtils.c #-}
49 ioException = ioError
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 = Int
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 || s_ischr  c_mode
114                                 -> return Stream
115         | s_isreg c_mode        -> return RegularFile
116         | otherwise             -> ioError ioe_unknownfiletype
117     
118
119 ioe_unknownfiletype = IOError Nothing UnsupportedOperation "fdType"
120                         "unknown file type" Nothing
121
122 -- It isn't clear whether ftruncate is POSIX or not (I've read several
123 -- manpages and they seem to conflict), so we truncate using open/2.
124 fileTruncate :: FilePath -> IO ()
125 fileTruncate file = do
126   let flags = o_WRONLY .|. o_TRUNC
127   withCString file $ \file_cstr -> do
128     fd <- fromIntegral `liftM`
129             throwErrnoIfMinus1Retry "fileTruncate"
130                 (c_open file_cstr (fromIntegral flags) 0o666)
131     c_close fd
132   return ()
133
134 #if defined(mingw32_TARGET_OS) || defined(__MINGW32__)
135 closeFd :: Bool -> CInt -> IO CInt
136 closeFd isStream fd 
137   | isStream  = c_closesocket fd
138   | otherwise = c_close fd
139
140 foreign import stdcall unsafe "HsBase.h closesocket"
141    c_closesocket :: CInt -> IO CInt
142 #endif
143
144 fdGetMode :: Int -> IO IOMode
145 fdGetMode fd = do
146 #if defined(mingw32_TARGET_OS) || defined(__MINGW32__)
147     -- XXX: this code is *BROKEN*, _setmode only deals with O_TEXT/O_BINARY
148     flags1 <- throwErrnoIfMinus1Retry "fdGetMode" 
149                 (c__setmode (fromIntegral fd) (fromIntegral o_WRONLY))
150     flags  <- throwErrnoIfMinus1Retry "fdGetMode" 
151                 (c__setmode (fromIntegral fd) (fromIntegral flags1))
152 #else
153     flags <- throwErrnoIfMinus1Retry "fdGetMode" 
154                 (c_fcntl_read (fromIntegral fd) const_f_getfl)
155 #endif
156     let
157        wH  = (flags .&. o_WRONLY) /= 0
158        aH  = (flags .&. o_APPEND) /= 0
159        rwH = (flags .&. o_RDWR) /= 0
160
161        mode
162          | wH && aH  = AppendMode
163          | wH        = WriteMode
164          | rwH       = ReadWriteMode
165          | otherwise = ReadMode
166           
167     return mode
168
169 -- ---------------------------------------------------------------------------
170 -- Terminal-related stuff
171
172 fdIsTTY :: Int -> IO Bool
173 fdIsTTY fd = c_isatty (fromIntegral fd) >>= return.toBool
174
175 #if defined(HTYPE_TCFLAG_T)
176
177 setEcho :: Int -> Bool -> IO ()
178 setEcho fd on = do
179   tcSetAttr fd $ \ p_tios -> do
180     c_lflag <- c_lflag p_tios :: IO CTcflag
181     let new_c_lflag
182          | on        = c_lflag .|. fromIntegral const_echo
183          | otherwise = c_lflag .&. complement (fromIntegral const_echo)
184     poke_c_lflag p_tios (new_c_lflag :: CTcflag)
185
186 getEcho :: Int -> IO Bool
187 getEcho fd = do
188   tcSetAttr fd $ \ p_tios -> do
189     c_lflag <- c_lflag p_tios :: IO CTcflag
190     return ((c_lflag .&. fromIntegral const_echo) /= 0)
191
192 setCooked :: Int -> Bool -> IO ()
193 setCooked fd cooked = 
194   tcSetAttr fd $ \ p_tios -> do
195
196     -- turn on/off ICANON
197     c_lflag <- c_lflag p_tios :: IO CTcflag
198     let new_c_lflag | cooked    = c_lflag .|. (fromIntegral const_icanon)
199                     | otherwise = c_lflag .&. complement (fromIntegral const_icanon)
200     poke_c_lflag p_tios (new_c_lflag :: CTcflag)
201
202     -- set VMIN & VTIME to 1/0 respectively
203     when (not cooked) $ do
204             c_cc <- ptr_c_cc p_tios
205             let vmin  = (c_cc `plusPtr` (fromIntegral const_vmin))  :: Ptr Word8
206                 vtime = (c_cc `plusPtr` (fromIntegral const_vtime)) :: Ptr Word8
207             poke vmin  1
208             poke vtime 0
209
210 tcSetAttr :: FD -> (Ptr CTermios -> IO a) -> IO a
211 tcSetAttr fd fun = do
212      allocaBytes sizeof_termios  $ \p_tios -> do
213         throwErrnoIfMinus1Retry "tcSetAttr"
214            (c_tcgetattr (fromIntegral fd) p_tios)
215
216 #ifdef __GLASGOW_HASKELL__
217         -- Save a copy of termios, if this is a standard file descriptor.
218         -- These terminal settings are restored in hs_exit().
219         when (fd <= 2) $ do
220           p <- get_saved_termios fd
221           when (p == nullPtr) $ do
222              saved_tios <- mallocBytes sizeof_termios
223              copyBytes saved_tios p_tios sizeof_termios
224              set_saved_termios fd saved_tios
225 #endif
226
227         -- tcsetattr() when invoked by a background process causes the process
228         -- to be sent SIGTTOU regardless of whether the process has TOSTOP set
229         -- in its terminal flags (try it...).  This function provides a
230         -- wrapper which temporarily blocks SIGTTOU around the call, making it
231         -- transparent.
232         allocaBytes sizeof_sigset_t $ \ p_sigset -> do
233         allocaBytes sizeof_sigset_t $ \ p_old_sigset -> do
234              c_sigemptyset p_sigset
235              c_sigaddset   p_sigset const_sigttou
236              c_sigprocmask const_sig_block p_sigset p_old_sigset
237              r <- fun p_tios  -- do the business
238              throwErrnoIfMinus1Retry_ "tcSetAttr" $
239                  c_tcsetattr (fromIntegral fd) const_tcsanow p_tios
240              c_sigprocmask const_sig_setmask p_old_sigset nullPtr
241              return r
242
243 #ifdef __GLASGOW_HASKELL__
244 foreign import ccall unsafe "HsBase.h __hscore_get_saved_termios"
245    get_saved_termios :: Int -> IO (Ptr CTermios)
246
247 foreign import ccall unsafe "HsBase.h __hscore_set_saved_termios"
248    set_saved_termios :: Int -> (Ptr CTermios) -> IO ()
249 #endif
250
251 #else
252
253 -- 'raw' mode for Win32 means turn off 'line input' (=> buffering and
254 -- character translation for the console.) The Win32 API for doing
255 -- this is GetConsoleMode(), which also requires echoing to be disabled
256 -- when turning off 'line input' processing. Notice that turning off
257 -- 'line input' implies enter/return is reported as '\r' (and it won't
258 -- report that character until another character is input..odd.) This
259 -- latter feature doesn't sit too well with IO actions like IO.hGetLine..
260 -- consider yourself warned.
261 setCooked :: Int -> Bool -> IO ()
262 setCooked fd cooked = do
263   x <- set_console_buffering (fromIntegral fd) (if cooked then 1 else 0)
264   if (x /= 0)
265    then ioException (ioe_unk_error "setCooked" "failed to set buffering")
266    else return ()
267
268 ioe_unk_error loc msg 
269  = IOError Nothing OtherError loc msg Nothing
270
271 -- Note: echoing goes hand in hand with enabling 'line input' / raw-ness
272 -- for Win32 consoles, hence setEcho ends up being the inverse of setCooked.
273 setEcho :: Int -> Bool -> IO ()
274 setEcho fd on = do
275   x <- set_console_echo (fromIntegral fd) (if on then 1 else 0)
276   if (x /= 0)
277    then ioException (ioe_unk_error "setEcho" "failed to set echoing")
278    else return ()
279
280 getEcho :: Int -> IO Bool
281 getEcho fd = do
282   r <- get_console_echo (fromIntegral fd)
283   if (r == (-1))
284    then ioException (ioe_unk_error "getEcho" "failed to get echoing")
285    else return (r == 1)
286
287 foreign import ccall unsafe "consUtils.h set_console_buffering__"
288    set_console_buffering :: CInt -> CInt -> IO CInt
289
290 foreign import ccall unsafe "consUtils.h set_console_echo__"
291    set_console_echo :: CInt -> CInt -> IO CInt
292
293 foreign import ccall unsafe "consUtils.h get_console_echo__"
294    get_console_echo :: CInt -> IO CInt
295
296 #endif
297
298 -- ---------------------------------------------------------------------------
299 -- Turning on non-blocking for a file descriptor
300
301 #if !defined(mingw32_TARGET_OS) && !defined(__MINGW32__)
302
303 setNonBlockingFD fd = do
304   flags <- throwErrnoIfMinus1Retry "setNonBlockingFD"
305                  (c_fcntl_read (fromIntegral fd) const_f_getfl)
306   -- An error when setting O_NONBLOCK isn't fatal: on some systems 
307   -- there are certain file handles on which this will fail (eg. /dev/null
308   -- on FreeBSD) so we throw away the return code from fcntl_write.
309   unless (testBit flags (fromIntegral o_NONBLOCK)) $ do
310     c_fcntl_write (fromIntegral fd) const_f_setfl (flags .|. o_NONBLOCK)
311     return ()
312 #else
313
314 -- bogus defns for win32
315 setNonBlockingFD fd = return ()
316
317 #endif
318
319 -- -----------------------------------------------------------------------------
320 -- foreign imports
321
322 foreign import ccall unsafe "HsBase.h access"
323    c_access :: CString -> CMode -> IO CInt
324
325 foreign import ccall unsafe "HsBase.h chmod"
326    c_chmod :: CString -> CMode -> IO CInt
327
328 foreign import ccall unsafe "HsBase.h chdir"
329    c_chdir :: CString -> IO CInt
330
331 foreign import ccall unsafe "HsBase.h close"
332    c_close :: CInt -> IO CInt
333
334 foreign import ccall unsafe "HsBase.h closedir" 
335    c_closedir :: Ptr CDir -> IO CInt
336
337 foreign import ccall unsafe "HsBase.h creat"
338    c_creat :: CString -> CMode -> IO CInt
339
340 foreign import ccall unsafe "HsBase.h dup"
341    c_dup :: CInt -> IO CInt
342
343 foreign import ccall unsafe "HsBase.h dup2"
344    c_dup2 :: CInt -> CInt -> IO CInt
345
346 foreign import ccall unsafe "HsBase.h __hscore_fstat"
347    c_fstat :: CInt -> Ptr CStat -> IO CInt
348
349 foreign import ccall unsafe "HsBase.h getcwd"
350    c_getcwd   :: Ptr CChar -> CInt -> IO (Ptr CChar)
351
352 foreign import ccall unsafe "HsBase.h isatty"
353    c_isatty :: CInt -> IO CInt
354
355 foreign import ccall unsafe "HsBase.h __hscore_lseek"
356    c_lseek :: CInt -> COff -> CInt -> IO COff
357
358 foreign import ccall unsafe "HsBase.h __hscore_lstat"
359    lstat :: CString -> Ptr CStat -> IO CInt
360
361 foreign import ccall unsafe "HsBase.h __hscore_open"
362    c_open :: CString -> CInt -> CMode -> IO CInt
363
364 foreign import ccall unsafe "HsBase.h opendir" 
365    c_opendir :: CString  -> IO (Ptr CDir)
366
367 foreign import ccall unsafe "HsBase.h __hscore_mkdir"
368    mkdir :: CString -> CInt -> IO CInt
369
370 foreign import ccall unsafe "HsBase.h read" 
371    c_read :: CInt -> Ptr CChar -> CSize -> IO CSsize
372
373 foreign import ccall unsafe "dirUtils.h __hscore_renameFile"
374    c_rename :: CString -> CString -> IO CInt
375                      
376 foreign import ccall unsafe "HsBase.h rewinddir"
377    c_rewinddir :: Ptr CDir -> IO ()
378
379 foreign import ccall unsafe "HsBase.h rmdir"
380    c_rmdir :: CString -> IO CInt
381
382 foreign import ccall unsafe "HsBase.h __hscore_stat"
383    c_stat :: CString -> Ptr CStat -> IO CInt
384
385 foreign import ccall unsafe "HsBase.h umask"
386    c_umask :: CMode -> IO CMode
387
388 foreign import ccall unsafe "HsBase.h write" 
389    c_write :: CInt -> Ptr CChar -> CSize -> IO CSsize
390
391 foreign import ccall unsafe "HsBase.h unlink"
392    c_unlink :: CString -> IO CInt
393
394 #if !defined(mingw32_TARGET_OS) && !defined(__MINGW32__)
395 foreign import ccall unsafe "HsBase.h fcntl"
396    c_fcntl_read  :: CInt -> CInt -> IO CInt
397
398 foreign import ccall unsafe "HsBase.h fcntl"
399    c_fcntl_write :: CInt -> CInt -> CInt -> IO CInt
400
401 foreign import ccall unsafe "HsBase.h fcntl"
402    c_fcntl_lock  :: CInt -> CInt -> Ptr CFLock -> IO CInt
403
404 foreign import ccall unsafe "HsBase.h fork"
405    c_fork :: IO CPid 
406
407 foreign import ccall unsafe "HsBase.h getpid"
408    c_getpid :: 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 CMode
436
437 foreign import ccall unsafe "HsBase.h waitpid"
438    c_waitpid :: CPid -> Ptr CInt -> CInt -> IO CPid
439 #else
440 foreign import ccall unsafe "HsBase.h _setmode"
441    c__setmode :: CInt -> CInt -> IO CInt
442
443 --   /* Set "stdin" to have binary mode: */
444 --   result = _setmode( _fileno( stdin ), _O_BINARY );
445 --   if( result == -1 )
446 --      perror( "Cannot set mode" );
447 --   else
448 --      printf( "'stdin' successfully changed to binary mode\n" );
449 #endif
450
451 -- traversing directories
452 foreign import ccall unsafe "dirUtils.h __hscore_readdir"
453   readdir  :: Ptr CDir -> Ptr (Ptr CDirent) -> IO CInt
454  
455 foreign import ccall unsafe "HsBase.h __hscore_free_dirent"
456   freeDirEnt  :: Ptr CDirent -> IO ()
457  
458 foreign import ccall unsafe "HsBase.h __hscore_end_of_dir"
459   end_of_dir :: CInt
460  
461 foreign import ccall unsafe "HsBase.h __hscore_d_name"
462   d_name :: Ptr CDirent -> IO CString
463
464 -- POSIX flags only:
465 foreign import ccall unsafe "HsBase.h __hscore_o_rdonly" o_RDONLY :: CInt
466 foreign import ccall unsafe "HsBase.h __hscore_o_wronly" o_WRONLY :: CInt
467 foreign import ccall unsafe "HsBase.h __hscore_o_rdwr"   o_RDWR   :: CInt
468 foreign import ccall unsafe "HsBase.h __hscore_o_append" o_APPEND :: CInt
469 foreign import ccall unsafe "HsBase.h __hscore_o_creat"  o_CREAT  :: CInt
470 foreign import ccall unsafe "HsBase.h __hscore_o_excl"   o_EXCL   :: CInt
471 foreign import ccall unsafe "HsBase.h __hscore_o_trunc"  o_TRUNC  :: CInt
472
473 -- non-POSIX flags.
474 foreign import ccall unsafe "HsBase.h __hscore_o_noctty"   o_NOCTTY   :: CInt
475 foreign import ccall unsafe "HsBase.h __hscore_o_nonblock" o_NONBLOCK :: CInt
476 foreign import ccall unsafe "HsBase.h __hscore_o_binary"   o_BINARY   :: CInt
477
478 foreign import ccall unsafe "HsBase.h __hscore_s_isreg"  s_isreg  :: CMode -> Bool
479 foreign import ccall unsafe "HsBase.h __hscore_s_ischr"  s_ischr  :: CMode -> Bool
480 foreign import ccall unsafe "HsBase.h __hscore_s_isblk"  s_isblk  :: CMode -> Bool
481 foreign import ccall unsafe "HsBase.h __hscore_s_isdir"  s_isdir  :: CMode -> Bool
482 foreign import ccall unsafe "HsBase.h __hscore_s_isfifo" s_isfifo :: CMode -> Bool
483
484 foreign import ccall unsafe "HsBase.h __hscore_sizeof_stat" sizeof_stat :: Int
485 foreign import ccall unsafe "HsBase.h __hscore_st_mtime" st_mtime :: Ptr CStat -> IO CTime
486 foreign import ccall unsafe "HsBase.h __hscore_st_size" st_size :: Ptr CStat -> IO COff
487 foreign import ccall unsafe "HsBase.h __hscore_st_mode" st_mode :: Ptr CStat -> IO CMode
488
489 foreign import ccall unsafe "HsBase.h __hscore_echo"         const_echo :: CInt
490 foreign import ccall unsafe "HsBase.h __hscore_tcsanow"      const_tcsanow :: CInt
491 foreign import ccall unsafe "HsBase.h __hscore_icanon"       const_icanon :: CInt
492 foreign import ccall unsafe "HsBase.h __hscore_vmin"         const_vmin   :: CInt
493 foreign import ccall unsafe "HsBase.h __hscore_vtime"        const_vtime  :: CInt
494 foreign import ccall unsafe "HsBase.h __hscore_sigttou"      const_sigttou :: CInt
495 foreign import ccall unsafe "HsBase.h __hscore_sig_block"    const_sig_block :: CInt
496 foreign import ccall unsafe "HsBase.h __hscore_sig_setmask"  const_sig_setmask :: CInt
497 foreign import ccall unsafe "HsBase.h __hscore_f_getfl"      const_f_getfl :: CInt
498 foreign import ccall unsafe "HsBase.h __hscore_f_setfl"      const_f_setfl :: CInt
499
500 #if defined(HTYPE_TCFLAG_T)
501 foreign import ccall unsafe "HsBase.h __hscore_sizeof_termios"  sizeof_termios :: Int
502 foreign import ccall unsafe "HsBase.h __hscore_sizeof_sigset_t" sizeof_sigset_t :: Int
503
504 foreign import ccall unsafe "HsBase.h __hscore_lflag" c_lflag :: Ptr CTermios -> IO CTcflag
505 foreign import ccall unsafe "HsBase.h __hscore_poke_lflag" poke_c_lflag :: Ptr CTermios -> CTcflag -> IO ()
506 foreign import ccall unsafe "HsBase.h __hscore_ptr_c_cc" ptr_c_cc  :: Ptr CTermios -> IO (Ptr Word8)
507 #endif
508
509 #if !defined(mingw32_TARGET_OS) && !defined(__MINGW32__)
510 foreign import ccall unsafe "HsBase.h __hscore_s_issock" s_issock :: CMode -> Bool
511 #else
512 s_issock :: CMode -> Bool
513 s_issock cmode = False
514 #endif