{-# LANGUAGE Trustworthy       #-}
{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE CPP               #-}
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 <!>
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
(<!>) :: a -> a -> a
<!> :: forall a. a -> a -> a
(<!>) = forall a. a -> a -> a
conditional
isWindowsNativeIO :: Bool
isWindowsNativeIO :: Bool
isWindowsNativeIO = Bool
False 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
                         forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (IoSubSystem
sub forall a. Eq a => a -> a -> Bool
== IoSubSystem
m) IO ()
f