diff --git a/libraries/base/src/GHC/IO/Handle.hs b/libraries/base/src/GHC/IO/Handle.hs index 319b39e14584d79c95eb735aa5f72b3fe43b7ae5..6a4531b8dc500a8b6f01230cd49ca779f9d92a50 100644 --- a/libraries/base/src/GHC/IO/Handle.hs +++ b/libraries/base/src/GHC/IO/Handle.hs @@ -73,4 +73,4 @@ module GHC.IO.Handle hPutBufNonBlocking ) where -import GHC.Internal.IO.Handle \ No newline at end of file +import GHC.Internal.IO.Handle diff --git a/libraries/base/src/GHC/IO/StdHandles.hs b/libraries/base/src/GHC/IO/StdHandles.hs index 978435175293601e514601a13204826a9df373ab..e51480c87cfac61f4f26e923508c0c7538870859 100644 --- a/libraries/base/src/GHC/IO/StdHandles.hs +++ b/libraries/base/src/GHC/IO/StdHandles.hs @@ -26,4 +26,4 @@ module GHC.IO.StdHandles withFileBlocking ) where -import GHC.Internal.IO.StdHandles \ No newline at end of file +import GHC.Internal.IO.StdHandles diff --git a/libraries/base/src/System/IO.hs b/libraries/base/src/System/IO.hs index c4b7d2bbaba40a93978b02250a7bfab532a76c9d..0c99974eb11df14f0ba75f83517d4ab89e41b72b 100644 --- a/libraries/base/src/System/IO.hs +++ b/libraries/base/src/System/IO.hs @@ -14,7 +14,10 @@ -- module System.IO - (-- * The IO monad + (-- * Examples + -- $stdio_examples + + -- * The IO monad IO, fixIO, -- * Files and handles @@ -199,3 +202,18 @@ import GHC.Internal.System.IO -- It follows that an attempt to write to a file (using 'writeFile', for -- example) that was earlier opened by 'readFile' will usually result in -- failure with 'GHC.Internal.System.IO.Error.isAlreadyInUseError'. + +-- $stdio_examples +-- Note: Some of the examples in this module do not work "as is" in ghci. +-- This is because using 'stdin' in combination with lazy IO +-- does not work well in interactive mode. +-- +-- Lines starting with @>@ indicate 'stdin' and @^D@ signales EOF. +-- +-- ==== __Example__ +-- +-- >>> foo +-- > input +-- output +-- > input^D +-- output diff --git a/libraries/ghc-internal/src/GHC/Internal/IO/Handle.hs b/libraries/ghc-internal/src/GHC/Internal/IO/Handle.hs index 1cec0dcc7a260aac1fd4dc4a43a8f4de9026511c..596031254b4acd9d73c892b1ea7f2b4f8278c1dd 100644 --- a/libraries/ghc-internal/src/GHC/Internal/IO/Handle.hs +++ b/libraries/ghc-internal/src/GHC/Internal/IO/Handle.hs @@ -74,6 +74,7 @@ import GHC.Internal.Real import GHC.Internal.Data.Maybe import GHC.Internal.Data.Typeable + -- --------------------------------------------------------------------------- -- Closing a handle @@ -468,6 +469,9 @@ hTell handle = -- handle. Each of these operations returns `True' if the handle has -- the specified property, and `False' otherwise. +-- | @'hIsOpen' hdl@ returns whether the handle is open. +-- If the 'haType' of @hdl@ is 'ClosedHandle' or 'SemiClosedHandle' this returns 'False' +-- and 'True' otherwise. hIsOpen :: Handle -> IO Bool hIsOpen handle = withHandle_ "hIsOpen" handle $ \ handle_ -> do @@ -476,6 +480,9 @@ hIsOpen handle = SemiClosedHandle -> return False _ -> return True +-- | @'hIsOpen' hdl@ returns whether the handle is closed. +-- If the 'haType' of @hdl@ is 'ClosedHandle' this returns 'True' +-- and 'False' otherwise. hIsClosed :: Handle -> IO Bool hIsClosed handle = withHandle_ "hIsClosed" handle $ \ handle_ -> do @@ -493,6 +500,7 @@ hIsClosed handle = return (not (ho || hc)) -} +-- | @'hIsReadable' hdl@ returns whether it is possible to read from the handle. hIsReadable :: Handle -> IO Bool hIsReadable (DuplexHandle _ _ _) = return True hIsReadable handle = @@ -502,6 +510,7 @@ hIsReadable handle = SemiClosedHandle -> ioe_semiclosedHandle htype -> return (isReadableHandleType htype) +-- | @'hIsWritable' hdl@ returns whether it is possible to write to the handle. hIsWritable :: Handle -> IO Bool hIsWritable (DuplexHandle _ _ _) = return True hIsWritable handle = @@ -524,6 +533,7 @@ hGetBuffering handle = -- of a semi-closed handle to be queried. -- sof 6/98 return (haBufferMode handle_) -- could be stricter.. +-- | @'hIsSeekable' hdl@ returns whether it is possible to 'hSeek' with the given handle. hIsSeekable :: Handle -> IO Bool hIsSeekable handle = withHandle_ "hIsSeekable" handle $ \ handle_@Handle__{..} -> do @@ -775,4 +785,3 @@ showHandle' filepath is_duplex h = where def :: Int def = bufSize buf - diff --git a/libraries/ghc-internal/src/GHC/Internal/IO/Handle/Text.hs b/libraries/ghc-internal/src/GHC/Internal/IO/Handle/Text.hs index 18a4d77865603ce3864cdc820b6505a56b4c8da5..c62a08138e2e0dbfc80727ffc123586e25ad25e1 100644 --- a/libraries/ghc-internal/src/GHC/Internal/IO/Handle/Text.hs +++ b/libraries/ghc-internal/src/GHC/Internal/IO/Handle/Text.hs @@ -484,8 +484,9 @@ getSomeCharacters handle_@Handle__{..} buf@Buffer{..} = -- | The 'hGetContents'' operation reads all input on the given handle -- before returning it as a 'String' and closing the handle. -- +-- This is a strict version of 'hGetContents' +-- -- @since base-4.15.0.0 - hGetContents' :: Handle -> IO String hGetContents' handle = do es <- wantReadableHandle "hGetContents'" handle (strictRead handle) @@ -565,7 +566,7 @@ lazyBuffersToString CRLF = loop '\0' where -- -- This operation may fail with: -- --- * 'isFullError' if the device is full; or +-- * 'isFullError' if the device is full. -- -- * 'isPermissionError' if another system resource limit would be exceeded. @@ -623,16 +624,28 @@ hPutcBuffered handle_@Handle__{..} c = do -- | Computation 'hPutStr' @hdl s@ writes the string -- @s@ to the file or channel managed by @hdl@. -- +-- Note that 'hPutStr' is not concurrency safe unless the 'BufferMode' of +-- @hdl@ is set to 'LineBuffering' or 'BlockBuffering': +-- +-- >>> let f = forkIO . hPutStr stdout +-- >>> in do hSetBuffering stdout NoBuffering; f "This is a longer string"; f ":D"; f "Hello Haskell"; pure () +-- This: HDiesl lao lHoansgkeerl lstring +-- +-- >>> let f = forkIO . hPutStr stdout +-- >>> in do hSetBuffering stdout LineBuffering; f "This is a longer string"; f ":D"; f "Hello Haskell"; pure () +-- This is a longer string:DHello Haskell +-- -- This operation may fail with: -- --- * 'isFullError' if the device is full; or +-- * 'isFullError' if the device is full. -- -- * 'isPermissionError' if another system resource limit would be exceeded. - hPutStr :: Handle -> String -> IO () hPutStr handle str = hPutStr' handle str False -- | The same as 'hPutStr', but adds a newline character. +-- +-- This operation may fail with the same errors, and has the same issues with concurrency, as 'hPutStr'! hPutStrLn :: Handle -> String -> IO () hPutStrLn handle str = hPutStr' handle str True @@ -1176,4 +1189,3 @@ illegalBufferSize handle fn sz = InvalidArgument fn ("illegal buffer size " ++ showsPrec 9 sz []) Nothing Nothing) - diff --git a/libraries/ghc-internal/src/GHC/Internal/IO/Handle/Types.hs b/libraries/ghc-internal/src/GHC/Internal/IO/Handle/Types.hs index bf3be8e1a3c1e737b12f0d77af61094a37f9bc7d..6e02a771d760c76830e4a90e85c5482489bfd26b 100644 --- a/libraries/ghc-internal/src/GHC/Internal/IO/Handle/Types.hs +++ b/libraries/ghc-internal/src/GHC/Internal/IO/Handle/Types.hs @@ -162,21 +162,29 @@ data HandleType | AppendHandle | ReadWriteHandle +-- | @'isReadableHandleType' hdlType@ returns 'True' if +-- @hdlType@ is one of 'ReadHandle' and 'ReadWriteHandle'. isReadableHandleType :: HandleType -> Bool isReadableHandleType ReadHandle = True isReadableHandleType ReadWriteHandle = True isReadableHandleType _ = False +-- | @'isWritableHandleType' hdlType@ returns 'True' if +-- @hdlType@ is one of 'AppendHandle', 'WriteHandle' and 'ReadWriteHandle'. isWritableHandleType :: HandleType -> Bool isWritableHandleType AppendHandle = True isWritableHandleType WriteHandle = True isWritableHandleType ReadWriteHandle = True isWritableHandleType _ = False +-- | @'isReadWriteHandleType' hdlType@ returns 'True' if +-- @hdlType@ is 'ReadWriteHandle'. isReadWriteHandleType :: HandleType -> Bool isReadWriteHandleType ReadWriteHandle{} = True isReadWriteHandleType _ = False +-- | @'isAppendHandleType' hdlType@ returns 'True' if +-- @hdlType@ is 'AppendHandle'. isAppendHandleType :: HandleType -> Bool isAppendHandleType AppendHandle = True isAppendHandleType _ = False @@ -450,4 +458,3 @@ instance Show Handle where showHandle :: FilePath -> String -> String showHandle file = showString "{handle: " . showString file . showString "}" - diff --git a/libraries/ghc-internal/src/GHC/Internal/IO/StdHandles.hs b/libraries/ghc-internal/src/GHC/Internal/IO/StdHandles.hs index 352ecc879e2b46936059e8a5a9a8355967467adf..a71c71685538417fb985c65128a04231315fc826 100644 --- a/libraries/ghc-internal/src/GHC/Internal/IO/StdHandles.hs +++ b/libraries/ghc-internal/src/GHC/Internal/IO/StdHandles.hs @@ -29,72 +29,122 @@ import GHC.Internal.IO.IOMode import GHC.Internal.IO.Handle.Types import qualified GHC.Internal.IO.Handle.FD as POSIX + +-- windows only imports #if defined(mingw32_HOST_OS) import GHC.Internal.IO.SubSystem import qualified GHC.Internal.IO.Handle.Windows as Win import GHC.Internal.IO.Handle.Internals (hClose_impl) +#endif +-- | 'stdin' is a handle managing the programs standard input. stdin :: Handle +#if defined(mingw32_HOST_OS) stdin = POSIX.stdin <!> Win.stdin +#else +stdin = POSIX.stdin +#endif +-- | 'stdout' is a handle managing the programs standard output. stdout :: Handle +#if defined(mingw32_HOST_OS) stdout = POSIX.stdout <!> Win.stdout +#else +stdout = POSIX.stdout +#endif +-- | 'stderr' is a handle managing the programs standard error. stderr :: Handle +#if defined(mingw32_HOST_OS) stderr = POSIX.stderr <!> Win.stderr +#else +stderr = POSIX.stderr +#endif -openFile :: FilePath -> IOMode -> IO Handle +-- | The computation @'openFile' path mode@ returns a file handle that can be +-- used to interact with the file. +-- +-- The handle is open in text mode with 'System.IO.localeEncoding'. +-- You can change the encoding with 'System.IO.hSetEncoding'. +openFile + :: FilePath -- ^ The path to the file that should be opened + -> IOMode -- ^ The mode in which the file should be opened + -> IO Handle +#if defined(mingw32_HOST_OS) openFile = POSIX.openFile <!> Win.openFile +#else +openFile = POSIX.openFile +#endif +-- | The computation @'openBinaryFile' path mode@ returns a file handle that can be +-- used to interact with the binary file. +-- +-- This is different from 'openFile' as in that it does not use any file encoding. +openBinaryFile + :: FilePath -- ^ The path to the binary file that should be opened + -> IOMode -- ^ The mode in which the binary file should be opened + -> IO Handle +#if defined(mingw32_HOST_OS) +openBinaryFile = POSIX.openBinaryFile <!> Win.openBinaryFile +#else +openBinaryFile = POSIX.openBinaryFile +#endif + +-- | The computation @'withFile' path mode action@ opens the file and runs @action@ +-- with the obtained handle before closing the file. +-- +-- Even when an exception is raised within the 'action', the file will still be closed. +-- This is why @'withFile' path mode act@ is preferable to +-- +-- @'openFile' path mode >>= (\\hdl -> act hdl >>= 'System.IO.hClose' hdl)@ +-- +-- See also: 'System.IO.bracket' +withFile + :: FilePath -- ^ The path to the file that should be opened + -> IOMode -- ^ The mode in which the file should be opened + -> (Handle -> IO r) -- ^ The action to run with the obtained handle + -> IO r +#if defined(mingw32_HOST_OS) -- TODO: implement as for POSIX -withFile :: FilePath -> IOMode -> (Handle -> IO r) -> IO r withFile = POSIX.withFile <!> wf where wf path mode act = bracket (Win.openFile path mode) hClose_impl act +#else +withFile = POSIX.withFile +#endif -openBinaryFile :: FilePath -> IOMode -> IO Handle -openBinaryFile = POSIX.openBinaryFile <!> Win.openBinaryFile - +-- | The computation @'withBinaryFile' path mode action@ opens the binary file +-- and runs @action@ with the obtained handle before closing the binary file. +-- +-- This is different from 'withFile' as in that it does not use any file encoding. +-- +-- Even when an exception is raised within the 'action', the file will still be closed. +-- This is why @'withBinaryFile' path mode act@ is preferable to +-- +-- @'openBinaryFile' path mode >>= (\\hdl -> act hdl >>= 'System.IO.hClose' hdl)@ +-- +-- See also: 'System.IO.bracket' withBinaryFile :: FilePath -> IOMode -> (Handle -> IO r) -> IO r +#if defined(mingw32_HOST_OS) withBinaryFile = POSIX.withBinaryFile <!> wf where wf path mode act = bracket (Win.openBinaryFile path mode) hClose_impl act +#else +withBinaryFile = POSIX.withBinaryFile +#endif openFileBlocking :: FilePath -> IOMode -> IO Handle +#if defined(mingw32_HOST_OS) openFileBlocking = POSIX.openFileBlocking <!> Win.openFileBlocking +#else +openFileBlocking = POSIX.openFileBlocking +#endif withFileBlocking :: FilePath -> IOMode -> (Handle -> IO r) -> IO r +#if defined(mingw32_HOST_OS) withFileBlocking = POSIX.withFileBlocking <!> wf where wf path mode act = bracket (Win.openFileBlocking path mode) hClose_impl act - #else - -stdin :: Handle -stdin = POSIX.stdin - -stdout :: Handle -stdout = POSIX.stdout - -stderr :: Handle -stderr = POSIX.stderr - -openFile :: FilePath -> IOMode -> IO Handle -openFile = POSIX.openFile - -withFile :: FilePath -> IOMode -> (Handle -> IO r) -> IO r -withFile = POSIX.withFile - -openBinaryFile :: FilePath -> IOMode -> IO Handle -openBinaryFile = POSIX.openBinaryFile - -withBinaryFile :: FilePath -> IOMode -> (Handle -> IO r) -> IO r -withBinaryFile = POSIX.withBinaryFile - -openFileBlocking :: FilePath -> IOMode -> IO Handle -openFileBlocking = POSIX.openFileBlocking - -withFileBlocking :: FilePath -> IOMode -> (Handle -> IO r) -> IO r withFileBlocking = POSIX.withFileBlocking - #endif diff --git a/libraries/ghc-internal/src/GHC/Internal/System/IO.hs b/libraries/ghc-internal/src/GHC/Internal/System/IO.hs index 5e733f7e09e34890e4bfad950c5948e8c4063c63..2fb186c6c829b4f638403b525137ff8a19455bde 100644 --- a/libraries/ghc-internal/src/GHC/Internal/System/IO.hs +++ b/libraries/ghc-internal/src/GHC/Internal/System/IO.hs @@ -257,24 +257,49 @@ import GHC.Internal.Text.Read import GHC.Internal.IO.StdHandles import GHC.Internal.Show import GHC.Internal.MVar - --- ----------------------------------------------------------------------------- +----------------------------------------------------------------------------- -- Standard IO -- | Write a character to the standard output device --- (same as 'hPutChar' 'stdout'). - +-- +-- 'putChar' is implemented as @'hPutChar' 'stdout'@. +-- +-- This operation may fail with the same errors as 'hPutChar'. +-- +-- ==== __Examples__ +-- +-- Note that the following do not put a newline. +-- +-- >>> putChar 'x' +-- x +-- +-- >>> putChar '\0042' +-- * putChar :: Char -> IO () putChar c = hPutChar stdout c -- | Write a string to the standard output device --- (same as 'hPutStr' 'stdout'). - +-- +-- 'putStr' is implemented as @'hPutStr' 'stdout'@. +-- +-- This operation may fail with the same errors, and has the same issues with concurrency, as 'hPutStr'! +-- +-- ==== __Examples__ +-- +-- Note that the following do not put a newline. +-- +-- >>> putStr "Hello, World!" +-- Hello, World! +-- +-- >>> putStr "\0052\0042\0050" +-- 4*2 +-- putStr :: String -> IO () putStr s = hPutStr stdout s -- | The same as 'putStr', but adds a newline character. - +-- +-- This operation may fail with the same errors, and has the same issues with concurrency, as 'hPutStr'! putStrLn :: String -> IO () putStrLn s = hPutStrLn stdout s @@ -284,94 +309,242 @@ putStrLn s = hPutStrLn stdout s -- converts values to strings for output using the 'show' operation and -- adds a newline. -- --- For example, a program to print the first 20 integers and their +-- 'print' is implemented as @'putStrLn' '.' 'show'@ +-- +-- This operation may fail with the same errors, and has the same issues with concurrency, as 'hPutStr'! +-- +-- ==== __Examples__ +-- +-- >>> print [1, 2, 3] +-- [1,2,3] +-- +-- Be careful when using 'print' for outputting strings, +-- as this will invoke 'show' and cause strings to be printed +-- with quotation marks and non-ascii symbols escaped. +-- +-- >>> print "λ :D" +-- "\995 :D" +-- +-- A program to print the first 8 integers and their -- powers of 2 could be written as: -- --- > main = print ([(n, 2^n) | n <- [0..19]]) - +-- >>> print [(n, 2^n) | n <- [0..8]] +-- [(0,1),(1,2),(2,4),(3,8),(4,16),(5,32),(6,64),(7,128),(8,256)] print :: Show a => a -> IO () print x = putStrLn (show x) --- | Read a character from the standard input device --- (same as 'hGetChar' 'stdin'). - +-- | Read a single character from the standard input device. +-- +-- 'getChar' is implemented as @'hGetChar' 'stdin'@. +-- +-- This operation may fail with the same errors as 'hGetChar'. +-- +-- ==== __Examples__ +-- +-- >>> getChar +-- a'a' +-- +-- >>> getChar +-- > +-- '\n' getChar :: IO Char getChar = hGetChar stdin --- | Read a line from the standard input device --- (same as 'hGetLine' 'stdin'). - +-- | Read a line from the standard input device. +-- +-- 'getLine' is implemented as @'hGetLine' 'stdin'@. +-- +-- This operation may fail with the same errors as 'hGetLine'. +-- +-- ==== __Examples__ +-- +-- >>> getLine +-- > Hello World! +-- "Hello World!" +-- +-- >>> getLine +-- > +-- "" getLine :: IO String getLine = hGetLine stdin -- | The 'getContents' operation returns all user input as a single string, --- which is read lazily as it is needed --- (same as 'hGetContents' 'stdin'). - +-- which is read lazily as it is needed. +-- +-- 'getContents' is implemented as @'hGetContents' 'stdin'@. +-- +-- This operation may fail with the same errors as 'hGetContents'. +-- +-- ==== __Examples__ +-- +-- >>> getContents >>= putStr +-- > aaabbbccc :D +-- aaabbbccc :D +-- > I hope you have a great day +-- I hope you have a great day +-- > ^D +-- +-- >>> getContents >>= print . length +-- > abc +-- > <3 +-- > def ^D +-- 11 getContents :: IO String getContents = hGetContents stdin -- | The 'getContents'' operation returns all user input as a single string, -- which is fully read before being returned --- (same as 'hGetContents'' 'stdin'). +-- +-- 'getContents'' is implemented as @'hGetContents'' 'stdin'@. +-- +-- This operation may fail with the same errors as 'hGetContents''. +-- +-- ==== __Examples__ +-- +-- >>> getContents' >>= putStr +-- > aaabbbccc :D +-- > I hope you have a great day +-- aaabbbccc :D +-- I hope you have a great day +-- +-- >>> getContents' >>= print . length +-- > abc +-- > <3 +-- > def ^D +-- 11 -- -- @since base-4.15.0.0 - getContents' :: IO String getContents' = hGetContents' stdin --- | The 'interact' function takes a function of type @String->String@ --- as its argument. The entire input from the standard input device is --- passed to this function as its argument, and the resulting string is --- output on the standard output device. - +-- | @'interact' f@ takes the entire input from 'stdin' and applies @f@ to it. +-- The resulting string is written to the 'stdout' device. +-- +-- Note that this operation is lazy, which allows to produce output +-- even before all input has been consumed. +-- +-- This operation may fail with the same errors as 'getContents' and 'putStr'. +-- +-- ==== __Examples__ +-- +-- >>> interact (\str -> str ++ str) +-- > hi :) +-- hi :) +-- > ^D +-- hi :) +-- +-- >>> interact (const ":D") +-- :D +-- +-- >>> interact (show . words) +-- > hello world! +-- > I hope you have a great day +-- > ^D +-- ["hello","world!","I","hope","you","have","a","great","day"] interact :: (String -> String) -> IO () interact f = do s <- getContents putStr (f s) -- | The 'readFile' function reads a file and -- returns the contents of the file as a string. +-- -- The file is read lazily, on demand, as with 'getContents'. - +-- +-- This operation may fail with the same errors as 'hGetContents' and 'openFile'. +-- +-- ==== __Examples__ +-- +-- >>> readFile "~/hello_world" +-- "Greetings!" +-- +-- >>> take 5 <$> readFile "/dev/zero" +-- "\NUL\NUL\NUL\NUL\NUL" readFile :: FilePath -> IO String readFile name = openFile name ReadMode >>= hGetContents -- | The 'readFile'' function reads a file and -- returns the contents of the file as a string. --- The file is fully read before being returned, as with 'getContents''. +-- +-- This is identical to 'readFile', but the file is fully read before being returned, +-- as with 'getContents''. -- -- @since base-4.15.0.0 - readFile' :: FilePath -> IO String -- There's a bit of overkill here—both withFile and -- hGetContents' will close the file in the end. readFile' name = withFile name ReadMode hGetContents' --- | The computation 'writeFile' @file str@ function writes the string @str@, +-- | The computation @'writeFile' file str@ function writes the string @str@, -- to the file @file@. +-- +-- This operation may fail with the same errors as 'hPutStr' and 'withFile'. +-- +-- ==== __Examples__ +-- +-- >>> writeFile "hello" "world" >> readFile "hello" +-- "world" +-- +-- >>> writeFile "~/" "D:" +-- *** Exception: ~/: withFile: inappropriate type (Is a directory) writeFile :: FilePath -> String -> IO () writeFile f txt = withFile f WriteMode (\ hdl -> hPutStr hdl txt) --- | The computation 'appendFile' @file str@ function appends the string @str@, +-- | The computation @'appendFile' file str@ function appends the string @str@, -- to the file @file@. -- -- Note that 'writeFile' and 'appendFile' write a literal string -- to a file. To write a value of any printable type, as with 'print', -- use the 'show' function to convert the value to a string first. -- --- > main = appendFile "squares" (show [(x,x*x) | x <- [0,0.1..2]]) - +-- This operation may fail with the same errors as 'hPutStr' and 'withFile'. +-- +-- ==== __Examples__ +-- +-- The following example could be more efficently written by acquiring a handle +-- instead with 'openFile' and using the computations capable of writing to handles +-- such as 'hPutStr'. +-- +-- >>> let fn = "hello_world" +-- >>> in writeFile fn "hello" >> appendFile fn " world!" >> (readFile fn >>= putStrLn) +-- "hello world!" +-- +-- >>> let fn = "foo"; output = readFile' fn >>= putStrLn +-- >>> in output >> appendFile fn (show [1,2,3]) >> output +-- this is what's in the file +-- this is what's in the file[1,2,3] appendFile :: FilePath -> String -> IO () appendFile f txt = withFile f AppendMode (\ hdl -> hPutStr hdl txt) -- | The 'readLn' function combines 'getLine' and 'readIO'. - +-- +-- This operation may fail with the same errors as 'getLine' and 'readIO'. +-- +-- ==== __Examples__ +-- +-- >>> fmap (+ 5) readLn +-- > 25 +-- 30 +-- +-- >>> readLn :: IO String +-- > this is not a string literal +-- *** Exception: user error (Prelude.readIO: no parse) readLn :: Read a => IO a readLn = getLine >>= readIO -- | The 'readIO' function is similar to 'read' except that it signals -- parse failure to the 'IO' monad instead of terminating the program. - +-- +-- This operation may fail with: +-- +-- * 'GHC.Internal.System.IO.Error.isUserError' if there is no unambiguous parse. +-- +-- ==== __Examples__ +-- +-- >>> fmap (+ 1) (readIO "1") +-- 2 +-- +-- >>> readIO "not quite ()" :: IO () +-- *** Exception: user error (Prelude.readIO: no parse) readIO :: Read a => String -> IO a readIO s = case (do { (x,t) <- reads s ; ("","") <- lex t ; @@ -380,7 +553,7 @@ readIO s = case (do { (x,t) <- reads s ; [] -> ioError (userError "Prelude.readIO: no parse") _ -> ioError (userError "Prelude.readIO: ambiguous parse") --- | The Unicode encoding of the current locale +-- | The encoding of the current locale. -- -- This is the initial locale encoding: if it has been subsequently changed by -- 'GHC.Internal.IO.Encoding.setLocaleEncoding' this value will not reflect that change. @@ -393,21 +566,22 @@ localeEncoding = initLocaleEncoding -- This operation may fail with: -- -- * 'GHC.Internal.System.IO.Error.isEOFError' if the end of file has been reached. - hReady :: Handle -> IO Bool hReady h = hWaitForInput h 0 -- | Computation 'hPrint' @hdl t@ writes the string representation of @t@ --- given by the 'shows' function to the file or channel managed by @hdl@ +-- given by the 'show' function to the file or channel managed by @hdl@ -- and appends a newline. -- --- This operation may fail with: +-- This operation may fail with the same errors as 'hPutStrLn' -- --- * 'GHC.Internal.System.IO.Error.isFullError' if the device is full; or +-- ==== __Examples__ -- --- * 'GHC.Internal.System.IO.Error.isPermissionError' if another system resource limit --- would be exceeded. - +-- >>> hPrint stdout [1,2,3] +-- [1,2,3] +-- +-- >>> hPrint stdin [4,5,6] +-- *** Exception: <stdin>: hPutStr: illegal operation (handle is not open for writing) hPrint :: Show a => Handle -> a -> IO () hPrint hdl = hPutStrLn hdl . show @@ -415,9 +589,50 @@ hPrint hdl = hPutStrLn hdl . show -- --------------------------------------------------------------------------- -- fixIO --- | The implementation of 'GHC.Internal.Control.Monad.Fix.mfix' for 'IO'. If the function --- passed to 'fixIO' inspects its argument, the resulting action will throw --- 'FixIOException'. +-- | The implementation of 'Control.Monad.Fix.mfix' for 'IO'. +-- +-- This operation may fail with: +-- +-- * 'FixIOException' if the function passed to 'fixIO' inspects its argument. +-- +-- ==== __Examples__ +-- +-- the IO-action is only executed once. The recursion is only on the values. +-- +-- >>> take 3 <$> fixIO (\x -> putStr ":D" >> (:x) <$> readLn @Int) +-- :D +-- 2 +-- [2,2,2] +-- +-- If we are strict in the value, just as with 'Data.Function.fix', we do not get termination: +-- +-- >>> fixIO (\x -> putStr x >> pure ('x' : x)) +-- * hangs forever * +-- +-- We can tie the knot of a structure within 'IO' using 'fixIO': +-- +-- @ +-- data Node = MkNode Int (IORef Node) +-- +-- foo :: IO () +-- foo = do +-- p \<- fixIO (\p -> newIORef (MkNode 0 p)) +-- q <- output p +-- r <- output q +-- _ <- output r +-- pure () +-- +-- output :: IORef Node -> IO (IORef Node) +-- output ref = do +-- MkNode x p <- readIORef ref +-- print x +-- pure p +-- @ +-- +-- >>> foo +-- 0 +-- 0 +-- 0 fixIO :: (a -> IO a) -> IO a fixIO k = do m <- newEmptyMVar @@ -465,7 +680,6 @@ fixIO k = do -- @O_EXCL@ flags are used to prevent this attack, but note that -- @O_EXCL@ is sometimes not supported on NFS filesystems, so if you -- rely on this behaviour it is best to use local filesystems only. --- openTempFile :: FilePath -- ^ Directory in which to create the file -> String -- ^ File name template. If the template is \"foo.ext\" then -- the created file will be \"fooXXX.ext\" where XXX is some