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