{-# LANGUAGE CPP #-}
{-# LANGUAGE NoMonomorphismRestriction #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TemplateHaskell #-}
{-# OPTIONS_HADDOCK hide #-}
-- | The input layer used to be a single function that correctly
-- accounted for the non-threaded runtime by emulating the terminal
-- VMIN adn VTIME handling. This has been removed and replace with a
-- more straightforward parser. The non-threaded runtime is no longer
-- supported.
--
-- This is an example of an algorithm where code coverage could be high,
-- even 100%, but the behavior is still under tested. I should collect
-- more of these examples...
--
-- reference: http://www.unixwiz.net/techtips/termios-vmin-vtime.html
module Graphics.Vty.Platform.Unix.Input.Loop
  ( initInput
  )
where

import Graphics.Vty.Input

import Graphics.Vty.Platform.Unix.Settings
import Graphics.Vty.Platform.Unix.Input.Classify
import Graphics.Vty.Platform.Unix.Input.Classify.Types

import Control.Applicative
import Control.Concurrent
import Control.Concurrent.STM
import Control.Exception (mask, try, SomeException)
import qualified Data.ByteString.Char8 as BS8
import qualified Data.ByteString as BS
import Data.ByteString.Char8 (ByteString)
import Data.Word (Word8)
import Foreign (allocaArray)
import Foreign.C.Types (CInt(..))
import Foreign.Ptr (Ptr, castPtr)
import Lens.Micro hiding ((<>~))
import Lens.Micro.TH
import Lens.Micro.Mtl
import Control.Monad (when, mzero, forM_, forever)
import Control.Monad.IO.Class (liftIO)
import Control.Monad.Trans (lift)
import Control.Monad.Trans.State (StateT(..), evalStateT)
import Control.Monad.State.Class (MonadState, modify)
import Control.Monad.Trans.Reader (ReaderT(..), asks)
import System.Posix.IO (fdReadBuf, setFdOption, FdOption(..))
import System.Posix.Types (Fd(..))

data InputBuffer = InputBuffer
    { InputBuffer -> Ptr Word8
_ptr :: Ptr Word8
    , InputBuffer -> Int
_size :: Int
    }

makeLenses ''InputBuffer

data InputState = InputState
    { InputState -> ByteString
_unprocessedBytes :: ByteString
    , InputState -> ClassifierState
_classifierState :: ClassifierState
    , InputState -> Fd
_deviceFd :: Fd
    , InputState -> Input
_originalInput :: Input
    , InputState -> InputBuffer
_inputBuffer :: InputBuffer
    , InputState -> ClassifierState -> ByteString -> KClass
_classifier :: ClassifierState -> ByteString -> KClass
    }

makeLenses ''InputState

type InputM a = StateT InputState (ReaderT Input IO) a

logMsg :: String -> InputM ()
logMsg :: String -> InputM ()
logMsg String
msg = do
    Input
i <- Getting Input InputState Input
-> StateT InputState (ReaderT Input IO) Input
forall s (m :: * -> *) a. MonadState s m => Getting a s a -> m a
use Getting Input InputState Input
Lens' InputState Input
originalInput
    IO () -> InputM ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> InputM ()) -> IO () -> InputM ()
forall a b. (a -> b) -> a -> b
$ Input -> String -> IO ()
inputLogMsg Input
i String
msg

-- this must be run on an OS thread dedicated to this input handling.
-- otherwise the terminal timing read behavior will block the execution
-- of the lightweight threads.
loopInputProcessor :: InputM ()
loopInputProcessor :: InputM ()
loopInputProcessor = InputM () -> InputM ()
forall (f :: * -> *) a b. Applicative f => f a -> f b
forever (InputM () -> InputM ()) -> InputM () -> InputM ()
forall a b. (a -> b) -> a -> b
$ do
    InputM ByteString
readFromDevice InputM ByteString -> (ByteString -> InputM ()) -> InputM ()
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= ByteString -> InputM ()
addBytesToProcess
    [Event]
validEvents <- StateT InputState (ReaderT Input IO) Event
-> StateT InputState (ReaderT Input IO) [Event]
forall (f :: * -> *) a. Alternative f => f a -> f [a]
many StateT InputState (ReaderT Input IO) Event
parseEvent
    [Event] -> (Event -> InputM ()) -> InputM ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
t a -> (a -> m b) -> m ()
forM_ [Event]
validEvents Event -> InputM ()
emit
    InputM ()
dropInvalid

addBytesToProcess :: ByteString -> InputM ()
addBytesToProcess :: ByteString -> InputM ()
addBytesToProcess ByteString
block = (ByteString -> Identity ByteString)
-> InputState -> Identity InputState
Lens' InputState ByteString
unprocessedBytes ((ByteString -> Identity ByteString)
 -> InputState -> Identity InputState)
-> ByteString -> InputM ()
forall s (m :: * -> *) a.
(MonadState s m, Monoid a) =>
ASetter' s a -> a -> m ()
<>= ByteString
block

emit :: Event -> InputM ()
emit :: Event -> InputM ()
emit Event
event = do
    String -> InputM ()
logMsg (String -> InputM ()) -> String -> InputM ()
forall a b. (a -> b) -> a -> b
$ String
"parsed event: " String -> String -> String
forall a. [a] -> [a] -> [a]
++ Event -> String
forall a. Show a => a -> String
show Event
event
    (ReaderT Input IO (TChan InternalEvent)
-> StateT InputState (ReaderT Input IO) (TChan InternalEvent)
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (ReaderT Input IO (TChan InternalEvent)
 -> StateT InputState (ReaderT Input IO) (TChan InternalEvent))
-> ReaderT Input IO (TChan InternalEvent)
-> StateT InputState (ReaderT Input IO) (TChan InternalEvent)
forall a b. (a -> b) -> a -> b
$ (Input -> TChan InternalEvent)
-> ReaderT Input IO (TChan InternalEvent)
forall (m :: * -> *) r a. Monad m => (r -> a) -> ReaderT r m a
asks Input -> TChan InternalEvent
eventChannel) StateT InputState (ReaderT Input IO) (TChan InternalEvent)
-> (TChan InternalEvent -> InputM ()) -> InputM ()
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= IO () -> InputM ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> InputM ())
-> (TChan InternalEvent -> IO ())
-> TChan InternalEvent
-> InputM ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. STM () -> IO ()
forall a. STM a -> IO a
atomically (STM () -> IO ())
-> (TChan InternalEvent -> STM ()) -> TChan InternalEvent -> IO ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (TChan InternalEvent -> InternalEvent -> STM ())
-> InternalEvent -> TChan InternalEvent -> STM ()
forall a b c. (a -> b -> c) -> b -> a -> c
flip TChan InternalEvent -> InternalEvent -> STM ()
forall a. TChan a -> a -> STM ()
writeTChan (Event -> InternalEvent
InputEvent Event
event)

-- The timing requirements are assured by the VMIN and VTIME set for the
-- device.
--
-- Precondition: Under the threaded runtime. Only current use is from a
-- forkOS thread. That case satisfies precondition.
readFromDevice :: InputM ByteString
readFromDevice :: InputM ByteString
readFromDevice = do
    Fd
fd <- Getting Fd InputState Fd -> StateT InputState (ReaderT Input IO) Fd
forall s (m :: * -> *) a. MonadState s m => Getting a s a -> m a
use Getting Fd InputState Fd
Lens' InputState Fd
deviceFd

    Ptr Word8
bufferPtr <- Getting (Ptr Word8) InputState (Ptr Word8)
-> StateT InputState (ReaderT Input IO) (Ptr Word8)
forall s (m :: * -> *) a. MonadState s m => Getting a s a -> m a
use (Getting (Ptr Word8) InputState (Ptr Word8)
 -> StateT InputState (ReaderT Input IO) (Ptr Word8))
-> Getting (Ptr Word8) InputState (Ptr Word8)
-> StateT InputState (ReaderT Input IO) (Ptr Word8)
forall a b. (a -> b) -> a -> b
$ (InputBuffer -> Const (Ptr Word8) InputBuffer)
-> InputState -> Const (Ptr Word8) InputState
Lens' InputState InputBuffer
inputBuffer((InputBuffer -> Const (Ptr Word8) InputBuffer)
 -> InputState -> Const (Ptr Word8) InputState)
-> ((Ptr Word8 -> Const (Ptr Word8) (Ptr Word8))
    -> InputBuffer -> Const (Ptr Word8) InputBuffer)
-> Getting (Ptr Word8) InputState (Ptr Word8)
forall b c a. (b -> c) -> (a -> b) -> a -> c
.(Ptr Word8 -> Const (Ptr Word8) (Ptr Word8))
-> InputBuffer -> Const (Ptr Word8) InputBuffer
Lens' InputBuffer (Ptr Word8)
ptr
    Int
maxBytes  <- Getting Int InputState Int
-> StateT InputState (ReaderT Input IO) Int
forall s (m :: * -> *) a. MonadState s m => Getting a s a -> m a
use (Getting Int InputState Int
 -> StateT InputState (ReaderT Input IO) Int)
-> Getting Int InputState Int
-> StateT InputState (ReaderT Input IO) Int
forall a b. (a -> b) -> a -> b
$ (InputBuffer -> Const Int InputBuffer)
-> InputState -> Const Int InputState
Lens' InputState InputBuffer
inputBuffer((InputBuffer -> Const Int InputBuffer)
 -> InputState -> Const Int InputState)
-> ((Int -> Const Int Int) -> InputBuffer -> Const Int InputBuffer)
-> Getting Int InputState Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
.(Int -> Const Int Int) -> InputBuffer -> Const Int InputBuffer
Lens' InputBuffer Int
size
    ByteString
stringRep <- IO ByteString -> InputM ByteString
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO ByteString -> InputM ByteString)
-> IO ByteString -> InputM ByteString
forall a b. (a -> b) -> a -> b
$ do
        -- The killThread used in shutdownInput will not interrupt the
        -- foreign call fdReadBuf uses this provides a location to be
        -- interrupted prior to the foreign call. If there is input on
        -- the FD then the fdReadBuf will return in a finite amount of
        -- time due to the vtime terminal setting.
        Fd -> IO ()
