{-# LINE 1 "System/Posix/IO/Common.hsc" #-}{-# LANGUAGE CApiFFI #-}{-# LANGUAGE NondecreasingIndentation #-}{-# LANGUAGE RecordWildCards #-}{-# LANGUAGE Safe #-}------------------------------------------------------------------------------- |-- Module : System.Posix.IO.Common-- Copyright : (c) The University of Glasgow 2002-- License : BSD-style (see the file libraries/base/LICENSE)---- Maintainer : libraries@haskell.org-- Stability : provisional-- Portability : non-portable (requires POSIX)-------------------------------------------------------------------------------moduleSystem.Posix.IO.Common(-- * Input \/ Output-- ** Standard file descriptorsstdInput ,stdOutput ,stdError ,-- ** Opening and closing filesOpenMode (..),OpenFileFlags (..),defaultFileFlags ,openat_ ,closeFd ,-- ** Reading\/writing data-- |Programmers using the 'fdRead' and 'fdWrite' API should be aware that-- EAGAIN exceptions may occur for non-blocking IO!fdReadBuf ,fdWriteBuf ,-- ** SeekingfdSeek ,-- ** File optionsFdOption (..),queryFdOption ,setFdOption ,-- ** LockingFileLock ,LockRequest (..),getLock ,setLock ,waitToSetLock ,-- ** PipescreatePipe ,-- ** Duplicating file descriptorsdup ,dupTo ,-- ** Converting file descriptors to\/from HandleshandleToFd ,fdToHandle ,)whereimportSystem.IOimportSystem.IO.ErrorimportSystem.Posix.TypesimportqualifiedSystem.Posix.InternalsasBaseimportForeignimportForeign.CimportGHC.IO.Handle.InternalsimportGHC.IO.Handle.TypesimportqualifiedGHC.IO.FDasFDimportqualifiedGHC.IO.Handle.FDasFDimportGHC.IO.ExceptionimportData.Typeable(cast){-# LINE 81 "System/Posix/IO/Common.hsc" #-}{-# LINE 92 "System/Posix/IO/Common.hsc" #-}-- ------------------------------------------------------------------------------- Pipes-- |The 'createPipe' function creates a pair of connected file-- descriptors. The first component is the fd to read from, the second-- is the write end. Although pipes may be bidirectional, this-- behaviour is not portable and programmers should use two separate-- pipes for this purpose. May throw an exception if this is an-- invalid descriptor.createPipe ::IO(Fd,Fd)createPipe :: IO (Fd, Fd) createPipe =Int -> (Ptr CInt -> IO (Fd, Fd)) -> IO (Fd, Fd) forall a b. Storable a => Int -> (Ptr a -> IO b) -> IO b allocaArrayInt 2((Ptr CInt -> IO (Fd, Fd)) -> IO (Fd, Fd)) -> (Ptr CInt -> IO (Fd, Fd)) -> IO (Fd, Fd) forall a b. (a -> b) -> a -> b $\Ptr CInt p_fd ->doString -> IO CInt -> IO () forall a. (Eq a, Num a) => String -> IO a -> IO () throwErrnoIfMinus1_String "createPipe"(Ptr CInt -> IO CInt c_pipe Ptr CInt p_fd )CInt rfd <-Ptr CInt -> Int -> IO CInt forall a. Storable a => Ptr a -> Int -> IO a peekElemOffPtr CInt p_fd Int 0CInt wfd <-Ptr CInt -> Int -> IO CInt forall a. Storable a => Ptr a -> Int -> IO a peekElemOffPtr CInt p_fd Int 1(Fd, Fd) -> IO (Fd, Fd) forall a. a -> IO a forall (m :: * -> *) a. Monad m => a -> m a return(CInt -> Fd FdCInt rfd ,CInt -> Fd FdCInt wfd )foreignimportccallunsafe"pipe"c_pipe ::PtrCInt->IOCInt{-# LINE 114 "System/Posix/IO/Common.hsc" #-}{-# LINE 128 "System/Posix/IO/Common.hsc" #-}-- ------------------------------------------------------------------------------- Duplicating file descriptors-- | May throw an exception if this is an invalid descriptor.dup ::Fd->IOFddup :: Fd -> IO Fd dup (FdCInt fd )=doCInt r <-String -> IO CInt -> IO CInt forall a. (Eq a, Num a) => String -> IO a -> IO a throwErrnoIfMinus1String "dup"(CInt -> IO CInt c_dup CInt fd );Fd -> IO Fd forall a. a -> IO a forall (m :: * -> *) a. Monad m => a -> m a return(CInt -> Fd FdCInt r )-- | May throw an exception if this is an invalid descriptor.dupTo ::Fd->Fd->IOFddupTo :: Fd -> Fd -> IO Fd dupTo (FdCInt fd1 )(FdCInt fd2 )=doCInt r <-String -> IO CInt -> IO CInt forall a. (Eq a, Num a) => String -> IO a -> IO a throwErrnoIfMinus1String "dupTo"(CInt -> CInt -> IO CInt c_dup2 CInt fd1 CInt fd2 )Fd -> IO Fd forall a. a -> IO a forall (m :: * -> *) a. Monad m => a -> m a return(CInt -> Fd FdCInt r )foreignimportccallunsafe"dup"c_dup ::CInt->IOCIntforeignimportccallunsafe"dup2"c_dup2 ::CInt->CInt->IOCInt{-# LINE 149 "System/Posix/IO/Common.hsc" #-}-- ------------------------------------------------------------------------------- Opening and closing filesstdInput ,stdOutput ,stdError ::FdstdInput :: Fd stdInput =CInt -> Fd Fd(CInt 0){-# LINE 155 "System/Posix/IO/Common.hsc" #-}stdOutput=Fd(1)stdError :: Fd {-# LINE 156 "System/Posix/IO/Common.hsc" #-} stdError=Fd(2){-# LINE 157 "System/Posix/IO/Common.hsc" #-}dataOpenMode =ReadOnly |WriteOnly |ReadWrite deriving(ReadPrec [OpenMode] ReadPrec OpenMode Int -> ReadS OpenMode ReadS [OpenMode] (Int -> ReadS OpenMode) -> ReadS [OpenMode] -> ReadPrec OpenMode -> ReadPrec [OpenMode] -> Read OpenMode forall a. (Int -> ReadS a) -> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a $creadsPrec :: Int -> ReadS OpenMode readsPrec :: Int -> ReadS OpenMode $creadList :: ReadS [OpenMode] readList :: ReadS [OpenMode] $creadPrec :: ReadPrec OpenMode readPrec :: ReadPrec OpenMode $creadListPrec :: ReadPrec [OpenMode] readListPrec :: ReadPrec [OpenMode] Read,Int -> OpenMode -> ShowS [OpenMode] -> ShowS OpenMode -> String (Int -> OpenMode -> ShowS) -> (OpenMode -> String) -> ([OpenMode] -> ShowS) -> Show OpenMode forall a. (Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a $cshowsPrec :: Int -> OpenMode -> ShowS showsPrec :: Int -> OpenMode -> ShowS $cshow :: OpenMode -> String show :: OpenMode -> String $cshowList :: [OpenMode] -> ShowS showList :: [OpenMode] -> ShowS Show,OpenMode -> OpenMode -> Bool (OpenMode -> OpenMode -> Bool) -> (OpenMode -> OpenMode -> Bool) -> Eq OpenMode forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a $c== :: OpenMode -> OpenMode -> Bool == :: OpenMode -> OpenMode -> Bool $c/= :: OpenMode -> OpenMode -> Bool /= :: OpenMode -> OpenMode -> Bool Eq,Eq OpenMode Eq OpenMode => (OpenMode -> OpenMode -> Ordering) -> (OpenMode -> OpenMode -> Bool) -> (OpenMode -> OpenMode -> Bool) -> (OpenMode -> OpenMode -> Bool) -> (OpenMode -> OpenMode -> Bool) -> (OpenMode -> OpenMode -> OpenMode) -> (OpenMode -> OpenMode -> OpenMode) -> Ord OpenMode OpenMode -> OpenMode -> Bool OpenMode -> OpenMode -> Ordering OpenMode -> OpenMode -> OpenMode forall a. Eq a => (a -> a -> Ordering) -> (a -> a -> Bool) -> (a -> a -> Bool) -> (a -> a -> Bool) -> (a -> a -> Bool) -> (a -> a -> a) -> (a -> a -> a) -> Ord a $ccompare :: OpenMode -> OpenMode -> Ordering compare :: OpenMode -> OpenMode -> Ordering $c< :: OpenMode -> OpenMode -> Bool < :: OpenMode -> OpenMode -> Bool $c<= :: OpenMode -> OpenMode -> Bool <= :: OpenMode -> OpenMode -> Bool $c> :: OpenMode -> OpenMode -> Bool > :: OpenMode -> OpenMode -> Bool $c>= :: OpenMode -> OpenMode -> Bool >= :: OpenMode -> OpenMode -> Bool $cmax :: OpenMode -> OpenMode -> OpenMode max :: OpenMode -> OpenMode -> OpenMode $cmin :: OpenMode -> OpenMode -> OpenMode min :: OpenMode -> OpenMode -> OpenMode Ord)-- |Correspond to some of the int flags from C's fcntl.h.dataOpenFileFlags =OpenFileFlags {OpenFileFlags -> Bool append ::Bool,-- ^ O_APPENDOpenFileFlags -> Bool exclusive ::Bool,-- ^ O_EXCL, result is undefined if O_CREAT is False---- __NOTE__: Result is undefined if 'creat' is 'Nothing'.OpenFileFlags -> Bool noctty ::Bool,-- ^ O_NOCTTYOpenFileFlags -> Bool nonBlock ::Bool,-- ^ O_NONBLOCKOpenFileFlags -> Bool trunc ::Bool,-- ^ O_TRUNCOpenFileFlags -> Bool nofollow ::Bool,-- ^ O_NOFOLLOW---- @since 2.8.0.0OpenFileFlags -> Maybe FileMode creat ::MaybeFileMode,-- ^ O_CREAT---- @since 2.8.0.0OpenFileFlags -> Bool cloexec ::Bool,-- ^ O_CLOEXEC---- @since 2.8.0.0OpenFileFlags -> Bool directory ::Bool,-- ^ O_DIRECTORY---- @since 2.8.0.0OpenFileFlags -> Bool sync ::Bool-- ^ O_SYNC---- @since 2.8.0.0}deriving(ReadPrec [OpenFileFlags] ReadPrec OpenFileFlags Int -> ReadS OpenFileFlags ReadS [OpenFileFlags] (Int -> ReadS OpenFileFlags) -> ReadS [OpenFileFlags] -> ReadPrec OpenFileFlags -> ReadPrec [OpenFileFlags] -> Read OpenFileFlags forall a. (Int -> ReadS a) -> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a $creadsPrec :: Int -> ReadS OpenFileFlags readsPrec :: Int -> ReadS OpenFileFlags $creadList :: ReadS [OpenFileFlags] readList :: ReadS [OpenFileFlags] $creadPrec :: ReadPrec OpenFileFlags readPrec :: ReadPrec OpenFileFlags $creadListPrec :: ReadPrec [OpenFileFlags] readListPrec :: ReadPrec [OpenFileFlags] Read,Int -> OpenFileFlags -> ShowS [OpenFileFlags] -> ShowS OpenFileFlags -> String (Int -> OpenFileFlags -> ShowS) -> (OpenFileFlags -> String) -> ([OpenFileFlags] -> ShowS) -> Show OpenFileFlags forall a. (Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a $cshowsPrec :: Int -> OpenFileFlags -> ShowS showsPrec :: Int -> OpenFileFlags -> ShowS $cshow :: OpenFileFlags -> String show :: OpenFileFlags -> String $cshowList :: [OpenFileFlags] -> ShowS showList :: [OpenFileFlags] -> ShowS Show,OpenFileFlags -> OpenFileFlags -> Bool (OpenFileFlags -> OpenFileFlags -> Bool) -> (OpenFileFlags -> OpenFileFlags -> Bool) -> Eq OpenFileFlags forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a $c== :: OpenFileFlags -> OpenFileFlags -> Bool == :: OpenFileFlags -> OpenFileFlags -> Bool $c/= :: OpenFileFlags -> OpenFileFlags -> Bool /= :: OpenFileFlags -> OpenFileFlags -> Bool Eq,Eq OpenFileFlags Eq OpenFileFlags => (OpenFileFlags -> OpenFileFlags -> Ordering) -> (OpenFileFlags -> OpenFileFlags -> Bool) -> (OpenFileFlags -> OpenFileFlags -> Bool) -> (OpenFileFlags -> OpenFileFlags -> Bool) -> (OpenFileFlags -> OpenFileFlags -> Bool) -> (OpenFileFlags -> OpenFileFlags -> OpenFileFlags) -> (OpenFileFlags -> OpenFileFlags -> OpenFileFlags) -> Ord OpenFileFlags OpenFileFlags -> OpenFileFlags -> Bool OpenFileFlags -> OpenFileFlags -> Ordering OpenFileFlags -> OpenFileFlags -> OpenFileFlags forall a. Eq a => (a -> a -> Ordering) -> (a -> a -> Bool) -> (a -> a -> Bool) -> (a -> a -> Bool) -> (a -> a -> Bool) -> (a -> a -> a) -> (a -> a -> a) -> Ord a $ccompare :: OpenFileFlags -> OpenFileFlags -> Ordering compare :: OpenFileFlags -> OpenFileFlags -> Ordering $c< :: OpenFileFlags -> OpenFileFlags -> Bool < :: OpenFileFlags -> OpenFileFlags -> Bool $c<= :: OpenFileFlags -> OpenFileFlags -> Bool <= :: OpenFileFlags -> OpenFileFlags -> Bool $c> :: OpenFileFlags -> OpenFileFlags -> Bool > :: OpenFileFlags -> OpenFileFlags -> Bool $c>= :: OpenFileFlags -> OpenFileFlags -> Bool >= :: OpenFileFlags -> OpenFileFlags -> Bool $cmax :: OpenFileFlags -> OpenFileFlags -> OpenFileFlags max :: OpenFileFlags -> OpenFileFlags -> OpenFileFlags $cmin :: OpenFileFlags -> OpenFileFlags -> OpenFileFlags min :: OpenFileFlags -> OpenFileFlags -> OpenFileFlags Ord)-- | Default values for the 'OpenFileFlags' type.---- Each field of 'OpenFileFlags' is either 'False' or 'Nothing'-- respectively.defaultFileFlags ::OpenFileFlags defaultFileFlags :: OpenFileFlags defaultFileFlags =OpenFileFlags {append :: Bool append =Bool False,exclusive :: Bool exclusive =Bool False,noctty :: Bool noctty =Bool False,nonBlock :: Bool nonBlock =Bool False,trunc :: Bool trunc =Bool False,nofollow :: Bool nofollow =Bool False,creat :: Maybe FileMode creat =Maybe FileMode forall a. Maybe a Nothing,cloexec :: Bool cloexec =Bool False,directory :: Bool directory =Bool False,sync :: Bool sync =Bool False}-- |Open and optionally create a file relative to an optional-- directory file descriptor.openat_ ::MaybeFd-- ^ Optional directory file descriptor->CString-- ^ Pathname to open->OpenMode -- ^ Read-only, read-write or write-only->OpenFileFlags -- ^ Append, exclusive, etc.->IOFdopenat_ :: Maybe Fd -> CString -> OpenMode -> OpenFileFlags -> IO Fd openat_ Maybe Fd fdMay CString str OpenMode how (OpenFileFlags Bool appendFlag Bool exclusiveFlag Bool nocttyFlag Bool nonBlockFlag Bool truncateFlag Bool nofollowFlag Maybe FileMode creatFlag Bool cloexecFlag Bool directoryFlag Bool syncFlag )=CInt -> Fd Fd(CInt -> Fd) -> IO CInt -> IO Fd forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b <$>CInt -> CString -> CInt -> FileMode -> IO CInt c_openat CInt c_fd CString str CInt all_flags FileMode mode_w wherec_fd :: CInt c_fd =CInt -> (Fd -> CInt) -> Maybe Fd -> CInt forall b a. b -> (a -> b) -> Maybe a -> b maybe(-CInt 100)(\(FdCInt fd )->CInt fd )Maybe Fd fdMay {-# LINE 224 "System/Posix/IO/Common.hsc" #-}all_flags=creat.|.flags.|.open_modeflags :: CInt flags =(ifBool appendFlag then(CInt 1024)elseCInt 0)CInt -> CInt -> CInt forall a. Bits a => a -> a -> a .|.{-# LINE 228 "System/Posix/IO/Common.hsc" #-}(ifexclusiveFlagthen(128)else0)CInt -> CInt -> CInt forall a. Bits a => a -> a -> a .|.{-# LINE 229 "System/Posix/IO/Common.hsc" #-}(ifnocttyFlagthen(256)else0)CInt -> CInt -> CInt forall a. Bits a => a -> a -> a .|.{-# LINE 230 "System/Posix/IO/Common.hsc" #-}(ifnonBlockFlagthen(2048)else0)CInt -> CInt -> CInt forall a. Bits a => a -> a -> a .|.{-# LINE 231 "System/Posix/IO/Common.hsc" #-}(iftruncateFlagthen(512)else0)CInt -> CInt -> CInt forall a. Bits a => a -> a -> a .|.{-# LINE 232 "System/Posix/IO/Common.hsc" #-}(ifnofollowFlagthen(131072)else0)CInt -> CInt -> CInt forall a. Bits a => a -> a -> a .|.{-# LINE 233 "System/Posix/IO/Common.hsc" #-}(ifcloexecFlagthen(524288)else0)CInt -> CInt -> CInt forall a. Bits a => a -> a -> a .|.{-# LINE 234 "System/Posix/IO/Common.hsc" #-}(ifdirectoryFlagthen(65536)else0)CInt -> CInt -> CInt forall a. Bits a => a -> a -> a .|.{-# LINE 235 "System/Posix/IO/Common.hsc" #-}(ifsyncFlagthen(1052672)else0){-# LINE 236 "System/Posix/IO/Common.hsc" #-}(CInt creat ,FileMode mode_w )=caseMaybe FileMode creatFlag ofMaybe FileMode Nothing->(CInt 0,FileMode 0)JustFileMode x ->((CInt 64),FileMode x ){-# LINE 240 "System/Posix/IO/Common.hsc" #-}open_mode :: CInt open_mode =caseOpenMode how ofOpenMode ReadOnly ->(CInt 0){-# LINE 243 "System/Posix/IO/Common.hsc" #-}OpenMode WriteOnly ->(CInt 1){-# LINE 244 "System/Posix/IO/Common.hsc" #-}OpenMode ReadWrite ->(CInt 2){-# LINE 245 "System/Posix/IO/Common.hsc" #-}foreignimportcapiunsafe"HsUnix.h openat"c_openat ::CInt->CString->CInt->CMode->IOCInt-- |Close this file descriptor. May throw an exception if this is an-- invalid descriptor.closeFd ::Fd->IO()closeFd :: Fd -> IO () closeFd (FdCInt fd )=String -> IO CInt -> IO () forall a. (Eq a, Num a) => String -> IO a -> IO () throwErrnoIfMinus1_String "closeFd"(CInt -> IO CInt c_close CInt fd )-- Here we don't to retry on EINTR because according to-- http://pubs.opengroup.org/onlinepubs/9699919799/functions/close.html-- "with errno set to [EINTR] [...] the state of fildes is unspecified"-- and on Linux, already the first close() removes the FD from the process's-- FD table so closing a second time is invalid-- (see http://man7.org/linux/man-pages/man2/close.2.html#NOTES).foreignimportccallunsafe"HsUnix.h close"c_close ::CInt->IOCInt-- ------------------------------------------------------------------------------- Converting file descriptors to/from Handles-- | Extracts the 'Fd' from a 'Handle'. This function has the side effect-- of closing the 'Handle' (and flushing its write buffer, if necessary),-- without closing the underlying 'Fd'.---- __Warning:__ This means you take over ownership of the underlying 'Fd'.-- 'hClose` on the 'Handle' will no longer have any effect.-- This will break common patterns to avoid file descriptor leaks,-- such as using 'hClose' in the cleanup action of @Control.Exception.bracket@,-- making it a silent no-op.-- Be sure to close the returned 'Fd' yourself to not leak it.handleToFd ::Handle->IOFd-- | Converts an 'Fd' into a 'Handle' that can be used with the-- standard Haskell IO library (see "System.IO").fdToHandle ::Fd->IOHandlefdToHandle :: Fd -> IO Handle fdToHandle Fd fd =CInt -> IO Handle FD.fdToHandle(Fd -> CInt forall a b. (Integral a, Num b) => a -> b fromIntegralFd fd )handleToFd :: Handle -> IO Fd handleToFd h :: Handle h @(FileHandleString _MVar Handle__ m )=doString -> Handle -> MVar Handle__ -> (Handle__ -> IO (Handle__, Fd)) -> IO Fd forall a. String -> Handle -> MVar Handle__ -> (Handle__ -> IO (Handle__, a)) -> IO a withHandle'String "handleToFd"Handle h MVar Handle__ m ((Handle__ -> IO (Handle__, Fd)) -> IO Fd) -> (Handle__ -> IO (Handle__, Fd)) -> IO Fd forall a b. (a -> b) -> a -> b $Handle -> Handle__ -> IO (Handle__, Fd) handleToFd' Handle h handleToFd h :: Handle h @(DuplexHandleString _MVar Handle__ r MVar Handle__ w )=doFd _<-String -> Handle -> MVar Handle__ -> (Handle__ -> IO (Handle__, Fd)) -> IO Fd forall a. String -> Handle -> MVar Handle__ -> (Handle__ -> IO (Handle__, a)) -> IO a withHandle'String "handleToFd"Handle h MVar Handle__ r ((Handle__ -> IO (Handle__, Fd)) -> IO Fd) -> (Handle__ -> IO (Handle__, Fd)) -> IO Fd forall a b. (a -> b) -> a -> b $Handle -> Handle__ -> IO (Handle__, Fd) handleToFd' Handle h String -> Handle -> MVar Handle__ -> (Handle__ -> IO (Handle__, Fd)) -> IO Fd forall a. String -> Handle -> MVar Handle__ -> (Handle__ -> IO (Handle__, a)) -> IO a withHandle'String "handleToFd"Handle h MVar Handle__ w ((Handle__ -> IO (Handle__, Fd)) -> IO Fd) -> (Handle__ -> IO (Handle__, Fd)) -> IO Fd forall a b. (a -> b) -> a -> b $Handle -> Handle__ -> IO (Handle__, Fd) handleToFd' Handle h -- for a DuplexHandle, make sure we mark both sides as closed,-- otherwise a finalizer will come along later and close the other-- side. (#3914)handleToFd' ::Handle->Handle__->IO(Handle__,Fd)handleToFd' :: Handle -> Handle__ -> IO (Handle__, Fd) handleToFd' Handle h h_ :: Handle__ h_ @Handle__{haType :: Handle__ -> HandleType haType=HandleType _,dev Maybe (MVar Handle__) Maybe TextEncoding Maybe (TextEncoder enc_state) Maybe (TextDecoder dec_state) IORef (dec_state, Buffer Word8) IORef (Buffer CharBufElem) IORef (Buffer Word8) IORef (BufferList CharBufElem) Newline BufferMode haDevice :: dev haByteBuffer :: IORef (Buffer Word8) haBufferMode :: BufferMode haLastDecode :: IORef (dec_state, Buffer Word8) haCharBuffer :: IORef (Buffer CharBufElem) haBuffers :: IORef (BufferList CharBufElem) haEncoder :: Maybe (TextEncoder enc_state) haDecoder :: Maybe (TextDecoder dec_state) haCodec :: Maybe TextEncoding haInputNL :: Newline haOutputNL :: Newline haOtherSide :: Maybe (MVar Handle__) haOtherSide :: Handle__ -> Maybe (MVar Handle__) haOutputNL :: Handle__ -> Newline haInputNL :: Handle__ -> Newline haCodec :: Handle__ -> Maybe TextEncoding haDecoder :: () haEncoder :: () haBuffers :: Handle__ -> IORef (BufferList CharBufElem) haCharBuffer :: Handle__ -> IORef (Buffer CharBufElem) haLastDecode :: () haBufferMode :: Handle__ -> BufferMode haByteBuffer :: Handle__ -> IORef (Buffer Word8) haDevice :: () .. }=docasedev -> Maybe FD forall a b. (Typeable a, Typeable b) => a -> Maybe b castdev haDevice ofMaybe FD Nothing->IOError -> IO (Handle__, Fd) forall a. IOError -> IO a ioError(IOError -> String -> IOError ioeSetErrorString(IOErrorType -> String -> Maybe Handle -> Maybe String -> IOError mkIOErrorIOErrorType IllegalOperationString "handleToFd"(Handle -> Maybe Handle forall a. a -> Maybe a JustHandle h )Maybe String forall a. Maybe a Nothing)String "handle is not a file descriptor")JustFD fd ->do-- converting a Handle into an Fd effectively means-- letting go of the Handle; it is put into a closed-- state as a result.Handle__ -> IO () flushWriteBufferHandle__ h_ FD -> IO () FD.releaseFD fd (Handle__, Fd) -> IO (Handle__, Fd) forall a. a -> IO a forall (m :: * -> *) a. Monad m => a -> m a return(Handle__{haType :: HandleType haType=HandleType ClosedHandle,dev Maybe (MVar Handle__) Maybe TextEncoding Maybe (TextEncoder enc_state) Maybe (TextDecoder dec_state) IORef (dec_state, Buffer Word8) IORef (Buffer CharBufElem) IORef (Buffer Word8) IORef (BufferList CharBufElem) Newline BufferMode haDevice :: dev haByteBuffer :: IORef (Buffer Word8) haBufferMode :: BufferMode haLastDecode :: IORef (dec_state, Buffer Word8) haCharBuffer :: IORef (Buffer CharBufElem) haBuffers :: IORef (BufferList CharBufElem) haEncoder :: Maybe (TextEncoder enc_state) haDecoder :: Maybe (TextDecoder dec_state) haCodec :: Maybe TextEncoding haInputNL :: Newline haOutputNL :: Newline haOtherSide :: Maybe (MVar Handle__) haOtherSide :: Maybe (MVar Handle__) haOutputNL :: Newline haInputNL :: Newline haCodec :: Maybe TextEncoding haDecoder :: Maybe (TextDecoder dec_state) haEncoder :: Maybe (TextEncoder enc_state) haBuffers :: IORef (BufferList CharBufElem) haCharBuffer :: IORef (Buffer CharBufElem) haLastDecode :: IORef (dec_state, Buffer Word8) haBufferMode :: BufferMode haByteBuffer :: IORef (Buffer Word8) haDevice :: dev .. },CInt -> Fd Fd(FD -> CInt FD.fdFDFD fd ))-- ------------------------------------------------------------------------------- Fd optionsdataFdOption =AppendOnWrite -- ^O_APPEND|CloseOnExec -- ^FD_CLOEXEC|NonBlockingRead -- ^O_NONBLOCK|SynchronousWrites -- ^O_SYNCfdOption2Int ::FdOption ->CIntfdOption2Int :: FdOption -> CInt fdOption2Int FdOption CloseOnExec =(CInt 1){-# LINE 318 "System/Posix/IO/Common.hsc" #-}fdOption2IntAppendOnWrite=(1024){-# LINE 319 "System/Posix/IO/Common.hsc" #-}fdOption2IntNonBlockingRead=(2048){-# LINE 320 "System/Posix/IO/Common.hsc" #-}fdOption2IntSynchronousWrites=(1052672){-# LINE 321 "System/Posix/IO/Common.hsc" #-}-- | May throw an exception if this is an invalid descriptor.queryFdOption ::Fd->FdOption ->IOBoolqueryFdOption :: Fd -> FdOption -> IO Bool queryFdOption (FdCInt fd )FdOption opt =doCInt r <-String -> IO CInt -> IO CInt forall a. (Eq a, Num a) => String -> IO a -> IO a throwErrnoIfMinus1String "queryFdOption"(CInt -> CInt -> IO CInt Base.c_fcntl_readCInt fd CInt flag )Bool -> IO Bool forall a. a -> IO a forall (m :: * -> *) a. Monad m => a -> m a return((CInt r CInt -> CInt -> CInt forall a. Bits a => a -> a -> a .&.FdOption -> CInt fdOption2Int FdOption opt )CInt -> CInt -> Bool forall a. Eq a => a -> a -> Bool /=CInt 0)whereflag :: CInt flag =caseFdOption opt ofFdOption CloseOnExec ->(CInt 1){-# LINE 330 "System/Posix/IO/Common.hsc" #-}FdOption _->(CInt 3){-# LINE 331 "System/Posix/IO/Common.hsc" #-}-- | May throw an exception if this is an invalid descriptor.setFdOption ::Fd->FdOption ->Bool->IO()setFdOption :: Fd -> FdOption -> Bool -> IO () setFdOption (FdCInt fd )FdOption opt Bool val =doCInt r <-String -> IO CInt -> IO CInt forall a. (Eq a, Num a) => String -> IO a -> IO a throwErrnoIfMinus1String "setFdOption"(CInt -> CInt -> IO CInt Base.c_fcntl_readCInt fd CInt getflag )letr' :: CInt r' |Bool val =CInt r CInt -> CInt -> CInt forall a. Bits a => a -> a -> a .|.CInt opt_val |Bool otherwise=CInt r CInt -> CInt -> CInt forall a. Bits a => a -> a -> a .&.(CInt -> CInt forall a. Bits a => a -> a complementCInt opt_val )String -> IO CInt -> IO () forall a. (Eq a, Num a) => String -> IO a -> IO () throwErrnoIfMinus1_String "setFdOption"(CInt -> CInt -> CLong -> IO CInt Base.c_fcntl_writeCInt fd CInt setflag (CInt -> CLong forall a b. (Integral a, Num b) => a -> b fromIntegralCInt r' ))where(CInt getflag ,CInt setflag )=caseFdOption opt ofFdOption CloseOnExec ->((CInt 1),(CInt 2)){-# LINE 343 "System/Posix/IO/Common.hsc" #-}FdOption _->((CInt 3),(CInt 4)){-# LINE 344 "System/Posix/IO/Common.hsc" #-}opt_val=fdOption2Intopt-- ------------------------------------------------------------------------------- Seekingmode2Int ::SeekMode->CIntmode2Int :: SeekMode -> CInt mode2Int SeekMode AbsoluteSeek=(CInt 0){-# LINE 351 "System/Posix/IO/Common.hsc" #-} mode2IntRelativeSeek=(1){-# LINE 352 "System/Posix/IO/Common.hsc" #-} mode2IntSeekFromEnd=(2){-# LINE 353 "System/Posix/IO/Common.hsc" #-}-- | May throw an exception if this is an invalid descriptor.fdSeek ::Fd->SeekMode->FileOffset->IOFileOffsetfdSeek :: Fd -> SeekMode -> FileOffset -> IO FileOffset fdSeek (FdCInt fd )SeekMode mode FileOffset off =String -> IO FileOffset -> IO FileOffset forall a. (Eq a, Num a) => String -> IO a -> IO a throwErrnoIfMinus1String "fdSeek"(CInt -> FileOffset -> CInt -> IO FileOffset Base.c_lseekCInt fd FileOffset off (SeekMode -> CInt mode2Int SeekMode mode ))-- ------------------------------------------------------------------------------- LockingdataLockRequest =ReadLock |WriteLock |Unlock typeFileLock =(LockRequest ,SeekMode,FileOffset,FileOffset){-# LINE 386 "System/Posix/IO/Common.hsc" #-}-- | May throw an exception if this is an invalid descriptor.getLock ::Fd->FileLock ->IO(Maybe(ProcessID,FileLock ))getLock :: Fd -> FileLock -> IO (Maybe (ProcessID, FileLock)) getLock (FdCInt fd )FileLock lock =FileLock -> (Ptr CFLock -> IO (Maybe (ProcessID, FileLock))) -> IO (Maybe (ProcessID, FileLock)) forall a. FileLock -> (Ptr CFLock -> IO a) -> IO a allocaLock FileLock lock ((Ptr CFLock -> IO (Maybe (ProcessID, FileLock))) -> IO (Maybe (ProcessID, FileLock))) -> (Ptr CFLock -> IO (Maybe (ProcessID, FileLock))) -> IO (Maybe (ProcessID, FileLock)) forall a b. (a -> b) -> a -> b $\Ptr CFLock p_flock ->doString -> IO CInt -> IO () forall a. (Eq a, Num a) => String -> IO a -> IO () throwErrnoIfMinus1_String "getLock"(CInt -> CInt -> Ptr CFLock -> IO CInt Base.c_fcntl_lockCInt fd (CInt 5)Ptr CFLock p_flock ){-# LINE 392 "System/Posix/IO/Common.hsc" #-}result<-bytes2ProcessIDAndLockp_flockMaybe (ProcessID, FileLock) -> IO (Maybe (ProcessID, FileLock)) forall a. a -> IO a forall (m :: * -> *) a. Monad m => a -> m a return((ProcessID, FileLock) -> Maybe (ProcessID, FileLock) forall {a} {b} {c} {d}. (a, (LockRequest, b, c, d)) -> Maybe (a, (LockRequest, b, c, d)) maybeResult (ProcessID, FileLock) result )wheremaybeResult :: (a, (LockRequest, b, c, d)) -> Maybe (a, (LockRequest, b, c, d)) maybeResult (a _,(LockRequest Unlock ,b _,c _,d _))=Maybe (a, (LockRequest, b, c, d)) forall a. Maybe a NothingmaybeResult (a, (LockRequest, b, c, d)) x =(a, (LockRequest, b, c, d)) -> Maybe (a, (LockRequest, b, c, d)) forall a. a -> Maybe a Just(a, (LockRequest, b, c, d)) x allocaLock ::FileLock ->(PtrBase.CFLock->IOa )->IOa allocaLock :: forall a. FileLock -> (Ptr CFLock -> IO a) -> IO a allocaLock (LockRequest lockreq ,SeekMode mode ,FileOffset start ,FileOffset len )Ptr CFLock -> IO a io =Int -> (Ptr CFLock -> IO a) -> IO a forall a b. Int -> (Ptr a -> IO b) -> IO b allocaBytes(Int 32)((Ptr CFLock -> IO a) -> IO a) -> (Ptr CFLock -> IO a) -> IO a forall a b. (a -> b) -> a -> b $\Ptr CFLock p ->do{-# LINE 401 "System/Posix/IO/Common.hsc" #-}((\hsc_ptr->pokeByteOffhsc_ptr0))p(lockReq2Intlockreq::CShort){-# LINE 402 "System/Posix/IO/Common.hsc" #-}((\hsc_ptr->pokeByteOffhsc_ptr2))p(fromIntegral(mode2Intmode)::CShort){-# LINE 403 "System/Posix/IO/Common.hsc" #-}((\hsc_ptr->pokeByteOffhsc_ptr8))pstart{-# LINE 404 "System/Posix/IO/Common.hsc" #-}((\hsc_ptr->pokeByteOffhsc_ptr16))plen{-# LINE 405 "System/Posix/IO/Common.hsc" #-}ioplockReq2Int ::LockRequest ->CShortlockReq2Int :: LockRequest -> CShort lockReq2Int LockRequest ReadLock =(CShort 0){-# LINE 409 "System/Posix/IO/Common.hsc" #-}lockReq2IntWriteLock=(1){-# LINE 410 "System/Posix/IO/Common.hsc" #-}lockReq2IntUnlock=(2){-# LINE 411 "System/Posix/IO/Common.hsc" #-}bytes2ProcessIDAndLock ::PtrBase.CFLock->IO(ProcessID,FileLock )bytes2ProcessIDAndLock :: Ptr CFLock -> IO (ProcessID, FileLock) bytes2ProcessIDAndLock Ptr CFLock p =doCShort req <-((\Ptr CFLock hsc_ptr ->Ptr CFLock -> Int -> IO CShort forall b. Ptr b -> Int -> IO CShort forall a b. Storable a => Ptr b -> Int -> IO a peekByteOffPtr CFLock hsc_ptr Int 0))Ptr CFLock p {-# LINE 415 "System/Posix/IO/Common.hsc" #-}mode<-((\hsc_ptr->peekByteOffhsc_ptr2))p{-# LINE 416 "System/Posix/IO/Common.hsc" #-}start<-((\hsc_ptr->peekByteOffhsc_ptr8))p{-# LINE 417 "System/Posix/IO/Common.hsc" #-}len<-((\hsc_ptr->peekByteOffhsc_ptr16))p{-# LINE 418 "System/Posix/IO/Common.hsc" #-}pid<-((\hsc_ptr->peekByteOffhsc_ptr24))p{-# LINE 419 "System/Posix/IO/Common.hsc" #-}return(pid,(int2reqreq,int2modemode,start,len))whereint2req ::CShort->LockRequest int2req :: CShort -> LockRequest int2req (CShort 0)=LockRequest ReadLock {-# LINE 423 "System/Posix/IO/Common.hsc" #-}int2req(1)=WriteLock{-# LINE 424 "System/Posix/IO/Common.hsc" #-}int2req(2)=Unlock{-# LINE 425 "System/Posix/IO/Common.hsc" #-}int2req_=error$"int2req: bad argument"int2mode ::CShort->SeekModeint2mode :: CShort -> SeekMode int2mode (CShort 0)=SeekMode AbsoluteSeek{-# LINE 429 "System/Posix/IO/Common.hsc" #-}int2mode(1)=RelativeSeek{-# LINE 430 "System/Posix/IO/Common.hsc" #-}int2mode(2)=SeekFromEnd{-# LINE 431 "System/Posix/IO/Common.hsc" #-}int2mode_=error$"int2mode: bad argument"-- | May throw an exception if this is an invalid descriptor.setLock ::Fd->FileLock ->IO()setLock :: Fd -> FileLock -> IO () setLock (FdCInt fd )FileLock lock =doFileLock -> (Ptr CFLock -> IO ()) -> IO () forall a. FileLock -> (Ptr CFLock -> IO a) -> IO a allocaLock FileLock lock ((Ptr CFLock -> IO ()) -> IO ()) -> (Ptr CFLock -> IO ()) -> IO () forall a b. (a -> b) -> a -> b $\Ptr CFLock p_flock ->String -> IO CInt -> IO () forall a. (Eq a, Num a) => String -> IO a -> IO () throwErrnoIfMinus1_String "setLock"(CInt -> CInt -> Ptr CFLock -> IO CInt Base.c_fcntl_lockCInt fd (CInt 6)Ptr CFLock p_flock ){-# LINE 438 "System/Posix/IO/Common.hsc" #-}-- | May throw an exception if this is an invalid descriptor.waitToSetLock ::Fd->FileLock ->IO()waitToSetLock :: Fd -> FileLock -> IO () waitToSetLock (FdCInt fd )FileLock lock =doFileLock -> (Ptr CFLock -> IO ()) -> IO () forall a. FileLock -> (Ptr CFLock -> IO a) -> IO a allocaLock FileLock lock ((Ptr CFLock -> IO ()) -> IO ()) -> (Ptr CFLock -> IO ()) -> IO () forall a b. (a -> b) -> a -> b $\Ptr CFLock p_flock ->String -> IO CInt -> IO () forall a. (Eq a, Num a) => String -> IO a -> IO () throwErrnoIfMinus1_String "waitToSetLock"(CInt -> CInt -> Ptr CFLock -> IO CInt Base.c_fcntl_lockCInt fd (CInt 7)Ptr CFLock p_flock ){-# LINE 445 "System/Posix/IO/Common.hsc" #-}{-# LINE 447 "System/Posix/IO/Common.hsc" #-}-- ------------------------------------------------------------------------------- fd{Read,Write}Buf-- | Read data from an 'Fd' into memory. This is exactly equivalent-- to the POSIX @read@ function.fdReadBuf ::Fd->PtrWord8-- ^ Memory in which to put the data->ByteCount-- ^ Maximum number of bytes to read->IOByteCount-- ^ Number of bytes read (zero for EOF)fdReadBuf :: Fd -> Ptr Word8 -> ByteCount -> IO ByteCount fdReadBuf Fd _fd Ptr Word8 _buf ByteCount 0=ByteCount -> IO ByteCount forall a. a -> IO a forall (m :: * -> *) a. Monad m => a -> m a returnByteCount 0fdReadBuf Fd fd Ptr Word8 buf ByteCount nbytes =(CSsize -> ByteCount) -> IO CSsize -> IO ByteCount forall a b. (a -> b) -> IO a -> IO b forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b fmapCSsize -> ByteCount forall a b. (Integral a, Num b) => a -> b fromIntegral(IO CSsize -> IO ByteCount) -> IO CSsize -> IO ByteCount forall a b. (a -> b) -> a -> b $String -> IO CSsize -> IO CSsize forall a. (Eq a, Num a) => String -> IO a -> IO a throwErrnoIfMinus1RetryString "fdReadBuf"(IO CSsize -> IO CSsize) -> IO CSsize -> IO CSsize forall a b. (a -> b) -> a -> b $CInt -> CString -> ByteCount -> IO CSsize c_safe_read (Fd -> CInt forall a b. (Integral a, Num b) => a -> b fromIntegralFd fd )(Ptr Word8 -> CString forall a b. Ptr a -> Ptr b castPtrPtr Word8 buf )ByteCount nbytes foreignimportccallsafe"read"c_safe_read ::CInt->PtrCChar->CSize->IOCSsize-- | Write data from memory to an 'Fd'. This is exactly equivalent-- to the POSIX @write@ function.fdWriteBuf ::Fd->PtrWord8-- ^ Memory containing the data to write->ByteCount-- ^ Maximum number of bytes to write->IOByteCount-- ^ Number of bytes writtenfdWriteBuf :: Fd -> Ptr Word8 -> ByteCount -> IO ByteCount fdWriteBuf Fd fd Ptr Word8 buf ByteCount len =(CSsize -> ByteCount) -> IO CSsize -> IO ByteCount forall a b. (a -> b) -> IO a -> IO b forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b fmapCSsize -> ByteCount forall a b. (Integral a, Num b) => a -> b fromIntegral(IO CSsize -> IO ByteCount) -> IO CSsize -> IO ByteCount forall a b. (a -> b) -> a -> b $String -> IO CSsize -> IO CSsize forall a. (Eq a, Num a) => String -> IO a -> IO a throwErrnoIfMinus1RetryString "fdWriteBuf"(IO CSsize -> IO CSsize) -> IO CSsize -> IO CSsize forall a b. (a -> b) -> a -> b $CInt -> CString -> ByteCount -> IO CSsize c_safe_write (Fd -> CInt forall a b. (Integral a, Num b) => a -> b fromIntegralFd fd )(Ptr Word8 -> CString forall a b. Ptr a -> Ptr b castPtrPtr Word8 buf )ByteCount len foreignimportccallsafe"write"c_safe_write ::CInt->PtrCChar->CSize->IOCSsize