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