threadWaitRead Fd
fd
        ByteCount
bytesRead <- Fd -> Ptr Word8 -> ByteCount -> IO ByteCount
fdReadBuf Fd
fd Ptr Word8
bufferPtr (Int -> ByteCount
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
maxBytes)
        if ByteCount
bytesRead ByteCount -> ByteCount -> Bool
forall a. Ord a => a -> a -> Bool
> ByteCount
0
        then CStringLen -> IO ByteString
BS.packCStringLen (Ptr Word8 -> Ptr CChar
forall a b. Ptr a -> Ptr b
castPtr Ptr Word8
bufferPtr, ByteCount -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral ByteCount
bytesRead)
        else ByteString -> IO ByteString
forall (m :: * -> *) a. Monad m => a -> m a
return ByteString
BS.empty
    Bool -> InputM () -> InputM ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Bool -> Bool
not (Bool -> Bool) -> Bool -> Bool
forall a b. (a -> b) -> a -> b
$ ByteString -> Bool
BS.null ByteString
stringRep) (InputM () -> InputM ()) -> InputM () -> InputM ()
forall a b. (a -> b) -> a -> b
$
        String -> InputM ()
logMsg (String -> InputM ()) -> String -> InputM ()
forall a b. (a -> b) -> a -> b
$ String
"input bytes: " String -> String -> String
forall a. [a] -> [a] -> [a]
++ String -> String
forall a. Show a => a -> String
show (ByteString -> String
BS8.unpack ByteString
stringRep)
    ByteString -> InputM ByteString
