(original) (raw)
{-# LANGUAGE Trustworthy #-} {-# LANGUAGE NoImplicitPrelude #-} {-# LANGUAGE CPP #-}
-- | -- Module : GHC.IO.SubSystem -- Copyright : (c) The University of Glasgow, 2017 -- License : see libraries/base/LICENSE
-- Maintainer : libraries@haskell.org -- Stability : internal -- Portability : non-portable
-- The SubSystem control interface. These methods can be used to disambiguate -- between the two operations.
module GHC.IO.SubSystem ( withIoSubSystem, withIoSubSystem', whenIoSubSystem, ioSubSystem, IoSubSystem(..), conditional, (<!>), isWindowsNativeIO ) where
import GHC.Base import GHC.RTS.Flags
#if defined(mingw32_HOST_OS) import GHC.IO.Unsafe #endif
infixl 7 <!>
-- | Conditionally execute an action depending on the configured I/O subsystem. -- On POSIX systems always execute the first action. -- On windows execute the second action if WINIO as active, otherwise fall back to -- the first action. conditional :: a -> a -> a #if defined(mingw32_HOST_OS) conditional posix windows = case ioSubSystem of IoPOSIX -> posix IoNative -> windows #else conditional :: forall a. a -> a -> a conditional a posix a _ = a posix #endif
-- | Infix version of conditional.
-- posix <!> windows == conditional posix windows
(<!>) :: a -> a -> a
<!> :: forall a. a -> a -> a
(<!>) = a -> a -> a
forall a. a -> a -> a
conditional
isWindowsNativeIO :: Bool isWindowsNativeIO :: Bool isWindowsNativeIO = Bool False Bool -> Bool -> Bool forall a. a -> a -> a <!> Bool True
ioSubSystem :: IoSubSystem #if defined(mingw32_HOST_OS) {-# NOINLINE ioSubSystem #-} ioSubSystem = unsafeDupablePerformIO getIoManagerFlag #else ioSubSystem :: IoSubSystem ioSubSystem = IoSubSystem IoPOSIX #endif
withIoSubSystem :: (IoSubSystem -> IO a) -> IO a withIoSubSystem :: forall a. (IoSubSystem -> IO a) -> IO a withIoSubSystem IoSubSystem -> IO a f = IoSubSystem -> IO a f IoSubSystem ioSubSystem
withIoSubSystem' :: (IoSubSystem -> a) -> a withIoSubSystem' :: forall a. (IoSubSystem -> a) -> a withIoSubSystem' IoSubSystem -> a f = IoSubSystem -> a f IoSubSystem ioSubSystem
whenIoSubSystem :: IoSubSystem -> IO () -> IO () whenIoSubSystem :: IoSubSystem -> IO () -> IO () whenIoSubSystem IoSubSystem m IO () f = do let sub :: IoSubSystem sub = IoSubSystem ioSubSystem Bool -> IO () -> IO () forall (f :: * -> *). Applicative f => Bool -> f () -> f () when (IoSubSystem sub IoSubSystem -> IoSubSystem -> Bool forall a. Eq a => a -> a -> Bool == IoSubSystem m) IO () f