Windows: Unicode openFile and stat functions
[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   withFilePath 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 #ifdef mingw32_HOST_OS
176 withFilePath :: FilePath -> (CWString -> IO a) -> IO a
177 withFilePath = withCWString 
178 #else
179 withFilePath :: FilePath -> (CString -> IO a) -> IO a
180 withFilePath = withCString
181 #endif
182
183 -- ---------------------------------------------------------------------------
184 -- Terminal-related stuff
185
186 #if defined(HTYPE_TCFLAG_T)
187
188 setEcho :: FD -> Bool -> IO ()
189 setEcho fd on = do
190   tcSetAttr fd $ \ p_tios -> do
191     lflag <- c_lflag p_tios :: IO CTcflag
192     let new_lflag
193          | on        = lflag .|. fromIntegral const_echo
194          | otherwise = lflag .&. complement (fromIntegral const_echo)
195     poke_c_lflag p_tios (new_lflag :: CTcflag)
196
197 getEcho :: FD -> IO Bool
198 getEcho fd = do
199   tcSetAttr fd $ \ p_tios -> do
200     lflag <- c_lflag p_tios :: IO CTcflag
201     return ((lflag .&. fromIntegral const_echo) /= 0)
202
203 setCooked :: FD -> Bool -> IO ()
204 setCooked fd cooked = 
205   tcSetAttr fd $ \ p_tios -> do
206
207     -- turn on/off ICANON
208     lflag <- c_lflag p_tios :: IO CTcflag
209     let new_lflag | cooked    = lflag .|. (fromIntegral const_icanon)
210                   | otherwise = lflag .&. complement (fromIntegral const_icanon)
211     poke_c_lflag p_tios (new_lflag :: CTcflag)
212
213     -- set VMIN & VTIME to 1/0 respectively
214     when (not cooked) $ do
215             c_cc <- ptr_c_cc p_tios
216             let vmin  = (c_cc `plusPtr` (fromIntegral const_vmin))  :: Ptr Word8
217                 vtime = (c_cc `plusPtr` (fromIntegral const_vtime)) :: Ptr Word8
218             poke vmin  1
219             poke vtime 0
220
221 tcSetAttr :: FD -> (Ptr CTermios -> IO a) -> IO a
222 tcSetAttr fd fun = do
223      allocaBytes sizeof_termios  $ \p_tios -> do
224         throwErrnoIfMinus1Retry "tcSetAttr"
225            (c_tcgetattr fd p_tios)
226
227 #ifdef __GLASGOW_HASKELL__
228         -- Save a copy of termios, if this is a standard file descriptor.
229         -- These terminal settings are restored in hs_exit().
230         when (fd <= 2) $ do
231           p <- get_saved_termios fd
232           when (p == nullPtr) $ do
233              saved_tios <- mallocBytes sizeof_termios
234              copyBytes saved_tios p_tios sizeof_termios
235              set_saved_termios fd saved_tios
236 #endif
237
238         -- tcsetattr() when invoked by a background process causes the process
239         -- to be sent SIGTTOU regardless of whether the process has TOSTOP set
240         -- in its terminal flags (try it...).  This function provides a
241         -- wrapper which temporarily blocks SIGTTOU around the call, making it
242         -- transparent.
243         allocaBytes sizeof_sigset_t $ \ p_sigset -> do
244           allocaBytes sizeof_sigset_t $ \ p_old_sigset -> do
245              c_sigemptyset p_sigset
246              c_sigaddset   p_sigset const_sigttou
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              c_sigprocmask const_sig_setmask p_old_sigset nullPtr
252              return r
253
254 #ifdef __GLASGOW_HASKELL__
255 foreign import ccall unsafe "HsBase.h __hscore_get_saved_termios"
256    get_saved_termios :: CInt -> IO (Ptr CTermios)
257
258 foreign import ccall unsafe "HsBase.h __hscore_set_saved_termios"
259    set_saved_termios :: CInt -> (Ptr CTermios) -> IO ()
260 #endif
261
262 #else
263
264 -- 'raw' mode for Win32 means turn off 'line input' (=> buffering and
265 -- character translation for the console.) The Win32 API for doing
266 -- this is GetConsoleMode(), which also requires echoing to be disabled
267 -- when turning off 'line input' processing. Notice that turning off
268 -- 'line input' implies enter/return is reported as '\r' (and it won't
269 -- report that character until another character is input..odd.) This
270 -- latter feature doesn't sit too well with IO actions like IO.hGetLine..
271 -- consider yourself warned.
272 setCooked :: FD -> Bool -> IO ()
273 setCooked fd cooked = do
274   x <- set_console_buffering fd (if cooked then 1 else 0)
275   if (x /= 0)
276    then ioError (ioe_unk_error "setCooked" "failed to set buffering")
277    else return ()
278
279 ioe_unk_error :: String -> String -> IOException
280 ioe_unk_error loc msg 
281 #ifndef __NHC__
282  = ioeSetErrorString (mkIOError OtherError loc Nothing Nothing) msg
283 #else
284  = UserError loc msg
285 #endif
286
287 -- Note: echoing goes hand in hand with enabling 'line input' / raw-ness
288 -- for Win32 consoles, hence setEcho ends up being the inverse of setCooked.
289 setEcho :: FD -> Bool -> IO ()
290 setEcho fd on = do
291   x <- set_console_echo fd (if on then 1 else 0)
292   if (x /= 0)
293    then ioError (ioe_unk_error "setEcho" "failed to set echoing")
294    else return ()
295
296 getEcho :: FD -> IO Bool
297 getEcho fd = do
298   r <- get_console_echo fd
299   if (r == (-1))
300    then ioError (ioe_unk_error "getEcho" "failed to get echoing")
301    else return (r == 1)
302
303 foreign import ccall unsafe "consUtils.h set_console_buffering__"
304    set_console_buffering :: CInt -> CInt -> IO CInt
305
306 foreign import ccall unsafe "consUtils.h set_console_echo__"
307    set_console_echo :: CInt -> CInt -> IO CInt
308
309 foreign import ccall unsafe "consUtils.h get_console_echo__"
310    get_console_echo :: CInt -> IO CInt
311
312 #endif
313
314 -- ---------------------------------------------------------------------------
315 -- Turning on non-blocking for a file descriptor
316
317 setNonBlockingFD :: FD -> IO ()
318 #if !defined(mingw32_HOST_OS) && !defined(__MINGW32__)
319 setNonBlockingFD fd = do
320   flags <- throwErrnoIfMinus1Retry "setNonBlockingFD"
321                  (c_fcntl_read fd const_f_getfl)
322   -- An error when setting O_NONBLOCK isn't fatal: on some systems 
323   -- there are certain file handles on which this will fail (eg. /dev/null
324   -- on FreeBSD) so we throw away the return code from fcntl_write.
325   unless (testBit flags (fromIntegral o_NONBLOCK)) $ do
326     c_fcntl_write fd const_f_setfl (fromIntegral (flags .|. o_NONBLOCK))
327     return ()
328 #else
329
330 -- bogus defns for win32
331 setNonBlockingFD _ = return ()
332
333 #endif
334
335 -- -----------------------------------------------------------------------------
336 -- Set close-on-exec for a file descriptor
337
338 #if !defined(mingw32_HOST_OS) && !defined(__MINGW32__)
339 setCloseOnExec :: FD -> IO ()
340 setCloseOnExec fd = do
341   throwErrnoIfMinus1 "setCloseOnExec" $
342     c_fcntl_write fd const_f_setfd const_fd_cloexec
343   return ()
344 #endif
345
346 -- -----------------------------------------------------------------------------
347 -- foreign imports
348
349 #if !defined(mingw32_HOST_OS) && !defined(__MINGW32__)
350 type CFilePath = CString
351 #else
352 type CFilePath = CWString
353 #endif
354
355 foreign import ccall unsafe "HsBase.h access"
356    c_access :: CString -> CInt -> IO CInt
357
358 foreign import ccall unsafe "HsBase.h chmod"
359    c_chmod :: CString -> CMode -> IO CInt
360
361 foreign import ccall unsafe "HsBase.h close"
362    c_close :: CInt -> IO CInt
363
364 foreign import ccall unsafe "HsBase.h closedir" 
365    c_closedir :: Ptr CDir -> IO CInt
366
367 foreign import ccall unsafe "HsBase.h creat"
368    c_creat :: CString -> CMode -> IO CInt
369
370 foreign import ccall unsafe "HsBase.h dup"
371    c_dup :: CInt -> IO CInt
372
373 foreign import ccall unsafe "HsBase.h dup2"
374    c_dup2 :: CInt -> CInt -> IO CInt
375
376 foreign import ccall unsafe "HsBase.h __hscore_fstat"
377    c_fstat :: CInt -> Ptr CStat -> IO CInt
378
379 foreign import ccall unsafe "HsBase.h isatty"
380    c_isatty :: CInt -> IO CInt
381
382 #if defined(mingw32_HOST_OS) || defined(__MINGW32__)
383 foreign import ccall unsafe "HsBase.h __hscore_lseek"
384    c_lseek :: CInt -> Int64 -> CInt -> IO Int64
385 #else
386 foreign import ccall unsafe "HsBase.h __hscore_lseek"
387    c_lseek :: CInt -> COff -> CInt -> IO COff
388 #endif
389
390 foreign import ccall unsafe "HsBase.h __hscore_lstat"
391    lstat :: CFilePath -> Ptr CStat -> IO CInt
392
393 foreign import ccall unsafe "__hscore_open"
394    c_open :: CFilePath -> CInt -> CMode -> IO CInt
395
396 foreign import ccall unsafe "HsBase.h opendir" 
397    c_opendir :: CString  -> IO (Ptr CDir)
398
399 foreign import ccall unsafe "HsBase.h __hscore_mkdir"
400    mkdir :: CString -> CInt -> IO CInt
401
402 foreign import ccall unsafe "HsBase.h read" 
403    c_read :: CInt -> Ptr CChar -> CSize -> IO CSsize
404
405 foreign import ccall unsafe "HsBase.h rewinddir"
406    c_rewinddir :: Ptr CDir -> IO ()
407
408 foreign import ccall unsafe "__hscore_stat"
409    c_stat :: CFilePath -> Ptr CStat -> IO CInt
410
411 foreign import ccall unsafe "HsBase.h umask"
412    c_umask :: CMode -> IO CMode
413
414 foreign import ccall unsafe "HsBase.h write" 
415    c_write :: CInt -> Ptr CChar -> 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 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 -- traversing directories
471 foreign import ccall unsafe "dirUtils.h __hscore_readdir"
472   readdir  :: Ptr CDir -> Ptr (Ptr CDirent) -> IO CInt
473  
474 foreign import ccall unsafe "HsBase.h __hscore_free_dirent"
475   freeDirEnt  :: Ptr CDirent -> IO ()
476  
477 foreign import ccall unsafe "HsBase.h __hscore_end_of_dir"
478   end_of_dir :: CInt
479  
480 foreign import ccall unsafe "HsBase.h __hscore_d_name"
481   d_name :: Ptr CDirent -> IO CString
482
483 -- POSIX flags only:
484 foreign import ccall unsafe "HsBase.h __hscore_o_rdonly" o_RDONLY :: CInt
485 foreign import ccall unsafe "HsBase.h __hscore_o_wronly" o_WRONLY :: CInt
486 foreign import ccall unsafe "HsBase.h __hscore_o_rdwr"   o_RDWR   :: CInt
487 foreign import ccall unsafe "HsBase.h __hscore_o_append" o_APPEND :: CInt
488 foreign import ccall unsafe "HsBase.h __hscore_o_creat"  o_CREAT  :: CInt
489 foreign import ccall unsafe "HsBase.h __hscore_o_excl"   o_EXCL   :: CInt
490 foreign import ccall unsafe "HsBase.h __hscore_o_trunc"  o_TRUNC  :: CInt
491
492 -- non-POSIX flags.
493 foreign import ccall unsafe "HsBase.h __hscore_o_noctty"   o_NOCTTY   :: CInt
494 foreign import ccall unsafe "HsBase.h __hscore_o_nonblock" o_NONBLOCK :: CInt
495 foreign import ccall unsafe "HsBase.h __hscore_o_binary"   o_BINARY   :: CInt
496
497 foreign import ccall unsafe "HsBase.h __hscore_s_isreg"  c_s_isreg  :: CMode -> CInt
498 foreign import ccall unsafe "HsBase.h __hscore_s_ischr"  c_s_ischr  :: CMode -> CInt
499 foreign import ccall unsafe "HsBase.h __hscore_s_isblk"  c_s_isblk  :: CMode -> CInt
500 foreign import ccall unsafe "HsBase.h __hscore_s_isdir"  c_s_isdir  :: CMode -> CInt
501 foreign import ccall unsafe "HsBase.h __hscore_s_isfifo" c_s_isfifo :: CMode -> CInt
502
503 s_isreg  :: CMode -> Bool
504 s_isreg cm = c_s_isreg cm /= 0
505 s_ischr  :: CMode -> Bool
506 s_ischr cm = c_s_ischr cm /= 0
507 s_isblk  :: CMode -> Bool
508 s_isblk cm = c_s_isblk cm /= 0
509 s_isdir  :: CMode -> Bool
510 s_isdir cm = c_s_isdir cm /= 0
511 s_isfifo :: CMode -> Bool
512 s_isfifo cm = c_s_isfifo cm /= 0
513
514 foreign import ccall unsafe "HsBase.h __hscore_sizeof_stat" sizeof_stat :: Int
515 foreign import ccall unsafe "HsBase.h __hscore_st_mtime" st_mtime :: Ptr CStat -> IO CTime
516 #ifdef mingw32_HOST_OS
517 foreign import ccall unsafe "HsBase.h __hscore_st_size" st_size :: Ptr CStat -> IO Int64
518 #else
519 foreign import ccall unsafe "HsBase.h __hscore_st_size" st_size :: Ptr CStat -> IO COff
520 #endif
521 foreign import ccall unsafe "HsBase.h __hscore_st_mode" st_mode :: Ptr CStat -> IO CMode
522 foreign import ccall unsafe "HsBase.h __hscore_st_dev" st_dev :: Ptr CStat -> IO CDev
523 foreign import ccall unsafe "HsBase.h __hscore_st_ino" st_ino :: Ptr CStat -> IO CIno
524
525 foreign import ccall unsafe "HsBase.h __hscore_echo"         const_echo :: CInt
526 foreign import ccall unsafe "HsBase.h __hscore_tcsanow"      const_tcsanow :: CInt
527 foreign import ccall unsafe "HsBase.h __hscore_icanon"       const_icanon :: CInt
528 foreign import ccall unsafe "HsBase.h __hscore_vmin"         const_vmin   :: CInt
529 foreign import ccall unsafe "HsBase.h __hscore_vtime"        const_vtime  :: CInt
530 foreign import ccall unsafe "HsBase.h __hscore_sigttou"      const_sigttou :: CInt
531 foreign import ccall unsafe "HsBase.h __hscore_sig_block"    const_sig_block :: CInt
532 foreign import ccall unsafe "HsBase.h __hscore_sig_setmask"  const_sig_setmask :: CInt
533 foreign import ccall unsafe "HsBase.h __hscore_f_getfl"      const_f_getfl :: CInt
534 foreign import ccall unsafe "HsBase.h __hscore_f_setfl"      const_f_setfl :: CInt
535 foreign import ccall unsafe "HsBase.h __hscore_f_setfd"      const_f_setfd :: CInt
536 foreign import ccall unsafe "HsBase.h __hscore_fd_cloexec"   const_fd_cloexec :: CLong
537
538 #if defined(HTYPE_TCFLAG_T)
539 foreign import ccall unsafe "HsBase.h __hscore_sizeof_termios"  sizeof_termios :: Int
540 foreign import ccall unsafe "HsBase.h __hscore_sizeof_sigset_t" sizeof_sigset_t :: Int
541
542 foreign import ccall unsafe "HsBase.h __hscore_lflag" c_lflag :: Ptr CTermios -> IO CTcflag
543 foreign import ccall unsafe "HsBase.h __hscore_poke_lflag" poke_c_lflag :: Ptr CTermios -> CTcflag -> IO ()
544 foreign import ccall unsafe "HsBase.h __hscore_ptr_c_cc" ptr_c_cc  :: Ptr CTermios -> IO (Ptr Word8)
545 #endif
546
547 s_issock :: CMode -> Bool
548 #if !defined(mingw32_HOST_OS) && !defined(__MINGW32__)
549 s_issock cmode = c_s_issock cmode /= 0
550 foreign import ccall unsafe "HsBase.h __hscore_s_issock" c_s_issock :: CMode -> CInt
551 #else
552 s_issock _ = False
553 #endif
554
555 foreign import ccall unsafe "__hscore_bufsiz"   dEFAULT_BUFFER_SIZE :: Int
556 foreign import ccall unsafe "__hscore_seek_cur" sEEK_CUR :: CInt
557 foreign import ccall unsafe "__hscore_seek_set" sEEK_SET :: CInt
558 foreign import ccall unsafe "__hscore_seek_end" sEEK_END :: CInt