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