{-# LANGUAGE Trustworthy #-}{-# LANGUAGE CPP, NoImplicitPrelude, CApiFFI #-}{-# OPTIONS_HADDOCK hide #-}------------------------------------------------------------------------------- |-- 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)-------------------------------------------------------------------------------moduleSystem.Posix.Internalswhere#include "HsBaseConfig.h"
importSystem.Posix.Types importForeign importForeign.C -- import Data.BitsimportData.Maybe #if !defined(HTYPE_TCFLAG_T)
importSystem.IO.Error#endif
importGHC.Base importGHC.Num importGHC.Real importGHC.IO importGHC.IO.IOMode importGHC.IO.Exception importGHC.IO.Device #if !defined(mingw32_HOST_OS)
import{-# SOURCE#-}GHC.IO.Encoding (getFileSystemEncoding )importqualifiedGHC.Foreign asGHC#endif
-- ----------------------------------------------------------------------------- Debugging the base packageputs::String ->IO()puts s =withCAStringLen (s ++ "\n")$ \(p ,len )->do-- In reality should be withCString, but assume ASCII to avoid loop-- if this is called by GHC.Foreign_<-c_write 1(castPtr p )(fromIntegral len )return ()-- ----------------------------------------------------------------------------- Typesdata{-# 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 typeFD =CInt -- ----------------------------------------------------------------------------- stat()-related stufffdFileSize::FD ->IOIntegerfdFileSize fd =allocaBytes sizeof_stat $ \p_stat ->dothrowErrnoIfMinus1Retry_ "fileSize"$ c_fstat fd p_stat c_mode <-st_mode p_stat ::IOCMode ifnot(s_isreg c_mode )thenreturn (-1)elsedoc_size <-st_size p_stat return (fromIntegral c_size )fileType::FilePath ->IOIODeviceType fileType file =allocaBytes sizeof_stat $ \p_stat ->dowithFilePath file $ \p_file ->dothrowErrnoIfMinus1Retry_ "fileType"$ c_stat p_file p_stat statGetType 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 fd =allocaBytes sizeof_stat $ \p_stat ->dothrowErrnoIfMinus1Retry_ "fdType"$ c_fstat fd p_stat ty <-statGetType p_stat dev <-st_dev p_stat ino <-st_ino p_stat return (ty ,dev ,ino )fdType::FD ->IOIODeviceType fdType fd =do(ty ,_,_)<-fdStat fd ;return ty statGetType::Ptr CStat ->IOIODeviceType statGetType p_stat =doc_mode <-st_mode p_stat ::IOCMode case()of_|s_isdir c_mode ->return Directory |s_isfifo c_mode ||s_issock c_mode ||s_ischr c_mode ->return Stream |s_isreg c_mode ->return RegularFile -- Q: map char devices to RawDevice too?|s_isblk c_mode ->return RawDevice |otherwise ->ioError ioe_unknownfiletype ioe_unknownfiletype::IOException ioe_unknownfiletype =IOError Nothing UnsupportedOperation "fdType""unknown file type"Nothing Nothing fdGetMode::FD ->IOIOMode #if defined(mingw32_HOST_OS)
fdGetMode_=do-- We don't have a way of finding out which flags are set on FDs-- on Windows, so make a handle that thinks that anything goes.letflags=o_RDWR#else
fdGetMode fd =doflags <-throwErrnoIfMinus1Retry "fdGetMode"(c_fcntl_read fd const_f_getfl )#endif
letwH =(flags .&. o_WRONLY )/=0aH =(flags .&. o_APPEND )/=0rwH =(flags .&. o_RDWR )/=0mode |wH &&aH =AppendMode |wH =WriteMode |rwH =ReadWriteMode |otherwise =ReadMode return mode #if defined(mingw32_HOST_OS)
withFilePath::FilePath->(CWString->IOa)->IOawithFilePath=withCWStringnewFilePath::FilePath->IOCWStringnewFilePath=newCWStringpeekFilePath::CWString->IOFilePathpeekFilePath=peekCWString#else
withFilePath::FilePath ->(CString ->IOa )->IOa newFilePath::FilePath ->IOCString peekFilePath::CString ->IOFilePath peekFilePathLen::CStringLen ->IOFilePath withFilePath fp f =getFileSystemEncoding >>= \enc ->GHC.withCString enc fp f newFilePath fp =getFileSystemEncoding >>= \enc ->GHC.newCString enc fp peekFilePath fp =getFileSystemEncoding >>= \enc ->GHC.peekCString enc fp peekFilePathLen fp =getFileSystemEncoding >>= \enc ->GHC.peekCStringLen enc fp #endif
-- ----------------------------------------------------------------------------- Terminal-related stuff#if defined(HTYPE_TCFLAG_T)
setEcho::FD ->Bool->IO()setEcho fd on =dotcSetAttr fd $ \p_tios ->dolflag <-c_lflag p_tios ::IOCTcflag letnew_lflag |on =lflag .|. fromIntegral const_echo |otherwise =lflag .&. complement (fromIntegral const_echo )poke_c_lflag p_tios (new_lflag ::CTcflag )getEcho::FD ->IOBoolgetEcho fd =dotcSetAttr fd $ \p_tios ->dolflag <-c_lflag p_tios ::IOCTcflag return ((lflag .&. fromIntegral const_echo )/=0)setCooked::FD ->Bool->IO()setCooked fd cooked =tcSetAttr fd $ \p_tios ->do-- turn on/off ICANONlflag <-c_lflag p_tios ::IOCTcflag letnew_lflag |cooked =lflag .|. (fromIntegral const_icanon )|otherwise =lflag .&. complement (fromIntegral const_icanon )poke_c_lflag p_tios (new_lflag ::CTcflag )-- set VMIN & VTIME to 1/0 respectivelywhen (notcooked )$ doc_cc <-ptr_c_cc p_tios letvmin =(c_cc `plusPtr `(fromIntegral const_vmin ))::Ptr Word8 vtime =(c_cc `plusPtr `(fromIntegral const_vtime ))::Ptr Word8 poke vmin 1poke vtime 0tcSetAttr::FD ->(Ptr CTermios ->IOa )->IOa tcSetAttr fd fun =doallocaBytes sizeof_termios $ \p_tios ->dothrowErrnoIfMinus1Retry_ "tcSetAttr"(c_tcgetattr fd p_tios )-- Save a copy of termios, if this is a standard file descriptor.-- These terminal settings are restored in hs_exit().when (fd <=2)$ dop <-get_saved_termios fd when (p ==nullPtr )$ dosaved_tios <-mallocBytes sizeof_termios copyBytes saved_tios p_tios sizeof_termios set_saved_termios fd 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.allocaBytes sizeof_sigset_t $ \p_sigset ->doallocaBytes sizeof_sigset_t $ \p_old_sigset ->dothrowErrnoIfMinus1_ "sigemptyset"$ c_sigemptyset p_sigset throwErrnoIfMinus1_ "sigaddset"$ c_sigaddset p_sigset const_sigttou throwErrnoIfMinus1_ "sigprocmask"$ c_sigprocmask const_sig_block p_sigset p_old_sigset r <-fun p_tios -- do the businessthrowErrnoIfMinus1Retry_ "tcSetAttr"$ c_tcsetattr fd const_tcsanow p_tios throwErrnoIfMinus1_ "sigprocmask"$ c_sigprocmask const_sig_setmask p_old_sigset nullPtr return r foreignimportccallunsafe"HsBase.h __hscore_get_saved_termios"get_saved_termios::CInt ->IO(Ptr CTermios )foreignimportccallunsafe"HsBase.h __hscore_set_saved_termios"set_saved_termios::CInt ->(Ptr CTermios )->IO()#else
-- '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()setCookedfdcooked=dox<-set_console_bufferingfd(ifcookedthen1else0)if(x/=0)thenioError(ioe_unk_error"setCooked""failed to set buffering")elsereturn()ioe_unk_error::String->String->IOExceptionioe_unk_errorlocmsg=ioeSetErrorString(mkIOErrorOtherErrorlocNothingNothing)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()setEchofdon=dox<-set_console_echofd(ifonthen1else0)if(x/=0)thenioError(ioe_unk_error"setEcho""failed to set echoing")elsereturn()getEcho::FD->IOBoolgetEchofd=dor<-get_console_echofdif(r==(-1))thenioError(ioe_unk_error"getEcho""failed to get echoing")elsereturn(r==1)foreignimportccallunsafe"consUtils.h set_console_buffering__"set_console_buffering::CInt->CInt->IOCIntforeignimportccallunsafe"consUtils.h set_console_echo__"set_console_echo::CInt->CInt->IOCIntforeignimportccallunsafe"consUtils.h get_console_echo__"get_console_echo::CInt->IOCIntforeignimportccallunsafe"consUtils.h is_console__"is_console::CInt->IOCInt#endif
-- ----------------------------------------------------------------------------- Turning on non-blocking for a file descriptorsetNonBlockingFD::FD ->Bool->IO()#if !defined(mingw32_HOST_OS)
setNonBlockingFD fd set =doflags <-throwErrnoIfMinus1Retry "setNonBlockingFD"(c_fcntl_read fd const_f_getfl )letflags' |set =flags .|. o_NONBLOCK |otherwise =flags .&. complement o_NONBLOCK when (flags /=flags' )$ 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._<-c_fcntl_write fd const_f_setfl (fromIntegral flags' )return ()#else
-- bogus defns for win32setNonBlockingFD__=return()#endif
-- ------------------------------------------------------------------------------- Set close-on-exec for a file descriptor#if !defined(mingw32_HOST_OS)
setCloseOnExec::FD ->IO()setCloseOnExec fd =dothrowErrnoIfMinus1_ "setCloseOnExec"$ c_fcntl_write fd const_f_setfd const_fd_cloexec #endif
-- ------------------------------------------------------------------------------- foreign imports#if !defined(mingw32_HOST_OS)
typeCFilePath =CString #else
typeCFilePath=CWString#endif
foreignimportccallunsafe"HsBase.h __hscore_open"c_open::CFilePath ->CInt ->CMode ->IOCInt foreignimportccallsafe"HsBase.h __hscore_open"c_safe_open::CFilePath ->CInt ->CMode ->IOCInt foreignimportccallunsafe"HsBase.h __hscore_fstat"c_fstat::CInt ->Ptr CStat ->IOCInt foreignimportccallunsafe"HsBase.h __hscore_lstat"lstat::CFilePath ->Ptr CStat ->IOCInt {- Note: Win32 POSIX functions
Functions that are not part of the POSIX standards were
at some point deprecated by Microsoft. This deprecation
was performed by renaming the functions according to the
C++ ABI Section 17.6.4.3.2b. This was done to free up the
namespace of normal Windows programs since Windows isn't
POSIX compliant anyway.
These were working before since the RTS was re-exporting
these symbols under the undeprecated names. This is no longer
being done. See #11223
See https://msdn.microsoft.com/en-us/library/ms235384.aspx
for more.
However since we can't hope to get people to support Windows
packages we should support the deprecated names. See #12497
-}foreignimportcapiunsafe"unistd.h lseek"c_lseek::CInt ->COff ->CInt ->IOCOff foreignimportccallunsafe"HsBase.h access"c_access::CString ->CInt ->IOCInt foreignimportccallunsafe"HsBase.h chmod"c_chmod::CString ->CMode ->IOCInt foreignimportccallunsafe"HsBase.h close"c_close::CInt ->IOCInt foreignimportccallunsafe"HsBase.h creat"c_creat::CString ->CMode ->IOCInt foreignimportccallunsafe"HsBase.h dup"c_dup::CInt ->IOCInt foreignimportccallunsafe"HsBase.h dup2"c_dup2::CInt ->CInt ->IOCInt foreignimportccallunsafe"HsBase.h isatty"c_isatty::CInt ->IOCInt #if defined(mingw32_HOST_OS)
-- See Note: Windows typesforeignimportcapiunsafe"HsBase.h _read"c_read::CInt->PtrWord8->CUInt->IOCInt-- See Note: Windows typesforeignimportcapisafe"HsBase.h _read"c_safe_read::CInt->PtrWord8->CUInt->IOCIntforeignimportccallunsafe"HsBase.h _umask"c_umask::CMode->IOCMode-- See Note: Windows typesforeignimportcapiunsafe"HsBase.h _write"c_write::CInt->PtrWord8->CUInt->IOCInt-- See Note: Windows typesforeignimportcapisafe"HsBase.h _write"c_safe_write::CInt->PtrWord8->CUInt->IOCIntforeignimportccallunsafe"HsBase.h _pipe"c_pipe::PtrCInt->IOCInt#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 typesforeignimportcapiunsafe"HsBase.h read"c_read::CInt ->Ptr Word8 ->CSize ->IOCSsize -- See Note: Windows typesforeignimportcapisafe"HsBase.h read"c_safe_read::CInt ->Ptr Word8 ->CSize ->IOCSsize foreignimportccallunsafe"HsBase.h umask"c_umask::CMode ->IOCMode -- See Note: Windows typesforeignimportcapiunsafe"HsBase.h write"c_write::CInt ->Ptr Word8 ->CSize ->IOCSsize -- See Note: Windows typesforeignimportcapisafe"HsBase.h write"c_safe_write::CInt ->Ptr Word8 ->CSize ->IOCSsize foreignimportccallunsafe"HsBase.h pipe"c_pipe::Ptr CInt ->IOCInt #endif
foreignimportccallunsafe"HsBase.h unlink"c_unlink::CString ->IOCInt foreignimportcapiunsafe"HsBase.h utime"c_utime::CString ->Ptr CUtimbuf ->IOCInt foreignimportccallunsafe"HsBase.h getpid"c_getpid::IOCPid foreignimportccallunsafe"HsBase.h __hscore_stat"c_stat::CFilePath ->Ptr CStat ->IOCInt foreignimportccallunsafe"HsBase.h __hscore_ftruncate"c_ftruncate::CInt ->COff ->IOCInt #if !defined(mingw32_HOST_OS)
foreignimportcapiunsafe"HsBase.h fcntl"c_fcntl_read::CInt ->CInt ->IOCInt foreignimportcapiunsafe"HsBase.h fcntl"c_fcntl_write::CInt ->CInt ->CLong ->IOCInt foreignimportcapiunsafe"HsBase.h fcntl"c_fcntl_lock::CInt ->CInt ->Ptr CFLock ->IOCInt foreignimportccallunsafe"HsBase.h fork"c_fork::IOCPid foreignimportccallunsafe"HsBase.h link"c_link::CString ->CString ->IOCInt -- capi is required at least on Androidforeignimportcapiunsafe"HsBase.h mkfifo"c_mkfifo::CString ->CMode ->IOCInt foreignimportcapiunsafe"signal.h sigemptyset"c_sigemptyset::Ptr CSigset ->IOCInt foreignimportcapiunsafe"signal.h sigaddset"c_sigaddset::Ptr CSigset ->CInt ->IOCInt foreignimportcapiunsafe"signal.h sigprocmask"c_sigprocmask::CInt ->Ptr CSigset ->Ptr CSigset ->IOCInt -- capi is required at least on Androidforeignimportcapiunsafe"HsBase.h tcgetattr"c_tcgetattr::CInt ->Ptr CTermios ->IOCInt -- capi is required at least on Androidforeignimportcapiunsafe"HsBase.h tcsetattr"c_tcsetattr::CInt ->CInt ->Ptr CTermios ->IOCInt foreignimportccallunsafe"HsBase.h waitpid"c_waitpid::CPid ->Ptr CInt ->CInt ->IOCPid #endif
-- POSIX flags only:foreignimportccallunsafe"HsBase.h __hscore_o_rdonly"o_RDONLY::CInt foreignimportccallunsafe"HsBase.h __hscore_o_wronly"o_WRONLY::CInt foreignimportccallunsafe"HsBase.h __hscore_o_rdwr"o_RDWR::CInt foreignimportccallunsafe"HsBase.h __hscore_o_append"o_APPEND::CInt foreignimportccallunsafe"HsBase.h __hscore_o_creat"o_CREAT::CInt foreignimportccallunsafe"HsBase.h __hscore_o_excl"o_EXCL::CInt foreignimportccallunsafe"HsBase.h __hscore_o_trunc"o_TRUNC::CInt -- non-POSIX flags.foreignimportccallunsafe"HsBase.h __hscore_o_noctty"o_NOCTTY::CInt foreignimportccallunsafe"HsBase.h __hscore_o_nonblock"o_NONBLOCK::CInt foreignimportccallunsafe"HsBase.h __hscore_o_binary"o_BINARY::CInt foreignimportcapiunsafe"sys/stat.h S_ISREG"c_s_isreg::CMode ->CInt foreignimportcapiunsafe"sys/stat.h S_ISCHR"c_s_ischr::CMode ->CInt foreignimportcapiunsafe"sys/stat.h S_ISBLK"c_s_isblk::CMode ->CInt foreignimportcapiunsafe"sys/stat.h S_ISDIR"c_s_isdir::CMode ->CInt foreignimportcapiunsafe"sys/stat.h S_ISFIFO"c_s_isfifo::CMode ->CInt s_isreg::CMode ->Bools_isreg cm =c_s_isreg cm /=0s_ischr::CMode ->Bools_ischr cm =c_s_ischr cm /=0s_isblk::CMode ->Bools_isblk cm =c_s_isblk cm /=0s_isdir::CMode ->Bools_isdir cm =c_s_isdir cm /=0s_isfifo::CMode ->Bools_isfifo cm =c_s_isfifo cm /=0foreignimportccallunsafe"HsBase.h __hscore_sizeof_stat"sizeof_stat::Intforeignimportccallunsafe"HsBase.h __hscore_st_mtime"st_mtime::Ptr CStat ->IOCTime #if defined(mingw32_HOST_OS)
foreignimportccallunsafe"HsBase.h __hscore_st_size"st_size::PtrCStat->IOInt64#else
foreignimportccallunsafe"HsBase.h __hscore_st_size"st_size::Ptr CStat ->IOCOff #endif
foreignimportccallunsafe"HsBase.h __hscore_st_mode"st_mode::Ptr CStat ->IOCMode foreignimportccallunsafe"HsBase.h __hscore_st_dev"st_dev::Ptr CStat ->IOCDev foreignimportccallunsafe"HsBase.h __hscore_st_ino"st_ino::Ptr CStat ->IOCIno foreignimportccallunsafe"HsBase.h __hscore_echo"const_echo::CInt foreignimportccallunsafe"HsBase.h __hscore_tcsanow"const_tcsanow::CInt foreignimportccallunsafe"HsBase.h __hscore_icanon"const_icanon::CInt foreignimportccallunsafe"HsBase.h __hscore_vmin"const_vmin::CInt foreignimportccallunsafe"HsBase.h __hscore_vtime"const_vtime::CInt foreignimportccallunsafe"HsBase.h __hscore_sigttou"const_sigttou::CInt foreignimportccallunsafe"HsBase.h __hscore_sig_block"const_sig_block::CInt foreignimportccallunsafe"HsBase.h __hscore_sig_setmask"const_sig_setmask::CInt foreignimportccallunsafe"HsBase.h __hscore_f_getfl"const_f_getfl::CInt foreignimportccallunsafe"HsBase.h __hscore_f_setfl"const_f_setfl::CInt foreignimportccallunsafe"HsBase.h __hscore_f_setfd"const_f_setfd::CInt foreignimportccallunsafe"HsBase.h __hscore_fd_cloexec"const_fd_cloexec::CLong #if defined(HTYPE_TCFLAG_T)
foreignimportccallunsafe"HsBase.h __hscore_sizeof_termios"sizeof_termios::Intforeignimportccallunsafe"HsBase.h __hscore_sizeof_sigset_t"sizeof_sigset_t::Intforeignimportccallunsafe"HsBase.h __hscore_lflag"c_lflag::Ptr CTermios ->IOCTcflag foreignimportccallunsafe"HsBase.h __hscore_poke_lflag"poke_c_lflag::Ptr CTermios ->CTcflag ->IO()foreignimportccallunsafe"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 =c_s_issock cmode /=0foreignimportcapiunsafe"sys/stat.h S_ISSOCK"c_s_issock::CMode ->CInt #else
s_issock_=False#endif
foreignimportccallunsafe"__hscore_bufsiz"dEFAULT_BUFFER_SIZE::Intforeignimportcapiunsafe"stdio.h value SEEK_CUR"sEEK_CUR::CInt foreignimportcapiunsafe"stdio.h value SEEK_SET"sEEK_SET::CInt foreignimportcapiunsafe"stdio.h value SEEK_END"sEEK_END::CInt {-
Note: Windows types
Windows' _read and _write have types that differ from POSIX. They take an
unsigned int for lengh 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.
-}

AltStyle によって変換されたページ (->オリジナル) /