Wolfgang Jeltsch pushed to branch wip/jeltsch/obtaining-os-handles at Glasgow Haskell Compiler / GHC
Commits:
-
9b010c8f
by Wolfgang Jeltsch at 2025-12-20T18:32:15+02:00
9 changed files:
- libraries/base/base.cabal.in
- libraries/base/changelog.md
- + libraries/base/src/System/IO/OS.hs
- libraries/ghc-internal/ghc-internal.cabal.in
- + libraries/ghc-internal/src/GHC/Internal/System/IO/OS.hs
- testsuite/tests/interface-stability/base-exports.stdout
- testsuite/tests/interface-stability/base-exports.stdout-javascript-unknown-ghcjs
- testsuite/tests/interface-stability/base-exports.stdout-mingw32
- testsuite/tests/interface-stability/base-exports.stdout-ws-32
Changes:
| ... | ... | @@ -258,6 +258,7 @@ Library |
| 258 | 258 | , System.Exit
|
| 259 | 259 | , System.IO
|
| 260 | 260 | , System.IO.Error
|
| 261 | + , System.IO.OS
|
|
| 261 | 262 | , System.Mem
|
| 262 | 263 | , System.Mem.StableName
|
| 263 | 264 | , System.Posix.Internals
|
| ... | ... | @@ -16,6 +16,7 @@ |
| 16 | 16 | * Adjust the strictness of `Data.List.iterate'` to be more reasonable: every element of the output list is forced to WHNF when the `(:)` containing it is forced. ([CLC proposal #335)](https://github.com/haskell/core-libraries-committee/issues/335)
|
| 17 | 17 | * Add `nubOrd` / `nubOrdBy` to `Data.List` and `Data.List.NonEmpty`. ([CLC proposal #336](https://github.com/haskell/core-libraries-committee/issues/336))
|
| 18 | 18 | * Add `Semigroup` and `Monoid` instances for `Control.Monad.ST.Lazy`. ([CLC proposal #374](https://github.com/haskell/core-libraries-committee/issues/374))
|
| 19 | + * 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))
|
|
| 19 | 20 | |
| 20 | 21 | ## 4.22.0.0 *TBA*
|
| 21 | 22 | * Shipped with GHC 9.14.1
|
| 1 | +{-# LANGUAGE Safe #-}
|
|
| 2 | + |
|
| 3 | +{-|
|
|
| 4 | + This module bridges between Haskell handles and underlying operating-system
|
|
| 5 | + features.
|
|
| 6 | +-}
|
|
| 7 | +module System.IO.OS
|
|
| 8 | +(
|
|
| 9 | + -- * Obtaining file descriptors and Windows handles
|
|
| 10 | + withFileDescriptorReadingBiased,
|
|
| 11 | + withFileDescriptorWritingBiased,
|
|
| 12 | + withWindowsHandleReadingBiased,
|
|
| 13 | + withWindowsHandleWritingBiased,
|
|
| 14 | + withFileDescriptorReadingBiasedRaw,
|
|
| 15 | + withFileDescriptorWritingBiasedRaw,
|
|
| 16 | + withWindowsHandleReadingBiasedRaw,
|
|
| 17 | + withWindowsHandleWritingBiasedRaw
|
|
| 18 | + |
|
| 19 | + -- ** Caveats
|
|
| 20 | + -- $with-ref-caveats
|
|
| 21 | +)
|
|
| 22 | +where
|
|
| 23 | + |
|
| 24 | +import GHC.Internal.System.IO.OS
|
|
| 25 | + (
|
|
| 26 | + withFileDescriptorReadingBiased,
|
|
| 27 | + withFileDescriptorWritingBiased,
|
|
| 28 | + withWindowsHandleReadingBiased,
|
|
| 29 | + withWindowsHandleWritingBiased,
|
|
| 30 | + withFileDescriptorReadingBiasedRaw,
|
|
| 31 | + withFileDescriptorWritingBiasedRaw,
|
|
| 32 | + withWindowsHandleReadingBiasedRaw,
|
|
| 33 | + withWindowsHandleWritingBiasedRaw
|
|
| 34 | + )
|
|
| 35 | + |
|
| 36 | +-- ** Caveats
|
|
| 37 | + |
|
| 38 | +{-$with-ref-caveats
|
|
| 39 | + #with-ref-caveats#There are the following caveats regarding the above
|
|
| 40 | + operations:
|
|
| 41 | + |
|
| 42 | + * Flushing of buffers can fail if the given handle is readable but not
|
|
| 43 | + seekable.
|
|
| 44 | + |
|
| 45 | + * If one of these operations is performed as part of an action executed by
|
|
| 46 | + 'System.IO.Unsafe.unsafePerformIO',
|
|
| 47 | + 'System.IO.Unsafe.unsafeInterleaveIO', or one of their “dupable”
|
|
| 48 | + variants and the user-provided action receives an asychnchronous
|
|
| 49 | + exception and does not catch it, then the following happens:
|
|
| 50 | + |
|
| 51 | + - Before the overall computation is suspended, the blocking of handle
|
|
| 52 | + operations is removed.
|
|
| 53 | + |
|
| 54 | + - When the computation is later resumed due to another evaluation
|
|
| 55 | + attempt, the blocking of handle operations is reinstantiated, the
|
|
| 56 | + Haskell-managed buffers are flushed again, and the user-provided
|
|
| 57 | + action is run from the beginning.
|
|
| 58 | + |
|
| 59 | + Repeating the previously executed part of the user-provided action
|
|
| 60 | + cannot be avoided apparently. See the @[async]@ note in the source code
|
|
| 61 | + of "GHC.Internal.IO.Handle.Internals" for further explanation.
|
|
| 62 | +-} |
| ... | ... | @@ -327,6 +327,7 @@ Library |
| 327 | 327 | GHC.Internal.System.Exit
|
| 328 | 328 | GHC.Internal.System.IO
|
| 329 | 329 | GHC.Internal.System.IO.Error
|
| 330 | + GHC.Internal.System.IO.OS
|
|
| 330 | 331 | GHC.Internal.System.Mem
|
| 331 | 332 | GHC.Internal.System.Mem.StableName
|
| 332 | 333 | GHC.Internal.System.Posix.Internals
|
| 1 | +{-# LANGUAGE Safe #-}
|
|
| 2 | +{-# LANGUAGE CPP #-}
|
|
| 3 | +{-# LANGUAGE RankNTypes #-}
|
|
| 4 | + |
|
| 5 | +{-|
|
|
| 6 | + This module bridges between Haskell handles and underlying operating-system
|
|
| 7 | + features.
|
|
| 8 | +-}
|
|
| 9 | +module GHC.Internal.System.IO.OS
|
|
| 10 | +(
|
|
| 11 | + -- * Obtaining file descriptors and Windows handles
|
|
| 12 | + withFileDescriptorReadingBiased,
|
|
| 13 | + withFileDescriptorWritingBiased,
|
|
| 14 | + withWindowsHandleReadingBiased,
|
|
| 15 | + withWindowsHandleWritingBiased,
|
|
| 16 | + withFileDescriptorReadingBiasedRaw,
|
|
| 17 | + withFileDescriptorWritingBiasedRaw,
|
|
| 18 | + withWindowsHandleReadingBiasedRaw,
|
|
| 19 | + withWindowsHandleWritingBiasedRaw
|
|
| 20 | + |
|
| 21 | + -- ** Caveats
|
|
| 22 | + -- $with-ref-caveats
|
|
| 23 | +)
|
|
| 24 | +where
|
|
| 25 | + |
|
| 26 | +import GHC.Internal.Control.Monad (return)
|
|
| 27 | +import GHC.Internal.Control.Concurrent.MVar (MVar)
|
|
| 28 | +import GHC.Internal.Control.Exception (mask)
|
|
| 29 | +import GHC.Internal.Data.Function (const, (.), ($))
|
|
| 30 | +import GHC.Internal.Data.Functor (fmap)
|
|
| 31 | +#if defined(mingw32_HOST_OS)
|
|
| 32 | +import GHC.Internal.Data.Bool (otherwise)
|
|
| 33 | +#endif
|
|
| 34 | +import GHC.Internal.Data.Maybe (Maybe (Nothing), maybe)
|
|
| 35 | +#if defined(mingw32_HOST_OS)
|
|
| 36 | +import GHC.Internal.Data.Maybe (Maybe (Just))
|
|
| 37 | +#endif
|
|
| 38 | +import GHC.Internal.Data.List ((++))
|
|
| 39 | +import GHC.Internal.Data.String (String)
|
|
| 40 | +import GHC.Internal.Data.Typeable (Typeable, cast)
|
|
| 41 | +import GHC.Internal.System.IO (IO)
|
|
| 42 | +import GHC.Internal.IO.FD (fdFD)
|
|
| 43 | +#if defined(mingw32_HOST_OS)
|
|
| 44 | +import GHC.Internal.IO.Windows.Handle
|
|
| 45 | + (
|
|
| 46 | + NativeHandle,
|
|
| 47 | + ConsoleHandle,
|
|
| 48 | + IoHandle,
|
|
| 49 | + toHANDLE
|
|
| 50 | + )
|
|
| 51 | +#endif
|
|
| 52 | +import GHC.Internal.IO.Handle.Types
|
|
| 53 | + (
|
|
| 54 | + Handle (FileHandle, DuplexHandle),
|
|
| 55 | + Handle__ (Handle__, haDevice)
|
|
| 56 | + )
|
|
| 57 | +import GHC.Internal.IO.Handle.Internals (withHandle_', flushBuffer)
|
|
| 58 | +import GHC.Internal.IO.Exception
|
|
| 59 | + (
|
|
| 60 | + IOErrorType (InappropriateType),
|
|
| 61 | + IOException (IOError),
|
|
| 62 | + ioException
|
|
| 63 | + )
|
|
| 64 | +import GHC.Internal.Foreign.Ptr (Ptr)
|
|
| 65 | +import GHC.Internal.Foreign.C.Types (CInt)
|
|
| 66 | + |
|
| 67 | +-- * Obtaining POSIX file descriptors and Windows handles
|
|
| 68 | + |
|
| 69 | +{-|
|
|
| 70 | + Executes a user-provided action on an operating-system handle that underlies
|
|
| 71 | + a Haskell handle. Before the user-provided action is run, user-defined
|
|
| 72 | + perparation based on the handle state that contains the operating-system
|
|
| 73 | + handle is performed. While the user-provided action is executed, further
|
|
| 74 | + operations on the Haskell handle are blocked to a degree that interference
|
|
| 75 | + with this action is prevented.
|
|
| 76 | + |
|
| 77 | + See [below](#with-ref-caveats) for caveats regarding this operation.
|
|
| 78 | +-}
|
|
| 79 | +withOSHandle :: String
|
|
| 80 | + -- ^ The name of the overall operation
|
|
| 81 | + -> (Handle -> MVar Handle__)
|
|
| 82 | + {-^
|
|
| 83 | + Obtaining of the handle state variable that holds the
|
|
| 84 | + operating-system handle
|
|
| 85 | + -}
|
|
| 86 | + -> (forall d. Typeable d => d -> IO a)
|
|
| 87 | + -- ^ Conversion of a device into an operating-system handle
|
|
| 88 | + -> (Handle__ -> IO ())
|
|
| 89 | + -- ^ The preparation
|
|
| 90 | + -> Handle
|
|
| 91 | + -- ^ The Haskell handle to use
|
|
| 92 | + -> (a -> IO r)
|
|
| 93 | + -- ^ The action to execute on the operating-system handle
|
|
| 94 | + -> IO r
|
|
| 95 | +withOSHandle opName handleStateVar getOSHandle prepare handle act
|
|
| 96 | + = mask $ \ withOriginalMaskingState ->
|
|
| 97 | + withHandleState $ \ handleState@Handle__ {haDevice = dev} -> do
|
|
| 98 | + osHandle <- getOSHandle dev
|
|
| 99 | + prepare handleState
|
|
| 100 | + withOriginalMaskingState $ act osHandle
|
|
| 101 | + where
|
|
| 102 | + |
|
| 103 | + withHandleState = withHandle_' opName handle (handleStateVar handle)
|
|
| 104 | +{-
|
|
| 105 | + The 'withHandle_'' operation, which we use here, already performs masking.
|
|
| 106 | + Still, we have to employ 'mask', in order do obtain the operation that
|
|
| 107 | + restores the original masking state. The user-provided action should be
|
|
| 108 | + executed with this original masking state, as there is no inherent reason to
|
|
| 109 | + generally perform it with masking in place. The masking that 'withHandle_''
|
|
| 110 | + performs is only for safely accessing handle state and thus constitutes an
|
|
| 111 | + implementation detail; it has nothing to do with the user-provided action.
|
|
| 112 | +-}
|
|
| 113 | +{-
|
|
| 114 | + The order of actions in 'withOSHandle' is such that any exception from
|
|
| 115 | + 'getOSHandle' is thrown before the flushing of the Haskell-managed buffers.
|
|
| 116 | +-}
|
|
| 117 | + |
|
| 118 | +{-|
|
|
| 119 | + Obtains the handle state variable that underlies a handle or specifically
|
|
| 120 | + the handle state variable for reading if the handle uses different state
|
|
| 121 | + variables for reading and writing.
|
|
| 122 | +-}
|
|
| 123 | +handleStateVarReadingBiased :: Handle -> MVar Handle__
|
|
| 124 | +handleStateVarReadingBiased (FileHandle _ var) = var
|
|
| 125 | +handleStateVarReadingBiased (DuplexHandle _ readingVar _) = readingVar
|
|
| 126 | + |
|
| 127 | +{-|
|
|
| 128 | + Obtains the handle state variable that underlies a handle or specifically
|
|
| 129 | + the handle state variable for writing if the handle uses different state
|
|
| 130 | + variables for reading and writing.
|
|
| 131 | +-}
|
|
| 132 | +handleStateVarWritingBiased :: Handle -> MVar Handle__
|
|
| 133 | +handleStateVarWritingBiased (FileHandle _ var) = var
|
|
| 134 | +handleStateVarWritingBiased (DuplexHandle _ _ writingVar) = writingVar
|
|
| 135 | + |
|
| 136 | +{-|
|
|
| 137 | + Yields the result of another operation if that operation succeeded, and
|
|
| 138 | + otherwise throws an exception that signals that the other operation failed
|
|
| 139 | + because some Haskell handle does not use an operating-system handle of a
|
|
| 140 | + required type.
|
|
| 141 | +-}
|
|
| 142 | +requiringOSHandleOfType :: String
|
|
| 143 | + -- ^ The name of the operating-system handle type
|
|
| 144 | + -> Maybe a
|
|
| 145 | + {-^
|
|
| 146 | + The result of the other operation if it succeeded
|
|
| 147 | + -}
|
|
| 148 | + -> IO a
|
|
| 149 | +requiringOSHandleOfType osHandleTypeName
|
|
| 150 | + = maybe (ioException osHandleOfTypeRequired) return
|
|
| 151 | + where
|
|
| 152 | + |
|
| 153 | + osHandleOfTypeRequired :: IOException
|
|
| 154 | + osHandleOfTypeRequired
|
|
| 155 | + = IOError Nothing
|
|
| 156 | + InappropriateType
|
|
| 157 | + ""
|
|
| 158 | + ("handle does not use " ++ osHandleTypeName ++ "s")
|
|
| 159 | + Nothing
|
|
| 160 | + Nothing
|
|
| 161 | + |
|
| 162 | +{-|
|
|
| 163 | + Obtains the POSIX file descriptor of a device if the device contains one,
|
|
| 164 | + and throws an exception otherwise.
|
|
| 165 | +-}
|
|
| 166 | +getFileDescriptor :: Typeable d => d -> IO CInt
|
|
| 167 | +getFileDescriptor = requiringOSHandleOfType "POSIX file descriptor" .
|
|
| 168 | + fmap fdFD . cast
|
|
| 169 | + |
|
| 170 | +{-|
|
|
| 171 | + Obtains the Windows handle of a device if the device contains one, and
|
|
| 172 | + throws an exception otherwise.
|
|
| 173 | +-}
|
|
| 174 | +getWindowsHandle :: Typeable d => d -> IO (Ptr ())
|
|
| 175 | +getWindowsHandle = requiringOSHandleOfType "Windows handle" .
|
|
| 176 | + toMaybeWindowsHandle
|
|
| 177 | + where
|
|
| 178 | + |
|
| 179 | + toMaybeWindowsHandle :: Typeable d => d -> Maybe (Ptr ())
|
|
| 180 | +#if defined(mingw32_HOST_OS)
|
|
| 181 | + toMaybeWindowsHandle dev
|
|
| 182 | + | Just nativeHandle <- cast dev :: Maybe (IoHandle NativeHandle)
|
|
| 183 | + = Just (toHANDLE nativeHandle)
|
|
| 184 | + | Just consoleHandle <- cast dev :: Maybe (IoHandle ConsoleHandle)
|
|
| 185 | + = Just (toHANDLE consoleHandle)
|
|
| 186 | + | otherwise
|
|
| 187 | + = Nothing
|
|
| 188 | + {-
|
|
| 189 | + This is inspired by the implementation of
|
|
| 190 | + 'System.Win32.Types.withHandleToHANDLENative'.
|
|
| 191 | + -}
|
|
| 192 | +#else
|
|
| 193 | + toMaybeWindowsHandle _ = Nothing
|
|
| 194 | +#endif
|
|
| 195 | + |
|
| 196 | +{-|
|
|
| 197 | + Executes a user-provided action on the POSIX file descriptor that underlies
|
|
| 198 | + a handle or specifically on the POSIX file descriptor for reading if the
|
|
| 199 | + handle uses different file descriptors for reading and writing. The
|
|
| 200 | + Haskell-managed buffers related to the file descriptor are flushed before
|
|
| 201 | + the user-provided action is run. While this action is executed, further
|
|
| 202 | + operations on the handle are blocked to a degree that interference with this
|
|
| 203 | + action is prevented.
|
|
| 204 | + |
|
| 205 | + If the handle does not use POSIX file descriptors, an exception is thrown.
|
|
| 206 | + |
|
| 207 | + See [below](#with-ref-caveats) for caveats regarding this operation.
|
|
| 208 | +-}
|
|
| 209 | +withFileDescriptorReadingBiased :: Handle -> (CInt -> IO r) -> IO r
|
|
| 210 | +withFileDescriptorReadingBiased = withOSHandle "withFileDescriptorReadingBiased"
|
|
| 211 | + handleStateVarReadingBiased
|
|
| 212 | + getFileDescriptor
|
|
| 213 | + flushBuffer
|
|
| 214 | + |
|
| 215 | +{-|
|
|
| 216 | + Executes a user-provided action on the POSIX file descriptor that underlies
|
|
| 217 | + a handle or specifically on the POSIX file descriptor for writing if the
|
|
| 218 | + handle uses different file descriptors for reading and writing. The
|
|
| 219 | + Haskell-managed buffers related to the file descriptor are flushed before
|
|
| 220 | + the user-provided action is run. While this action is executed, further
|
|
| 221 | + operations on the handle are blocked to a degree that interference with this
|
|
| 222 | + action is prevented.
|
|
| 223 | + |
|
| 224 | + If the handle does not use POSIX file descriptors, an exception is thrown.
|
|
| 225 | + |
|
| 226 | + See [below](#with-ref-caveats) for caveats regarding this operation.
|
|
| 227 | +-}
|
|
| 228 | +withFileDescriptorWritingBiased :: Handle -> (CInt -> IO r) -> IO r
|
|
| 229 | +withFileDescriptorWritingBiased = withOSHandle "withFileDescriptorWritingBiased"
|
|
| 230 | + handleStateVarWritingBiased
|
|
| 231 | + getFileDescriptor
|
|
| 232 | + flushBuffer
|
|
| 233 | + |
|
| 234 | +{-|
|
|
| 235 | + Executes a user-provided action on the Windows handle that underlies a
|
|
| 236 | + Haskell handle or specifically on the Windows handle for reading if the
|
|
| 237 | + Haskell handle uses different Windows handles for reading and writing. The
|
|
| 238 | + Haskell-managed buffers related to the Windows handle are flushed before the
|
|
| 239 | + user-provided action is run. While this action is executed, further
|
|
| 240 | + operations on the Haskell handle are blocked to a degree that interference
|
|
| 241 | + with this action is prevented.
|
|
| 242 | + |
|
| 243 | + If the Haskell handle does not use Windows handles, an exception is thrown.
|
|
| 244 | + |
|
| 245 | + See [below](#with-ref-caveats) for caveats regarding this operation.
|
|
| 246 | +-}
|
|
| 247 | +withWindowsHandleReadingBiased :: Handle -> (Ptr () -> IO r) -> IO r
|
|
| 248 | +withWindowsHandleReadingBiased = withOSHandle "withWindowsHandleReadingBiased"
|
|
| 249 | + handleStateVarReadingBiased
|
|
| 250 | + getWindowsHandle
|
|
| 251 | + flushBuffer
|
|
| 252 | + |
|
| 253 | +{-|
|
|
| 254 | + Executes a user-provided action on the Windows handle that underlies a
|
|
| 255 | + Haskell handle or specifically on the Windows handle for writing if the
|
|
| 256 | + Haskell handle uses different Windows handles for reading and writing. The
|
|
| 257 | + Haskell-managed buffers related to the Windows handle are flushed before the
|
|
| 258 | + user-provided action is run. While this action is executed, further
|
|
| 259 | + operations on the Haskell handle are blocked to a degree that interference
|
|
| 260 | + with this action is prevented.
|
|
| 261 | + |
|
| 262 | + If the Haskell handle does not use Windows handles, an exception is thrown.
|
|
| 263 | + |
|
| 264 | + See [below](#with-ref-caveats) for caveats regarding this operation.
|
|
| 265 | +-}
|
|
| 266 | +withWindowsHandleWritingBiased :: Handle -> (Ptr () -> IO r) -> IO r
|
|
| 267 | +withWindowsHandleWritingBiased = withOSHandle "withWindowsHandleWritingBiased"
|
|
| 268 | + handleStateVarWritingBiased
|
|
| 269 | + getWindowsHandle
|
|
| 270 | + flushBuffer
|
|
| 271 | + |
|
| 272 | +{-|
|
|
| 273 | + Like 'withFileDescriptorReadingBiased' except that Haskell-managed buffers
|
|
| 274 | + are not flushed.
|
|
| 275 | +-}
|
|
| 276 | +withFileDescriptorReadingBiasedRaw :: Handle -> (CInt -> IO r) -> IO r
|
|
| 277 | +withFileDescriptorReadingBiasedRaw
|
|
| 278 | + = withOSHandle "withFileDescriptorReadingBiasedRaw"
|
|
| 279 | + handleStateVarReadingBiased
|
|
| 280 | + getFileDescriptor
|
|
| 281 | + (const $ return ())
|
|
| 282 | + |
|
| 283 | +{-|
|
|
| 284 | + Like 'withFileDescriptorWritingBiased' except that Haskell-managed buffers
|
|
| 285 | + are not flushed.
|
|
| 286 | +-}
|
|
| 287 | +withFileDescriptorWritingBiasedRaw :: Handle -> (CInt -> IO r) -> IO r
|
|
| 288 | +withFileDescriptorWritingBiasedRaw
|
|
| 289 | + = withOSHandle "withFileDescriptorWritingBiasedRaw"
|
|
| 290 | + handleStateVarWritingBiased
|
|
| 291 | + getFileDescriptor
|
|
| 292 | + (const $ return ())
|
|
| 293 | + |
|
| 294 | +{-|
|
|
| 295 | + Like 'withWindowsHandleReadingBiased' except that Haskell-managed buffers
|
|
| 296 | + are not flushed.
|
|
| 297 | +-}
|
|
| 298 | +withWindowsHandleReadingBiasedRaw :: Handle -> (Ptr () -> IO r) -> IO r
|
|
| 299 | +withWindowsHandleReadingBiasedRaw
|
|
| 300 | + = withOSHandle "withWindowsHandleReadingBiasedRaw"
|
|
| 301 | + handleStateVarReadingBiased
|
|
| 302 | + getWindowsHandle
|
|
| 303 | + (const $ return ())
|
|
| 304 | + |
|
| 305 | +{-|
|
|
| 306 | + Like 'withWindowsHandleWritingBiased' except that Haskell-managed buffers
|
|
| 307 | + are not flushed.
|
|
| 308 | +-}
|
|
| 309 | +withWindowsHandleWritingBiasedRaw :: Handle -> (Ptr () -> IO r) -> IO r
|
|
| 310 | +withWindowsHandleWritingBiasedRaw
|
|
| 311 | + = withOSHandle "withWindowsHandleWritingBiasedRaw"
|
|
| 312 | + handleStateVarWritingBiased
|
|
| 313 | + getWindowsHandle
|
|
| 314 | + (const $ return ())
|
|
| 315 | + |
|
| 316 | +-- ** Caveats
|
|
| 317 | + |
|
| 318 | +{-$with-ref-caveats
|
|
| 319 | + #with-ref-caveats#This subsection is just a dummy, whose purpose is to serve
|
|
| 320 | + as the target of the hyperlinks above. The real documentation of the caveats
|
|
| 321 | + is in the /Caveats/ subsection in the @base@ module @System.IO.OS@, which
|
|
| 322 | + re-exports the above operations.
|
|
| 323 | +-} |
| ... | ... | @@ -10379,6 +10379,17 @@ module System.IO.Error where |
| 10379 | 10379 | userError :: GHC.Internal.Base.String -> IOError
|
| 10380 | 10380 | userErrorType :: IOErrorType
|
| 10381 | 10381 | |
| 10382 | +module System.IO.OS where
|
|
| 10383 | + -- Safety: Safe
|
|
| 10384 | + 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
|
|
| 10385 | + 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
|
|
| 10386 | + 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
|
|
| 10387 | + withFileDescriptorWritingBiasedRaw :: forall r. GHC.Internal.IO.Handle.Types.Handle -> (GHC.Internal.Foreign.C.Types.CInt -> GHC.Internal.Types.IO r) -> GHC.Internal.Types.IO r
|
|
| 10388 | + withWindowsHandleReadingBiased :: forall r. GHC.Internal.IO.Handle.Types.Handle -> (GHC.Internal.Ptr.Ptr () -> GHC.Internal.Types.IO r) -> GHC.Internal.Types.IO r
|
|
| 10389 | + withWindowsHandleReadingBiasedRaw :: forall r. GHC.Internal.IO.Handle.Types.Handle -> (GHC.Internal.Ptr.Ptr () -> GHC.Internal.Types.IO r) -> GHC.Internal.Types.IO r
|
|
| 10390 | + withWindowsHandleWritingBiased :: forall r. GHC.Internal.IO.Handle.Types.Handle -> (GHC.Internal.Ptr.Ptr () -> GHC.Internal.Types.IO r) -> GHC.Internal.Types.IO r
|
|
| 10391 | + withWindowsHandleWritingBiasedRaw :: forall r. GHC.Internal.IO.Handle.Types.Handle -> (GHC.Internal.Ptr.Ptr () -> GHC.Internal.Types.IO r) -> GHC.Internal.Types.IO r
|
|
| 10392 | + |
|
| 10382 | 10393 | module System.IO.Unsafe where
|
| 10383 | 10394 | -- Safety: Unsafe
|
| 10384 | 10395 | unsafeDupablePerformIO :: forall a. GHC.Internal.Types.IO a -> a
|
| ... | ... | @@ -13425,6 +13425,17 @@ module System.IO.Error where |
| 13425 | 13425 | userError :: GHC.Internal.Base.String -> IOError
|
| 13426 | 13426 | userErrorType :: IOErrorType
|
| 13427 | 13427 | |
| 13428 | +module System.IO.OS where
|
|
| 13429 | + -- Safety: Safe
|
|
| 13430 | + 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
|
|
| 13431 | + 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
|
|
| 13432 | + 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
|
|
| 13433 | + withFileDescriptorWritingBiasedRaw :: forall r. GHC.Internal.IO.Handle.Types.Handle -> (GHC.Internal.Foreign.C.Types.CInt -> GHC.Internal.Types.IO r) -> GHC.Internal.Types.IO r
|
|
| 13434 | + withWindowsHandleReadingBiased :: forall r. GHC.Internal.IO.Handle.Types.Handle -> (GHC.Internal.Ptr.Ptr () -> GHC.Internal.Types.IO r) -> GHC.Internal.Types.IO r
|
|
| 13435 | + withWindowsHandleReadingBiasedRaw :: forall r. GHC.Internal.IO.Handle.Types.Handle -> (GHC.Internal.Ptr.Ptr () -> GHC.Internal.Types.IO r) -> GHC.Internal.Types.IO r
|
|
| 13436 | + withWindowsHandleWritingBiased :: forall r. GHC.Internal.IO.Handle.Types.Handle -> (GHC.Internal.Ptr.Ptr () -> GHC.Internal.Types.IO r) -> GHC.Internal.Types.IO r
|
|
| 13437 | + withWindowsHandleWritingBiasedRaw :: forall r. GHC.Internal.IO.Handle.Types.Handle -> (GHC.Internal.Ptr.Ptr () -> GHC.Internal.Types.IO r) -> GHC.Internal.Types.IO r
|
|
| 13438 | + |
|
| 13428 | 13439 | module System.IO.Unsafe where
|
| 13429 | 13440 | -- Safety: Unsafe
|
| 13430 | 13441 | unsafeDupablePerformIO :: forall a. GHC.Internal.Types.IO a -> a
|
| ... | ... | @@ -10659,6 +10659,17 @@ module System.IO.Error where |
| 10659 | 10659 | userError :: GHC.Internal.Base.String -> IOError
|
| 10660 | 10660 | userErrorType :: IOErrorType
|
| 10661 | 10661 | |
| 10662 | +module System.IO.OS where
|
|
| 10663 | + -- Safety: Safe
|
|
| 10664 | + 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
|
|
| 10665 | + 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
|
|
| 10666 | + 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
|
|
| 10667 | + withFileDescriptorWritingBiasedRaw :: forall r. GHC.Internal.IO.Handle.Types.Handle -> (GHC.Internal.Foreign.C.Types.CInt -> GHC.Internal.Types.IO r) -> GHC.Internal.Types.IO r
|
|
| 10668 | + withWindowsHandleReadingBiased :: forall r. GHC.Internal.IO.Handle.Types.Handle -> (GHC.Internal.Ptr.Ptr () -> GHC.Internal.Types.IO r) -> GHC.Internal.Types.IO r
|
|
| 10669 | + withWindowsHandleReadingBiasedRaw :: forall r. GHC.Internal.IO.Handle.Types.Handle -> (GHC.Internal.Ptr.Ptr () -> GHC.Internal.Types.IO r) -> GHC.Internal.Types.IO r
|
|
| 10670 | + withWindowsHandleWritingBiased :: forall r. GHC.Internal.IO.Handle.Types.Handle -> (GHC.Internal.Ptr.Ptr () -> GHC.Internal.Types.IO r) -> GHC.Internal.Types.IO r
|
|
| 10671 | + withWindowsHandleWritingBiasedRaw :: forall r. GHC.Internal.IO.Handle.Types.Handle -> (GHC.Internal.Ptr.Ptr () -> GHC.Internal.Types.IO r) -> GHC.Internal.Types.IO r
|
|
| 10672 | + |
|
| 10662 | 10673 | module System.IO.Unsafe where
|
| 10663 | 10674 | -- Safety: Unsafe
|
| 10664 | 10675 | unsafeDupablePerformIO :: forall a. GHC.Internal.Types.IO a -> a
|
| ... | ... | @@ -10379,6 +10379,17 @@ module System.IO.Error where |
| 10379 | 10379 | userError :: GHC.Internal.Base.String -> IOError
|
| 10380 | 10380 | userErrorType :: IOErrorType
|
| 10381 | 10381 | |
| 10382 | +module System.IO.OS where
|
|
| 10383 | + -- Safety: Safe
|
|
| 10384 | + 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
|
|
| 10385 | + 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
|
|
| 10386 | + 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
|
|
| 10387 | + withFileDescriptorWritingBiasedRaw :: forall r. GHC.Internal.IO.Handle.Types.Handle -> (GHC.Internal.Foreign.C.Types.CInt -> GHC.Internal.Types.IO r) -> GHC.Internal.Types.IO r
|
|
| 10388 | + withWindowsHandleReadingBiased :: forall r. GHC.Internal.IO.Handle.Types.Handle -> (GHC.Internal.Ptr.Ptr () -> GHC.Internal.Types.IO r) -> GHC.Internal.Types.IO r
|
|
| 10389 | + withWindowsHandleReadingBiasedRaw :: forall r. GHC.Internal.IO.Handle.Types.Handle -> (GHC.Internal.Ptr.Ptr () -> GHC.Internal.Types.IO r) -> GHC.Internal.Types.IO r
|
|
| 10390 | + withWindowsHandleWritingBiased :: forall r. GHC.Internal.IO.Handle.Types.Handle -> (GHC.Internal.Ptr.Ptr () -> GHC.Internal.Types.IO r) -> GHC.Internal.Types.IO r
|
|
| 10391 | + withWindowsHandleWritingBiasedRaw :: forall r. GHC.Internal.IO.Handle.Types.Handle -> (GHC.Internal.Ptr.Ptr () -> GHC.Internal.Types.IO r) -> GHC.Internal.Types.IO r
|
|
| 10392 | + |
|
| 10382 | 10393 | module System.IO.Unsafe where
|
| 10383 | 10394 | -- Safety: Unsafe
|
| 10384 | 10395 | unsafeDupablePerformIO :: forall a. GHC.Internal.Types.IO a -> a
|