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