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