forall (m :: * -> *) a. Monad m => a -> m a
return ByteString
stringRep

parseEvent :: InputM Event
parseEvent :: StateT InputState (ReaderT Input IO) Event
parseEvent = do
    ClassifierState -> ByteString -> KClass
c <- Getting
  (ClassifierState -> ByteString -> KClass)
  InputState
  (ClassifierState -> ByteString -> KClass)
-> StateT
     InputState
     (ReaderT Input IO)
     (ClassifierState -> ByteString -> KClass)
forall s (m :: * -> *) a. MonadState s m => Getting a s a -> m a
use Getting
  (ClassifierState -> ByteString -> KClass)
  InputState
  (ClassifierState -> ByteString -> KClass)
Lens' InputState (ClassifierState -> ByteString -> KClass)
classifier
    ClassifierState
s <- Getting ClassifierState InputState ClassifierState
-> StateT InputState (ReaderT Input IO) ClassifierState
forall s (m :: * -> *) a. MonadState s m => Getting a s a -> m a
use Getting ClassifierState InputState ClassifierState
Lens' InputState ClassifierState
classifierState
    ByteString
b <- Getting ByteString InputState ByteString -> InputM ByteString
forall s (m :: * -> *) a. MonadState s m => Getting a s a -> m a
use Getting ByteString InputState ByteString
Lens' InputState ByteString
unprocessedBytes
    case ClassifierState -> ByteString -> KClass
