{-# LANGUAGE Trustworthy #-}
{-# LANGUAGE InterruptibleFFI #-}
{-# LANGUAGE CPP, NoImplicitPrelude, CApiFFI #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE UnboxedTuples #-}
{-# LANGUAGE MagicHash #-}
{-# OPTIONS_HADDOCK not-home #-}

-----------------------------------------------------------------------------
-- |
-- Module      :  System.Posix.Internals
-- Copyright   :  (c) The University of Glasgow, 1992-2002
-- License     :  see libraries/base/LICENSE
--
-- Maintainer  :  cvs-ghc@haskell.org
-- Stability   :  internal
-- Portability :  non-portable (requires POSIX)
--
-- POSIX support layer for the standard libraries.
-- This library is built on *every* platform, including Win32.
--
-- Non-posix compliant in order to support the following features:
--      * S_ISSOCK (no sockets in POSIX)
--
-----------------------------------------------------------------------------

module System.Posix.Internals where

#include <ghcplatform.h>
#include "HsBaseConfig.h"

import System.Posix.Types

import Foreign
import Foreign.C

import Data.Maybe

#if !defined(HTYPE_TCFLAG_T)
import System.IO.Error
#endif

import GHC.Base
import GHC.Num
import GHC.Real
import GHC.IO
import GHC.IO.IOMode
import GHC.IO.Exception
import GHC.IO.Device
#if !defined(mingw32_HOST_OS)
import {-# SOURCE #-} GHC.IO.Encoding (getFileSystemEncoding)
import qualified GHC.Foreign as GHC
import GHC.Ptr
#else
import Data.OldList (elem)
#endif

-- ---------------------------------------------------------------------------
-- Debugging the base package

puts :: String -> IO ()
puts :: String -> IO ()
puts String
s = String -> (CStringLen -> IO ()) -> IO ()
forall a. String -> (CStringLen -> IO a) -> IO a
withCAStringLen (String
s String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"\n") ((CStringLen -> IO ()) -> IO ()) -> (CStringLen -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \(Ptr CChar
p, Int
len) -> do
            -- In reality should be withCString, but assume ASCII to avoid loop
            -- if this is called by GHC.Foreign
           CSsize
_ <- CInt -> Ptr Word8 -> CSize -> IO CSsize
c_write CInt
1 (Ptr CChar -> Ptr Word8
forall a b. Ptr a -> Ptr b
castPtr Ptr CChar
p) (Int -> CSize
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
len)
           () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()


-- ---------------------------------------------------------------------------
-- Types

data {-# CTYPE "struct flock" #-} CFLock
data {-# CTYPE "struct group" #-} CGroup
data {-# CTYPE "struct lconv" #-} CLconv
data {-# CTYPE "struct passwd" #-} CPasswd
data {-# CTYPE "struct sigaction" #-} CSigaction
data {-# CTYPE "sigset_t" #-} CSigset
data {-# CTYPE "struct stat" #-}  CStat
data {-# CTYPE "struct termios" #-} CTermios
data {-# CTYPE "struct tm" #-} CTm
data {-# CTYPE "struct tms" #-} CTms
data {-# CTYPE "struct utimbuf" #-} CUtimbuf
data {-# CTYPE "struct utsname" #-} CUtsname

type FD = CInt

-- ---------------------------------------------------------------------------
-- stat()-related stuff

fdFileSize :: FD -> IO Integer
fdFileSize :: CInt -> IO Integer
fdFileSize CInt
fd =
  Int -> (Ptr CStat -> IO Integer) -> IO Integer
forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
sizeof_stat ((Ptr CStat -> IO Integer) -> IO Integer)
-> (Ptr CStat -> IO Integer) -> IO Integer
forall a b. (a -> b) -> a -> b
$ \ Ptr CStat
p_stat -> do
    String -> IO CInt -> IO ()
forall a. (Eq a, Num a) => String -> IO a -> IO ()
throwErrnoIfMinus1Retry_ String
"fileSize" (IO CInt -> IO ()) -> IO CInt -> IO ()
forall a b. (a -> b) -> a -> b
$
        CInt -> Ptr CStat -> IO CInt
c_fstat CInt
fd Ptr CStat
p_stat
    CMode
c_mode <- Ptr CStat -> IO CMode
st_mode Ptr CStat
p_stat :: IO CMode
    if Bool -> Bool
not (CMode -> Bool
s_isreg CMode
c_mode)
        then Integer -> IO Integer
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (-Integer
1)
        else do
      COff
c_size <- Ptr CStat -> IO COff
st_size Ptr CStat
p_stat
      Integer -> IO Integer
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (COff -> Integer
forall a b. (Integral a, Num b) => a -> b
fromIntegral COff
c_size)

fileType :: FilePath -> IO IODeviceType
fileType :: String -> IO IODeviceType
fileType String
file =
  Int -> (Ptr CStat -> IO IODeviceType) -> IO IODeviceType
forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
sizeof_stat ((Ptr CStat -> IO IODeviceType) -> IO IODeviceType)
-> (Ptr CStat -> IO IODeviceType) -> IO IODeviceType
forall a b. (a -> b) -> a -> b
$ \ Ptr CStat
p_stat ->
  String -> (Ptr CChar -> IO IODeviceType) -> IO IODeviceType
forall a. String -> (Ptr CChar -> IO a) -> IO a
withFilePath String
file ((Ptr CChar -> IO IODeviceType) -> IO IODeviceType)
-> (Ptr CChar -> IO IODeviceType) -> IO IODeviceType
forall a b. (a -> b) -> a -> b
$ \Ptr CChar
p_file -> do
    String -> IO CInt -> IO ()
forall a. (Eq a, Num a) => String -> IO a -> IO ()
throwErrnoIfMinus1Retry_ String
"fileType" (IO CInt -> IO ()) -> IO CInt -> IO ()
forall a b. (a -> b) -> a -> b
$
      Ptr CChar -> Ptr CStat -> IO CInt
c_stat Ptr CChar
p_file Ptr CStat
p_stat
    Ptr CStat -> IO IODeviceType
statGetType Ptr CStat
p_stat

-- NOTE: On Win32 platforms, this will only work with file descriptors
-- referring to file handles. i.e., it'll fail for socket FDs.
fdStat :: FD -> IO (IODeviceType, CDev, CIno)
fdStat :: CInt -> IO (IODeviceType, CDev, CIno)
fdStat CInt
fd =
  Int
-> (Ptr CStat -> IO (IODeviceType, CDev, CIno))
-> IO (IODeviceType, CDev, CIno)
forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
sizeof_stat ((Ptr CStat -> IO (IODeviceType, CDev, CIno))
 -> IO (IODeviceType, CDev, CIno))
-> (Ptr CStat -> IO (IODeviceType, CDev, CIno))
-> IO (IODeviceType, CDev, CIno)
forall a b. (a -> b) -> a -> b
$ \ Ptr CStat
p_stat -> do
    String -> IO CInt -> IO ()
forall a. (Eq a, Num a) => String -> IO a -> IO ()
throwErrnoIfMinus1Retry_ String
"fdType" (IO CInt -> IO ()) -> IO CInt -> IO ()
forall a b. (a -> b) -> a -> b
$
        CInt -> Ptr CStat -> IO CInt
c_fstat CInt
fd Ptr CStat
p_stat
    IODeviceType
ty <- Ptr CStat -> IO IODeviceType
statGetType Ptr CStat
p_stat
    CDev
dev <- Ptr CStat -> IO CDev
st_dev Ptr CStat
p_stat
    CIno
ino <- Ptr CStat -> IO CIno
st_ino Ptr CStat
p_stat
    (IODeviceType, CDev, CIno) -> IO (IODeviceType, CDev, CIno)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (IODeviceType
ty,CDev
dev,CIno
ino)

fdType :: FD -> IO IODeviceType
fdType :: CInt -> IO IODeviceType
fdType CInt
fd = do (IODeviceType
ty,CDev
_,CIno
_) <- CInt -> IO (IODeviceType, CDev, CIno)
fdStat CInt
fd; IODeviceType -> IO IODeviceType
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return IODeviceType
ty

statGetType :: Ptr CStat -> IO IODeviceType
statGetType :: Ptr CStat -> IO IODeviceType
statGetType Ptr CStat
p_stat = do
  CMode
c_mode <- Ptr CStat -> IO CMode
st_mode Ptr CStat
p_stat :: IO CMode
  case () of
      ()
_ | CMode -> Bool
s_isdir CMode
c_mode        -> IODeviceType -> IO IODeviceType
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return IODeviceType
Directory
        | CMode -> Bool
s_isfifo CMode
c_mode Bool -> Bool -> Bool
|| CMode -> Bool
s_issock CMode
c_mode Bool -> Bool -> Bool
|| CMode -> Bool
s_ischr  CMode
c_mode
                                -> IODeviceType -> IO IODeviceType
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return IODeviceType
Stream
        | CMode -> Bool
s_isreg CMode
c_mode        -> IODeviceType -> IO IODeviceType
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return IODeviceType
RegularFile
         -- Q: map char devices to RawDevice too?
        | CMode -> Bool
s_isblk CMode
c_mode        -> IODeviceType -> IO IODeviceType
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return IODeviceType
RawDevice
        | Bool
otherwise             -> IOError -> IO IODeviceType
forall a. IOError -> IO a
ioError IOError
ioe_unknownfiletype

ioe_unknownfiletype :: IOException
ioe_unknownfiletype :: IOError
ioe_unknownfiletype = Maybe Handle
-> IOErrorType
-> String
-> String
-> Maybe CInt
-> Maybe String
-> IOError
IOError Maybe Handle
forall a. Maybe a
Nothing IOErrorType
UnsupportedOperation String
"fdType"
                        String
"unknown file type"
                        Maybe CInt
forall a. Maybe a
Nothing
                        Maybe String
forall a. Maybe a
Nothing

fdGetMode :: FD -> IO IOMode
#if defined(mingw32_HOST_OS) || defined(javascript_HOST_ARCH)
fdGetMode _ = do
    -- We don't have a way of finding out which flags are set on FDs
    -- on Windows/JS, so make a handle that thinks that anything goes.
    let flags = o_RDWR
#else
fdGetMode :: CInt -> IO IOMode
fdGetMode CInt
fd = do
    CInt
flags <- String -> IO CInt -> IO CInt
forall a. (Eq a, Num a) => String -> IO a -> IO a
throwErrnoIfMinus1Retry String
"fdGetMode"
                (CInt -> CInt -> IO CInt
c_fcntl_read CInt
fd CInt
const_f_getfl)
#endif
    let
       wH :: Bool
wH  = (CInt
flags CInt -> CInt -> CInt
forall a. Bits a => a -> a -> a
.&. CInt
o_WRONLY) CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0
       aH :: Bool
aH  = (CInt
flags CInt -> CInt -> CInt
forall a. Bits a => a -> a -> a
.&. CInt
o_APPEND) CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0
       rwH :: Bool
rwH = (CInt
flags CInt -> CInt -> CInt
forall a. Bits a => a -> a -> a
.&. CInt
o_RDWR) CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0

       mode :: IOMode
mode
         | Bool
wH Bool -> Bool -> Bool
&& Bool
aH  = IOMode
AppendMode
         | Bool
wH        = IOMode
WriteMode
         | Bool
rwH       = IOMode
ReadWriteMode
         | Bool
otherwise = IOMode
ReadMode

    IOMode -> IO IOMode
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return IOMode
mode

#if defined(mingw32_HOST_OS)
withFilePath :: FilePath -> (CWString -> IO a) -> IO a
withFilePath fp f = do
    checkForInteriorNuls fp
    withCWString fp f

newFilePath :: FilePath -> IO CWString
newFilePath fp = do
    checkForInteriorNuls fp
    newCWString fp

peekFilePath :: CWString -> IO FilePath
peekFilePath = peekCWString

-- | Check a 'FilePath' for internal NUL codepoints as these are
-- disallowed in Windows filepaths. See #13660.
checkForInteriorNuls :: FilePath -> IO ()
checkForInteriorNuls fp = when ('\0' `elem` fp) (throwInternalNulError fp)

#else

withFilePath :: FilePath -> (CString -> IO a) -> IO a
newFilePath :: FilePath -> IO CString
peekFilePath :: CString -> IO FilePath
peekFilePathLen :: CStringLen -> IO FilePath

withFilePath :: forall a. String -> (Ptr CChar -> IO a) -> IO a
withFilePath String
fp Ptr CChar -> IO a
f = do
    TextEncoding
enc <- IO TextEncoding
getFileSystemEncoding
    TextEncoding -> String -> (CStringLen -> IO a) -> IO a
forall a. TextEncoding -> String -> (CStringLen -> IO a) -> IO a
GHC.withCStringLen0 TextEncoding
enc String
fp ((CStringLen -> IO a) -> IO a) -> (CStringLen -> IO a) -> IO a
forall a b. (a -> b) -> a -> b
$ \(Ptr CChar
str, Int
len) -> do
        String -> CStringLen -> IO ()
checkForInteriorNuls String
fp (Ptr CChar
str, Int
len)
        Ptr CChar -> IO a
f Ptr CChar
str
newFilePath :: String -> IO (Ptr CChar)
newFilePath String
fp = do
    TextEncoding
enc <- IO TextEncoding
getFileSystemEncoding
    (Ptr CChar
str, Int
len) <- TextEncoding -> String -> IO CStringLen
GHC.newCStringLen0 TextEncoding
enc String
fp
    String -> CStringLen -> IO ()
checkForInteriorNuls String
fp (Ptr CChar
str, Int
len)
    Ptr CChar -> IO (Ptr CChar)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr CChar
str
peekFilePath :: Ptr CChar -> IO String
peekFilePath Ptr CChar
fp = IO TextEncoding
getFileSystemEncoding IO TextEncoding -> (TextEncoding -> IO String) -> IO String
forall a b. IO a -> (a -> IO b) -> IO b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \TextEncoding
enc -> TextEncoding -> Ptr CChar -> IO String
GHC.peekCString TextEncoding
enc Ptr CChar
fp
peekFilePathLen :: CStringLen -> IO String
peekFilePathLen CStringLen
fp = IO TextEncoding
getFileSystemEncoding IO TextEncoding -> (TextEncoding -> IO String) -> IO String
forall a b. IO a -> (a -> IO b) -> IO b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \TextEncoding
enc -> TextEncoding -> CStringLen -> IO String
GHC.peekCStringLen TextEncoding
enc CStringLen
fp

-- | Check an encoded 'FilePath' for internal NUL octets as these are
-- disallowed in POSIX filepaths. See #13660.
checkForInteriorNuls :: FilePath -> CStringLen -> IO ()
checkForInteriorNuls :: String -> CStringLen -> IO ()
checkForInteriorNuls String
fp (Ptr CChar
str, Int
len) =
    Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Int
len' Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
/= Int
len) (String -> IO ()
forall a. String -> IO a
throwInternalNulError String
fp)
    -- N.B. If the string contains internal NUL codeunits then the strlen will
    -- indicate a size smaller than that returned by withCStringLen.
  where
    len' :: Int
len' = case Ptr CChar
str of Ptr Addr#
ptr -> Int# -> Int
I# (Addr# -> Int#
cstringLength# Addr#
ptr)
#endif

throwInternalNulError :: FilePath -> IO a
throwInternalNulError :: forall a. String -> IO a
throwInternalNulError String
fp = IOError -> IO a
forall a. IOError -> IO a
ioError IOError
err
  where
    err :: IOError
err =
      IOError
        { ioe_handle :: Maybe Handle
ioe_handle = Maybe Handle
forall a. Maybe a
Nothing
        , ioe_type :: IOErrorType
ioe_type = IOErrorType
InvalidArgument
        , ioe_location :: String
ioe_location = String
"checkForInteriorNuls"
        , ioe_description :: String
ioe_description = String
"FilePaths must not contain internal NUL code units."
        , ioe_errno :: Maybe CInt
ioe_errno = Maybe CInt
forall a. Maybe a
Nothing
        , ioe_filename :: Maybe String
ioe_filename = String -> Maybe String
forall a. a -> Maybe a
Just String
fp
        }

-- ---------------------------------------------------------------------------
-- Terminal-related stuff

#if defined(HTYPE_TCFLAG_T)

setEcho :: FD -> Bool -> IO ()
setEcho :: CInt -> Bool -> IO ()
setEcho CInt
fd Bool
on =
  CInt -> (Ptr CTermios -> IO ()) -> IO ()
forall a. CInt -> (Ptr CTermios -> IO a) -> IO a
tcSetAttr CInt
fd ((Ptr CTermios -> IO ()) -> IO ())
-> (Ptr CTermios -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \ Ptr CTermios
p_tios -> do
    CTcflag
lflag <- Ptr CTermios -> IO CTcflag
c_lflag Ptr CTermios
p_tios :: IO CTcflag
    let new_lflag :: CTcflag
new_lflag
         | Bool
on        = CTcflag
lflag CTcflag -> CTcflag -> CTcflag
forall a. Bits a => a -> a -> a
.|. CInt -> CTcflag
forall a b. (Integral a, Num b) => a -> b
fromIntegral CInt
const_echo
         | Bool
otherwise = CTcflag
lflag CTcflag -> CTcflag -> CTcflag
forall a. Bits a => a -> a -> a
.&. CTcflag -> CTcflag
forall a. Bits a => a -> a
complement (CInt -> CTcflag
forall a b. (Integral a, Num b) => a -> b
fromIntegral CInt
const_echo)
    Ptr CTermios -> CTcflag -> IO ()
poke_c_lflag Ptr CTermios
p_tios (CTcflag
new_lflag :: CTcflag)

getEcho :: FD -> IO Bool
getEcho :: CInt -> IO Bool
getEcho CInt
fd =
  CInt -> (Ptr CTermios -> IO Bool) -> IO Bool
forall a. CInt -> (Ptr CTermios -> IO a) -> IO a
tcSetAttr CInt
fd ((Ptr CTermios -> IO Bool) -> IO Bool)
-> (Ptr CTermios -> IO Bool) -> IO Bool
forall a b. (a -> b) -> a -> b
$ \ Ptr CTermios
p_tios -> do
    CTcflag
lflag <- Ptr CTermios -> IO CTcflag
c_lflag Ptr CTermios
p_tios :: IO CTcflag
    Bool -> IO Bool
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ((CTcflag
lflag CTcflag -> CTcflag -> CTcflag
forall a. Bits a => a -> a -> a
.&. CInt -> CTcflag
forall a b. (Integral a, Num b) => a -> b
fromIntegral CInt
const_echo) CTcflag -> CTcflag -> Bool
forall a. Eq a => a -> a -> Bool
/= CTcflag
0)

setCooked :: FD -> Bool -> IO ()
setCooked :: CInt -> Bool -> IO ()
setCooked CInt
fd Bool
cooked =
  CInt -> (Ptr CTermios -> IO ()) -> IO ()
forall a. CInt -> (Ptr CTermios -> IO a) -> IO a
tcSetAttr CInt
fd ((Ptr CTermios -> IO ()) -> IO ())
-> (Ptr CTermios -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \ Ptr CTermios
p_tios -> do

    -- turn on/off ICANON
    CTcflag
lflag <- Ptr CTermios -> IO CTcflag
c_lflag Ptr CTermios
p_tios :: IO CTcflag
    let new_lflag :: CTcflag
new_lflag | Bool
cooked    = CTcflag
lflag CTcflag -> CTcflag -> CTcflag
forall a. Bits a => a -> a -> a
.|. (CInt -> CTcflag
forall a b. (Integral a, Num b) => a -> b
fromIntegral CInt
const_icanon)
                  | Bool
otherwise = CTcflag
lflag CTcflag -> CTcflag -> CTcflag
forall a. Bits a => a -> a -> a
.&. CTcflag -> CTcflag
forall a. Bits a => a -> a
complement (CInt -> CTcflag
forall a b. (Integral a, Num b) => a -> b
fromIntegral CInt
const_icanon)
    Ptr CTermios -> CTcflag -> IO ()
poke_c_lflag Ptr CTermios
p_tios (CTcflag
new_lflag :: CTcflag)

    -- set VMIN & VTIME to 1/0 respectively
    Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Bool -> Bool
not Bool
cooked) (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$ do
            Ptr Word8
c_cc <- Ptr CTermios -> IO (Ptr Word8)
ptr_c_cc Ptr CTermios
p_tios
            let vmin :: Ptr Word8
vmin  = (Ptr Word8
c_cc Ptr Word8 -> Int -> Ptr Word8
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (CInt -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral CInt
const_vmin))  :: Ptr Word8
                vtime :: Ptr Word8
vtime = (Ptr Word8
c_cc Ptr Word8 -> Int -> Ptr Word8
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (CInt -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral CInt
const_vtime)) :: Ptr Word8
            Ptr Word8 -> Word8 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke Ptr Word8
vmin  Word8
1
            Ptr Word8 -> Word8 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke Ptr Word8
vtime Word8
0

tcSetAttr :: FD -> (Ptr CTermios -> IO a) -> IO a
tcSetAttr :: forall a. CInt -> (Ptr CTermios -> IO a) -> IO a
tcSetAttr CInt
fd Ptr CTermios -> IO a
fun =
     Int -> (Ptr CTermios -> IO a) -> IO a
forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
sizeof_termios  ((Ptr CTermios -> IO a) -> IO a) -> (Ptr CTermios -> IO a) -> IO a
forall a b. (a -> b) -> a -> b
$ \Ptr CTermios
p_tios -> do
        String -> IO CInt -> IO ()
forall a. (Eq a, Num a) => String -> IO a -> IO ()
throwErrnoIfMinus1Retry_ String
"tcSetAttr"
           (CInt -> Ptr CTermios -> IO CInt
c_tcgetattr CInt
fd Ptr CTermios
p_tios)

        -- Save a copy of termios, if this is a standard file descriptor.
        -- These terminal settings are restored in hs_exit().
        Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (CInt
fd CInt -> CInt -> Bool
forall a. Ord a => a -> a -> Bool
<= CInt
2) (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$ do
          Ptr CTermios
p <- CInt -> IO (Ptr CTermios)
get_saved_termios CInt
fd
          Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Ptr CTermios
p Ptr CTermios -> Ptr CTermios -> Bool
forall a. Eq a => a -> a -> Bool
== Ptr CTermios
forall a. Ptr a
nullPtr) (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$ do
             Ptr CTermios
saved_tios <- Int -> IO (Ptr CTermios)
forall a. Int -> IO (Ptr a)
mallocBytes Int
sizeof_termios
             Ptr CTermios -> Ptr CTermios -> Int -> IO ()
forall a. Ptr a -> Ptr a -> Int -> IO ()
copyBytes Ptr CTermios
saved_tios Ptr CTermios
p_tios Int
sizeof_termios
             CInt -> Ptr CTermios -> IO ()
set_saved_termios CInt
fd Ptr CTermios
saved_tios

        -- tcsetattr() when invoked by a background process causes the process
        -- to be sent SIGTTOU regardless of whether the process has TOSTOP set
        -- in its terminal flags (try it...).  This function provides a
        -- wrapper which temporarily blocks SIGTTOU around the call, making it
        -- transparent.
        Int -> (Ptr CSigset -> IO a) -> IO a
forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
sizeof_sigset_t ((Ptr CSigset -> IO a) -> IO a) -> (Ptr CSigset -> IO a) -> IO a
forall a b. (a -> b) -> a -> b
$ \ Ptr CSigset
p_sigset ->
          Int -> (Ptr CSigset -> IO a) -> IO a
forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
sizeof_sigset_t ((Ptr CSigset -> IO a) -> IO a) -> (Ptr CSigset -> IO a) -> IO a
forall a b. (a -> b) -> a -> b
$ \ Ptr CSigset
p_old_sigset -> do
             String -> IO CInt -> IO ()
forall a. (Eq a, Num a) => String -> IO a -> IO ()
throwErrnoIfMinus1_ String
"sigemptyset" (IO CInt -> IO ()) -> IO CInt -> IO ()
forall a b. (a -> b) -> a -> b
$
                 Ptr CSigset -> IO CInt
c_sigemptyset Ptr CSigset
p_sigset
             String -> IO CInt -> IO ()
forall a. (Eq a, Num a) => String -> IO a -> IO ()
throwErrnoIfMinus1_ String
"sigaddset" (IO CInt -> IO ()) -> IO CInt -> IO ()
forall a b. (a -> b) -> a -> b
$
                 Ptr CSigset -> CInt -> IO CInt
c_sigaddset   Ptr CSigset
p_sigset CInt
const_sigttou
             String -> IO CInt -> IO ()
forall a. (Eq a, Num a) => String -> IO a -> IO ()
throwErrnoIfMinus1_ String
"sigprocmask" (IO CInt -> IO ()) -> IO CInt -> IO ()
forall a b. (a -> b) -> a -> b
$
                 CInt -> Ptr CSigset -> Ptr CSigset -> IO CInt
c_sigprocmask CInt
const_sig_block Ptr CSigset
p_sigset Ptr CSigset
p_old_sigset
             a
r <- Ptr CTermios -> IO a
fun Ptr CTermios
p_tios  -- do the business
             String -> IO CInt -> IO ()
forall a. (Eq a, Num a) => String -> IO a -> IO ()
throwErrnoIfMinus1Retry_ String
"tcSetAttr" (IO CInt -> IO ()) -> IO CInt -> IO ()
forall a b. (a -> b) -> a -> b
$
                 CInt -> CInt -> Ptr CTermios -> IO CInt
c_tcsetattr CInt
fd CInt
const_tcsanow Ptr CTermios
p_tios
             String -> IO CInt -> IO ()
forall a. (Eq a, Num a) => String -> IO a -> IO ()
throwErrnoIfMinus1_ String
"sigprocmask" (IO CInt -> IO ()) -> IO CInt -> IO ()
forall a b. (a -> b) -> a -> b
$
                 CInt -> Ptr CSigset -> Ptr CSigset -> IO CInt
c_sigprocmask CInt
const_sig_setmask Ptr CSigset
p_old_sigset Ptr CSigset
forall a. Ptr a
nullPtr
             a -> IO a
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return a
r

foreign import ccall unsafe "HsBase.h __hscore_get_saved_termios"
   get_saved_termios :: CInt -> IO (Ptr CTermios)

foreign import ccall unsafe "HsBase.h __hscore_set_saved_termios"
   set_saved_termios :: CInt -> (Ptr CTermios) -> IO ()

#elif defined(mingw32_HOST_OS)

-- 'raw' mode for Win32 means turn off 'line input' (=> buffering and
-- character translation for the console.) The Win32 API for doing
-- this is GetConsoleMode(), which also requires echoing to be disabled
-- when turning off 'line input' processing. Notice that turning off
-- 'line input' implies enter/return is reported as '\r' (and it won't
-- report that character until another character is input..odd.) This
-- latter feature doesn't sit too well with IO actions like IO.hGetLine..
-- consider yourself warned.
setCooked :: FD -> Bool -> IO ()
setCooked fd cooked = do
  x <- set_console_buffering fd (if cooked then 1 else 0)
  if (x /= 0)
   then ioError (ioe_unk_error "setCooked" "failed to set buffering")
   else return ()

ioe_unk_error :: String -> String -> IOException
ioe_unk_error loc msg
 = ioeSetErrorString (mkIOError OtherError loc Nothing Nothing) msg

-- Note: echoing goes hand in hand with enabling 'line input' / raw-ness
-- for Win32 consoles, hence setEcho ends up being the inverse of setCooked.
setEcho :: FD -> Bool -> IO ()
setEcho fd on = do
  x <- set_console_echo fd (if on then 1 else 0)
  if (x /= 0)
   then ioError (ioe_unk_error "setEcho" "failed to set echoing")
   else return ()

getEcho :: FD -> IO Bool
getEcho fd = do
  r <- get_console_echo fd
  if (r == (-1))
   then ioError (ioe_unk_error "getEcho" "failed to get echoing")
   else return (r == 1)

foreign import ccall unsafe "consUtils.h set_console_buffering__"
   set_console_buffering :: CInt -> CInt -> IO CInt

foreign import ccall unsafe "consUtils.h set_console_echo__"
   set_console_echo :: CInt -> CInt -> IO CInt

foreign import ccall unsafe "consUtils.h get_console_echo__"
   get_console_echo :: CInt -> IO CInt

foreign import ccall unsafe "consUtils.h is_console__"
   is_console :: CInt -> IO CInt

#else

setCooked :: FD -> Bool -> IO ()
setCooked _ _ = errorWithoutStackTrace "setCooked"

setEcho :: FD -> Bool -> IO ()
setEcho _ _ = errorWithoutStackTrace "setEcho"

getEcho :: FD -> IO Bool
getEcho _ = errorWithoutStackTrace "getEcho"

#endif

-- ---------------------------------------------------------------------------
-- Turning on non-blocking for a file descriptor

setNonBlockingFD :: FD -> Bool -> IO ()
#if !defined(mingw32_HOST_OS)
setNonBlockingFD :: CInt -> Bool -> IO ()
setNonBlockingFD CInt
fd Bool
set = do
  CInt
flags <- String -> IO CInt -> IO CInt
forall a. (Eq a, Num a) => String -> IO a -> IO a
throwErrnoIfMinus1Retry String
"setNonBlockingFD"
                 (CInt -> CInt -> IO CInt
c_fcntl_read CInt
fd CInt
const_f_getfl)
  let flags' :: CInt
flags' | Bool
set       = CInt
flags CInt -> CInt -> CInt
forall a. Bits a => a -> a -> a
.|. CInt
o_NONBLOCK
             | Bool
otherwise = CInt
flags CInt -> CInt -> CInt
forall a. Bits a => a -> a -> a
.&. CInt -> CInt
forall a. Bits a => a -> a
complement CInt
o_NONBLOCK
  Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (CInt
flags CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
flags') (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$ do
    -- An error when setting O_NONBLOCK isn't fatal: on some systems
    -- there are certain file handles on which this will fail (eg. /dev/null
    -- on FreeBSD) so we throw away the return code from fcntl_write.
    CInt
_ <- CInt -> CInt -> CLong -> IO CInt
c_fcntl_write CInt
fd CInt
const_f_setfl (CInt -> CLong
forall a b. (Integral a, Num b) => a -> b
fromIntegral CInt
flags')
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#else

-- bogus defns for win32
setNonBlockingFD _ _ = return ()

#endif

-- -----------------------------------------------------------------------------
-- Set close-on-exec for a file descriptor

#if !defined(mingw32_HOST_OS)
setCloseOnExec :: FD -> IO ()
setCloseOnExec :: CInt -> IO ()
setCloseOnExec CInt
fd =
  String -> IO CInt -> IO ()
forall a. (Eq a, Num a) => String -> IO a -> IO ()
throwErrnoIfMinus1_ String
"setCloseOnExec" (IO CInt -> IO ()) -> IO CInt -> IO ()
forall a b. (a -> b) -> a -> b
$
    CInt -> CInt -> CLong -> IO CInt
c_fcntl_write CInt
fd CInt
const_f_setfd CLong
const_fd_cloexec
#endif

-- -----------------------------------------------------------------------------
-- foreign imports

#if !defined(mingw32_HOST_OS)
type CFilePath = CString
#else
type CFilePath = CWString
#endif

-- | The same as 'c_safe_open', but an /interruptible operation/
-- as described in "Control.Exception"—it respects `uninterruptibleMask`
-- but not `mask`.
--
-- We want to be able to interrupt an openFile call if
-- it's expensive (NFS, FUSE, etc.), and we especially
-- need to be able to interrupt a blocking open call.
-- See #17912.
--
-- @since 4.16.0.0
c_interruptible_open :: CFilePath -> CInt -> CMode -> IO CInt
c_interruptible_open :: Ptr CChar -> CInt -> CMode -> IO CInt
c_interruptible_open Ptr CChar
filepath CInt
oflags CMode
mode =
  IO MaskingState
getMaskingState IO MaskingState -> (MaskingState -> IO CInt) -> IO CInt
forall a b. IO a -> (a -> IO b) -> IO b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \case
    -- If we're in an uninterruptible mask, there's basically
    -- no point in using an interruptible FFI call. The open system call
    -- will be interrupted, but the exception won't be delivered
    -- unless the caller manually futzes with the masking state. So
    -- then the caller (assuming they're following the usual conventions)
    -- will retry the call (in response to EINTR), and we've just
    -- wasted everyone's time.
    MaskingState
MaskedUninterruptible -> Ptr CChar -> CInt -> CMode -> IO CInt
c_safe_open_ Ptr CChar
filepath CInt
oflags CMode
mode
    MaskingState
_ -> do
      CInt
open_res <- Ptr CChar -> CInt -> CMode -> IO CInt
c_interruptible_open_ Ptr CChar
filepath CInt
oflags CMode
mode
      -- c_interruptible_open_ is an interruptible foreign call.
      -- If the call is interrupted by an exception handler
      -- before the system call has returned (so the file is
      -- not yet open), we want to deliver the exception.
      -- In point of fact, we deliver any pending exception
      -- here regardless of the *reason* the system call
      -- fails.
      Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (CInt
open_res CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
== -CInt
1) (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$
        if Bool
hostIsThreaded
          then
            -- Control.Exception.allowInterrupt, inlined to avoid
            -- messing with any Haddock links.
            IO () -> IO ()
forall a. IO a -> IO a
interruptible (() -> IO ()
forall a. a -> IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure ())
          else
            -- Try to make this work somewhat better on the non-threaded
            -- RTS. See #8684. This inlines the definition of `yield`; module
            -- dependencies look pretty hairy here and I don't want to make
            -- things worse for one little wrapper.
            IO () -> IO ()
forall a. IO a -> IO a
interruptible ((State# RealWorld -> (# State# RealWorld, () #)) -> IO ()
forall a. (State# RealWorld -> (# State# RealWorld, a #)) -> IO a
IO ((State# RealWorld -> (# State# RealWorld, () #)) -> IO ())
-> (State# RealWorld -> (# State# RealWorld, () #)) -> IO ()
forall a b. (a -> b) -> a -> b
$ \State# RealWorld
s -> (# State# RealWorld -> State# RealWorld
yield# State# RealWorld
s, () #))
      CInt -> IO CInt
forall a. a -> IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure CInt
open_res

c_safe_open :: CFilePath -> CInt -> CMode -> IO CInt
c_safe_open :: Ptr CChar -> CInt -> CMode -> IO CInt
c_safe_open Ptr CChar
filepath CInt
oflags CMode
mode =
  IO MaskingState
getMaskingState IO MaskingState -> (MaskingState -> IO CInt) -> IO CInt
forall a b. IO a -> (a -> IO b) -> IO b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \case
    -- When exceptions are unmasked, we use an interruptible
    -- open call. If the system call is successfully
    -- interrupted, the situation will be the same as if
    -- the exception had arrived before this function was
    -- called.
    MaskingState
Unmasked -> Ptr CChar -> CInt -> CMode -> IO CInt
c_interruptible_open_ Ptr CChar
filepath CInt
oflags CMode
mode
    MaskingState
_ -> Ptr CChar -> CInt -> CMode -> IO CInt
c_safe_open_ Ptr CChar
filepath CInt
oflags CMode
mode

-- | Consult the RTS to find whether it is threaded.
--
-- @since 4.16.0.0
hostIsThreaded :: Bool
hostIsThreaded :: Bool
hostIsThreaded = Int
rtsIsThreaded_ Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
/= Int
0

#if !defined(javascript_HOST_ARCH)
foreign import ccall unsafe "HsBase.h __hscore_open"
   c_open :: CFilePath -> CInt -> CMode -> IO CInt

-- |
--
-- @since 4.16.0.0
foreign import ccall interruptible "HsBase.h __hscore_open"
   c_interruptible_open_ :: CFilePath -> CInt -> CMode -> IO CInt

-- |
--
-- @since 4.16.0.0
foreign import ccall unsafe "rts_isThreaded" rtsIsThreaded_ :: Int

foreign import ccall safe "HsBase.h __hscore_open"
   c_safe_open_ :: CFilePath -> CInt -> CMode -> IO CInt

foreign import ccall unsafe "HsBase.h __hscore_fstat"
   c_fstat :: CInt -> Ptr CStat -> IO CInt

foreign import ccall unsafe "HsBase.h __hscore_lstat"
   lstat :: CFilePath -> Ptr CStat -> IO CInt
#endif

#if defined(javascript_HOST_ARCH)

foreign import javascript unsafe "(() => { return rts_isThreaded; })" rtsIsThreaded_ :: Int
foreign import javascript interruptible "h$base_access"
    c_access :: CString -> CInt -> IO CInt
foreign import javascript interruptible "h$base_chmod"
    c_chmod :: CString -> CMode -> IO CInt
foreign import javascript interruptible "h$base_close"
    c_close :: CInt -> IO CInt
foreign import javascript interruptible "h$base_creat"
    c_creat :: CString -> CMode -> IO CInt
foreign import javascript interruptible "h$base_dup"
    c_dup :: CInt -> IO CInt
foreign import javascript interruptible "h$base_dup2"
    c_dup2 :: CInt -> CInt -> IO CInt
foreign import javascript interruptible "h$base_fstat" -- fixme wrong type
    c_fstat :: CInt -> Ptr CStat -> IO CInt
foreign import javascript unsafe "h$base_isatty"
    c_isatty :: CInt -> IO CInt
foreign import javascript interruptible "h$base_lseek"
   c_lseek :: CInt -> COff -> CInt -> IO COff
foreign import javascript interruptible "h$base_lstat"
   lstat :: CFilePath -> Ptr CStat -> IO CInt
foreign import javascript interruptible "h$base_open"
   c_open :: CFilePath -> CInt -> CMode -> IO CInt
foreign import javascript interruptible "h$base_open"
   c_interruptible_open_ :: CFilePath -> CInt -> CMode -> IO CInt
foreign import javascript interruptible "h$base_open"
   c_safe_open_ :: CFilePath -> CInt -> CMode -> IO CInt
foreign import javascript interruptible "h$base_read"
   c_read :: CInt -> Ptr Word8 -> CSize -> IO CSsize
foreign import javascript interruptible "h$base_read"
   c_safe_read :: CInt -> Ptr Word8 -> CSize -> IO CSsize
foreign import javascript interruptible "h$base_stat" -- fixme wrong type
   c_stat :: CFilePath -> Ptr CStat -> IO CInt
foreign import javascript unsafe "h$base_umask"
   c_umask :: CMode -> IO CMode
foreign import javascript interruptible "h$base_write"
   c_write :: CInt -> Ptr Word8 -> CSize -> IO CSsize
foreign import javascript interruptible "h$base_write"
   c_safe_write :: CInt -> Ptr Word8 -> CSize -> IO CSsize
foreign import javascript interruptible "h$base_ftruncate" -- fixme COff
   c_ftruncate :: CInt -> FileOffset -> IO CInt
foreign import javascript interruptible "h$base_unlink"
   c_unlink :: CString -> IO CInt
foreign import javascript unsafe "h$base_getpid"
   c_getpid :: IO CPid
-- foreign import ccall unsafe "HsBase.h fork"
--   c_fork :: IO CPid
foreign import javascript interruptible "h$base_link"
   c_link :: CString -> CString -> IO CInt
foreign import javascript interruptible "h$base_mkfifo"
   c_mkfifo :: CString -> CMode -> IO CInt
foreign import javascript interruptible "h$base_pipe"
  c_pipe :: Ptr CInt -> IO CInt
foreign import javascript unsafe "h$base_sigemptyset"
   c_sigemptyset :: Ptr CSigset -> IO CInt
foreign import javascript unsafe "h$base_sigaddset"
   c_sigaddset :: Ptr CSigset -> CInt -> IO CInt
foreign import javascript unsafe "h$base_sigprocmask"
   c_sigprocmask :: CInt -> Ptr CSigset -> Ptr CSigset -> IO CInt
foreign import javascript unsafe "h$base_tcgetattr"
   c_tcgetattr :: CInt -> Ptr CTermios -> IO CInt
foreign import javascript unsafe "h$base_tcsetattr"
   c_tcsetattr :: CInt -> CInt -> Ptr CTermios -> IO CInt
foreign import javascript interruptible "h$base_utime"
   c_utime :: CString -> Ptr CUtimbuf -> IO CInt
foreign import javascript interruptible "h$base_waitpid"
   c_waitpid :: CPid -> Ptr CInt -> CInt -> IO CPid

foreign import javascript unsafe "(() => { return h$base_o_rdonly; })"   o_RDONLY   :: CInt
foreign import javascript unsafe "(() => { return h$base_o_wronly; })"   o_WRONLY   :: CInt
foreign import javascript unsafe "(() => { return h$base_o_rdwr; })"     o_RDWR     :: CInt
foreign import javascript unsafe "(() => { return h$base_o_append; })"   o_APPEND   :: CInt
foreign import javascript unsafe "(() => { return h$base_o_creat; })"    o_CREAT    :: CInt
foreign import javascript unsafe "(() => { return h$base_o_excl; })"     o_EXCL     :: CInt
foreign import javascript unsafe "(() => { return h$base_o_trunc; })"    o_TRUNC    :: CInt
foreign import javascript unsafe "(() => { return h$base_o_noctty; })"   o_NOCTTY   :: CInt
foreign import javascript unsafe "(() => { return h$base_o_nonblock; })" o_NONBLOCK :: CInt
foreign import javascript unsafe "(() => { return h$base_o_binary; })"   o_BINARY   :: CInt

foreign import javascript unsafe "h$base_c_s_isreg"  c_s_isreg  :: CMode -> CInt
foreign import javascript unsafe "h$base_c_s_ischr"  c_s_ischr  :: CMode -> CInt
foreign import javascript unsafe "h$base_c_s_isblk"  c_s_isblk  :: CMode -> CInt
foreign import javascript unsafe "h$base_c_s_isdir"  c_s_isdir  :: CMode -> CInt
foreign import javascript unsafe "h$base_c_s_isfifo" c_s_isfifo :: CMode -> CInt

s_isreg  :: CMode -> Bool
s_isreg cm = c_s_isreg cm /= 0
s_ischr  :: CMode -> Bool
s_ischr cm = c_s_ischr cm /= 0
s_isblk  :: CMode -> Bool
s_isblk cm = c_s_isblk cm /= 0
s_isdir  :: CMode -> Bool
s_isdir cm = c_s_isdir cm /= 0
s_isfifo :: CMode -> Bool
s_isfifo cm = c_s_isfifo cm /= 0

foreign import javascript unsafe "h$base_sizeof_stat" sizeof_stat :: Int
foreign import javascript unsafe "h$base_st_mtime"    st_mtime :: Ptr CStat -> IO CTime
foreign import javascript unsafe "h$base_st_size"     st_size :: Ptr CStat -> IO Int64
foreign import javascript unsafe "h$base_st_mode"     st_mode :: Ptr CStat -> IO CMode
foreign import javascript unsafe "h$base_st_dev"      st_dev :: Ptr CStat -> IO CDev
foreign import javascript unsafe "h$base_st_ino"      st_ino :: Ptr CStat -> IO CIno

foreign import javascript unsafe "(() => { return h$base_echo; })"            const_echo :: CInt
foreign import javascript unsafe "(() => { return h$base_tcsanow; })"         const_tcsanow :: CInt
foreign import javascript unsafe "(() => { return h$base_icanon; })"          const_icanon :: CInt
foreign import javascript unsafe "(() => { return h$base_vmin; })"            const_vmin   :: CInt
foreign import javascript unsafe "(() => { return h$base_vtime; })"           const_vtime  :: CInt
foreign import javascript unsafe "(() => { return h$base_sigttou; })"         const_sigttou :: CInt
foreign import javascript unsafe "(() => { return h$base_sig_block; })"       const_sig_block :: CInt
foreign import javascript unsafe "(() => { return h$base_sig_setmask; })"     const_sig_setmask :: CInt
foreign import javascript unsafe "(() => { return h$base_f_getfl; })"         const_f_getfl :: CInt
foreign import javascript unsafe "(() => { return h$base_f_setfl; })"         const_f_setfl :: CInt
foreign import javascript unsafe "(() => { return h$base_f_setfd; })"         const_f_setfd :: CInt
foreign import javascript unsafe "(() => { return h$base_fd_cloexec; })"      const_fd_cloexec :: CLong
foreign import javascript unsafe "(() => { return h$base_sizeof_termios; })"  sizeof_termios :: Int
foreign import javascript unsafe "(() => { return h$base_sizeof_sigset_t; })" sizeof_sigset_t :: Int
foreign import javascript unsafe "h$base_lflag"           c_lflag :: Ptr CTermios -> IO CTcflag
foreign import javascript unsafe "h$base_poke_lflag"      poke_c_lflag :: Ptr CTermios -> CTcflag -> IO ()
foreign import javascript unsafe "h$base_ptr_c_cc"        ptr_c_cc  :: Ptr CTermios -> IO (Ptr Word8)
s_issock :: CMode -> Bool
s_issock cmode = c_s_issock cmode /= 0
foreign import javascript unsafe "h$base_c_s_issock"          c_s_issock :: CMode -> CInt
foreign import javascript unsafe "(() => { return h$base_default_buffer_size; })" dEFAULT_BUFFER_SIZE :: Int
foreign import javascript unsafe "(() => { return h$base_SEEK_CUR; })"            sEEK_CUR :: CInt
foreign import javascript unsafe "(() => { return h$base_SEEK_SET; })"            sEEK_SET :: CInt
foreign import javascript unsafe "(() => { return h$base_SEEK_END; })"            sEEK_END :: CInt

-- fixme, unclear if these can be supported, remove?
foreign import javascript unsafe "h$base_c_fcntl_read"  c_fcntl_read  :: CInt -> CInt -> IO CInt
foreign import javascript unsafe "h$base_c_fcntl_write" c_fcntl_write :: CInt -> CInt -> CLong -> IO CInt
foreign import javascript unsafe "h$base_c_fcntl_lock"  c_fcntl_lock  :: CInt -> CInt -> Ptr CFLock -> IO CInt

#else

#if defined(mingw32_HOST_OS)
-- See Note [Windows types]
foreign import capi unsafe "HsBase.h _read"
   c_read :: CInt -> Ptr Word8 -> CUInt -> IO CInt

-- See Note [Windows types]
foreign import capi safe "HsBase.h _read"
   c_safe_read :: CInt -> Ptr Word8 -> CUInt -> IO CInt

foreign import ccall unsafe "HsBase.h _umask"
   c_umask :: CMode -> IO CMode

-- See Note [Windows types]
foreign import capi unsafe "HsBase.h _write"
   c_write :: CInt -> Ptr Word8 -> CUInt -> IO CInt

-- See Note [Windows types]
foreign import capi safe "HsBase.h _write"
   c_safe_write :: CInt -> Ptr Word8 -> CUInt -> IO CInt

foreign import ccall unsafe "HsBase.h _pipe"
   c_pipe :: Ptr CInt -> IO CInt

foreign import capi unsafe "HsBase.h _lseeki64"
   c_lseek :: CInt -> Int64 -> CInt -> IO Int64

foreign import capi unsafe "HsBase.h _access"
   c_access :: CString -> CInt -> IO CInt

#if !defined(HAVE_CHMOD)
c_chmod :: CString -> CMode -> IO CInt
c_chmod _ _ = ioError (ioeSetLocation unsupportedOperation "_chmod")
#else
foreign import ccall unsafe "HsBase.h _chmod"
   c_chmod :: CString -> CMode -> IO CInt
#endif

foreign import capi unsafe "HsBase.h _close"
   c_close :: CInt -> IO CInt

foreign import capi unsafe "HsBase.h _creat"
   c_creat :: CString -> CMode -> IO CInt

#if !defined(HAVE_DUP)
c_dup :: CInt -> IO CInt
c_dup _ = ioError (ioeSetLocation unsupportedOperation "_dup")

c_dup2 :: CInt -> CInt -> IO CInt
c_dup2 _ _ = ioError (ioeSetLocation unsupportedOperation "_dup2")
#else
foreign import ccall unsafe "HsBase.h _dup"
   c_dup :: CInt -> IO CInt

foreign import ccall unsafe "HsBase.h _dup2"
   c_dup2 :: CInt -> CInt -> IO CInt
#endif

foreign import capi unsafe "HsBase.h _isatty"
   c_isatty :: CInt -> IO CInt

foreign import capi unsafe "HsBase.h _unlink"
   c_unlink :: CString -> IO CInt

foreign import capi unsafe "HsBase.h _utime"
   c_utime :: CString -> Ptr CUtimbuf -> IO CInt

foreign import capi unsafe "HsBase.h _getpid"
   c_getpid :: IO CPid
#else
-- We use CAPI as on some OSs (eg. Linux) this is wrapped by a macro
-- which redirects to the 64-bit-off_t versions when large file
-- support is enabled.

-- See Note [Windows types]
foreign import capi unsafe "HsBase.h read"
   c_read :: CInt -> Ptr Word8 -> CSize -> IO CSsize

-- See Note [Windows types]
foreign import capi safe "HsBase.h read"
   c_safe_read :: CInt -> Ptr Word8 -> CSize -> IO CSsize

foreign import ccall unsafe "HsBase.h umask"
   c_umask :: CMode -> IO CMode

-- See Note [Windows types]
foreign import capi unsafe "HsBase.h write"
   c_write :: CInt -> Ptr Word8 -> CSize -> IO CSsize

-- See Note [Windows types]
foreign import capi safe "HsBase.h write"
   c_safe_write :: CInt -> Ptr Word8 -> CSize -> IO CSsize

#if !defined(HAVE_PIPE)
c_pipe :: Ptr CInt -> IO CInt
c_pipe _ = ioError (ioeSetLocation unsupportedOperation "pipe")
#else
foreign import ccall unsafe "HsBase.h pipe"
   c_pipe :: Ptr CInt -> IO CInt
#endif

foreign import capi unsafe "unistd.h lseek"
   c_lseek :: CInt -> COff -> CInt -> IO COff

foreign import ccall unsafe "HsBase.h access"
   c_access :: CString -> CInt -> IO CInt

#if !defined(HAVE_CHMOD)
c_chmod :: CString -> CMode -> IO CInt
c_chmod _ _ = ioError (ioeSetLocation unsupportedOperation "chmod")
#else
foreign import ccall unsafe "HsBase.h chmod"
   c_chmod :: CString -> CMode -> IO CInt
#endif

foreign import ccall unsafe "HsBase.h close"
   c_close :: CInt -> IO CInt

foreign import ccall unsafe "HsBase.h creat"
   c_creat :: CString -> CMode -> IO CInt

#if !defined(HAVE_DUP)
c_dup :: CInt -> IO CInt
c_dup _ = ioError (ioeSetLocation unsupportedOperation "dup")

c_dup2 :: CInt -> CInt -> IO CInt
c_dup2 _ _ = ioError (ioeSetLocation unsupportedOperation "dup2")
#else
foreign import ccall unsafe "HsBase.h dup"
   c_dup :: CInt -> IO CInt

foreign import ccall unsafe "HsBase.h dup2"
   c_dup2 :: CInt -> CInt -> IO CInt
#endif

foreign import ccall unsafe "HsBase.h isatty"
   c_isatty :: CInt -> IO CInt

foreign import ccall unsafe "HsBase.h unlink"
   c_unlink :: CString -> IO CInt

foreign import capi unsafe "HsBase.h utime"
   c_utime :: CString -> Ptr CUtimbuf -> IO CInt

#if !defined(HAVE_GETPID)
c_getpid :: IO CPid
c_getpid = pure 1
#else
foreign import ccall unsafe "HsBase.h getpid"
   c_getpid :: IO CPid
#endif
#endif

#if !defined(javascript_HOST_ARCH)
foreign import ccall unsafe "HsBase.h __hscore_stat"
   c_stat :: CFilePath -> Ptr CStat -> IO CInt

foreign import ccall unsafe "HsBase.h __hscore_ftruncate"
   c_ftruncate :: CInt -> COff -> IO CInt
#endif

#if !defined(mingw32_HOST_OS) && !defined(javascript_HOST_ARCH)
foreign import capi unsafe "HsBase.h fcntl"
   c_fcntl_read  :: CInt -> CInt -> IO CInt

foreign import capi unsafe "HsBase.h fcntl"
   c_fcntl_write :: CInt -> CInt -> CLong -> IO CInt

foreign import capi unsafe "HsBase.h fcntl"
   c_fcntl_lock  :: CInt -> CInt -> Ptr CFLock -> IO CInt

#if !defined(HAVE_FORK)
c_fork :: IO CPid
c_fork = ioError (ioeSetLocation unsupportedOperation "fork")
#else
foreign import ccall unsafe "HsBase.h fork"
   c_fork :: IO CPid
#endif

foreign import ccall unsafe "HsBase.h link"
   c_link :: CString -> CString -> IO CInt

#if !defined(HAVE_MKFIFO)
c_mkfifo :: CString -> CMode -> IO CInt
c_mkfifo _ _ = ioError (ioeSetLocation unsupportedOperation "mkfifo")
#else
-- capi is required at least on Android
foreign import capi unsafe "HsBase.h mkfifo"
   c_mkfifo :: CString -> CMode -> IO CInt
#endif

#if HAVE_SIGNAL_H
foreign import capi unsafe "signal.h sigemptyset"
   c_sigemptyset :: Ptr CSigset -> IO CInt

foreign import capi unsafe "signal.h sigaddset"
   c_sigaddset :: Ptr CSigset -> CInt -> IO CInt

foreign import capi unsafe "signal.h sigprocmask"
   c_sigprocmask :: CInt -> Ptr CSigset -> Ptr CSigset -> IO CInt
#endif

#if !defined(HAVE_TERMIOS_H)

c_tcgetattr :: CInt -> Ptr CTermios -> IO CInt
c_tcgetattr _ _ = ioError (ioeSetLocation unsupportedOperation "tcgetattr")

c_tcsetattr :: CInt -> CInt -> Ptr CTermios -> IO CInt
c_tcsetattr _ _ _ = ioError (ioeSetLocation unsupportedOperation "tcsetattr")

#else

-- capi is required at least on Android
foreign import capi unsafe "HsBase.h tcgetattr"
   c_tcgetattr :: CInt -> Ptr CTermios -> IO CInt

-- capi is required at least on Android
foreign import capi unsafe "HsBase.h tcsetattr"
   c_tcsetattr :: CInt -> CInt -> Ptr CTermios -> IO CInt

#endif

#if defined(HAVE_GETPID)
foreign import ccall unsafe "HsBase.h waitpid"
   c_waitpid :: CPid -> Ptr CInt -> CInt -> IO CPid
#else
c_waitpid :: CPid -> Ptr CInt -> CInt -> IO CPid
c_waitpid _ _ _ = ioError (ioeSetLocation unsupportedOperation "waitpid")
#endif

#endif

#if !defined(javascript_HOST_ARCH)
-- POSIX flags only:
foreign import ccall unsafe "HsBase.h __hscore_o_rdonly" o_RDONLY :: CInt
foreign import ccall unsafe "HsBase.h __hscore_o_wronly" o_WRONLY :: CInt
foreign import ccall unsafe "HsBase.h __hscore_o_rdwr"   o_RDWR   :: CInt
foreign import ccall unsafe "HsBase.h __hscore_o_append" o_APPEND :: CInt
foreign import ccall unsafe "HsBase.h __hscore_o_creat"  o_CREAT  :: CInt
foreign import ccall unsafe "HsBase.h __hscore_o_excl"   o_EXCL   :: CInt
foreign import ccall unsafe "HsBase.h __hscore_o_trunc"  o_TRUNC  :: CInt

-- non-POSIX flags.
foreign import ccall unsafe "HsBase.h __hscore_o_noctty"   o_NOCTTY   :: CInt
foreign import ccall unsafe "HsBase.h __hscore_o_nonblock" o_NONBLOCK :: CInt
foreign import ccall unsafe "HsBase.h __hscore_o_binary"   o_BINARY   :: CInt

foreign import capi unsafe "sys/stat.h S_ISREG"  c_s_isreg  :: CMode -> CInt
foreign import capi unsafe "sys/stat.h S_ISCHR"  c_s_ischr  :: CMode -> CInt
foreign import capi unsafe "sys/stat.h S_ISBLK"  c_s_isblk  :: CMode -> CInt
foreign import capi unsafe "sys/stat.h S_ISDIR"  c_s_isdir  :: CMode -> CInt
foreign import capi unsafe "sys/stat.h S_ISFIFO" c_s_isfifo :: CMode -> CInt

s_isreg  :: CMode -> Bool
s_isreg :: CMode -> Bool
s_isreg CMode
cm = CMode -> CInt
c_s_isreg CMode
cm CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0
s_ischr  :: CMode -> Bool
s_ischr :: CMode -> Bool
s_ischr CMode
cm = CMode -> CInt
c_s_ischr CMode
cm CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0
s_isblk  :: CMode -> Bool
s_isblk :: CMode -> Bool
s_isblk CMode
cm = CMode -> CInt
c_s_isblk CMode
cm CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0
s_isdir  :: CMode -> Bool
s_isdir :: CMode -> Bool
s_isdir CMode
cm = CMode -> CInt
c_s_isdir CMode
cm CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0
s_isfifo :: CMode -> Bool
s_isfifo :: CMode -> Bool
s_isfifo CMode
cm = CMode -> CInt
c_s_isfifo CMode
cm CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0

foreign import ccall unsafe "HsBase.h __hscore_sizeof_stat" sizeof_stat :: Int
foreign import ccall unsafe "HsBase.h __hscore_st_mtime" st_mtime :: Ptr CStat -> IO CTime
#if defined(mingw32_HOST_OS)
foreign import ccall unsafe "HsBase.h __hscore_st_size" st_size :: Ptr CStat -> IO Int64
#else
foreign import ccall unsafe "HsBase.h __hscore_st_size" st_size :: Ptr CStat -> IO COff
#endif
foreign import ccall unsafe "HsBase.h __hscore_st_mode" st_mode :: Ptr CStat -> IO CMode
foreign import ccall unsafe "HsBase.h __hscore_st_dev" st_dev :: Ptr CStat -> IO CDev
foreign import ccall unsafe "HsBase.h __hscore_st_ino" st_ino :: Ptr CStat -> IO CIno

foreign import ccall unsafe "HsBase.h __hscore_echo"         const_echo :: CInt
foreign import ccall unsafe "HsBase.h __hscore_tcsanow"      const_tcsanow :: CInt
foreign import ccall unsafe "HsBase.h __hscore_icanon"       const_icanon :: CInt
foreign import ccall unsafe "HsBase.h __hscore_vmin"         const_vmin   :: CInt
foreign import ccall unsafe "HsBase.h __hscore_vtime"        const_vtime  :: CInt
foreign import ccall unsafe "HsBase.h __hscore_sigttou"      const_sigttou :: CInt
foreign import ccall unsafe "HsBase.h __hscore_sig_block"    const_sig_block :: CInt
foreign import ccall unsafe "HsBase.h __hscore_sig_setmask"  const_sig_setmask :: CInt
foreign import ccall unsafe "HsBase.h __hscore_f_getfl"      const_f_getfl :: CInt
foreign import ccall unsafe "HsBase.h __hscore_f_setfl"      const_f_setfl :: CInt
foreign import ccall unsafe "HsBase.h __hscore_f_setfd"      const_f_setfd :: CInt
foreign import ccall unsafe "HsBase.h __hscore_fd_cloexec"   const_fd_cloexec :: CLong

#if defined(HTYPE_TCFLAG_T)
foreign import ccall unsafe "HsBase.h __hscore_sizeof_termios"  sizeof_termios :: Int
foreign import ccall unsafe "HsBase.h __hscore_sizeof_sigset_t" sizeof_sigset_t :: Int

foreign import ccall unsafe "HsBase.h __hscore_lflag" c_lflag :: Ptr CTermios -> IO CTcflag
foreign import ccall unsafe "HsBase.h __hscore_poke_lflag" poke_c_lflag :: Ptr CTermios -> CTcflag -> IO ()
foreign import ccall unsafe "HsBase.h __hscore_ptr_c_cc" ptr_c_cc  :: Ptr CTermios -> IO (Ptr Word8)
#endif

s_issock :: CMode -> Bool
#if !defined(mingw32_HOST_OS)
s_issock :: CMode -> Bool
s_issock CMode
cmode = CMode -> CInt
c_s_issock CMode
cmode CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0
foreign import capi unsafe "sys/stat.h S_ISSOCK" c_s_issock :: CMode -> CInt
#else
s_issock _ = False
#endif

foreign import ccall unsafe "__hscore_bufsiz"  dEFAULT_BUFFER_SIZE :: Int
foreign import capi  unsafe "stdio.h value SEEK_CUR" sEEK_CUR :: CInt
foreign import capi  unsafe "stdio.h value SEEK_SET" sEEK_SET :: CInt
foreign import capi  unsafe "stdio.h value SEEK_END" sEEK_END :: CInt
#endif
#endif

{-
Note [Windows types]
~~~~~~~~~~~~~~~~~~~~

Windows' _read and _write have types that differ from POSIX. They take an
unsigned int for length and return a signed int where POSIX uses size_t and
ssize_t. Those are different on x86_64 and equivalent on x86. We import them
with the types in Microsoft's documentation which means that c_read,
c_safe_read, c_write and c_safe_write have different Haskell types depending on
the OS.
-}