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