c ClassifierState
s ByteString
b of
        Valid Event
e ByteString
remaining -> do
            String -> InputM ()
logMsg (String -> InputM ()) -> String -> InputM ()
forall a b. (a -> b) -> a -> b
$ String
"valid parse: " String -> String -> String
forall a. [a] -> [a] -> [a]
++ Event -> String
forall a. Show a => a -> String
show Event
e
            String -> InputM ()
logMsg (String -> InputM ()) -> String -> InputM ()
forall a b. (a -> b) -> a -> b
$ String
"remaining: " String -> String -> String
forall a. [a] -> [a] -> [a]
++ ByteString -> String
forall a. Show a => a -> String
show ByteString
remaining
            (ClassifierState -> Identity ClassifierState)
-> InputState -> Identity InputState
Lens' InputState ClassifierState
classifierState ((ClassifierState -> Identity ClassifierState)
 -> InputState -> Identity InputState)
-> ClassifierState -> InputM ()
forall s (m :: * -> *) a b.
MonadState s m =>
ASetter s s a b -> b -> m ()
.= ClassifierState
ClassifierStart
            (ByteString -> Identity ByteString)
-> InputState -> Identity InputState
Lens' InputState ByteString
unprocessedBytes ((ByteString -> Identity ByteString)
 -> InputState -> Identity InputState)
-> ByteString -> InputM ()
forall s (m :: * -> *) a b.
MonadState s m =>
ASetter s s a b -> b -> m ()
.= ByteString
remaining
            Event -> StateT InputState (ReaderT Input IO) Event
forall (m :: * -> *) a. Monad m => a -> m a
return Event
e
        KClass
_ -> StateT InputState (ReaderT Input IO) Event
forall (m :: * -> *) a. MonadPlus m => m a
mzero

dropInvalid :: InputM ()
dropInvalid :: InputM ()
dropInvalid = do
    ClassifierState -> ByteString -> KClass
c <- Getting
  (ClassifierState -> ByteString -> KClass)
  InputState
  (ClassifierState -> ByteString -> KClass)
-> StateT
     InputState
     (ReaderT Input IO)
     (ClassifierState -> ByteString -> KClass)
forall s (m :: * -> *) a. MonadState s m => Getting a s a -> m a
use Getting
  (ClassifierState -> ByteString -> KClass)
  InputState
  (ClassifierState -> ByteString -> KClass)
Lens' InputState (ClassifierState -> ByteString -> KClass)
classifier
    ClassifierState
s <- Getting ClassifierState InputState ClassifierState
-> StateT InputState (ReaderT Input IO) ClassifierState
forall s (m :: * -> *) a. MonadState s m => Getting a s a -> m a
use Getting ClassifierState InputState ClassifierState
Lens' InputState ClassifierState
classifierState
    ByteString
b <- Getting ByteString InputState ByteString -> InputM ByteString
forall s (m :: * -> *) a. MonadState s m => Getting a s a -> m a
use Getting ByteString InputState ByteString
Lens' InputState ByteString
unprocessedBytes
    case ClassifierState -> ByteString -> KClass
c ClassifierState
s ByteString
b of
        KClass
Chunk -> do
            (ClassifierState -> Identity ClassifierState)
-> InputState -> Identity InputState
Lens' InputState ClassifierState
classifierState ((ClassifierState -> Identity ClassifierState)
 -> InputState -> Identity InputState)
-> ClassifierState -> InputM ()
forall s (m :: * -> *) a b.
MonadState s m =>
ASetter s s a b -> b -> m ()
.=
                case ClassifierState
s of
                  ClassifierState
ClassifierStart -> ByteString -> [ByteString] -> ClassifierState
ClassifierInChunk ByteString
b []
                  ClassifierInChunk ByteString
p [ByteString]
bs -> ByteString -> [ByteString] -> ClassifierState
ClassifierInChunk ByteString
p (ByteString
bByteString -> [ByteString] -> [ByteString]
forall a. a -> [a] -> [a]
:[ByteString]
bs)
            (ByteString -> Identity ByteString)
