[Git][ghc/ghc][wip/document-system-io] Documentation: Improve documentation for symbols exported from System.IO

Jade (@Jade) gitlab at gitlab.haskell.org
Tue Mar 26 15:43:52 UTC 2024



Jade pushed to branch wip/document-system-io at Glasgow Haskell Compiler / GHC


Commits:
e1fa1c56 by Jade at 2024-03-26T16:48:23+01:00
Documentation: Improve documentation for symbols exported from System.IO

- - - - -


8 changed files:

- libraries/base/src/GHC/IO/Handle.hs
- libraries/base/src/GHC/IO/StdHandles.hs
- libraries/base/src/System/IO.hs
- libraries/ghc-internal/src/GHC/Internal/IO/Handle.hs
- libraries/ghc-internal/src/GHC/Internal/IO/Handle/Text.hs
- libraries/ghc-internal/src/GHC/Internal/IO/Handle/Types.hs
- libraries/ghc-internal/src/GHC/Internal/IO/StdHandles.hs
- libraries/ghc-internal/src/GHC/Internal/System/IO.hs


Changes:

=====================================
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


=====================================
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


=====================================
libraries/base/src/System/IO.hs
=====================================
@@ -199,3 +199,16 @@ 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.
+--
+-- >>> foo
+-- > input
+-- output
+-- > input^D
+-- output


=====================================
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
 
@@ -319,11 +320,11 @@ hFlushAll handle = withHandle_ "hFlushAll" handle flushBuffer
 
 data HandlePosn = HandlePosn Handle HandlePosition
 
--- | @since base-4.1.0.0
+-- | @since 4.1.0.0
 instance Eq HandlePosn where
     (HandlePosn h1 p1) == (HandlePosn h2 p2) = p1==p2 && h1==h2
 
--- | @since base-4.1.0.0
+-- | @since 4.1.0.0
 instance Show HandlePosn where
    showsPrec p (HandlePosn h pos) =
         showsPrec p h . showString " at position " . shows pos
@@ -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 type 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 type 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_ at Handle__{..} -> do
@@ -775,4 +785,3 @@ showHandle' filepath is_duplex h =
       where
        def :: Int
        def = bufSize buf
-


=====================================
libraries/ghc-internal/src/GHC/Internal/IO/Handle/Text.hs
=====================================
@@ -484,8 +484,9 @@ getSomeCharacters handle_ at Handle__{..} buf at 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.
 
@@ -625,7 +626,7 @@ hPutcBuffered handle_ at Handle__{..} c = do
 --
 -- 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.
 
@@ -633,6 +634,8 @@ 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 as 'hPutStr'
 hPutStrLn :: Handle -> String -> IO ()
 hPutStrLn handle str = hPutStr' handle str True
 
@@ -1176,4 +1179,3 @@ illegalBufferSize handle fn sz =
                             InvalidArgument  fn
                             ("illegal buffer size " ++ showsPrec 9 sz [])
                             Nothing Nothing)
-


=====================================
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 "}"
-


=====================================
libraries/ghc-internal/src/GHC/Internal/IO/StdHandles.hs
=====================================
@@ -29,72 +29,89 @@ 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 :: Handle
-stdin = POSIX.stdin <!> Win.stdin
+-- | 'stdin' is a handle managing input from the programs standard input.
+stdin  :: Handle
 
+-- | 'stdout' is a handle managing the programs standard output.
 stdout :: Handle
-stdout = POSIX.stdout <!> Win.stdout
 
+-- | 'stderr' is a handle managing the programs standard error.
 stderr :: Handle
+
+-- | The computation @'openFile' path mode@ returns a file handle that can be
+-- used to interact with the file.
+openFile
+  :: FilePath -- ^ The path to the file that should be opened
+  -> IOMode   -- ^ The mode in which the file should be opened
+  -> IO Handle
+
+-- | 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
+
+-- | The computation @'withFile' path mode action@ opens the file and runs @action@
+-- with the obtained handle before closing the file.
+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
+
+-- | 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.
+withBinaryFile :: FilePath -> IOMode -> (Handle -> IO r) -> IO r
+
+openFileBlocking :: FilePath -> IOMode -> IO Handle
+withFileBlocking :: FilePath -> IOMode -> (Handle -> IO r) -> IO r
+
+#if defined(mingw32_HOST_OS)
+stdin  = POSIX.stdin <!> Win.stdin
+stdout = POSIX.stdout <!> Win.stdout
 stderr = POSIX.stderr <!> Win.stderr
 
