module GHC.ConsoleHandler
#if !defined(mingw32_HOST_OS) && !defined(__HADDOCK__)
where
import Prelude
#else /* whole file */
( Handler(..)
, installHandler
, ConsoleEvent(..)
, flushConsole
) where
import Prelude
import Foreign
import Foreign.C
import GHC.IOBase
import GHC.Conc
import GHC.Handle
import Control.Exception (onException)
data Handler
= Default
| Ignore
| Catch (ConsoleEvent -> IO ())
installHandler :: Handler -> IO Handler
installHandler handler
| threaded =
modifyMVar win32ConsoleHandler $ \old_h -> do
(new_h,rc) <-
case handler of
Default -> do
r <- rts_installHandler STG_SIG_DFL nullPtr
return (no_handler, r)
Ignore -> do
r <- rts_installHandler STG_SIG_IGN nullPtr
return (no_handler, r)
Catch h -> do
r <- rts_installHandler STG_SIG_HAN nullPtr
return (h, r)
prev_handler <-
case rc of
STG_SIG_DFL -> return Default
STG_SIG_IGN -> return Ignore
STG_SIG_HAN -> return (Catch old_h)
_ -> error "installHandler: Bad threaded rc value"
return (new_h, prev_handler)
| otherwise =
alloca $ \ p_sp -> do
rc <-
case handler of
Default -> rts_installHandler STG_SIG_DFL p_sp
Ignore -> rts_installHandler STG_SIG_IGN p_sp
Catch h -> do
v <- newStablePtr (toHandler h)
poke p_sp v
rts_installHandler STG_SIG_HAN p_sp
case rc of
STG_SIG_DFL -> return Default
STG_SIG_IGN -> return Ignore
STG_SIG_HAN -> do
osptr <- peek p_sp
oldh <- deRefStablePtr osptr
freeStablePtr osptr
return (Catch (\ ev -> oldh (fromConsoleEvent ev)))
_ -> error "installHandler: Bad non-threaded rc value"
where
fromConsoleEvent ev =
case ev of
ControlC -> 0
Break -> 1
Close -> 2
Logoff -> 5
Shutdown -> 6
toHandler hdlr ev = do
case toWin32ConsoleEvent ev of
Just x -> hdlr x >> rts_ConsoleHandlerDone ev
Nothing -> return ()
no_handler = error "win32ConsoleHandler"
foreign import ccall "rtsSupportsBoundThreads" threaded :: Bool
foreign import ccall unsafe "RtsExternal.h rts_InstallConsoleEvent"
rts_installHandler :: CInt -> Ptr (StablePtr (CInt -> IO ())) -> IO CInt
foreign import ccall unsafe "RtsExternal.h rts_ConsoleHandlerDone"
rts_ConsoleHandlerDone :: CInt -> IO ()
flushConsole :: Handle -> IO ()
flushConsole h =
wantReadableHandle "flushConsole" h $ \ h_ ->
throwErrnoIfMinus1Retry_ "flushConsole"
(flush_console_fd (fromIntegral (haFD h_)))
foreign import ccall unsafe "consUtils.h flush_input_console__"
flush_console_fd :: CInt -> IO CInt
modifyMVar :: MVar a -> (a -> IO (a,b)) -> IO b
modifyMVar m io =
block $ do
a <- takeMVar m
(a',b) <- unblock (io a) `onException` putMVar m a
putMVar m a'
return b
#endif /* mingw32_HOST_OS */