-> InputState -> Identity InputState
Lens' InputState ByteString
unprocessedBytes ((ByteString -> Identity ByteString)
 -> InputState -> Identity InputState)
-> ByteString -> InputM ()
forall s (m :: * -> *) a b.
MonadState s m =>
ASetter s s a b -> b -> m ()
.= ByteString
BS8.empty
        KClass
Invalid -> do
            String -> InputM ()
logMsg String
"dropping input bytes"
            (ClassifierState -> Identity ClassifierState)
-> InputState -> Identity InputState
Lens' InputState ClassifierState
classifierState ((ClassifierState -> Identity ClassifierState)
 -> InputState -> Identity InputState)
-> ClassifierState -> InputM ()
forall s (m :: * -> *) a b.
MonadState s m =>
ASetter s s a b -> b -> m ()
.= ClassifierState
ClassifierStart
            (ByteString -> Identity ByteString)
-> InputState -> Identity InputState
Lens' InputState ByteString
unprocessedBytes ((ByteString -> Identity ByteString)
 -> InputState -> Identity InputState)
-> ByteString -> InputM ()
forall s (m :: * -> *) a b.
MonadState s m =>
ASetter s s a b -> b -> m ()
.= ByteString
BS8.empty
        KClass
_ -> () -> InputM ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

runInputProcessorLoop :: ClassifyMap -> Input -> Fd -> IO ()
runInputProcessorLoop :: ClassifyMap -> Input -> Fd -> IO ()
runInputProcessorLoop ClassifyMap
classifyTable Input
input Fd
devFd = do
    let bufferSize :: p
bufferSize = p
1024
    Int -> (Ptr Word8 -> IO ()) -> IO ()
