module Graphics.Vty.Input.Loop where
import Graphics.Vty.Config
import Graphics.Vty.Input.Classify
import Graphics.Vty.Input.Events
import Control.Applicative
import Control.Concurrent
import Control.Lens
import Control.Monad (when, mzero, forM_)
import Control.Monad.IO.Class (liftIO)
import Control.Monad.Trans.State (StateT(..), evalStateT)
import Control.Monad.Trans.Reader (ReaderT(..))
import Data.Char
import Data.IORef
import Data.Word (Word8)
import Foreign ( allocaArray, peekArray, Ptr )
import Foreign.C.Types (CInt(..))
import System.IO
import System.Posix.IO (fdReadBuf)
import System.Posix.Terminal
import System.Posix.Types (Fd(..))
import Text.Printf (hPrintf)
data Input = Input
{
_eventChannel :: Chan Event
, shutdownInput :: IO ()
, _configRef :: IORef Config
, _inputFd :: Fd
, _inputDebug :: Maybe Handle
}
makeLenses ''Input
data InputBuffer = InputBuffer
{ _ptr :: Ptr Word8
, _size :: Int
}
makeLenses ''InputBuffer
data InputState = InputState
{ _unprocessedBytes :: String
, _appliedConfig :: Config
, _inputBuffer :: InputBuffer
, _stopRequestRef :: IORef Bool
, _classifier :: String -> KClass
}
makeLenses ''InputState
type InputM a = StateT InputState (ReaderT Input IO) a
logMsg :: String -> InputM ()
logMsg msg = do
d <- view inputDebug
case d of
Nothing -> return ()
Just h -> liftIO $ hPutStrLn h msg >> hFlush h
loopInputProcessor :: InputM ()
loopInputProcessor = do
readFromDevice >>= addBytesToProcess
validEvents <- many parseEvent
forM_ validEvents emit
dropInvalid
stopIfRequested <|> loopInputProcessor
addBytesToProcess :: String -> InputM ()
addBytesToProcess block = unprocessedBytes <>= block
emit :: Event -> InputM ()
emit event = do
logMsg $ "parsed event: " ++ show event
view eventChannel >>= liftIO . flip writeChan event
readFromDevice :: InputM String
readFromDevice = do
newConfig <- view configRef >>= liftIO . readIORef
oldConfig <- use appliedConfig
fd <- view inputFd
when (newConfig /= oldConfig) $ do
liftIO $ applyTimingConfig fd newConfig
appliedConfig .= newConfig
bufferPtr <- use $ inputBuffer.ptr
maxBytes <- use $ inputBuffer.size
stringRep <- liftIO $ do
bytesRead <- fdReadBuf fd bufferPtr (fromIntegral maxBytes)
if bytesRead > 0
then fmap (map $ chr . fromIntegral) $ peekArray (fromIntegral bytesRead) bufferPtr
else return []
logMsg $ "input bytes: " ++ show stringRep
return stringRep
applyTimingConfig :: Fd -> Config -> IO ()
applyTimingConfig fd config =
let vtime = min 255 $ singleEscPeriod config `div` 100000
in setTermTiming fd 1 vtime
parseEvent :: InputM Event
parseEvent = do
c <- use classifier
b <- use unprocessedBytes
case c b of
Valid e remaining -> do
unprocessedBytes .= remaining
return e
_ -> mzero
dropInvalid :: InputM ()
dropInvalid = do
c <- use classifier
b <- use unprocessedBytes
when (c b == Invalid) $ unprocessedBytes .= []
stopIfRequested :: InputM ()
stopIfRequested = do
True <- (liftIO . readIORef) =<< use stopRequestRef
return ()
runInputProcessorLoop :: ClassifyMap -> Input -> IORef Bool -> IO ()
runInputProcessorLoop classifyTable input stopFlag = do
let bufferSize = 1024
allocaArray bufferSize $ \(bufferPtr :: Ptr Word8) -> do
s0 <- InputState [] <$> readIORef (_configRef input)
<*> pure (InputBuffer bufferPtr bufferSize)
<*> pure stopFlag
<*> pure (classify classifyTable)
runReaderT (evalStateT loopInputProcessor s0) input
attributeControl :: Fd -> IO (IO (), IO ())
attributeControl fd = do
original <- getTerminalAttributes fd
let vtyMode = foldl withoutMode original [ StartStopOutput, KeyboardInterrupts
, EnableEcho, ProcessInput, ExtendedFunctions
]
let setAttrs = setTerminalAttributes fd vtyMode Immediately
unsetAttrs = setTerminalAttributes fd original Immediately
return (setAttrs,unsetAttrs)
logClassifyMap :: Input -> String -> ClassifyMap -> IO()
logClassifyMap input termName classifyTable = case _inputDebug input of
Nothing -> return ()
Just h -> do
forM_ classifyTable $ \i -> case i of
(inBytes, EvKey k mods) -> hPrintf h "map %s %s %s %s\n" (show termName)
(show inBytes)
(show k)
(show mods)
_ -> return ()
initInputForFd :: Config -> String -> ClassifyMap -> Fd -> IO Input
initInputForFd config termName classifyTable inFd = do
applyTimingConfig inFd config
stopFlag <- newIORef False
input <- Input <$> newChan
<*> pure (writeIORef stopFlag True)
<*> newIORef config
<*> pure inFd
<*> maybe (return Nothing)
(\f -> Just <$> openFile f AppendMode)
(debugLog config)
logClassifyMap input termName classifyTable
_ <- forkOS $ runInputProcessorLoop classifyTable input stopFlag
return input
foreign import ccall "vty_set_term_timing" setTermTiming :: Fd -> Int -> Int -> IO ()