-openFile :: FilePath -> IOMode -> IO Handle
 openFile = POSIX.openFile <!> Win.openFile
-
 -- 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
 
-openBinaryFile :: FilePath -> IOMode -> IO Handle
 openBinaryFile = POSIX.openBinaryFile <!> Win.openBinaryFile
-
-withBinaryFile :: FilePath -> IOMode -> (Handle -> IO r) -> IO r
 withBinaryFile = POSIX.withBinaryFile <!> wf
   where
     wf path mode act = bracket (Win.openBinaryFile path mode) hClose_impl act
 
-openFileBlocking :: FilePath -> IOMode -> IO Handle
 openFileBlocking = POSIX.openFileBlocking <!> Win.openFileBlocking
-
-withFileBlocking :: FilePath -> IOMode -> (Handle -> IO r) -> IO r
 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
+stdin  = POSIX.stdin
 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


=====================================
libraries/ghc-internal/src/GHC/Internal/System/IO.hs
=====================================
@@ -257,24 +257,48 @@ 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 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 as 'putStr'.
 putStrLn        :: String -> IO ()
 putStrLn s      =  hPutStrLn stdout s
 
@@ -284,94 +308,244 @@ 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 as 'putStrLn'.
+--
+-- ==== __Examples__
+--
+-- >>> print [1, 2, 3]
+-- [1,2,3]
+--
+-- Be careful when using 'print' for outputting strings,
+-- as this will cause the quotation marks to be printed as well.
+--
+-- >>> print "Hello"
+-- "Hello"
+--
+-- 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').
 --
--- @since base-4.15.0.0
-
+-- '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 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 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!"
+--
+-- In the following example, because of laziness, no more than three characters are read
+-- from the file.
+--
+-- >>> fmap (take 3) (readFile "~/hello_world")
+-- "Gre"
 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''.
 --
--- @since base-4.15.0.0
-
+-- This is identical to 'readFile', but the file is fully read before being returned,
+-- as with 'getContents''.
+--
+-- @since 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 at .
+--
+-- 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 at .
 --
 -- 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:
+--
+--  * 'System.IO.Error.isUserError' if there is no unabiguous 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,10 +554,10 @@ 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 Unicode 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.
+-- 'GHC.IO.Encoding.setLocaleEncoding' this value will not reflect that change.
 localeEncoding :: TextEncoding
 localeEncoding = initLocaleEncoding
 
@@ -392,22 +566,23 @@ localeEncoding = initLocaleEncoding
 --
 -- This operation may fail with:
 --
---  * 'GHC.Internal.System.IO.Error.isEOFError' if the end of file has been reached.
-
+--  * '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 +590,11 @@ 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.
 fixIO :: (a -> IO a) -> IO a
 fixIO k = do
     m <- newEmptyMVar
@@ -465,7 +642,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
@@ -516,7 +692,7 @@ openTempFile' loc tmp_dir template binary mode
          -- Otherwise, something is wrong, because (break (== '.')) should
          -- always return a pair with either the empty string or a string
          -- beginning with '.' as the second component.
-         _                      -> errorWithoutStackTrace "bug in GHC.Internal.System.IO.openTempFile"
+         _                      -> errorWithoutStackTrace "bug in System.IO.openTempFile"
 #if defined(mingw32_HOST_OS)
     findTempName = findTempNamePosix <!> findTempNameWinIO
 



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/e1fa1c565be0029a00aaff4540cb0c54a170eda1

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/e1fa1c565be0029a00aaff4540cb0c54a170eda1
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20240326/fcc61b33/attachment-0001.html>


More information about the ghc-commits mailing list