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