Wolfgang Jeltsch pushed to branch wip/jeltsch/detecting-os-handle-types at Glasgow Haskell Compiler / GHC

Commits:

25 changed files:

Changes:

  • libraries/base/changelog.md
    ... ... @@ -23,7 +23,7 @@
    23 23
       * `GHC.Conc.catchSTM` and `GHC.Conc.Sync.catchSTM` now attach `WhileHandling` annotation to exceptions thrown from the handler. ([GHC #25365](https://gitlab.haskell.org/ghc/ghc/-/issues/25365))
    
    24 24
       * Remove `GHC.JS.Prim.Internal.Build`, as per [CLC #329](https://github.com/haskell/core-libraries-committee/issues/329)
    
    25 25
       * Export `labelThread` from `Control.Concurrent`.([CLC proposal #376](https://github.com/haskell/core-libraries-committee/issues/376))
    
    26
    -  * Add a new module `System.IO.OS` with operations for obtaining operating-system handles (file descriptors, Windows handles). ([CLC proposal #369](https://github.com/haskell/core-libraries-committee/issues/369))
    
    26
    +  * Add a new module `System.IO.OS` with operations for detecting the type of operating-system handles in use (file descriptors, Windows handles) and obtaining such handles. (CLC proposals [#395](https://github.com/haskell/core-libraries-committee/issues/395) and [#369](https://github.com/haskell/core-libraries-committee/issues/369))
    
    27 27
       * Evaluate backtraces for "error" exceptions at the moment they are thrown. ([CLC proposal #383](https://github.com/haskell/core-libraries-committee/issues/383))
    
    28 28
     
    
    29 29
     ## 4.22.0.0 *TBA*
    

  • libraries/base/src/GHC/IO/SubSystem.hs
    ... ... @@ -25,9 +25,9 @@ module GHC.IO.SubSystem
    25 25
          whenIoSubSystem,
    
    26 26
          ioSubSystem,
    
    27 27
          IoSubSystem(..),
    
    28
    -     conditional,
    
    29
    -     (<!>),
    
    28
    +     {-# DEPRECATED "Please use System.IO.OS.osHandleType." #-} conditional,
    
    29
    +     {-# DEPRECATED "Please use System.IO.OS.osHandleType." #-} (<!>),
    
    30 30
          isWindowsNativeIO
    
    31 31
          ) where
    
    32 32
     
    
    33
    -import GHC.Internal.IO.SubSystem
    \ No newline at end of file
    33
    +import GHC.Internal.IO.SubSystem

  • libraries/base/src/System/IO/OS.hs
    ... ... @@ -6,6 +6,10 @@
    6 6
     -}
    
    7 7
     module System.IO.OS
    
    8 8
     (
    
    9
    +    -- * OS handle type detection
    
    10
    +    OSHandleType (FileDescriptor, WindowsHandle),
    
    11
    +    osHandleType,
    
    12
    +
    
    9 13
         -- * Obtaining file descriptors and Windows handles
    
    10 14
         withFileDescriptorReadingBiased,
    
    11 15
         withFileDescriptorWritingBiased,
    
    ... ... @@ -23,6 +27,8 @@ where
    23 27
     
    
    24 28
     import GHC.Internal.System.IO.OS
    
    25 29
            (
    
    30
    +           OSHandleType (FileDescriptor, WindowsHandle),
    
    31
    +           osHandleType,
    
    26 32
                withFileDescriptorReadingBiased,
    
    27 33
                withFileDescriptorWritingBiased,
    
    28 34
                withWindowsHandleReadingBiased,
    

  • libraries/base/tests/IO/all.T
    ... ... @@ -189,9 +189,11 @@ test('mkdirExists', [exit_code(1), when(opsys('mingw32'), ignore_stderr)], compi
    189 189
     
    
    190 190
     test('osHandles001FileDescriptors', omit_ways(['winio', 'winio_threaded']), compile_and_run, [''])
    
    191 191
     test('osHandles001WindowsHandles', only_ways(['winio', 'winio_threaded']), compile_and_run, [''])
    
    192
    -test('osHandles002FileDescriptors', [when(opsys('mingw32'), skip), when(arch('javascript'), skip)], compile_and_run, [''])
    
    192
    +test('osHandles002FileDescriptors', omit_ways(['winio', 'winio_threaded']), compile_and_run, [''])
    
    193 193
     test('osHandles002WindowsHandles', only_ways(['winio', 'winio_threaded']), compile_and_run, [''])
    
    194
    -# It would be good to let `osHandles002FileDescriptors` run also on
    
    194
    +test('osHandles003FileDescriptors', [when(opsys('mingw32'), skip), when(arch('javascript'), skip)], compile_and_run, [''])
    
    195
    +test('osHandles003WindowsHandles', only_ways(['winio', 'winio_threaded']), compile_and_run, [''])
    
    196
    +# It would be good to let `osHandles003FileDescriptors` run also on
    
    195 197
     # Windows with the file-descriptor-based I/O manager. However, this
    
    196 198
     # test, as it is currently implemented, requires the `unix` package.
    
    197 199
     # That said, `UCRT.DLL`, which is used by GHC-generated Windows
    

  • libraries/base/tests/IO/osHandles001FileDescriptors.hs
    1
    -{-# LANGUAGE TypeApplications #-}
    
    2
    -
    
    3
    -import Control.Monad (mapM_)
    
    4
    -import Control.Exception (SomeException, try)
    
    5
    -import System.IO (stdin, stdout, stderr)
    
    6
    -import System.IO.OS
    
    7
    -       (
    
    8
    -           withFileDescriptorReadingBiasedRaw,
    
    9
    -           withFileDescriptorWritingBiasedRaw,
    
    10
    -           withWindowsHandleReadingBiasedRaw,
    
    11
    -           withWindowsHandleWritingBiasedRaw
    
    12
    -       )
    
    1
    +import System.IO.OS (osHandleType)
    
    13 2
     
    
    14 3
     main :: IO ()
    
    15
    -main = mapM_ ((>>= print) . try @SomeException) $
    
    16
    -       [
    
    17
    -           withFileDescriptorReadingBiasedRaw stdin  (return . show),
    
    18
    -           withFileDescriptorWritingBiasedRaw stdout (return . show),
    
    19
    -           withFileDescriptorWritingBiasedRaw stderr (return . show),
    
    20
    -           withWindowsHandleReadingBiasedRaw  stdin  (return . const "_"),
    
    21
    -           withWindowsHandleWritingBiasedRaw  stdout (return . const "_"),
    
    22
    -           withWindowsHandleWritingBiasedRaw  stderr (return . const "_")
    
    23
    -       ]
    4
    +main = print osHandleType

  • libraries/base/tests/IO/osHandles001FileDescriptors.stdout
    1
    -Right "0"
    
    2
    -Right "1"
    
    3
    -Right "2"
    
    4
    -Left <stdin>: withWindowsHandleReadingBiasedRaw: inappropriate type (handle does not use Windows handles)
    
    5
    -Left <stdout>: withWindowsHandleWritingBiasedRaw: inappropriate type (handle does not use Windows handles)
    
    6
    -Left <stderr>: withWindowsHandleWritingBiasedRaw: inappropriate type (handle does not use Windows handles)
    1
    +FileDescriptor

  • libraries/base/tests/IO/osHandles001WindowsHandles.hs
    1
    -{-# LANGUAGE TypeApplications #-}
    
    2
    -
    
    3
    -import Control.Monad (mapM_)
    
    4
    -import Control.Exception (SomeException, try)
    
    5
    -import System.IO (stdin, stdout, stderr)
    
    6
    -import System.IO.OS
    
    7
    -       (
    
    8
    -           withFileDescriptorReadingBiasedRaw,
    
    9
    -           withFileDescriptorWritingBiasedRaw,
    
    10
    -           withWindowsHandleReadingBiasedRaw,
    
    11
    -           withWindowsHandleWritingBiasedRaw
    
    12
    -       )
    
    1
    +import System.IO.OS (osHandleType)
    
    13 2
     
    
    14 3
     main :: IO ()
    
    15
    -main = mapM_ ((>>= print) . try @SomeException) $
    
    16
    -       [
    
    17
    -           withFileDescriptorReadingBiasedRaw stdin  (return . show),
    
    18
    -           withFileDescriptorWritingBiasedRaw stdout (return . show),
    
    19
    -           withFileDescriptorWritingBiasedRaw stderr (return . show),
    
    20
    -           withWindowsHandleReadingBiasedRaw  stdin  (return . const "_"),
    
    21
    -           withWindowsHandleWritingBiasedRaw  stdout (return . const "_"),
    
    22
    -           withWindowsHandleWritingBiasedRaw  stderr (return . const "_")
    
    23
    -       ]
    4
    +main = print osHandleType

  • libraries/base/tests/IO/osHandles001WindowsHandles.stdout
    1
    -Left <stdin>: withFileDescriptorReadingBiasedRaw: inappropriate type (handle does not use file descriptors)
    
    2
    -Left <stdout>: withFileDescriptorWritingBiasedRaw: inappropriate type (handle does not use file descriptors)
    
    3
    -Left <stderr>: withFileDescriptorWritingBiasedRaw: inappropriate type (handle does not use file descriptors)
    
    4
    -Right "_"
    
    5
    -Right "_"
    
    6
    -Right "_"
    1
    +WindowsHandle

  • libraries/base/tests/IO/osHandles002FileDescriptors.hs
    1
    -import Data.Functor (void)
    
    2
    -import Data.ByteString.Char8 (pack)
    
    3
    -import System.Posix.Types (Fd (Fd), ByteCount)
    
    4
    -import System.Posix.IO.ByteString (fdRead, fdWrite)
    
    1
    +{-# LANGUAGE TypeApplications #-}
    
    2
    +
    
    3
    +import Control.Monad (mapM_)
    
    4
    +import Control.Exception (SomeException, try)
    
    5 5
     import System.IO (stdin, stdout, stderr)
    
    6 6
     import System.IO.OS
    
    7 7
            (
    
    8
    -           withFileDescriptorReadingBiased,
    
    9
    -           withFileDescriptorWritingBiased
    
    8
    +           withFileDescriptorReadingBiasedRaw,
    
    9
    +           withFileDescriptorWritingBiasedRaw,
    
    10
    +           withWindowsHandleReadingBiasedRaw,
    
    11
    +           withWindowsHandleWritingBiasedRaw
    
    10 12
            )
    
    11 13
     
    
    12 14
     main :: IO ()
    
    13
    -main = withFileDescriptorReadingBiased stdin  $ \ stdinFD  ->
    
    14
    -       withFileDescriptorWritingBiased stdout $ \ stdoutFD ->
    
    15
    -       withFileDescriptorWritingBiased stderr $ \ stderrFD ->
    
    16
    -       do
    
    17
    -           regularMsg <- fdRead (Fd stdinFD) inputSizeApproximation
    
    18
    -           void $ fdWrite (Fd stdoutFD) regularMsg
    
    19
    -           void $ fdWrite (Fd stderrFD) (pack errorMsg)
    
    20
    -    where
    
    21
    -
    
    22
    -    inputSizeApproximation :: ByteCount
    
    23
    -    inputSizeApproximation = 100
    
    24
    -
    
    25
    -    errorMsg :: String
    
    26
    -    errorMsg = "And every single door\n\
    
    27
    -               \That I've walked through\n\
    
    28
    -               \Brings me back, back here again\n"
    15
    +main = mapM_ ((>>= print) . try @SomeException) $
    
    16
    +       [
    
    17
    +           withFileDescriptorReadingBiasedRaw stdin  (return . show),
    
    18
    +           withFileDescriptorWritingBiasedRaw stdout (return . show),
    
    19
    +           withFileDescriptorWritingBiasedRaw stderr (return . show),
    
    20
    +           withWindowsHandleReadingBiasedRaw  stdin  (return . const "_"),
    
    21
    +           withWindowsHandleWritingBiasedRaw  stdout (return . const "_"),
    
    22
    +           withWindowsHandleWritingBiasedRaw  stderr (return . const "_")
    
    23
    +       ]

  • libraries/base/tests/IO/osHandles002FileDescriptors.stdout
    1
    -We've got to get in to get out
    1
    +Right "0"
    
    2
    +Right "1"
    
    3
    +Right "2"
    
    4
    +Left <stdin>: withWindowsHandleReadingBiasedRaw: inappropriate type (handle does not use Windows handles)
    
    5
    +Left <stdout>: withWindowsHandleWritingBiasedRaw: inappropriate type (handle does not use Windows handles)
    
    6
    +Left <stderr>: withWindowsHandleWritingBiasedRaw: inappropriate type (handle does not use Windows handles)

  • libraries/base/tests/IO/osHandles002WindowsHandles.hs
    1
    -import Control.Monad (zipWithM_)
    
    2
    -import Data.Functor (void)
    
    3
    -import Data.Char (ord)
    
    4
    -import Foreign.Marshal.Alloc (allocaBytes)
    
    5
    -import Foreign.Storable (pokeElemOff)
    
    1
    +{-# LANGUAGE TypeApplications #-}
    
    2
    +
    
    3
    +import Control.Monad (mapM_)
    
    4
    +import Control.Exception (SomeException, try)
    
    6 5
     import System.IO (stdin, stdout, stderr)
    
    7 6
     import System.IO.OS
    
    8 7
            (
    
    9
    -           withWindowsHandleReadingBiased,
    
    10
    -           withWindowsHandleWritingBiased
    
    8
    +           withFileDescriptorReadingBiasedRaw,
    
    9
    +           withFileDescriptorWritingBiasedRaw,
    
    10
    +           withWindowsHandleReadingBiasedRaw,
    
    11
    +           withWindowsHandleWritingBiasedRaw
    
    11 12
            )
    
    12 13
     
    
    13 14
     main :: IO ()
    
    14
    -main = withWindowsHandleReadingBiased stdin  $ \ windowsStdin  ->
    
    15
    -       withWindowsHandleWritingBiased stdout $ \ windowsStdout ->
    
    16
    -       withWindowsHandleWritingBiased stderr $ \ windowsStderr ->
    
    17
    -       do
    
    18
    -           withBuffer inputSizeApproximation $ \ bufferPtr -> do
    
    19
    -               inputSize <- win32_ReadFile windowsStdin
    
    20
    -                                           bufferPtr
    
    21
    -                                           inputSizeApproximation
    
    22
    -                                           Nothing
    
    23
    -               void $ win32_WriteFile windowsStdout
    
    24
    -                                      bufferPtr
    
    25
    -                                      inputSize
    
    26
    -                                      Nothing
    
    27
    -           withBuffer errorMsgSize $ \ bufferPtr -> do
    
    28
    -               zipWithM_ (pokeElemOff bufferPtr)
    
    29
    -                         [0 ..]
    
    30
    -                         (map (fromIntegral . ord) errorMsg)
    
    31
    -               void $ win32_WriteFile windowsStderr
    
    32
    -                                      bufferPtr
    
    33
    -                                      errorMsgSize
    
    34
    -                                      Nothing
    
    35
    -    where
    
    36
    -
    
    37
    -    withBuffer :: DWORD -> (Ptr Word8 -> IO a) -> IO a
    
    38
    -    withBuffer = allocaBytes . fromIntegral
    
    39
    -
    
    40
    -    inputSizeApproximation :: DWORD
    
    41
    -    inputSizeApproximation = 100
    
    42
    -
    
    43
    -    errorMsg :: String
    
    44
    -    errorMsg = "And every single door\n\
    
    45
    -               \That I've walked through\n\
    
    46
    -               \Brings me back, back here again\n"
    
    47
    -
    
    48
    -    errorMsgSize :: DWORD
    
    49
    -    errorMsgSize = fromIntegral (length errorMsg)
    15
    +main = mapM_ ((>>= print) . try @SomeException) $
    
    16
    +       [
    
    17
    +           withFileDescriptorReadingBiasedRaw stdin  (return . show),
    
    18
    +           withFileDescriptorWritingBiasedRaw stdout (return . show),
    
    19
    +           withFileDescriptorWritingBiasedRaw stderr (return . show),
    
    20
    +           withWindowsHandleReadingBiasedRaw  stdin  (return . const "_"),
    
    21
    +           withWindowsHandleWritingBiasedRaw  stdout (return . const "_"),
    
    22
    +           withWindowsHandleWritingBiasedRaw  stderr (return . const "_")
    
    23
    +       ]

  • libraries/base/tests/IO/osHandles002WindowsHandles.stdout
    1
    -We've got to get in to get out
    1
    +Left <stdin>: withFileDescriptorReadingBiasedRaw: inappropriate type (handle does not use file descriptors)
    
    2
    +Left <stdout>: withFileDescriptorWritingBiasedRaw: inappropriate type (handle does not use file descriptors)
    
    3
    +Left <stderr>: withFileDescriptorWritingBiasedRaw: inappropriate type (handle does not use file descriptors)
    
    4
    +Right "_"
    
    5
    +Right "_"
    
    6
    +Right "_"

  • libraries/base/tests/IO/osHandles003FileDescriptors.hs
    1
    +import Data.Functor (void)
    
    2
    +import Data.ByteString.Char8 (pack)
    
    3
    +import System.Posix.Types (Fd (Fd), ByteCount)
    
    4
    +import System.Posix.IO.ByteString (fdRead, fdWrite)
    
    5
    +import System.IO (stdin, stdout, stderr)
    
    6
    +import System.IO.OS
    
    7
    +       (
    
    8
    +           withFileDescriptorReadingBiased,
    
    9
    +           withFileDescriptorWritingBiased
    
    10
    +       )
    
    11
    +
    
    12
    +main :: IO ()
    
    13
    +main = withFileDescriptorReadingBiased stdin  $ \ stdinFD  ->
    
    14
    +       withFileDescriptorWritingBiased stdout $ \ stdoutFD ->
    
    15
    +       withFileDescriptorWritingBiased stderr $ \ stderrFD ->
    
    16
    +       do
    
    17
    +           regularMsg <- fdRead (Fd stdinFD) inputSizeApproximation
    
    18
    +           void $ fdWrite (Fd stdoutFD) regularMsg
    
    19
    +           void $ fdWrite (Fd stderrFD) (pack errorMsg)
    
    20
    +    where
    
    21
    +
    
    22
    +    inputSizeApproximation :: ByteCount
    
    23
    +    inputSizeApproximation = 100
    
    24
    +
    
    25
    +    errorMsg :: String
    
    26
    +    errorMsg = "And every single door\n\
    
    27
    +               \That I've walked through\n\
    
    28
    +               \Brings me back, back here again\n"

  • libraries/base/tests/IO/osHandles002FileDescriptors.stderrlibraries/base/tests/IO/osHandles003FileDescriptors.stderr

  • libraries/base/tests/IO/osHandles002FileDescriptors.stdinlibraries/base/tests/IO/osHandles003FileDescriptors.stdin

  • libraries/base/tests/IO/osHandles002WindowsHandles.stdinlibraries/base/tests/IO/osHandles003FileDescriptors.stdout

  • libraries/base/tests/IO/osHandles003WindowsHandles.hs
    1
    +import Control.Monad (zipWithM_)
    
    2
    +import Data.Functor (void)
    
    3
    +import Data.Char (ord)
    
    4
    +import Foreign.Marshal.Alloc (allocaBytes)
    
    5
    +import Foreign.Storable (pokeElemOff)
    
    6
    +import System.IO (stdin, stdout, stderr)
    
    7
    +import System.IO.OS
    
    8
    +       (
    
    9
    +           withWindowsHandleReadingBiased,
    
    10
    +           withWindowsHandleWritingBiased
    
    11
    +       )
    
    12
    +
    
    13
    +main :: IO ()
    
    14
    +main = withWindowsHandleReadingBiased stdin  $ \ windowsStdin  ->
    
    15
    +       withWindowsHandleWritingBiased stdout $ \ windowsStdout ->
    
    16
    +       withWindowsHandleWritingBiased stderr $ \ windowsStderr ->
    
    17
    +       do
    
    18
    +           withBuffer inputSizeApproximation $ \ bufferPtr -> do
    
    19
    +               inputSize <- win32_ReadFile windowsStdin
    
    20
    +                                           bufferPtr
    
    21
    +                                           inputSizeApproximation
    
    22
    +                                           Nothing
    
    23
    +               void $ win32_WriteFile windowsStdout
    
    24
    +                                      bufferPtr
    
    25
    +                                      inputSize
    
    26
    +                                      Nothing
    
    27
    +           withBuffer errorMsgSize $ \ bufferPtr -> do
    
    28
    +               zipWithM_ (pokeElemOff bufferPtr)
    
    29
    +                         [0 ..]
    
    30
    +                         (map (fromIntegral . ord) errorMsg)
    
    31
    +               void $ win32_WriteFile windowsStderr
    
    32
    +                                      bufferPtr
    
    33
    +                                      errorMsgSize
    
    34
    +                                      Nothing
    
    35
    +    where
    
    36
    +
    
    37
    +    withBuffer :: DWORD -> (Ptr Word8 -> IO a) -> IO a
    
    38
    +    withBuffer = allocaBytes . fromIntegral
    
    39
    +
    
    40
    +    inputSizeApproximation :: DWORD
    
    41
    +    inputSizeApproximation = 100
    
    42
    +
    
    43
    +    errorMsg :: String
    
    44
    +    errorMsg = "And every single door\n\
    
    45
    +               \That I've walked through\n\
    
    46
    +               \Brings me back, back here again\n"
    
    47
    +
    
    48
    +    errorMsgSize :: DWORD
    
    49
    +    errorMsgSize = fromIntegral (length errorMsg)

  • libraries/base/tests/IO/osHandles002WindowsHandles.stderrlibraries/base/tests/IO/osHandles003WindowsHandles.stderr

  • libraries/base/tests/IO/osHandles003WindowsHandles.stdin
    1
    +We've got to get in to get out

  • libraries/base/tests/IO/osHandles003WindowsHandles.stdout
    1
    +We've got to get in to get out

  • libraries/ghc-internal/src/GHC/Internal/System/IO/OS.hs
    ... ... @@ -8,6 +8,10 @@
    8 8
     -}
    
    9 9
     module GHC.Internal.System.IO.OS
    
    10 10
     (
    
    11
    +    -- * OS handle type detection
    
    12
    +    OSHandleType (FileDescriptor, WindowsHandle),
    
    13
    +    osHandleType,
    
    14
    +
    
    11 15
         -- * Obtaining file descriptors and Windows handles
    
    12 16
         withFileDescriptorReadingBiased,
    
    13 17
         withFileDescriptorWritingBiased,
    
    ... ... @@ -23,6 +27,10 @@ module GHC.Internal.System.IO.OS
    23 27
     )
    
    24 28
     where
    
    25 29
     
    
    30
    +import GHC.Internal.Classes (Eq, Ord)
    
    31
    +import GHC.Internal.Enum (Bounded, Enum)
    
    32
    +import GHC.Internal.Show (Show)
    
    33
    +import GHC.Internal.Read (Read)
    
    26 34
     import GHC.Internal.Control.Monad (return)
    
    27 35
     import GHC.Internal.Control.Concurrent.MVar (MVar)
    
    28 36
     import GHC.Internal.Control.Exception (mask)
    
    ... ... @@ -39,6 +47,7 @@ import GHC.Internal.Data.List ((++))
    39 47
     import GHC.Internal.Data.String (String)
    
    40 48
     import GHC.Internal.Data.Typeable (Typeable, cast)
    
    41 49
     import GHC.Internal.System.IO (IO)
    
    50
    +import GHC.Internal.IO.SubSystem (conditional)
    
    42 51
     import GHC.Internal.IO.FD (fdFD)
    
    43 52
     #if defined(mingw32_HOST_OS)
    
    44 53
     import GHC.Internal.IO.Windows.Handle
    
    ... ... @@ -64,6 +73,19 @@ import GHC.Internal.IO.Exception
    64 73
     import GHC.Internal.Foreign.Ptr (Ptr)
    
    65 74
     import GHC.Internal.Foreign.C.Types (CInt)
    
    66 75
     
    
    76
    +-- * OS handle type detection
    
    77
    +
    
    78
    +-- | The type of operating-system handle types.
    
    79
    +data OSHandleType = FileDescriptor | WindowsHandle
    
    80
    +    deriving (Eq, Ord, Bounded, Enum, Show, Read)
    
    81
    +
    
    82
    +{-|
    
    83
    +    The type of operating-system handles that underlie Haskell handles with the
    
    84
    +    I/O manager currently in use.
    
    85
    +-}
    
    86
    +osHandleType :: OSHandleType
    
    87
    +osHandleType = conditional FileDescriptor WindowsHandle
    
    88
    +
    
    67 89
     -- * Obtaining POSIX file descriptors and Windows handles
    
    68 90
     
    
    69 91
     {-|
    

  • testsuite/tests/interface-stability/base-exports.stdout
    ... ... @@ -10050,6 +10050,9 @@ module System.IO.Error where
    10050 10050
     
    
    10051 10051
     module System.IO.OS where
    
    10052 10052
       -- Safety: Safe
    
    10053
    +  type OSHandleType :: *
    
    10054
    +  data OSHandleType = FileDescriptor | WindowsHandle
    
    10055
    +  osHandleType :: OSHandleType
    
    10053 10056
       withFileDescriptorReadingBiased :: forall r. GHC.Internal.IO.Handle.Types.Handle -> (GHC.Internal.Foreign.C.Types.CInt -> GHC.Internal.Types.IO r) -> GHC.Internal.Types.IO r
    
    10054 10057
       withFileDescriptorReadingBiasedRaw :: forall r. GHC.Internal.IO.Handle.Types.Handle -> (GHC.Internal.Foreign.C.Types.CInt -> GHC.Internal.Types.IO r) -> GHC.Internal.Types.IO r
    
    10055 10058
       withFileDescriptorWritingBiased :: forall r. GHC.Internal.IO.Handle.Types.Handle -> (GHC.Internal.Foreign.C.Types.CInt -> GHC.Internal.Types.IO r) -> GHC.Internal.Types.IO r
    
    ... ... @@ -11375,6 +11378,7 @@ instance forall (c :: GHC.Internal.Types.Char). GHC.Internal.Classes.Eq (GHC.Int
    11375 11378
     instance forall (s :: GHC.Internal.Types.Symbol). GHC.Internal.Classes.Eq (GHC.Internal.TypeLits.SSymbol s) -- Defined in ‘GHC.Internal.TypeLits’
    
    11376 11379
     instance GHC.Internal.Classes.Eq GHC.Internal.TypeLits.SomeChar -- Defined in ‘GHC.Internal.TypeLits’
    
    11377 11380
     instance GHC.Internal.Classes.Eq GHC.Internal.TypeLits.SomeSymbol -- Defined in ‘GHC.Internal.TypeLits’
    
    11381
    +instance [safe] GHC.Internal.Classes.Eq GHC.Internal.System.IO.OS.OSHandleType -- Defined in ‘GHC.Internal.System.IO.OS’
    
    11378 11382
     instance GHC.Internal.Classes.Eq System.Timeout.Timeout -- Defined in ‘System.Timeout’
    
    11379 11383
     instance GHC.Internal.Classes.Eq GHC.Internal.Text.Read.Lex.Lexeme -- Defined in ‘GHC.Internal.Text.Read.Lex’
    
    11380 11384
     instance GHC.Internal.Classes.Eq GHC.Internal.Text.Read.Lex.Number -- Defined in ‘GHC.Internal.Text.Read.Lex’
    
    ... ... @@ -11528,6 +11532,7 @@ instance forall (c :: GHC.Internal.Types.Char). GHC.Internal.Classes.Ord (GHC.In
    11528 11532
     instance forall (s :: GHC.Internal.Types.Symbol). GHC.Internal.Classes.Ord (GHC.Internal.TypeLits.SSymbol s) -- Defined in ‘GHC.Internal.TypeLits’
    
    11529 11533
     instance GHC.Internal.Classes.Ord GHC.Internal.TypeLits.SomeChar -- Defined in ‘GHC.Internal.TypeLits’
    
    11530 11534
     instance GHC.Internal.Classes.Ord GHC.Internal.TypeLits.SomeSymbol -- Defined in ‘GHC.Internal.TypeLits’
    
    11535
    +instance [safe] GHC.Internal.Classes.Ord GHC.Internal.System.IO.OS.OSHandleType -- Defined in ‘GHC.Internal.System.IO.OS’
    
    11531 11536
     instance GHC.Internal.Control.Arrow.Arrow (->) -- Defined in ‘GHC.Internal.Control.Arrow’
    
    11532 11537
     instance forall (m :: * -> *). GHC.Internal.Base.Monad m => GHC.Internal.Control.Arrow.Arrow (GHC.Internal.Control.Arrow.Kleisli m) -- Defined in ‘GHC.Internal.Control.Arrow’
    
    11533 11538
     instance GHC.Internal.Control.Arrow.ArrowApply (->) -- Defined in ‘GHC.Internal.Control.Arrow’
    
    ... ... @@ -11927,6 +11932,7 @@ instance GHC.Internal.Enum.Bounded GHC.Internal.Generics.Associativity -- Define
    11927 11932
     instance GHC.Internal.Enum.Bounded GHC.Internal.Generics.DecidedStrictness -- Defined in ‘GHC.Internal.Generics’
    
    11928 11933
     instance GHC.Internal.Enum.Bounded GHC.Internal.Generics.SourceStrictness -- Defined in ‘GHC.Internal.Generics’
    
    11929 11934
     instance GHC.Internal.Enum.Bounded GHC.Internal.Generics.SourceUnpackedness -- Defined in ‘GHC.Internal.Generics’
    
    11935
    +instance [safe] GHC.Internal.Enum.Bounded GHC.Internal.System.IO.OS.OSHandleType -- Defined in ‘GHC.Internal.System.IO.OS’
    
    11930 11936
     instance forall a k (b :: k). GHC.Internal.Enum.Enum a => GHC.Internal.Enum.Enum (GHC.Internal.Data.Functor.Const.Const a b) -- Defined in ‘GHC.Internal.Data.Functor.Const’
    
    11931 11937
     instance forall a. GHC.Internal.Enum.Enum a => GHC.Internal.Enum.Enum (GHC.Internal.Data.Bits.And a) -- Defined in ‘GHC.Internal.Data.Bits’
    
    11932 11938
     instance forall a. GHC.Internal.Enum.Enum a => GHC.Internal.Enum.Enum (GHC.Internal.Data.Bits.Iff a) -- Defined in ‘GHC.Internal.Data.Bits’
    
    ... ... @@ -12008,6 +12014,7 @@ instance GHC.Internal.Enum.Enum GHC.Internal.IO.Device.SeekMode -- Defined in
    12008 12014
     instance GHC.Internal.Enum.Enum GHC.Internal.IO.IOMode.IOMode -- Defined in ‘GHC.Internal.IO.IOMode’
    
    12009 12015
     instance GHC.Internal.Enum.Enum GHC.Internal.IO.SubSystem.IoSubSystem -- Defined in ‘GHC.Internal.IO.SubSystem’
    
    12010 12016
     instance GHC.Internal.Enum.Enum GHC.RTS.Flags.IoManagerFlag -- Defined in ‘GHC.RTS.Flags’
    
    12017
    +instance [safe] GHC.Internal.Enum.Enum GHC.Internal.System.IO.OS.OSHandleType -- Defined in ‘GHC.Internal.System.IO.OS’
    
    12011 12018
     instance GHC.Internal.Exception.Context.ExceptionAnnotation GHC.Internal.Exception.Type.WhileHandling -- Defined in ‘GHC.Internal.Exception.Type’
    
    12012 12019
     instance GHC.Internal.Exception.Context.ExceptionAnnotation GHC.Internal.Exception.Backtrace.Backtraces -- Defined in ‘GHC.Internal.Exception.Backtrace’
    
    12013 12020
     instance GHC.Internal.Exception.Type.Exception GHC.Internal.IO.Exception.AllocationLimitExceeded -- Defined in ‘GHC.Internal.IO.Exception’
    
    ... ... @@ -12555,6 +12562,7 @@ instance [safe] GHC.Internal.Read.Read GHC.Stats.RTSStats -- Defined in ‘GHC.S
    12555 12562
     instance GHC.Internal.Read.Read GHC.Internal.TypeNats.SomeNat -- Defined in ‘GHC.Internal.TypeNats’
    
    12556 12563
     instance GHC.Internal.Read.Read GHC.Internal.TypeLits.SomeChar -- Defined in ‘GHC.Internal.TypeLits’
    
    12557 12564
     instance GHC.Internal.Read.Read GHC.Internal.TypeLits.SomeSymbol -- Defined in ‘GHC.Internal.TypeLits’
    
    12565
    +instance [safe] GHC.Internal.Read.Read GHC.Internal.System.IO.OS.OSHandleType -- Defined in ‘GHC.Internal.System.IO.OS’
    
    12558 12566
     instance forall a k (b :: k). GHC.Internal.Real.Fractional a => GHC.Internal.Real.Fractional (GHC.Internal.Data.Functor.Const.Const a b) -- Defined in ‘GHC.Internal.Data.Functor.Const’
    
    12559 12567
     instance forall a. GHC.Internal.Float.RealFloat a => GHC.Internal.Real.Fractional (Data.Complex.Complex a) -- Defined in ‘Data.Complex’
    
    12560 12568
     instance forall k (a :: k). Data.Fixed.HasResolution a => GHC.Internal.Real.Fractional (Data.Fixed.Fixed a) -- Defined in ‘Data.Fixed’
    
    ... ... @@ -12894,6 +12902,7 @@ instance forall (c :: GHC.Internal.Types.Char). GHC.Internal.Show.Show (GHC.Inte
    12894 12902
     instance forall (s :: GHC.Internal.Types.Symbol). GHC.Internal.Show.Show (GHC.Internal.TypeLits.SSymbol s) -- Defined in ‘GHC.Internal.TypeLits’
    
    12895 12903
     instance GHC.Internal.Show.Show GHC.Internal.TypeLits.SomeChar -- Defined in ‘GHC.Internal.TypeLits’
    
    12896 12904
     instance GHC.Internal.Show.Show GHC.Internal.TypeLits.SomeSymbol -- Defined in ‘GHC.Internal.TypeLits’
    
    12905
    +instance [safe] GHC.Internal.Show.Show GHC.Internal.System.IO.OS.OSHandleType -- Defined in ‘GHC.Internal.System.IO.OS’
    
    12897 12906
     instance GHC.Internal.Show.Show System.Timeout.Timeout -- Defined in ‘System.Timeout’
    
    12898 12907
     instance GHC.Internal.Show.Show GHC.Internal.Text.Read.Lex.Lexeme -- Defined in ‘GHC.Internal.Text.Read.Lex’
    
    12899 12908
     instance GHC.Internal.Show.Show GHC.Internal.Text.Read.Lex.Number -- Defined in ‘GHC.Internal.Text.Read.Lex’
    

  • testsuite/tests/interface-stability/base-exports.stdout-javascript-unknown-ghcjs
    ... ... @@ -10088,6 +10088,9 @@ module System.IO.Error where
    10088 10088
     
    
    10089 10089
     module System.IO.OS where
    
    10090 10090
       -- Safety: Safe
    
    10091
    +  type OSHandleType :: *
    
    10092
    +  data OSHandleType = FileDescriptor | WindowsHandle
    
    10093
    +  osHandleType :: OSHandleType
    
    10091 10094
       withFileDescriptorReadingBiased :: forall r. GHC.Internal.IO.Handle.Types.Handle -> (GHC.Internal.Foreign.C.Types.CInt -> GHC.Internal.Types.IO r) -> GHC.Internal.Types.IO r
    
    10092 10095
       withFileDescriptorReadingBiasedRaw :: forall r. GHC.Internal.IO.Handle.Types.Handle -> (GHC.Internal.Foreign.C.Types.CInt -> GHC.Internal.Types.IO r) -> GHC.Internal.Types.IO r
    
    10093 10096
       withFileDescriptorWritingBiased :: forall r. GHC.Internal.IO.Handle.Types.Handle -> (GHC.Internal.Foreign.C.Types.CInt -> GHC.Internal.Types.IO r) -> GHC.Internal.Types.IO r
    
    ... ... @@ -11402,6 +11405,7 @@ instance forall (c :: GHC.Internal.Types.Char). GHC.Internal.Classes.Eq (GHC.Int
    11402 11405
     instance forall (s :: GHC.Internal.Types.Symbol). GHC.Internal.Classes.Eq (GHC.Internal.TypeLits.SSymbol s) -- Defined in ‘GHC.Internal.TypeLits’
    
    11403 11406
     instance GHC.Internal.Classes.Eq GHC.Internal.TypeLits.SomeChar -- Defined in ‘GHC.Internal.TypeLits’
    
    11404 11407
     instance GHC.Internal.Classes.Eq GHC.Internal.TypeLits.SomeSymbol -- Defined in ‘GHC.Internal.TypeLits’
    
    11408
    +instance [safe] GHC.Internal.Classes.Eq GHC.Internal.System.IO.OS.OSHandleType -- Defined in ‘GHC.Internal.System.IO.OS’
    
    11405 11409
     instance GHC.Internal.Classes.Eq System.Timeout.Timeout -- Defined in ‘System.Timeout’
    
    11406 11410
     instance GHC.Internal.Classes.Eq GHC.Internal.Text.Read.Lex.Lexeme -- Defined in ‘GHC.Internal.Text.Read.Lex’
    
    11407 11411
     instance GHC.Internal.Classes.Eq GHC.Internal.Text.Read.Lex.Number -- Defined in ‘GHC.Internal.Text.Read.Lex’
    
    ... ... @@ -11555,6 +11559,7 @@ instance forall (c :: GHC.Internal.Types.Char). GHC.Internal.Classes.Ord (GHC.In
    11555 11559
     instance forall (s :: GHC.Internal.Types.Symbol). GHC.Internal.Classes.Ord (GHC.Internal.TypeLits.SSymbol s) -- Defined in ‘GHC.Internal.TypeLits’
    
    11556 11560
     instance GHC.Internal.Classes.Ord GHC.Internal.TypeLits.SomeChar -- Defined in ‘GHC.Internal.TypeLits’
    
    11557 11561
     instance GHC.Internal.Classes.Ord GHC.Internal.TypeLits.SomeSymbol -- Defined in ‘GHC.Internal.TypeLits’
    
    11562
    +instance [safe] GHC.Internal.Classes.Ord GHC.Internal.System.IO.OS.OSHandleType -- Defined in ‘GHC.Internal.System.IO.OS’
    
    11558 11563
     instance GHC.Internal.Control.Arrow.Arrow (->) -- Defined in ‘GHC.Internal.Control.Arrow’
    
    11559 11564
     instance forall (m :: * -> *). GHC.Internal.Base.Monad m => GHC.Internal.Control.Arrow.Arrow (GHC.Internal.Control.Arrow.Kleisli m) -- Defined in ‘GHC.Internal.Control.Arrow’
    
    11560 11565
     instance GHC.Internal.Control.Arrow.ArrowApply (->) -- Defined in ‘GHC.Internal.Control.Arrow’
    
    ... ... @@ -11954,6 +11959,7 @@ instance GHC.Internal.Enum.Bounded GHC.Internal.Generics.Associativity -- Define
    11954 11959
     instance GHC.Internal.Enum.Bounded GHC.Internal.Generics.DecidedStrictness -- Defined in ‘GHC.Internal.Generics’
    
    11955 11960
     instance GHC.Internal.Enum.Bounded GHC.Internal.Generics.SourceStrictness -- Defined in ‘GHC.Internal.Generics’
    
    11956 11961
     instance GHC.Internal.Enum.Bounded GHC.Internal.Generics.SourceUnpackedness -- Defined in ‘GHC.Internal.Generics’
    
    11962
    +instance [safe] GHC.Internal.Enum.Bounded GHC.Internal.System.IO.OS.OSHandleType -- Defined in ‘GHC.Internal.System.IO.OS’
    
    11957 11963
     instance forall a k (b :: k). GHC.Internal.Enum.Enum a => GHC.Internal.Enum.Enum (GHC.Internal.Data.Functor.Const.Const a b) -- Defined in ‘GHC.Internal.Data.Functor.Const’
    
    11958 11964
     instance forall a. GHC.Internal.Enum.Enum a => GHC.Internal.Enum.Enum (GHC.Internal.Data.Bits.And a) -- Defined in ‘GHC.Internal.Data.Bits’
    
    11959 11965
     instance forall a. GHC.Internal.Enum.Enum a => GHC.Internal.Enum.Enum (GHC.Internal.Data.Bits.Iff a) -- Defined in ‘GHC.Internal.Data.Bits’
    
    ... ... @@ -12035,6 +12041,7 @@ instance GHC.Internal.Enum.Enum GHC.Internal.IO.Device.SeekMode -- Defined in
    12035 12041
     instance GHC.Internal.Enum.Enum GHC.Internal.IO.IOMode.IOMode -- Defined in ‘GHC.Internal.IO.IOMode’
    
    12036 12042
     instance GHC.Internal.Enum.Enum GHC.Internal.IO.SubSystem.IoSubSystem -- Defined in ‘GHC.Internal.IO.SubSystem’
    
    12037 12043
     instance GHC.Internal.Enum.Enum GHC.RTS.Flags.IoManagerFlag -- Defined in ‘GHC.RTS.Flags’
    
    12044
    +instance [safe] GHC.Internal.Enum.Enum GHC.Internal.System.IO.OS.OSHandleType -- Defined in ‘GHC.Internal.System.IO.OS’
    
    12038 12045
     instance GHC.Internal.Exception.Context.ExceptionAnnotation GHC.Internal.Exception.Type.WhileHandling -- Defined in ‘GHC.Internal.Exception.Type’
    
    12039 12046
     instance GHC.Internal.Exception.Context.ExceptionAnnotation GHC.Internal.Exception.Backtrace.Backtraces -- Defined in ‘GHC.Internal.Exception.Backtrace’
    
    12040 12047
     instance GHC.Internal.Exception.Type.Exception GHC.Internal.IO.Exception.AllocationLimitExceeded -- Defined in ‘GHC.Internal.IO.Exception’
    
    ... ... @@ -12584,6 +12591,7 @@ instance [safe] GHC.Internal.Read.Read GHC.Stats.RTSStats -- Defined in ‘GHC.S
    12584 12591
     instance GHC.Internal.Read.Read GHC.Internal.TypeNats.SomeNat -- Defined in ‘GHC.Internal.TypeNats’
    
    12585 12592
     instance GHC.Internal.Read.Read GHC.Internal.TypeLits.SomeChar -- Defined in ‘GHC.Internal.TypeLits’
    
    12586 12593
     instance GHC.Internal.Read.Read GHC.Internal.TypeLits.SomeSymbol -- Defined in ‘GHC.Internal.TypeLits’
    
    12594
    +instance [safe] GHC.Internal.Read.Read GHC.Internal.System.IO.OS.OSHandleType -- Defined in ‘GHC.Internal.System.IO.OS’
    
    12587 12595
     instance forall a k (b :: k). GHC.Internal.Real.Fractional a => GHC.Internal.Real.Fractional (GHC.Internal.Data.Functor.Const.Const a b) -- Defined in ‘GHC.Internal.Data.Functor.Const’
    
    12588 12596
     instance forall a. GHC.Internal.Float.RealFloat a => GHC.Internal.Real.Fractional (Data.Complex.Complex a) -- Defined in ‘Data.Complex’
    
    12589 12597
     instance forall k (a :: k). Data.Fixed.HasResolution a => GHC.Internal.Real.Fractional (Data.Fixed.Fixed a) -- Defined in ‘Data.Fixed’
    
    ... ... @@ -12918,6 +12926,7 @@ instance forall (c :: GHC.Internal.Types.Char). GHC.Internal.Show.Show (GHC.Inte
    12918 12926
     instance forall (s :: GHC.Internal.Types.Symbol). GHC.Internal.Show.Show (GHC.Internal.TypeLits.SSymbol s) -- Defined in ‘GHC.Internal.TypeLits’
    
    12919 12927
     instance GHC.Internal.Show.Show GHC.Internal.TypeLits.SomeChar -- Defined in ‘GHC.Internal.TypeLits’
    
    12920 12928
     instance GHC.Internal.Show.Show GHC.Internal.TypeLits.SomeSymbol -- Defined in ‘GHC.Internal.TypeLits’
    
    12929
    +instance [safe] GHC.Internal.Show.Show GHC.Internal.System.IO.OS.OSHandleType -- Defined in ‘GHC.Internal.System.IO.OS’
    
    12921 12930
     instance GHC.Internal.Show.Show System.Timeout.Timeout -- Defined in ‘System.Timeout’
    
    12922 12931
     instance GHC.Internal.Show.Show GHC.Internal.Text.Read.Lex.Lexeme -- Defined in ‘GHC.Internal.Text.Read.Lex’
    
    12923 12932
     instance GHC.Internal.Show.Show GHC.Internal.Text.Read.Lex.Number -- Defined in ‘GHC.Internal.Text.Read.Lex’
    

  • testsuite/tests/interface-stability/base-exports.stdout-mingw32
    ... ... @@ -10330,6 +10330,9 @@ module System.IO.Error where
    10330 10330
     
    
    10331 10331
     module System.IO.OS where
    
    10332 10332
       -- Safety: Safe
    
    10333
    +  type OSHandleType :: *
    
    10334
    +  data OSHandleType = FileDescriptor | WindowsHandle
    
    10335
    +  osHandleType :: OSHandleType
    
    10333 10336
       withFileDescriptorReadingBiased :: forall r. GHC.Internal.IO.Handle.Types.Handle -> (GHC.Internal.Foreign.C.Types.CInt -> GHC.Internal.Types.IO r) -> GHC.Internal.Types.IO r
    
    10334 10337
       withFileDescriptorReadingBiasedRaw :: forall r. GHC.Internal.IO.Handle.Types.Handle -> (GHC.Internal.Foreign.C.Types.CInt -> GHC.Internal.Types.IO r) -> GHC.Internal.Types.IO r
    
    10335 10338
       withFileDescriptorWritingBiased :: forall r. GHC.Internal.IO.Handle.Types.Handle -> (GHC.Internal.Foreign.C.Types.CInt -> GHC.Internal.Types.IO r) -> GHC.Internal.Types.IO r
    
    ... ... @@ -11631,6 +11634,7 @@ instance forall (c :: GHC.Internal.Types.Char). GHC.Internal.Classes.Eq (GHC.Int
    11631 11634
     instance forall (s :: GHC.Internal.Types.Symbol). GHC.Internal.Classes.Eq (GHC.Internal.TypeLits.SSymbol s) -- Defined in ‘GHC.Internal.TypeLits’
    
    11632 11635
     instance GHC.Internal.Classes.Eq GHC.Internal.TypeLits.SomeChar -- Defined in ‘GHC.Internal.TypeLits’
    
    11633 11636
     instance GHC.Internal.Classes.Eq GHC.Internal.TypeLits.SomeSymbol -- Defined in ‘GHC.Internal.TypeLits’
    
    11637
    +instance [safe] GHC.Internal.Classes.Eq GHC.Internal.System.IO.OS.OSHandleType -- Defined in ‘GHC.Internal.System.IO.OS’
    
    11634 11638
     instance GHC.Internal.Classes.Eq System.Timeout.Timeout -- Defined in ‘System.Timeout’
    
    11635 11639
     instance GHC.Internal.Classes.Eq GHC.Internal.Text.Read.Lex.Lexeme -- Defined in ‘GHC.Internal.Text.Read.Lex’
    
    11636 11640
     instance GHC.Internal.Classes.Eq GHC.Internal.Text.Read.Lex.Number -- Defined in ‘GHC.Internal.Text.Read.Lex’
    
    ... ... @@ -11786,6 +11790,7 @@ instance forall (c :: GHC.Internal.Types.Char). GHC.Internal.Classes.Ord (GHC.In
    11786 11790
     instance forall (s :: GHC.Internal.Types.Symbol). GHC.Internal.Classes.Ord (GHC.Internal.TypeLits.SSymbol s) -- Defined in ‘GHC.Internal.TypeLits’
    
    11787 11791
     instance GHC.Internal.Classes.Ord GHC.Internal.TypeLits.SomeChar -- Defined in ‘GHC.Internal.TypeLits’
    
    11788 11792
     instance GHC.Internal.Classes.Ord GHC.Internal.TypeLits.SomeSymbol -- Defined in ‘GHC.Internal.TypeLits’
    
    11793
    +instance [safe] GHC.Internal.Classes.Ord GHC.Internal.System.IO.OS.OSHandleType -- Defined in ‘GHC.Internal.System.IO.OS’
    
    11789 11794
     instance GHC.Internal.Control.Arrow.Arrow (->) -- Defined in ‘GHC.Internal.Control.Arrow’
    
    11790 11795
     instance forall (m :: * -> *). GHC.Internal.Base.Monad m => GHC.Internal.Control.Arrow.Arrow (GHC.Internal.Control.Arrow.Kleisli m) -- Defined in ‘GHC.Internal.Control.Arrow’
    
    11791 11796
     instance GHC.Internal.Control.Arrow.ArrowApply (->) -- Defined in ‘GHC.Internal.Control.Arrow’
    
    ... ... @@ -12185,6 +12190,7 @@ instance GHC.Internal.Enum.Bounded GHC.Internal.Generics.Associativity -- Define
    12185 12190
     instance GHC.Internal.Enum.Bounded GHC.Internal.Generics.DecidedStrictness -- Defined in ‘GHC.Internal.Generics’
    
    12186 12191
     instance GHC.Internal.Enum.Bounded GHC.Internal.Generics.SourceStrictness -- Defined in ‘GHC.Internal.Generics’
    
    12187 12192
     instance GHC.Internal.Enum.Bounded GHC.Internal.Generics.SourceUnpackedness -- Defined in ‘GHC.Internal.Generics’
    
    12193
    +instance [safe] GHC.Internal.Enum.Bounded GHC.Internal.System.IO.OS.OSHandleType -- Defined in ‘GHC.Internal.System.IO.OS’
    
    12188 12194
     instance forall a k (b :: k). GHC.Internal.Enum.Enum a => GHC.Internal.Enum.Enum (GHC.Internal.Data.Functor.Const.Const a b) -- Defined in ‘GHC.Internal.Data.Functor.Const’
    
    12189 12195
     instance forall a. GHC.Internal.Enum.Enum a => GHC.Internal.Enum.Enum (GHC.Internal.Data.Bits.And a) -- Defined in ‘GHC.Internal.Data.Bits’
    
    12190 12196
     instance forall a. GHC.Internal.Enum.Enum a => GHC.Internal.Enum.Enum (GHC.Internal.Data.Bits.Iff a) -- Defined in ‘GHC.Internal.Data.Bits’
    
    ... ... @@ -12267,6 +12273,7 @@ instance GHC.Internal.Enum.Enum GHC.Internal.IO.Device.SeekMode -- Defined in
    12267 12273
     instance GHC.Internal.Enum.Enum GHC.Internal.IO.IOMode.IOMode -- Defined in ‘GHC.Internal.IO.IOMode’
    
    12268 12274
     instance GHC.Internal.Enum.Enum GHC.Internal.IO.SubSystem.IoSubSystem -- Defined in ‘GHC.Internal.IO.SubSystem’
    
    12269 12275
     instance GHC.Internal.Enum.Enum GHC.RTS.Flags.IoManagerFlag -- Defined in ‘GHC.RTS.Flags’
    
    12276
    +instance [safe] GHC.Internal.Enum.Enum GHC.Internal.System.IO.OS.OSHandleType -- Defined in ‘GHC.Internal.System.IO.OS’
    
    12270 12277
     instance GHC.Internal.Exception.Context.ExceptionAnnotation GHC.Internal.Exception.Type.WhileHandling -- Defined in ‘GHC.Internal.Exception.Type’
    
    12271 12278
     instance GHC.Internal.Exception.Context.ExceptionAnnotation GHC.Internal.Exception.Backtrace.Backtraces -- Defined in ‘GHC.Internal.Exception.Backtrace’
    
    12272 12279
     instance GHC.Internal.Exception.Type.Exception GHC.Internal.IO.Exception.AllocationLimitExceeded -- Defined in ‘GHC.Internal.IO.Exception’
    
    ... ... @@ -12827,6 +12834,7 @@ instance [safe] GHC.Internal.Read.Read GHC.Stats.RTSStats -- Defined in ‘GHC.S
    12827 12834
     instance GHC.Internal.Read.Read GHC.Internal.TypeNats.SomeNat -- Defined in ‘GHC.Internal.TypeNats’
    
    12828 12835
     instance GHC.Internal.Read.Read GHC.Internal.TypeLits.SomeChar -- Defined in ‘GHC.Internal.TypeLits’
    
    12829 12836
     instance GHC.Internal.Read.Read GHC.Internal.TypeLits.SomeSymbol -- Defined in ‘GHC.Internal.TypeLits’
    
    12837
    +instance [safe] GHC.Internal.Read.Read GHC.Internal.System.IO.OS.OSHandleType -- Defined in ‘GHC.Internal.System.IO.OS’
    
    12830 12838
     instance forall a k (b :: k). GHC.Internal.Real.Fractional a => GHC.Internal.Real.Fractional (GHC.Internal.Data.Functor.Const.Const a b) -- Defined in ‘GHC.Internal.Data.Functor.Const’
    
    12831 12839
     instance forall a. GHC.Internal.Float.RealFloat a => GHC.Internal.Real.Fractional (Data.Complex.Complex a) -- Defined in ‘Data.Complex’
    
    12832 12840
     instance forall k (a :: k). Data.Fixed.HasResolution a => GHC.Internal.Real.Fractional (Data.Fixed.Fixed a) -- Defined in ‘Data.Fixed’
    
    ... ... @@ -13166,6 +13174,7 @@ instance forall (c :: GHC.Internal.Types.Char). GHC.Internal.Show.Show (GHC.Inte
    13166 13174
     instance forall (s :: GHC.Internal.Types.Symbol). GHC.Internal.Show.Show (GHC.Internal.TypeLits.SSymbol s) -- Defined in ‘GHC.Internal.TypeLits’
    
    13167 13175
     instance GHC.Internal.Show.Show GHC.Internal.TypeLits.SomeChar -- Defined in ‘GHC.Internal.TypeLits’
    
    13168 13176
     instance GHC.Internal.Show.Show GHC.Internal.TypeLits.SomeSymbol -- Defined in ‘GHC.Internal.TypeLits’
    
    13177
    +instance [safe] GHC.Internal.Show.Show GHC.Internal.System.IO.OS.OSHandleType -- Defined in ‘GHC.Internal.System.IO.OS’
    
    13169 13178
     instance GHC.Internal.Show.Show System.Timeout.Timeout -- Defined in ‘System.Timeout’
    
    13170 13179
     instance GHC.Internal.Show.Show GHC.Internal.Text.Read.Lex.Lexeme -- Defined in ‘GHC.Internal.Text.Read.Lex’
    
    13171 13180
     instance GHC.Internal.Show.Show GHC.Internal.Text.Read.Lex.Number -- Defined in ‘GHC.Internal.Text.Read.Lex’
    

  • testsuite/tests/interface-stability/base-exports.stdout-ws-32
    ... ... @@ -10050,6 +10050,9 @@ module System.IO.Error where
    10050 10050
     
    
    10051 10051
     module System.IO.OS where
    
    10052 10052
       -- Safety: Safe
    
    10053
    +  type OSHandleType :: *
    
    10054
    +  data OSHandleType = FileDescriptor | WindowsHandle
    
    10055
    +  osHandleType :: OSHandleType
    
    10053 10056
       withFileDescriptorReadingBiased :: forall r. GHC.Internal.IO.Handle.Types.Handle -> (GHC.Internal.Foreign.C.Types.CInt -> GHC.Internal.Types.IO r) -> GHC.Internal.Types.IO r
    
    10054 10057
       withFileDescriptorReadingBiasedRaw :: forall r. GHC.Internal.IO.Handle.Types.Handle -> (GHC.Internal.Foreign.C.Types.CInt -> GHC.Internal.Types.IO r) -> GHC.Internal.Types.IO r
    
    10055 10058
       withFileDescriptorWritingBiased :: forall r. GHC.Internal.IO.Handle.Types.Handle -> (GHC.Internal.Foreign.C.Types.CInt -> GHC.Internal.Types.IO r) -> GHC.Internal.Types.IO r
    
    ... ... @@ -11375,6 +11378,7 @@ instance forall (c :: GHC.Internal.Types.Char). GHC.Internal.Classes.Eq (GHC.Int
    11375 11378
     instance forall (s :: GHC.Internal.Types.Symbol). GHC.Internal.Classes.Eq (GHC.Internal.TypeLits.SSymbol s) -- Defined in ‘GHC.Internal.TypeLits’
    
    11376 11379
     instance GHC.Internal.Classes.Eq GHC.Internal.TypeLits.SomeChar -- Defined in ‘GHC.Internal.TypeLits’
    
    11377 11380
     instance GHC.Internal.Classes.Eq GHC.Internal.TypeLits.SomeSymbol -- Defined in ‘GHC.Internal.TypeLits’
    
    11381
    +instance [safe] GHC.Internal.Classes.Eq GHC.Internal.System.IO.OS.OSHandleType -- Defined in ‘GHC.Internal.System.IO.OS’
    
    11378 11382
     instance GHC.Internal.Classes.Eq System.Timeout.Timeout -- Defined in ‘System.Timeout’
    
    11379 11383
     instance GHC.Internal.Classes.Eq GHC.Internal.Text.Read.Lex.Lexeme -- Defined in ‘GHC.Internal.Text.Read.Lex’
    
    11380 11384
     instance GHC.Internal.Classes.Eq GHC.Internal.Text.Read.Lex.Number -- Defined in ‘GHC.Internal.Text.Read.Lex’
    
    ... ... @@ -11528,6 +11532,7 @@ instance forall (c :: GHC.Internal.Types.Char). GHC.Internal.Classes.Ord (GHC.In
    11528 11532
     instance forall (s :: GHC.Internal.Types.Symbol). GHC.Internal.Classes.Ord (GHC.Internal.TypeLits.SSymbol s) -- Defined in ‘GHC.Internal.TypeLits’
    
    11529 11533
     instance GHC.Internal.Classes.Ord GHC.Internal.TypeLits.SomeChar -- Defined in ‘GHC.Internal.TypeLits’
    
    11530 11534
     instance GHC.Internal.Classes.Ord GHC.Internal.TypeLits.SomeSymbol -- Defined in ‘GHC.Internal.TypeLits’
    
    11535
    +instance [safe] GHC.Internal.Classes.Ord GHC.Internal.System.IO.OS.OSHandleType -- Defined in ‘GHC.Internal.System.IO.OS’
    
    11531 11536
     instance GHC.Internal.Control.Arrow.Arrow (->) -- Defined in ‘GHC.Internal.Control.Arrow’
    
    11532 11537
     instance forall (m :: * -> *). GHC.Internal.Base.Monad m => GHC.Internal.Control.Arrow.Arrow (GHC.Internal.Control.Arrow.Kleisli m) -- Defined in ‘GHC.Internal.Control.Arrow’
    
    11533 11538
     instance GHC.Internal.Control.Arrow.ArrowApply (->) -- Defined in ‘GHC.Internal.Control.Arrow’
    
    ... ... @@ -11927,6 +11932,7 @@ instance GHC.Internal.Enum.Bounded GHC.Internal.Generics.Associativity -- Define
    11927 11932
     instance GHC.Internal.Enum.Bounded GHC.Internal.Generics.DecidedStrictness -- Defined in ‘GHC.Internal.Generics’
    
    11928 11933
     instance GHC.Internal.Enum.Bounded GHC.Internal.Generics.SourceStrictness -- Defined in ‘GHC.Internal.Generics’
    
    11929 11934
     instance GHC.Internal.Enum.Bounded GHC.Internal.Generics.SourceUnpackedness -- Defined in ‘GHC.Internal.Generics’
    
    11935
    +instance [safe] GHC.Internal.Enum.Bounded GHC.Internal.System.IO.OS.OSHandleType -- Defined in ‘GHC.Internal.System.IO.OS’
    
    11930 11936
     instance forall a k (b :: k). GHC.Internal.Enum.Enum a => GHC.Internal.Enum.Enum (GHC.Internal.Data.Functor.Const.Const a b) -- Defined in ‘GHC.Internal.Data.Functor.Const’
    
    11931 11937
     instance forall a. GHC.Internal.Enum.Enum a => GHC.Internal.Enum.Enum (GHC.Internal.Data.Bits.And a) -- Defined in ‘GHC.Internal.Data.Bits’
    
    11932 11938
     instance forall a. GHC.Internal.Enum.Enum a => GHC.Internal.Enum.Enum (GHC.Internal.Data.Bits.Iff a) -- Defined in ‘GHC.Internal.Data.Bits’
    
    ... ... @@ -12008,6 +12014,7 @@ instance GHC.Internal.Enum.Enum GHC.Internal.IO.Device.SeekMode -- Defined in
    12008 12014
     instance GHC.Internal.Enum.Enum GHC.Internal.IO.IOMode.IOMode -- Defined in ‘GHC.Internal.IO.IOMode’
    
    12009 12015
     instance GHC.Internal.Enum.Enum GHC.Internal.IO.SubSystem.IoSubSystem -- Defined in ‘GHC.Internal.IO.SubSystem’
    
    12010 12016
     instance GHC.Internal.Enum.Enum GHC.RTS.Flags.IoManagerFlag -- Defined in ‘GHC.RTS.Flags’
    
    12017
    +instance [safe] GHC.Internal.Enum.Enum GHC.Internal.System.IO.OS.OSHandleType -- Defined in ‘GHC.Internal.System.IO.OS’
    
    12011 12018
     instance GHC.Internal.Exception.Context.ExceptionAnnotation GHC.Internal.Exception.Type.WhileHandling -- Defined in ‘GHC.Internal.Exception.Type’
    
    12012 12019
     instance GHC.Internal.Exception.Context.ExceptionAnnotation GHC.Internal.Exception.Backtrace.Backtraces -- Defined in ‘GHC.Internal.Exception.Backtrace’
    
    12013 12020
     instance GHC.Internal.Exception.Type.Exception GHC.Internal.IO.Exception.AllocationLimitExceeded -- Defined in ‘GHC.Internal.IO.Exception’
    
    ... ... @@ -12555,6 +12562,7 @@ instance [safe] GHC.Internal.Read.Read GHC.Stats.RTSStats -- Defined in ‘GHC.S
    12555 12562
     instance GHC.Internal.Read.Read GHC.Internal.TypeNats.SomeNat -- Defined in ‘GHC.Internal.TypeNats’
    
    12556 12563
     instance GHC.Internal.Read.Read GHC.Internal.TypeLits.SomeChar -- Defined in ‘GHC.Internal.TypeLits’
    
    12557 12564
     instance GHC.Internal.Read.Read GHC.Internal.TypeLits.SomeSymbol -- Defined in ‘GHC.Internal.TypeLits’
    
    12565
    +instance [safe] GHC.Internal.Read.Read GHC.Internal.System.IO.OS.OSHandleType -- Defined in ‘GHC.Internal.System.IO.OS’
    
    12558 12566
     instance forall a k (b :: k). GHC.Internal.Real.Fractional a => GHC.Internal.Real.Fractional (GHC.Internal.Data.Functor.Const.Const a b) -- Defined in ‘GHC.Internal.Data.Functor.Const’
    
    12559 12567
     instance forall a. GHC.Internal.Float.RealFloat a => GHC.Internal.Real.Fractional (Data.Complex.Complex a) -- Defined in ‘Data.Complex’
    
    12560 12568
     instance forall k (a :: k). Data.Fixed.HasResolution a => GHC.Internal.Real.Fractional (Data.Fixed.Fixed a) -- Defined in ‘Data.Fixed’
    
    ... ... @@ -12894,6 +12902,7 @@ instance forall (c :: GHC.Internal.Types.Char). GHC.Internal.Show.Show (GHC.Inte
    12894 12902
     instance forall (s :: GHC.Internal.Types.Symbol). GHC.Internal.Show.Show (GHC.Internal.TypeLits.SSymbol s) -- Defined in ‘GHC.Internal.TypeLits’
    
    12895 12903
     instance GHC.Internal.Show.Show GHC.Internal.TypeLits.SomeChar -- Defined in ‘GHC.Internal.TypeLits’
    
    12896 12904
     instance GHC.Internal.Show.Show GHC.Internal.TypeLits.SomeSymbol -- Defined in ‘GHC.Internal.TypeLits’
    
    12905
    +instance [safe] GHC.Internal.Show.Show GHC.Internal.System.IO.OS.OSHandleType -- Defined in ‘GHC.Internal.System.IO.OS’
    
    12897 12906
     instance GHC.Internal.Show.Show System.Timeout.Timeout -- Defined in ‘System.Timeout’
    
    12898 12907
     instance GHC.Internal.Show.Show GHC.Internal.Text.Read.Lex.Lexeme -- Defined in ‘GHC.Internal.Text.Read.Lex’
    
    12899 12908
     instance GHC.Internal.Show.Show GHC.Internal.Text.Read.Lex.Number -- Defined in ‘GHC.Internal.Text.Read.Lex’