1{-# LANGUAGE Trustworthy #-}
2{-# LANGUAGE CPP, NoImplicitPrelude, CApiFFI #-}
3{-# OPTIONS_HADDOCK not-home #-}
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
23module System.Posix.Internals where
24
25#include "HsBaseConfig.h"
26
27import System.Posix.Types
28
29import Foreign
30import Foreign.C
31
32-- import Data.Bits
33import Data.Maybe
34
35#if !defined(HTYPE_TCFLAG_T)
36import System.IO.Error
37#endif
38
39import GHC.Base
40import GHC.Num
41import GHC.Real
42import GHC.IO
43import GHC.IO.IOMode
44import GHC.IO.Exception
45import GHC.IO.Device
46#if !defined(mingw32_HOST_OS)
47import {-# SOURCE #-} GHC.IO.Encoding (getFileSystemEncoding)
48import qualified GHC.Foreign as GHC
49#endif
50
51-- ---------------------------------------------------------------------------
52-- Debugging the base package
53
54puts :: String -> IO ()
55puts s = withCAStringLen (s ++ "\n") $ \(p, len) -> do
56            -- In reality should be withCString, but assume ASCII to avoid loop
57            -- if this is called by GHC.Foreign
58           _ <- c_write 1 (castPtr p) (fromIntegral len)
59           return ()
60
61
62-- ---------------------------------------------------------------------------
63-- Types
64
65data {-# CTYPE "struct flock" #-} CFLock
66data {-# CTYPE "struct group" #-} CGroup
67data {-# CTYPE "struct lconv" #-} CLconv
68data {-# CTYPE "struct passwd" #-} CPasswd
69data {-# CTYPE "struct sigaction" #-} CSigaction
70data {-# CTYPE "sigset_t" #-} CSigset
71data {-# CTYPE "struct stat" #-}  CStat
72data {-# CTYPE "struct termios" #-} CTermios
73data {-# CTYPE "struct tm" #-} CTm
74data {-# CTYPE "struct tms" #-} CTms
75data {-# CTYPE "struct utimbuf" #-} CUtimbuf
76data {-# CTYPE "struct utsname" #-} CUtsname
77
78type FD = CInt
79
80-- ---------------------------------------------------------------------------
81-- stat()-related stuff
82
83fdFileSize :: FD -> IO Integer
84fdFileSize fd =
85  allocaBytes sizeof_stat $ \ p_stat -> do
86    throwErrnoIfMinus1Retry_ "fileSize" $
87        c_fstat fd p_stat
88    c_mode <- st_mode p_stat :: IO CMode
89    if not (s_isreg c_mode)
90        then return (-1)
91        else do
92      c_size <- st_size p_stat
93      return (fromIntegral c_size)
94
95fileType :: FilePath -> IO IODeviceType
96fileType file =
97  allocaBytes sizeof_stat $ \ p_stat -> do
98  withFilePath file $ \p_file -> do
99    throwErrnoIfMinus1Retry_ "fileType" $
100      c_stat p_file p_stat
101    statGetType p_stat
102
103-- NOTE: On Win32 platforms, this will only work with file descriptors
104-- referring to file handles. i.e., it'll fail for socket FDs.
105fdStat :: FD -> IO (IODeviceType, CDev, CIno)
106fdStat fd =
107  allocaBytes sizeof_stat $ \ p_stat -> do
108    throwErrnoIfMinus1Retry_ "fdType" $
109        c_fstat fd p_stat
110    ty <- statGetType p_stat
111    dev <- st_dev p_stat
112    ino <- st_ino p_stat
113    return (ty,dev,ino)
114
115fdType :: FD -> IO IODeviceType
116fdType fd = do (ty,_,_) <- fdStat fd; return ty
117
118statGetType :: Ptr CStat -> IO IODeviceType
119statGetType p_stat = do
120  c_mode <- st_mode p_stat :: IO CMode
121  case () of
122      _ | s_isdir c_mode        -> return Directory
123        | s_isfifo c_mode || s_issock c_mode || s_ischr  c_mode
124                                -> return Stream
125        | s_isreg c_mode        -> return RegularFile
126         -- Q: map char devices to RawDevice too?
127        | s_isblk c_mode        -> return RawDevice
128        | otherwise             -> ioError ioe_unknownfiletype
129
130ioe_unknownfiletype :: IOException
131ioe_unknownfiletype = IOError Nothing UnsupportedOperation "fdType"
132                        "unknown file type"
133                        Nothing
134                        Nothing
135
136fdGetMode :: FD -> IO IOMode
137#if defined(mingw32_HOST_OS)
138fdGetMode _ = do
139    -- We don't have a way of finding out which flags are set on FDs
140    -- on Windows, so make a handle that thinks that anything goes.
141    let flags = o_RDWR
142#else
143fdGetMode fd = do
144    flags <- throwErrnoIfMinus1Retry "fdGetMode"
145                (c_fcntl_read fd const_f_getfl)
146#endif
147    let
148       wH  = (flags .&. o_WRONLY) /= 0
149       aH  = (flags .&. o_APPEND) /= 0
150       rwH = (flags .&. o_RDWR) /= 0
151
152       mode
153         | wH && aH  = AppendMode
154         | wH        = WriteMode
155         | rwH       = ReadWriteMode
156         | otherwise = ReadMode
157
158    return mode
159
160#if defined(mingw32_HOST_OS)
161withFilePath :: FilePath -> (CWString -> IO a) -> IO a
162withFilePath = withCWString
163
164newFilePath :: FilePath -> IO CWString
165newFilePath = newCWString
166
167peekFilePath :: CWString -> IO FilePath
168peekFilePath = peekCWString
169#else
170
171withFilePath :: FilePath -> (CString -> IO a) -> IO a
172newFilePath :: FilePath -> IO CString
173peekFilePath :: CString -> IO FilePath
174peekFilePathLen :: CStringLen -> IO FilePath
175
176withFilePath fp f = getFileSystemEncoding >>= \enc -> GHC.withCString enc fp f
177newFilePath fp = getFileSystemEncoding >>= \enc -> GHC.newCString enc fp
178peekFilePath fp = getFileSystemEncoding >>= \enc -> GHC.peekCString enc fp
179peekFilePathLen fp = getFileSystemEncoding >>= \enc -> GHC.peekCStringLen enc fp
180
181#endif
182
183-- ---------------------------------------------------------------------------
184-- Terminal-related stuff
185
186#if defined(HTYPE_TCFLAG_T)
187
188setEcho :: FD -> Bool -> IO ()
189setEcho 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
197getEcho :: FD -> IO Bool
198getEcho fd = do
199  tcSetAttr fd $ \ p_tios -> do
200    lflag <- c_lflag p_tios :: IO CTcflag
201    return ((lflag .&. fromIntegral const_echo) /= 0)
202
203setCooked :: FD -> Bool -> IO ()
204setCooked 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
221tcSetAttr :: FD -> (Ptr CTermios -> IO a) -> IO a
222tcSetAttr fd fun = do
223     allocaBytes sizeof_termios  $ \p_tios -> do
224        throwErrnoIfMinus1Retry_ "tcSetAttr"
225           (c_tcgetattr fd p_tios)
226
227        -- Save a copy of termios, if this is a standard file descriptor.
228        -- These terminal settings are restored in hs_exit().
229        when (fd <= 2) $ do
230          p <- get_saved_termios fd
231          when (p == nullPtr) $ do
232             saved_tios <- mallocBytes sizeof_termios
233             copyBytes saved_tios p_tios sizeof_termios
234             set_saved_termios fd saved_tios
235
236        -- tcsetattr() when invoked by a background process causes the process
237        -- to be sent SIGTTOU regardless of whether the process has TOSTOP set
238        -- in its terminal flags (try it...).  This function provides a
239        -- wrapper which temporarily blocks SIGTTOU around the call, making it
240        -- transparent.
241        allocaBytes sizeof_sigset_t $ \ p_sigset -> do
242          allocaBytes sizeof_sigset_t $ \ p_old_sigset -> do
243             throwErrnoIfMinus1_ "sigemptyset" $
244                 c_sigemptyset p_sigset
245             throwErrnoIfMinus1_ "sigaddset" $
246                 c_sigaddset   p_sigset const_sigttou
247             throwErrnoIfMinus1_ "sigprocmask" $
248                 c_sigprocmask const_sig_block p_sigset p_old_sigset
249             r <- fun p_tios  -- do the business
250             throwErrnoIfMinus1Retry_ "tcSetAttr" $
251                 c_tcsetattr fd const_tcsanow p_tios
252             throwErrnoIfMinus1_ "sigprocmask" $
253                 c_sigprocmask const_sig_setmask p_old_sigset nullPtr
254             return r
255
256foreign import ccall unsafe "HsBase.h __hscore_get_saved_termios"
257   get_saved_termios :: CInt -> IO (Ptr CTermios)
258
259foreign import ccall unsafe "HsBase.h __hscore_set_saved_termios"
260   set_saved_termios :: CInt -> (Ptr CTermios) -> IO ()
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.
272setCooked :: FD -> Bool -> IO ()
273setCooked 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
279ioe_unk_error :: String -> String -> IOException
280ioe_unk_error loc msg
281 = ioeSetErrorString (mkIOError OtherError loc Nothing Nothing) msg
282
283-- Note: echoing goes hand in hand with enabling 'line input' / raw-ness
284-- for Win32 consoles, hence setEcho ends up being the inverse of setCooked.
285setEcho :: FD -> Bool -> IO ()
286setEcho fd on = do
287  x <- set_console_echo fd (if on then 1 else 0)
288  if (x /= 0)
289   then ioError (ioe_unk_error "setEcho" "failed to set echoing")
290   else return ()
291
292getEcho :: FD -> IO Bool
293getEcho fd = do
294  r <- get_console_echo fd
295  if (r == (-1))
296   then ioError (ioe_unk_error "getEcho" "failed to get echoing")
297   else return (r == 1)
298
299foreign import ccall unsafe "consUtils.h set_console_buffering__"
300   set_console_buffering :: CInt -> CInt -> IO CInt
301
302foreign import ccall unsafe "consUtils.h set_console_echo__"
303   set_console_echo :: CInt -> CInt -> IO CInt
304
305foreign import ccall unsafe "consUtils.h get_console_echo__"
306   get_console_echo :: CInt -> IO CInt
307
308foreign import ccall unsafe "consUtils.h is_console__"
309   is_console :: CInt -> IO CInt
310
311#endif
312
313-- ---------------------------------------------------------------------------
314-- Turning on non-blocking for a file descriptor
315
316setNonBlockingFD :: FD -> Bool -> IO ()
317#if !defined(mingw32_HOST_OS)
318setNonBlockingFD fd set = do
319  flags <- throwErrnoIfMinus1Retry "setNonBlockingFD"
320                 (c_fcntl_read fd const_f_getfl)
321  let flags' | set       = flags .|. o_NONBLOCK
322             | otherwise = flags .&. complement o_NONBLOCK
323  when (flags /= flags') $ do
324    -- An error when setting O_NONBLOCK isn't fatal: on some systems
325    -- there are certain file handles on which this will fail (eg. /dev/null
326    -- on FreeBSD) so we throw away the return code from fcntl_write.
327    _ <- c_fcntl_write fd const_f_setfl (fromIntegral flags')
328    return ()
329#else
330
331-- bogus defns for win32
332setNonBlockingFD _ _ = return ()
333
334#endif
335
336-- -----------------------------------------------------------------------------
337-- Set close-on-exec for a file descriptor
338
339#if !defined(mingw32_HOST_OS)
340setCloseOnExec :: FD -> IO ()
341setCloseOnExec fd = do
342  throwErrnoIfMinus1_ "setCloseOnExec" $
343    c_fcntl_write fd const_f_setfd const_fd_cloexec
344#endif
345
346-- -----------------------------------------------------------------------------
347-- foreign imports
348
349#if !defined(mingw32_HOST_OS)
350type CFilePath = CString
351#else
352type CFilePath = CWString
353#endif
354
355foreign import ccall unsafe "HsBase.h __hscore_open"
356   c_open :: CFilePath -> CInt -> CMode -> IO CInt
357
358foreign import ccall safe "HsBase.h __hscore_open"
359   c_safe_open :: CFilePath -> CInt -> CMode -> IO CInt
360
361foreign import ccall unsafe "HsBase.h __hscore_fstat"
362   c_fstat :: CInt -> Ptr CStat -> IO CInt
363
364foreign import ccall unsafe "HsBase.h __hscore_lstat"
365   lstat :: CFilePath -> Ptr CStat -> IO CInt
366
367{- Note: Win32 POSIX functions
368Functions that are not part of the POSIX standards were
369at some point deprecated by Microsoft. This deprecation
370was performed by renaming the functions according to the
371C++ ABI Section 17.6.4.3.2b. This was done to free up the
372namespace of normal Windows programs since Windows isn't
373POSIX compliant anyway.
374
375These were working before since the RTS was re-exporting
376these symbols under the undeprecated names. This is no longer
377being done. See #11223
378
379See https://msdn.microsoft.com/en-us/library/ms235384.aspx
380for more.
381
382However since we can't hope to get people to support Windows
383packages we should support the deprecated names. See #12497
384-}
385foreign import capi unsafe "unistd.h lseek"
386   c_lseek :: CInt -> COff -> CInt -> IO COff
387
388foreign import ccall unsafe "HsBase.h access"
389   c_access :: CString -> CInt -> IO CInt
390
391foreign import ccall unsafe "HsBase.h chmod"
392   c_chmod :: CString -> CMode -> IO CInt
393
394foreign import ccall unsafe "HsBase.h close"
395   c_close :: CInt -> IO CInt
396
397foreign import ccall unsafe "HsBase.h creat"
398   c_creat :: CString -> CMode -> IO CInt
399
400foreign import ccall unsafe "HsBase.h dup"
401   c_dup :: CInt -> IO CInt
402
403foreign import ccall unsafe "HsBase.h dup2"
404   c_dup2 :: CInt -> CInt -> IO CInt
405
406foreign import ccall unsafe "HsBase.h isatty"
407   c_isatty :: CInt -> IO CInt
408
409#if defined(mingw32_HOST_OS)
410-- See Note: Windows types
411foreign import capi unsafe "HsBase.h _read"
412   c_read :: CInt -> Ptr Word8 -> CUInt -> IO CInt
413
414-- See Note: Windows types
415foreign import capi safe "HsBase.h _read"
416   c_safe_read :: CInt -> Ptr Word8 -> CUInt -> IO CInt
417
418foreign import ccall unsafe "HsBase.h _umask"
419   c_umask :: CMode -> IO CMode
420
421-- See Note: Windows types
422foreign import capi unsafe "HsBase.h _write"
423   c_write :: CInt -> Ptr Word8 -> CUInt -> IO CInt
424
425-- See Note: Windows types
426foreign import capi safe "HsBase.h _write"
427   c_safe_write :: CInt -> Ptr Word8 -> CUInt -> IO CInt
428
429foreign import ccall unsafe "HsBase.h _pipe"
430   c_pipe :: Ptr CInt -> IO CInt
431#else
432-- We use CAPI as on some OSs (eg. Linux) this is wrapped by a macro
433-- which redirects to the 64-bit-off_t versions when large file
434-- support is enabled.
435
436-- See Note: Windows types
437foreign import capi unsafe "HsBase.h read"
438   c_read :: CInt -> Ptr Word8 -> CSize -> IO CSsize
439
440-- See Note: Windows types
441foreign import capi safe "HsBase.h read"
442   c_safe_read :: CInt -> Ptr Word8 -> CSize -> IO CSsize
443
444foreign import ccall unsafe "HsBase.h umask"
445   c_umask :: CMode -> IO CMode
446
447-- See Note: Windows types
448foreign import capi unsafe "HsBase.h write"
449   c_write :: CInt -> Ptr Word8 -> CSize -> IO CSsize
450
451-- See Note: Windows types
452foreign import capi safe "HsBase.h write"
453   c_safe_write :: CInt -> Ptr Word8 -> CSize -> IO CSsize
454
455foreign import ccall unsafe "HsBase.h pipe"
456   c_pipe :: Ptr CInt -> IO CInt
457#endif
458
459foreign import ccall unsafe "HsBase.h unlink"
460   c_unlink :: CString -> IO CInt
461
462foreign import capi unsafe "HsBase.h utime"
463   c_utime :: CString -> Ptr CUtimbuf -> IO CInt
464
465foreign import ccall unsafe "HsBase.h getpid"
466   c_getpid :: IO CPid
467
468foreign import ccall unsafe "HsBase.h __hscore_stat"
469   c_stat :: CFilePath -> Ptr CStat -> IO CInt
470
471foreign import ccall unsafe "HsBase.h __hscore_ftruncate"
472   c_ftruncate :: CInt -> COff -> IO CInt
473
474#if !defined(mingw32_HOST_OS)
475foreign import capi unsafe "HsBase.h fcntl"
476   c_fcntl_read  :: CInt -> CInt -> IO CInt
477
478foreign import capi unsafe "HsBase.h fcntl"
479   c_fcntl_write :: CInt -> CInt -> CLong -> IO CInt
480
481foreign import capi unsafe "HsBase.h fcntl"
482   c_fcntl_lock  :: CInt -> CInt -> Ptr CFLock -> IO CInt
483
484foreign import ccall unsafe "HsBase.h fork"
485   c_fork :: IO CPid
486
487foreign import ccall unsafe "HsBase.h link"
488   c_link :: CString -> CString -> IO CInt
489
490-- capi is required at least on Android
491foreign import capi unsafe "HsBase.h mkfifo"
492   c_mkfifo :: CString -> CMode -> IO CInt
493
494foreign import capi unsafe "signal.h sigemptyset"
495   c_sigemptyset :: Ptr CSigset -> IO CInt
496
497foreign import capi unsafe "signal.h sigaddset"
498   c_sigaddset :: Ptr CSigset -> CInt -> IO CInt
499
500foreign import capi unsafe "signal.h sigprocmask"
501   c_sigprocmask :: CInt -> Ptr CSigset -> Ptr CSigset -> IO CInt
502
503-- capi is required at least on Android
504foreign import capi unsafe "HsBase.h tcgetattr"
505   c_tcgetattr :: CInt -> Ptr CTermios -> IO CInt
506
507-- capi is required at least on Android
508foreign import capi unsafe "HsBase.h tcsetattr"
509   c_tcsetattr :: CInt -> CInt -> Ptr CTermios -> IO CInt
510
511foreign import ccall unsafe "HsBase.h waitpid"
512   c_waitpid :: CPid -> Ptr CInt -> CInt -> IO CPid
513#endif
514
515-- POSIX flags only:
516foreign import ccall unsafe "HsBase.h __hscore_o_rdonly" o_RDONLY :: CInt
517foreign import ccall unsafe "HsBase.h __hscore_o_wronly" o_WRONLY :: CInt
518foreign import ccall unsafe "HsBase.h __hscore_o_rdwr"   o_RDWR   :: CInt
519foreign import ccall unsafe "HsBase.h __hscore_o_append" o_APPEND :: CInt
520foreign import ccall unsafe "HsBase.h __hscore_o_creat"  o_CREAT  :: CInt
521foreign import ccall unsafe "HsBase.h __hscore_o_excl"   o_EXCL   :: CInt
522foreign import ccall unsafe "HsBase.h __hscore_o_trunc"  o_TRUNC  :: CInt
523
524-- non-POSIX flags.
525foreign import ccall unsafe "HsBase.h __hscore_o_noctty"   o_NOCTTY   :: CInt
526foreign import ccall unsafe "HsBase.h __hscore_o_nonblock" o_NONBLOCK :: CInt
527foreign import ccall unsafe "HsBase.h __hscore_o_binary"   o_BINARY   :: CInt
528
529foreign import capi unsafe "sys/stat.h S_ISREG"  c_s_isreg  :: CMode -> CInt
530foreign import capi unsafe "sys/stat.h S_ISCHR"  c_s_ischr  :: CMode -> CInt
531foreign import capi unsafe "sys/stat.h S_ISBLK"  c_s_isblk  :: CMode -> CInt
532foreign import capi unsafe "sys/stat.h S_ISDIR"  c_s_isdir  :: CMode -> CInt
533foreign import capi unsafe "sys/stat.h S_ISFIFO" c_s_isfifo :: CMode -> CInt
534
535s_isreg  :: CMode -> Bool
536s_isreg cm = c_s_isreg cm /= 0
537s_ischr  :: CMode -> Bool
538s_ischr cm = c_s_ischr cm /= 0
539s_isblk  :: CMode -> Bool
540s_isblk cm = c_s_isblk cm /= 0
541s_isdir  :: CMode -> Bool
542s_isdir cm = c_s_isdir cm /= 0
543s_isfifo :: CMode -> Bool
544s_isfifo cm = c_s_isfifo cm /= 0
545
546foreign import ccall unsafe "HsBase.h __hscore_sizeof_stat" sizeof_stat :: Int
547foreign import ccall unsafe "HsBase.h __hscore_st_mtime" st_mtime :: Ptr CStat -> IO CTime
548#if defined(mingw32_HOST_OS)
549foreign import ccall unsafe "HsBase.h __hscore_st_size" st_size :: Ptr CStat -> IO Int64
550#else
551foreign import ccall unsafe "HsBase.h __hscore_st_size" st_size :: Ptr CStat -> IO COff
552#endif
553foreign import ccall unsafe "HsBase.h __hscore_st_mode" st_mode :: Ptr CStat -> IO CMode
554foreign import ccall unsafe "HsBase.h __hscore_st_dev" st_dev :: Ptr CStat -> IO CDev
555foreign import ccall unsafe "HsBase.h __hscore_st_ino" st_ino :: Ptr CStat -> IO CIno
556
557foreign import ccall unsafe "HsBase.h __hscore_echo"         const_echo :: CInt
558foreign import ccall unsafe "HsBase.h __hscore_tcsanow"      const_tcsanow :: CInt
559foreign import ccall unsafe "HsBase.h __hscore_icanon"       const_icanon :: CInt
560foreign import ccall unsafe "HsBase.h __hscore_vmin"         const_vmin   :: CInt
561foreign import ccall unsafe "HsBase.h __hscore_vtime"        const_vtime  :: CInt
562foreign import ccall unsafe "HsBase.h __hscore_sigttou"      const_sigttou :: CInt
563foreign import ccall unsafe "HsBase.h __hscore_sig_block"    const_sig_block :: CInt
564foreign import ccall unsafe "HsBase.h __hscore_sig_setmask"  const_sig_setmask :: CInt
565foreign import ccall unsafe "HsBase.h __hscore_f_getfl"      const_f_getfl :: CInt
566foreign import ccall unsafe "HsBase.h __hscore_f_setfl"      const_f_setfl :: CInt
567foreign import ccall unsafe "HsBase.h __hscore_f_setfd"      const_f_setfd :: CInt
568foreign import ccall unsafe "HsBase.h __hscore_fd_cloexec"   const_fd_cloexec :: CLong
569
570#if defined(HTYPE_TCFLAG_T)
571foreign import ccall unsafe "HsBase.h __hscore_sizeof_termios"  sizeof_termios :: Int
572foreign import ccall unsafe "HsBase.h __hscore_sizeof_sigset_t" sizeof_sigset_t :: Int
573
574foreign import ccall unsafe "HsBase.h __hscore_lflag" c_lflag :: Ptr CTermios -> IO CTcflag
575foreign import ccall unsafe "HsBase.h __hscore_poke_lflag" poke_c_lflag :: Ptr CTermios -> CTcflag -> IO ()
576foreign import ccall unsafe "HsBase.h __hscore_ptr_c_cc" ptr_c_cc  :: Ptr CTermios -> IO (Ptr Word8)
577#endif
578
579s_issock :: CMode -> Bool
580#if !defined(mingw32_HOST_OS)
581s_issock cmode = c_s_issock cmode /= 0
582foreign import capi unsafe "sys/stat.h S_ISSOCK" c_s_issock :: CMode -> CInt
583#else
584s_issock _ = False
585#endif
586
587foreign import ccall unsafe "__hscore_bufsiz"  dEFAULT_BUFFER_SIZE :: Int
588foreign import capi  unsafe "stdio.h value SEEK_CUR" sEEK_CUR :: CInt
589foreign import capi  unsafe "stdio.h value SEEK_SET" sEEK_SET :: CInt
590foreign import capi  unsafe "stdio.h value SEEK_END" sEEK_END :: CInt
591
592{-
593Note: Windows types
594
595Windows' _read and _write have types that differ from POSIX. They take an
596unsigned int for lengh and return a signed int where POSIX uses size_t and
597ssize_t. Those are different on x86_64 and equivalent on x86. We import them
598with the types in Microsoft's documentation which means that c_read,
599c_safe_read, c_write and c_safe_write have different Haskell types depending on
600the OS.
601-}
602
603