forall a b. Storable a => Int -> (Ptr a -> IO b) -> IO b
allocaArray Int
forall p. Num p => p
bufferSize ((Ptr Word8 -> IO ()) -> IO ()) -> (Ptr Word8 -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \(Ptr Word8
bufferPtr :: Ptr Word8) -> do
        let s0 :: InputState
s0 = ByteString
-> ClassifierState
-> Fd
-> Input
-> InputBuffer
-> (ClassifierState -> ByteString -> KClass)
-> InputState
InputState ByteString
BS8.empty ClassifierState
ClassifierStart
                    Fd
devFd Input
input
                    (Ptr Word8 -> Int -> InputBuffer
InputBuffer Ptr Word8
bufferPtr Int
forall p. Num p => p
bufferSize)
                    (ClassifyMap -> ClassifierState -> ByteString -> KClass
classify ClassifyMap
classifyTable)
        ReaderT Input IO () -> Input -> IO ()
forall r (m :: * -> *) a. ReaderT r m a -> r -> m a
runReaderT (InputM () -> InputState -> ReaderT Input IO ()
forall (m :: * -> *) s a. Monad m => StateT s m a -> s -> m a
evalStateT InputM ()
loopInputProcessor InputState
s0) Input
input

initInput :: UnixSettings -> ClassifyMap -> IO Input
initInput :: UnixSettings -> ClassifyMap -> IO Input
initInput UnixSettings
settings ClassifyMap
classifyTable = do
    let devFd :: Fd
devFd = UnixSettings -> Fd
settingInputFd UnixSettings
settings
        theVmin :: Int
theVmin = UnixSettings -> Int
settingVmin UnixSettings
settings
        theVtime :: Int
theVtime = UnixSettings -> Int
settingVtime UnixSettings
settings

    Fd -> FdOption -> Bool -> IO ()
setFdOption Fd
devFd FdOption
NonBlockingRead Bool
False
    Fd -> Int -> Int -> IO ()
setTermTiming Fd
devFd Int
theVmin (Int
theVtime Int -> Int -> Int
forall a. Integral a => a -> a -> a
`div` Int
100)

    MVar ()
stopSync <- IO (MVar ())
forall a. IO (MVar a)
newEmptyMVar
    Input
input <- TChan InternalEvent -> IO () -> IO () -> (String -> IO ()) -> Input
Input (TChan InternalEvent
 -> IO () -> IO () -> (String -> IO ()) -> Input)
-> IO (TChan InternalEvent)
-> IO (IO () -> IO () -> (String -> IO ()) -> Input)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> STM (TChan InternalEvent) -> IO (TChan InternalEvent)
forall a. STM a -> IO a
atomically STM (TChan InternalEvent)
forall a. STM (TChan a)
newTChan
                   IO (IO () -> IO () -> (String -> IO ()) -> Input)
-> IO (IO ()) -> IO (IO () -> (String -> IO ()) -> Input)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> IO () -> IO (IO ())
forall (f :: * -> *) a. Applicative f => a -> f a
pure (() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ())
                   IO (IO () -> (String -> IO ()) -> Input)
-> IO (IO ()) -> IO ((String -> IO ()) -> Input)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> IO () -> IO (IO ())
forall (f :: * -> *) a. Applicative f => a -> f a
pure (() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ())
                   IO ((String -> IO ()) -> Input) -> IO (String -> IO ()) -> IO Input
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (String -> IO ()) -> IO (String -> IO ())
forall (f :: * -> *) a. Applicative f => a -> f a
pure (IO () -> String -> IO ()
forall a b. a -> b -> a
const (IO () -> String -> IO ()) -> IO () -> String -> IO ()
forall a b. (a -> b) -> a -> b
$ () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ())
    ThreadId
inputThread <- IO () -> (Either SomeException () -> IO ()) -> IO ThreadId
forall a. IO a -> (Either SomeException a -> IO ()) -> IO ThreadId
forkOSFinally (ClassifyMap -> Input -> Fd -> IO ()
runInputProcessorLoop ClassifyMap
classifyTable Input
input Fd
devFd)
                                 (\Either SomeException ()
_ -> MVar () -> () -> IO ()
forall a. MVar a -> a -> IO ()
putMVar MVar ()
stopSync ())
    let killAndWait :: IO ()
killAndWait = do
          ThreadId -> IO ()
killThread ThreadId
inputThread
          MVar () -> IO ()
forall a. MVar a -> IO a
takeMVar MVar ()
stopSync
    Input -> IO Input
forall (m :: * -> *) a. Monad m => a -> m a
return (Input -> IO Input) -> Input -> IO Input
forall a b. (a -> b) -> a -> b
$ Input
input { shutdownInput :: IO ()
shutdownInput = IO ()
killAndWait }

foreign import ccall "vty_set_term_timing" setTermTiming :: Fd -> Int -> Int -> IO ()

forkOSFinally :: IO a -> (Either SomeException a -> IO ()) -> IO ThreadId
forkOSFinally :: IO a -> (Either SomeException a -> IO ()) -> IO ThreadId
forkOSFinally IO a
action Either SomeException a -> IO ()
and_then =
  ((forall a. IO a -> IO a) -> IO ThreadId) -> IO ThreadId
forall b. ((forall a. IO a -> IO a) -> IO b) -> IO b
mask (((forall a. IO a -> IO a) -> IO ThreadId) -> IO ThreadId)
-> ((forall a. IO a -> IO a) -> IO ThreadId) -> IO ThreadId
forall a b. (a -> b) -> a -> b
$ \forall a. IO a -> IO a
restore -> IO () -> IO ThreadId
forkOS (IO () -> IO ThreadId) -> IO () -> IO ThreadId
forall a b. (a -> b) -> a -> b
$ IO a -> IO (Either SomeException a)
forall e a. Exception e => IO a -> IO (Either e a)
try (IO a -> IO a
forall a. IO a -> IO a
restore IO a
action) IO (Either SomeException a)
-> (Either SomeException a -> IO ()) -> IO ()
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Either SomeException a -> IO ()
and_then

(<>=) :: (MonadState s m, Monoid a) => ASetter' s a -> a -> m ()
ASetter' s a
l <>= :: ASetter' s a -> a -> m ()
<>= a
a = (s -> s) -> m ()
forall s (m :: * -> *). MonadState s m => (s -> s) -> m ()
modify (ASetter' s a
l ASetter' s a -> a -> s -> s
forall a s t. Monoid a => ASetter s t a a -> a -> s -> t
<>~ a
a)

(<>~) :: Monoid a => ASetter s t a a -> a -> s -> t
ASetter s t a a
l <>~ :: ASetter s t a a -> a -> s -> t
<>~ a
n = ASetter s t a a -> (a -> a) -> s -> t
forall s t a b. ASetter s t a b -> (a -> b) -> s -> t
over ASetter s t a a
l (a -> a -> a
forall a. Monoid a => a -> a -> a
`mappend` a
n)