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