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