{-# LANGUAGE Trustworthy #-}{-# LANGUAGE CPP, NoImplicitPrelude #-}------------------------------------------------------------------------------- |-- Module : GHC.IO.Handle.FD-- Copyright : (c) The University of Glasgow, 1994-2008-- License : see libraries/base/LICENSE-- -- Maintainer : libraries@haskell.org-- Stability : internal-- Portability : non-portable---- Handle operations implemented by file descriptors (FDs)-------------------------------------------------------------------------------moduleGHC.IO.Handle.FD(stdin ,stdout ,stderr ,openFile ,openBinaryFile ,openFileBlocking ,mkHandleFromFD ,fdToHandle ,fdToHandle' ,handleToFd )whereimportGHC.Base importGHC.Show importData.Maybe importData.Typeable importForeign.C.Types importGHC.MVar importGHC.IO importGHC.IO.Encoding importGHC.IO.Device asIODeviceimportGHC.IO.Exception importGHC.IO.IOMode importGHC.IO.Handle.Types importGHC.IO.Handle.Internals importqualifiedGHC.IO.FD asFDimportqualifiedSystem.Posix.Internals asPosix-- ----------------------------------------------------------------------------- Standard Handles-- Three handles are allocated during program initialisation. The first-- two manage input or output from the Haskell program's standard input-- or output channel respectively. The third manages output to the-- standard error channel. These handles are initially open.-- | A handle managing input from the Haskell program's standard input channel.stdin ::Handle {-# NOINLINEstdin #-}stdin :: Handle stdin =IO Handle -> Handle forall a. IO a -> a unsafePerformIO (IO Handle -> Handle) -> IO Handle -> Handle forall a b. (a -> b) -> a -> b $ do-- ToDo: acquire lockFD -> IO () setBinaryMode FD FD.stdin TextEncoding enc <-IO TextEncoding getLocaleEncoding FD -> FilePath -> HandleType -> Bool -> Maybe TextEncoding -> NewlineMode -> Maybe HandleFinalizer -> Maybe (MVar Handle__) -> IO Handle forall dev. (IODevice dev, BufferedIO dev, Typeable dev) => dev -> FilePath -> HandleType -> Bool -> Maybe TextEncoding -> NewlineMode -> Maybe HandleFinalizer -> Maybe (MVar Handle__) -> IO Handle mkHandle FD FD.stdin "<stdin>"HandleType ReadHandle Bool True(TextEncoding -> Maybe TextEncoding forall a. a -> Maybe a Just TextEncoding enc )NewlineMode nativeNewlineMode {-translate newlines-}(HandleFinalizer -> Maybe HandleFinalizer forall a. a -> Maybe a Just HandleFinalizer stdHandleFinalizer )Maybe (MVar Handle__) forall a. Maybe a Nothing -- | A handle managing output to the Haskell program's standard output channel.stdout ::Handle {-# NOINLINEstdout #-}stdout :: Handle stdout =IO Handle -> Handle forall a. IO a -> a unsafePerformIO (IO Handle -> Handle) -> IO Handle -> Handle forall a b. (a -> b) -> a -> b $ do-- ToDo: acquire lockFD -> IO () setBinaryMode FD FD.stdout TextEncoding enc <-IO TextEncoding getLocaleEncoding FD -> FilePath -> HandleType -> Bool -> Maybe TextEncoding -> NewlineMode -> Maybe HandleFinalizer -> Maybe (MVar Handle__) -> IO Handle forall dev. (IODevice dev, BufferedIO dev, Typeable dev) => dev -> FilePath -> HandleType -> Bool -> Maybe TextEncoding -> NewlineMode -> Maybe HandleFinalizer -> Maybe (MVar Handle__) -> IO Handle mkHandle FD FD.stdout "<stdout>"HandleType WriteHandle Bool True(TextEncoding -> Maybe TextEncoding forall a. a -> Maybe a Just TextEncoding enc )NewlineMode nativeNewlineMode {-translate newlines-}(HandleFinalizer -> Maybe HandleFinalizer forall a. a -> Maybe a Just HandleFinalizer stdHandleFinalizer )Maybe (MVar Handle__) forall a. Maybe a Nothing -- | A handle managing output to the Haskell program's standard error channel.stderr ::Handle {-# NOINLINEstderr #-}stderr :: Handle stderr =IO Handle -> Handle forall a. IO a -> a unsafePerformIO (IO Handle -> Handle) -> IO Handle -> Handle forall a b. (a -> b) -> a -> b $ do-- ToDo: acquire lockFD -> IO () setBinaryMode FD FD.stderr TextEncoding enc <-IO TextEncoding getLocaleEncoding FD -> FilePath -> HandleType -> Bool -> Maybe TextEncoding -> NewlineMode -> Maybe HandleFinalizer -> Maybe (MVar Handle__) -> IO Handle forall dev. (IODevice dev, BufferedIO dev, Typeable dev) => dev -> FilePath -> HandleType -> Bool -> Maybe TextEncoding -> NewlineMode -> Maybe HandleFinalizer -> Maybe (MVar Handle__) -> IO Handle mkHandle FD FD.stderr "<stderr>"HandleType WriteHandle Bool False{-stderr is unbuffered-}(TextEncoding -> Maybe TextEncoding forall a. a -> Maybe a Just TextEncoding enc )NewlineMode nativeNewlineMode {-translate newlines-}(HandleFinalizer -> Maybe HandleFinalizer forall a. a -> Maybe a Just HandleFinalizer stdHandleFinalizer )Maybe (MVar Handle__) forall a. Maybe a Nothing stdHandleFinalizer ::FilePath ->MVar Handle__ ->IO()stdHandleFinalizer :: HandleFinalizer stdHandleFinalizer fp :: FilePath fp m :: MVar Handle__ m =doHandle__ h_ <-MVar Handle__ -> IO Handle__ forall a. MVar a -> IO a takeMVar MVar Handle__ m Handle__ -> IO () flushWriteBuffer Handle__ h_ caseHandle__ -> HandleType haType Handle__ h_ ofClosedHandle ->() -> IO () forall (m :: * -> *) a. Monad m => a -> m a return ()_other :: HandleType _other ->Handle__ -> IO () closeTextCodecs Handle__ h_ MVar Handle__ -> Handle__ -> IO () forall a. MVar a -> a -> IO () putMVar MVar Handle__ m (FilePath -> Handle__ ioe_finalizedHandle FilePath fp )-- We have to put the FDs into binary mode on Windows to avoid the newline-- translation that the CRT IO library does.setBinaryMode ::FD.FD ->IO() #if defined(mingw32_HOST_OS) setBinaryModefd=do_<-setmode(FD.fdFDfd)Truereturn() #else setBinaryMode :: FD -> IO () setBinaryMode _=() -> IO () forall (m :: * -> *) a. Monad m => a -> m a return () #endif #if defined(mingw32_HOST_OS) foreignimportccallunsafe"__hscore_setmode"setmode::CInt->Bool->IOCInt #endif -- ----------------------------------------------------------------------------- Opening and Closing FilesaddFilePathToIOError ::String ->FilePath ->IOException ->IOException addFilePathToIOError :: FilePath -> FilePath -> IOException -> IOException addFilePathToIOError fun :: FilePath fun fp :: FilePath fp ioe :: IOException ioe =IOException ioe {ioe_location :: FilePath ioe_location =FilePath fun ,ioe_filename :: Maybe FilePath ioe_filename =FilePath -> Maybe FilePath forall a. a -> Maybe a Just FilePath fp }-- | Computation 'openFile' @file mode@ allocates and returns a new, open-- handle to manage the file @file@. It manages input if @mode@-- is 'ReadMode', output if @mode@ is 'WriteMode' or 'AppendMode',-- and both input and output if mode is 'ReadWriteMode'.---- If the file does not exist and it is opened for output, it should be-- created as a new file. If @mode@ is 'WriteMode' and the file-- already exists, then it should be truncated to zero length.-- Some operating systems delete empty files, so there is no guarantee-- that the file will exist following an 'openFile' with @mode@-- 'WriteMode' unless it is subsequently written to successfully.-- The handle is positioned at the end of the file if @mode@ is-- 'AppendMode', and otherwise at the beginning (in which case its-- internal position is 0).-- The initial buffer mode is implementation-dependent.---- This operation may fail with:---- * 'System.IO.Error.isAlreadyInUseError' if the file is already open and-- cannot be reopened;---- * 'System.IO.Error.isDoesNotExistError' if the file does not exist or-- (on POSIX systems) is a FIFO without a reader and 'WriteMode' was-- requested; or---- * 'System.IO.Error.isPermissionError' if the user does not have permission-- to open the file.---- Note: if you will be working with files containing binary data, you'll want to-- be using 'openBinaryFile'.openFile ::FilePath ->IOMode ->IOHandle openFile :: FilePath -> IOMode -> IO Handle openFile fp :: FilePath fp im :: IOMode im =IO Handle -> (IOException -> IO Handle) -> IO Handle forall e a. Exception e => IO a -> (e -> IO a) -> IO a catchException (FilePath -> IOMode -> Bool -> Bool -> IO Handle openFile' FilePath fp IOMode im Bool dEFAULT_OPEN_IN_BINARY_MODE Bool True)(\e :: IOException e ->IOException -> IO Handle forall a. IOException -> IO a ioError (FilePath -> FilePath -> IOException -> IOException addFilePathToIOError "openFile"FilePath fp IOException e ))-- | Like 'openFile', but opens the file in ordinary blocking mode.-- This can be useful for opening a FIFO for writing: if we open in-- non-blocking mode then the open will fail if there are no readers,-- whereas a blocking open will block until a reader appear.---- @since 4.4.0.0openFileBlocking ::FilePath ->IOMode ->IOHandle openFileBlocking :: FilePath -> IOMode -> IO Handle openFileBlocking fp :: FilePath fp im :: IOMode im =IO Handle -> (IOException -> IO Handle) -> IO Handle forall e a. Exception e => IO a -> (e -> IO a) -> IO a catchException (FilePath -> IOMode -> Bool -> Bool -> IO Handle openFile' FilePath fp IOMode im Bool dEFAULT_OPEN_IN_BINARY_MODE Bool False)(\e :: IOException e ->IOException -> IO Handle forall a. IOException -> IO a ioError (FilePath -> FilePath -> IOException -> IOException addFilePathToIOError "openFile"FilePath fp IOException e ))-- | Like 'openFile', but open the file in binary mode.-- On Windows, reading a file in text mode (which is the default)-- will translate CRLF to LF, and writing will translate LF to CRLF.-- This is usually what you want with text files. With binary files-- this is undesirable; also, as usual under Microsoft operating systems,-- text mode treats control-Z as EOF. Binary mode turns off all special-- treatment of end-of-line and end-of-file characters.-- (See also 'System.IO.hSetBinaryMode'.)openBinaryFile ::FilePath ->IOMode ->IOHandle openBinaryFile :: FilePath -> IOMode -> IO Handle openBinaryFile fp :: FilePath fp m :: IOMode m =IO Handle -> (IOException -> IO Handle) -> IO Handle forall e a. Exception e => IO a -> (e -> IO a) -> IO a catchException (FilePath -> IOMode -> Bool -> Bool -> IO Handle openFile' FilePath fp IOMode m Bool TrueBool True)(\e :: IOException e ->IOException -> IO Handle forall a. IOException -> IO a ioError (FilePath -> FilePath -> IOException -> IOException addFilePathToIOError "openBinaryFile"FilePath fp IOException e ))openFile' ::String ->IOMode ->Bool->Bool->IOHandle openFile' :: FilePath -> IOMode -> Bool -> Bool -> IO Handle openFile' filepath :: FilePath filepath iomode :: IOMode iomode binary :: Bool binary non_blocking :: Bool non_blocking =do-- first open the file to get an FD(fd :: FD fd ,fd_type :: IODeviceType fd_type )<-FilePath -> IOMode -> Bool -> IO (FD, IODeviceType) FD.openFile FilePath filepath IOMode iomode Bool non_blocking Maybe TextEncoding mb_codec <-ifBool binary thenMaybe TextEncoding -> IO (Maybe TextEncoding) forall (m :: * -> *) a. Monad m => a -> m a return Maybe TextEncoding forall a. Maybe a Nothing else(TextEncoding -> Maybe TextEncoding) -> IO TextEncoding -> IO (Maybe TextEncoding) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b fmap TextEncoding -> Maybe TextEncoding forall a. a -> Maybe a Just IO TextEncoding getLocaleEncoding -- then use it to make a HandleFD -> IODeviceType -> FilePath -> IOMode -> Bool -> Maybe TextEncoding -> IO Handle mkHandleFromFD FD fd IODeviceType fd_type FilePath filepath IOMode iomode Bool False{- do not *set* non-blocking mode -}Maybe TextEncoding mb_codec IO Handle -> IO () -> IO Handle forall a b. IO a -> IO b -> IO a `onException` FD -> IO () forall a. IODevice a => a -> IO () IODevice.close FD fd -- NB. don't forget to close the FD if mkHandleFromFD fails, otherwise-- this FD leaks.-- ASSERT: if we just created the file, then fdToHandle' won't fail-- (so we don't need to worry about removing the newly created file-- in the event of an error).-- ----------------------------------------------------------------------------- Converting file descriptors from/to HandlesmkHandleFromFD ::FD.FD ->IODeviceType ->FilePath -- a string describing this file descriptor (e.g. the filename)->IOMode ->Bool-- *set* non-blocking mode on the FD->Maybe TextEncoding ->IOHandle mkHandleFromFD :: FD -> IODeviceType -> FilePath -> IOMode -> Bool -> Maybe TextEncoding -> IO Handle mkHandleFromFD fd0 :: FD fd0 fd_type :: IODeviceType fd_type filepath :: FilePath filepath iomode :: IOMode iomode set_non_blocking :: Bool set_non_blocking mb_codec :: Maybe TextEncoding mb_codec =do #if !defined(mingw32_HOST_OS) -- turn on non-blocking modeFD fd <-ifBool set_non_blocking thenFD -> Bool -> IO FD FD.setNonBlockingMode FD fd0 Bool TrueelseFD -> IO FD forall (m :: * -> *) a. Monad m => a -> m a return FD fd0 #else let_=set_non_blocking-- warning suppressionfd<-returnfd0 #endif letnl :: NewlineMode nl |Maybe TextEncoding -> Bool forall a. Maybe a -> Bool isJust Maybe TextEncoding mb_codec =NewlineMode nativeNewlineMode |Bool otherwise =NewlineMode noNewlineTranslation caseIODeviceType fd_type ofDirectory ->IOException -> IO Handle forall a. IOException -> IO a ioException (Maybe Handle -> IOErrorType -> FilePath -> FilePath -> Maybe CInt -> Maybe FilePath -> IOException IOError Maybe Handle forall a. Maybe a Nothing IOErrorType InappropriateType "openFile""is a directory"Maybe CInt forall a. Maybe a Nothing Maybe FilePath forall a. Maybe a Nothing )Stream -- only *Streams* can be DuplexHandles. Other read/write-- Handles must share a buffer.|IOMode ReadWriteMode <-IOMode iomode ->FD -> FilePath -> Maybe TextEncoding -> NewlineMode -> IO Handle forall dev. (IODevice dev, BufferedIO dev, Typeable dev) => dev -> FilePath -> Maybe TextEncoding -> NewlineMode -> IO Handle mkDuplexHandle FD fd FilePath filepath Maybe TextEncoding mb_codec NewlineMode nl _other :: IODeviceType _other ->FD -> FilePath -> IOMode -> Maybe TextEncoding -> NewlineMode -> IO Handle forall dev. (IODevice dev, BufferedIO dev, Typeable dev) => dev -> FilePath -> IOMode -> Maybe TextEncoding -> NewlineMode -> IO Handle mkFileHandle FD fd FilePath filepath IOMode iomode Maybe TextEncoding mb_codec NewlineMode nl -- | Old API kept to avoid breaking clientsfdToHandle' ::CInt ->Maybe IODeviceType ->Bool-- is_socket on Win, non-blocking on Unix->FilePath ->IOMode ->Bool-- binary->IOHandle fdToHandle' :: CInt -> Maybe IODeviceType -> Bool -> FilePath -> IOMode -> Bool -> IO Handle fdToHandle' fdint :: CInt fdint mb_type :: Maybe IODeviceType mb_type is_socket :: Bool is_socket filepath :: FilePath filepath iomode :: IOMode iomode binary :: Bool binary =doletmb_stat :: Maybe (IODeviceType, CDev, CIno) mb_stat =caseMaybe IODeviceType mb_type ofNothing ->Maybe (IODeviceType, CDev, CIno) forall a. Maybe a Nothing -- mkFD will do the stat:Just RegularFile ->Maybe (IODeviceType, CDev, CIno) forall a. Maybe a Nothing -- no stat required for streams etc.:Just other :: IODeviceType other ->(IODeviceType, CDev, CIno) -> Maybe (IODeviceType, CDev, CIno) forall a. a -> Maybe a Just (IODeviceType other ,0,0)(fd :: FD fd ,fd_type :: IODeviceType fd_type )<-CInt -> IOMode -> Maybe (IODeviceType, CDev, CIno) -> Bool -> Bool -> IO (FD, IODeviceType) FD.mkFD CInt fdint IOMode iomode Maybe (IODeviceType, CDev, CIno) mb_stat Bool is_socket Bool is_socket Maybe TextEncoding enc <-ifBool binary thenMaybe TextEncoding -> IO (Maybe TextEncoding) forall (m :: * -> *) a. Monad m => a -> m a return Maybe TextEncoding forall a. Maybe a Nothing else(TextEncoding -> Maybe TextEncoding) -> IO TextEncoding -> IO (Maybe TextEncoding) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b fmap TextEncoding -> Maybe TextEncoding forall a. a -> Maybe a Just IO TextEncoding getLocaleEncoding FD -> IODeviceType -> FilePath -> IOMode -> Bool -> Maybe TextEncoding -> IO Handle mkHandleFromFD FD fd IODeviceType fd_type FilePath filepath IOMode iomode Bool is_socket Maybe TextEncoding enc -- | Turn an existing file descriptor into a Handle. This is used by-- various external libraries to make Handles.---- Makes a binary Handle. This is for historical reasons; it should-- probably be a text Handle with the default encoding and newline-- translation instead.fdToHandle ::Posix.FD ->IOHandle fdToHandle :: CInt -> IO Handle fdToHandle fdint :: CInt fdint =doIOMode iomode <-CInt -> IO IOMode Posix.fdGetMode CInt fdint (fd :: FD fd ,fd_type :: IODeviceType fd_type )<-CInt -> IOMode -> Maybe (IODeviceType, CDev, CIno) -> Bool -> Bool -> IO (FD, IODeviceType) FD.mkFD CInt fdint IOMode iomode Maybe (IODeviceType, CDev, CIno) forall a. Maybe a Nothing Bool False{-is_socket-}-- NB. the is_socket flag is False, meaning that:-- on Windows we're guessing this is not a socket (XXX)Bool False{-is_nonblock-}-- file descriptors that we get from external sources are-- not put into non-blocking mode, because that would affect-- other users of the file descriptorletfd_str :: FilePath fd_str ="<file descriptor: "FilePath -> FilePath -> FilePath forall a. [a] -> [a] -> [a] ++ FD -> FilePath forall a. Show a => a -> FilePath show FD fd FilePath -> FilePath -> FilePath forall a. [a] -> [a] -> [a] ++ ">"FD -> IODeviceType -> FilePath -> IOMode -> Bool -> Maybe TextEncoding -> IO Handle mkHandleFromFD FD fd IODeviceType fd_type FilePath fd_str IOMode iomode Bool False{-non-block-}Maybe TextEncoding forall a. Maybe a Nothing -- bin mode-- | Turn an existing Handle into a file descriptor. This function throws an-- IOError if the Handle does not reference a file descriptor.handleToFd ::Handle ->IOFD.FD handleToFd :: Handle -> IO FD handleToFd h :: Handle h =caseHandle h ofFileHandle _mv :: MVar Handle__ mv ->doHandle__ {haDevice :: () haDevice =dev dev }<-MVar Handle__ -> IO Handle__ forall a. MVar a -> IO a readMVar MVar Handle__ mv casedev -> Maybe FD forall a b. (Typeable a, Typeable b) => a -> Maybe b cast dev dev ofJust fd :: FD fd ->FD -> IO FD forall (m :: * -> *) a. Monad m => a -> m a return FD fd Nothing ->FilePath -> IO FD forall a. FilePath -> IO a throwErr "not a file descriptor"DuplexHandle {}->FilePath -> IO FD forall a. FilePath -> IO a throwErr "not a file handle"wherethrowErr :: FilePath -> IO a throwErr msg :: FilePath msg =IOException -> IO a forall a. IOException -> IO a ioException (IOException -> IO a) -> IOException -> IO a forall a b. (a -> b) -> a -> b $ Maybe Handle -> IOErrorType -> FilePath -> FilePath -> Maybe CInt -> Maybe FilePath -> IOException IOError (Handle -> Maybe Handle forall a. a -> Maybe a Just Handle h )IOErrorType InappropriateType "handleToFd"FilePath msg Maybe CInt forall a. Maybe a Nothing Maybe FilePath forall a. Maybe a Nothing -- ----------------------------------------------------------------------------- Are files opened by default in text or binary mode, if the user doesn't-- specify?dEFAULT_OPEN_IN_BINARY_MODE ::BooldEFAULT_OPEN_IN_BINARY_MODE :: Bool dEFAULT_OPEN_IN_BINARY_MODE =Bool False