[project @ 2002-04-24 16:31:37 by simonmar]
[ghc-base.git] / GHC / Posix.hs
1 {-# OPTIONS -fno-implicit-prelude #-}
2
3 -- ---------------------------------------------------------------------------
4 -- $Id: Posix.hs,v 1.6 2002/03/26 10:53:03 simonmar Exp $
5 --
6 -- POSIX support layer for the standard libraries
7 --
8 -- Non-posix compliant in order to support the following features:
9 --      * S_ISSOCK (no sockets in POSIX)
10
11 module GHC.Posix where
12
13 #include "config.h"
14
15 import Control.Monad
16
17 import Foreign
18 import Foreign.C
19
20 import Data.Bits
21 import Data.Maybe
22
23 import GHC.Base
24 import GHC.Num
25 import GHC.Real
26 import GHC.IOBase
27
28 -- ---------------------------------------------------------------------------
29 -- Types
30
31 type CDir       = ()
32 type CDirent    = ()
33 type CFLock     = ()
34 type CGroup     = ()
35 type CLconv     = ()
36 type CPasswd    = ()
37 type CSigaction = ()
38 type CSigset    = ()
39 type CStat      = ()
40 type CTermios   = ()
41 type CTm        = ()
42 type CTms       = ()
43 type CUtimbuf   = ()
44 type CUtsname   = ()
45
46 type CDev    = HTYPE_DEV_T
47 type CIno    = HTYPE_INO_T
48 type CMode   = HTYPE_MODE_T
49 type COff    = HTYPE_OFF_T
50 type CPid    = HTYPE_PID_T
51
52 #ifdef mingw32_TARGET_OS
53 type CSsize  = HTYPE_SIZE_T
54 #else
55 type CGid    = HTYPE_GID_T
56 type CNlink  = HTYPE_NLINK_T
57 type CSsize  = HTYPE_SSIZE_T
58 type CUid    = HTYPE_UID_T
59 type CCc     = HTYPE_CC_T
60 type CSpeed  = HTYPE_SPEED_T
61 type CTcflag = HTYPE_TCFLAG_T
62 #endif
63
64 -- ---------------------------------------------------------------------------
65 -- stat()-related stuff
66
67 fdFileSize :: Int -> IO Integer
68 fdFileSize fd = 
69   allocaBytes sizeof_stat $ \ p_stat -> do
70     throwErrnoIfMinus1Retry "fileSize" $
71         c_fstat (fromIntegral fd) p_stat
72     c_mode <- st_mode p_stat :: IO CMode 
73     if not (s_isreg c_mode)
74         then return (-1)
75         else do
76     c_size <- st_size p_stat :: IO COff
77     return (fromIntegral c_size)
78
79 data FDType  = Directory | Stream | RegularFile
80                deriving (Eq)
81
82 fileType :: FilePath -> IO FDType
83 fileType file =
84   allocaBytes sizeof_stat $ \ p_stat -> do
85   withCString file $ \p_file -> do
86     throwErrnoIfMinus1Retry "fileType" $
87       c_stat p_file p_stat
88     statGetType p_stat
89
90 -- NOTE: On Win32 platforms, this will only work with file descriptors
91 -- referring to file handles. i.e., it'll fail for socket FDs.
92 fdType :: Int -> IO FDType
93 fdType fd = 
94   allocaBytes sizeof_stat $ \ p_stat -> do
95     throwErrnoIfMinus1Retry "fdType" $
96         c_fstat (fromIntegral fd) p_stat
97     statGetType p_stat
98
99 statGetType p_stat = do
100   c_mode <- st_mode p_stat :: IO CMode
101   case () of
102       _ | s_isdir c_mode                     -> return Directory
103         | s_isfifo c_mode || s_issock c_mode -> return Stream
104         | s_isreg c_mode                     -> return RegularFile
105         | otherwise                          -> ioException ioe_unknownfiletype
106     
107
108 ioe_unknownfiletype = IOError Nothing UnsupportedOperation "fdType"
109                         "unknown file type" Nothing
110
111 -- It isn't clear whether ftruncate is POSIX or not (I've read several
112 -- manpages and they seem to conflict), so we truncate using open/2.
113 fileTruncate :: FilePath -> IO ()
114 fileTruncate file = do
115   let flags = o_WRONLY .|. o_TRUNC
116   withCString file $ \file_cstr -> do
117     fd <- fromIntegral `liftM`
118             throwErrnoIfMinus1Retry "fileTruncate"
119                 (c_open file_cstr (fromIntegral flags) 0o666)
120     c_close fd
121   return ()
122
123 #ifdef mingw32_TARGET_OS
124 closeFd :: Bool -> CInt -> IO CInt
125 closeFd isStream fd 
126   | isStream  = c_closesocket fd
127   | otherwise = c_close fd
128
129 foreign import ccall unsafe "closesocket"
130    c_closesocket :: CInt -> IO CInt
131 #endif
132
133 -- ---------------------------------------------------------------------------
134 -- Terminal-related stuff
135
136 fdIsTTY :: Int -> IO Bool
137 fdIsTTY fd = c_isatty (fromIntegral fd) >>= return.toBool
138
139 #ifndef mingw32_TARGET_OS
140
141 setEcho :: Int -> Bool -> IO ()
142 setEcho fd on = do
143   allocaBytes sizeof_termios  $ \p_tios -> do
144     throwErrnoIfMinus1Retry "setEcho"
145         (c_tcgetattr (fromIntegral fd) p_tios)
146     c_lflag <- c_lflag p_tios :: IO CTcflag
147     let new_c_lflag
148          | on        = c_lflag .|. fromIntegral const_echo
149          | otherwise = c_lflag .&. complement (fromIntegral const_echo)
150     poke_c_lflag p_tios (new_c_lflag :: CTcflag)
151     tcSetAttr fd const_tcsanow p_tios
152
153 getEcho :: Int -> IO Bool
154 getEcho fd = do
155   allocaBytes sizeof_termios  $ \p_tios -> do
156     throwErrnoIfMinus1Retry "setEcho"
157         (c_tcgetattr (fromIntegral fd) p_tios)
158     c_lflag <- c_lflag p_tios :: IO CTcflag
159     return ((c_lflag .&. fromIntegral const_echo) /= 0)
160
161 setCooked :: Int -> Bool -> IO ()
162 setCooked fd cooked = 
163   allocaBytes sizeof_termios  $ \p_tios -> do
164     throwErrnoIfMinus1Retry "setCooked"
165         (c_tcgetattr (fromIntegral fd) p_tios)
166
167     -- turn on/off ICANON
168     c_lflag <- c_lflag p_tios :: IO CTcflag
169     let new_c_lflag | cooked    = c_lflag .|. (fromIntegral const_icanon)
170                     | otherwise = c_lflag .&. complement (fromIntegral const_icanon)
171     poke_c_lflag p_tios (new_c_lflag :: CTcflag)
172
173     -- set VMIN & VTIME to 1/0 respectively
174     when cooked $ do
175             c_cc <- ptr_c_cc p_tios
176             let vmin  = (c_cc `plusPtr` (fromIntegral const_vmin))  :: Ptr Word8
177                 vtime = (c_cc `plusPtr` (fromIntegral const_vtime)) :: Ptr Word8
178             poke vmin  1
179             poke vtime 0
180
181     tcSetAttr fd const_tcsanow p_tios
182
183 -- tcsetattr() when invoked by a background process causes the process
184 -- to be sent SIGTTOU regardless of whether the process has TOSTOP set
185 -- in its terminal flags (try it...).  This function provides a
186 -- wrapper which temporarily blocks SIGTTOU around the call, making it
187 -- transparent.
188
189 tcSetAttr :: FD -> CInt -> Ptr CTermios -> IO ()
190 tcSetAttr fd options p_tios = do
191   allocaBytes sizeof_sigset_t $ \ p_sigset -> do
192   allocaBytes sizeof_sigset_t $ \ p_old_sigset -> do
193      c_sigemptyset p_sigset
194      c_sigaddset   p_sigset const_sigttou
195      c_sigprocmask const_sig_block p_sigset p_old_sigset
196      throwErrnoIfMinus1Retry_ "tcSetAttr" $
197          c_tcsetattr (fromIntegral fd) options p_tios
198      c_sigprocmask const_sig_setmask p_old_sigset nullPtr
199
200 #else
201
202 -- bogus defns for win32
203 setCooked :: Int -> Bool -> IO ()
204 setCooked fd cooked = return ()
205
206 setEcho :: Int -> Bool -> IO ()
207 setEcho fd on = return ()
208
209 getEcho :: Int -> IO Bool
210 getEcho fd = return False
211
212 #endif
213
214 -- ---------------------------------------------------------------------------
215 -- Turning on non-blocking for a file descriptor
216
217 #ifndef mingw32_TARGET_OS
218
219 setNonBlockingFD fd = do
220   flags <- throwErrnoIfMinus1Retry "setNonBlockingFD"
221                  (c_fcntl_read (fromIntegral fd) const_f_getfl)
222   -- An error when setting O_NONBLOCK isn't fatal: on some systems 
223   -- there are certain file handles on which this will fail (eg. /dev/null
224   -- on FreeBSD) so we throw away the return code from fcntl_write.
225   c_fcntl_write (fromIntegral fd) const_f_setfl (flags .|. o_NONBLOCK)
226 #else
227
228 -- bogus defns for win32
229 setNonBlockingFD fd = return ()
230
231 #endif
232
233 -- -----------------------------------------------------------------------------
234 -- foreign imports
235
236 foreign import ccall unsafe "access"
237    c_access :: CString -> CMode -> IO CInt
238
239 foreign import ccall unsafe "chmod"
240    c_chmod :: CString -> CMode -> IO CInt
241
242 foreign import ccall unsafe "chdir"
243    c_chdir :: CString -> IO CInt
244
245 foreign import ccall unsafe "close"
246    c_close :: CInt -> IO CInt
247
248 foreign import ccall unsafe "closedir" 
249    c_closedir :: Ptr CDir -> IO CInt
250
251 foreign import ccall unsafe "creat"
252    c_creat :: CString -> CMode -> IO CInt
253
254 foreign import ccall unsafe "dup"
255    c_dup :: CInt -> IO CInt
256
257 foreign import ccall unsafe "dup2"
258    c_dup2 :: CInt -> CInt -> IO CInt
259
260 foreign import ccall unsafe "fstat"
261    c_fstat :: CInt -> Ptr CStat -> IO CInt
262
263 foreign import ccall unsafe "getcwd"
264    c_getcwd   :: Ptr CChar -> CInt -> IO (Ptr CChar)
265
266 foreign import ccall unsafe "isatty"
267    c_isatty :: CInt -> IO CInt
268
269 foreign import ccall unsafe "lseek"
270    c_lseek :: CInt -> COff -> CInt -> IO COff
271
272 foreign import ccall unsafe "__hscore_lstat"
273    lstat :: CString -> Ptr CStat -> IO CInt
274
275 foreign import ccall unsafe "open"
276    c_open :: CString -> CInt -> CMode -> IO CInt
277
278 foreign import ccall unsafe "opendir" 
279    c_opendir :: CString  -> IO (Ptr CDir)
280
281 foreign import ccall unsafe "__hscore_mkdir"
282    mkdir :: CString -> CInt -> IO CInt
283
284 foreign import ccall unsafe "read" 
285    c_read :: CInt -> Ptr CChar -> CSize -> IO CSsize
286
287 foreign import ccall unsafe "readdir" 
288    c_readdir :: Ptr CDir -> IO (Ptr CDirent)
289
290 foreign import ccall unsafe "rename"
291    c_rename :: CString -> CString -> IO CInt
292                      
293 foreign import ccall unsafe "rewinddir"
294    c_rewinddir :: Ptr CDir -> IO ()
295
296 foreign import ccall unsafe "rmdir"
297    c_rmdir :: CString -> IO CInt
298
299 foreign import ccall unsafe "stat"
300    c_stat :: CString -> Ptr CStat -> IO CInt
301
302 foreign import ccall unsafe "umask"
303    c_umask :: CMode -> IO CMode
304
305 foreign import ccall unsafe "write" 
306    c_write :: CInt -> Ptr CChar -> CSize -> IO CSsize
307
308 foreign import ccall unsafe "unlink"
309    c_unlink :: CString -> IO CInt
310
311 #ifndef mingw32_TARGET_OS
312 foreign import ccall unsafe "fcntl"
313    c_fcntl_read  :: CInt -> CInt -> IO CInt
314
315 foreign import ccall unsafe "fcntl"
316    c_fcntl_write :: CInt -> CInt -> CInt -> IO CInt
317
318 foreign import ccall unsafe "fcntl"
319    c_fcntl_lock  :: CInt -> CInt -> Ptr CFLock -> IO CInt
320
321 foreign import ccall unsafe "fork"
322    c_fork :: IO CPid 
323
324 foreign import ccall unsafe "fpathconf"
325    c_fpathconf :: CInt -> CInt -> IO CLong
326
327 foreign import ccall unsafe "__hscore_sigemptyset"
328    c_sigemptyset :: Ptr CSigset -> IO ()
329
330 foreign import ccall unsafe "link"
331    c_link :: CString -> CString -> IO CInt
332
333 foreign import ccall unsafe "mkfifo"
334    c_mkfifo :: CString -> CMode -> IO CInt
335
336 foreign import ccall unsafe "pathconf"
337    c_pathconf :: CString -> CInt -> IO CLong
338
339 foreign import ccall unsafe "pipe"
340    c_pipe :: Ptr CInt -> IO CInt
341
342 foreign import ccall unsafe "__hscore_sigaddset"
343    c_sigaddset :: Ptr CSigset -> CInt -> IO CInt
344
345 foreign import ccall unsafe "sigprocmask"
346    c_sigprocmask :: CInt -> Ptr CSigset -> Ptr CSigset -> IO ()
347
348 foreign import ccall unsafe "tcgetattr"
349    c_tcgetattr :: CInt -> Ptr CTermios -> IO CInt
350
351 foreign import ccall unsafe "tcsetattr"
352    c_tcsetattr :: CInt -> CInt -> Ptr CTermios -> IO CInt
353
354 foreign import ccall unsafe "uname"
355    c_uname :: Ptr CUtsname -> IO CInt
356
357 foreign import ccall unsafe "utime"
358    c_utime :: CString -> Ptr CUtimbuf -> IO CMode
359
360 foreign import ccall unsafe "waitpid"
361    c_waitpid :: CPid -> Ptr CInt -> CInt -> IO CPid
362 #endif
363
364 -- POSIX flags only:
365 foreign import ccall unsafe "__hscore_o_rdonly" o_RDONLY :: CInt
366 foreign import ccall unsafe "__hscore_o_wronly" o_WRONLY :: CInt
367 foreign import ccall unsafe "__hscore_o_rdwr"   o_RDWR   :: CInt
368 foreign import ccall unsafe "__hscore_o_append" o_APPEND :: CInt
369 foreign import ccall unsafe "__hscore_o_creat"  o_CREAT  :: CInt
370 foreign import ccall unsafe "__hscore_o_excl"   o_EXCL   :: CInt
371 foreign import ccall unsafe "__hscore_o_trunc"  o_TRUNC  :: CInt
372
373 -- non-POSIX flags.
374 foreign import ccall unsafe "__hscore_o_noctty"   o_NOCTTY   :: CInt
375 foreign import ccall unsafe "__hscore_o_nonblock" o_NONBLOCK :: CInt
376 foreign import ccall unsafe "__hscore_o_binary"   o_BINARY   :: CInt
377
378 foreign import ccall unsafe "__hscore_s_isreg"  s_isreg  :: CMode -> Bool
379 foreign import ccall unsafe "__hscore_s_ischr"  s_ischr  :: CMode -> Bool
380 foreign import ccall unsafe "__hscore_s_isblk"  s_isblk  :: CMode -> Bool
381 foreign import ccall unsafe "__hscore_s_isdir"  s_isdir  :: CMode -> Bool
382 foreign import ccall unsafe "__hscore_s_isfifo" s_isfifo :: CMode -> Bool
383
384 foreign import ccall unsafe "__hscore_sizeof_stat" sizeof_stat :: Int
385 foreign import ccall unsafe "__hscore_st_mtime" st_mtime :: Ptr CStat -> IO CTime
386 foreign import ccall unsafe "__hscore_st_size" st_size :: Ptr CStat -> IO COff
387 foreign import ccall unsafe "__hscore_st_mode" st_mode :: Ptr CStat -> IO CMode
388
389 foreign import ccall unsafe "__hscore_echo"         const_echo :: CInt
390 foreign import ccall unsafe "__hscore_tcsanow"      const_tcsanow :: CInt
391 foreign import ccall unsafe "__hscore_icanon"       const_icanon :: CInt
392 foreign import ccall unsafe "__hscore_vmin"         const_vmin   :: CInt
393 foreign import ccall unsafe "__hscore_vtime"        const_vtime  :: CInt
394 foreign import ccall unsafe "__hscore_sigttou"      const_sigttou :: CInt
395 foreign import ccall unsafe "__hscore_sig_block"    const_sig_block :: CInt
396 foreign import ccall unsafe "__hscore_sig_setmask"  const_sig_setmask :: CInt
397 foreign import ccall unsafe "__hscore_f_getfl"      const_f_getfl :: CInt
398 foreign import ccall unsafe "__hscore_f_setfl"      const_f_setfl :: CInt
399
400 #ifndef mingw32_TARGET_OS
401 foreign import ccall unsafe "__hscore_sizeof_termios"  sizeof_termios :: Int
402 foreign import ccall unsafe "__hscore_sizeof_sigset_t" sizeof_sigset_t :: Int
403
404 foreign import ccall unsafe "__hscore_lflag" c_lflag :: Ptr CTermios -> IO CTcflag
405 foreign import ccall unsafe "__hscore_poke_lflag" poke_c_lflag :: Ptr CTermios -> CTcflag -> IO ()
406 foreign import ccall unsafe "__hscore_ptr_c_cc" ptr_c_cc  :: Ptr CTermios -> IO (Ptr Word8)
407 #endif
408
409 #ifndef mingw32_TARGET_OS
410 foreign import ccall unsafe "__hscore_s_issock" s_issock :: CMode -> Bool
411 #else
412 s_issock :: CMode -> Bool
413 s_issock cmode = False
414 #endif