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