2013-10-20 11:21:51 +04:00
|
|
|
{-# LANGUAGE MultiParamTypeClasses #-}
|
|
|
|
{-# LANGUAGE FlexibleInstances #-}
|
2014-02-01 00:10:45 +04:00
|
|
|
{- Generate some input bytes and delays between blocks of input bytes. Verify the events produced
|
|
|
|
- are as expected.
|
2013-08-30 04:00:07 +04:00
|
|
|
-}
|
2013-10-20 10:20:29 +04:00
|
|
|
module Main where
|
2013-08-30 04:00:07 +04:00
|
|
|
|
2013-12-20 10:24:56 +04:00
|
|
|
import Verify.Graphics.Vty.Output
|
2013-10-13 14:01:53 +04:00
|
|
|
|
2013-10-05 11:30:38 +04:00
|
|
|
import Graphics.Vty hiding (resize)
|
2014-01-19 12:19:56 +04:00
|
|
|
import Graphics.Vty.Input.Events
|
2014-04-17 03:44:44 +04:00
|
|
|
import Graphics.Vty.Input.Loop
|
2013-10-21 01:18:29 +04:00
|
|
|
import Graphics.Vty.Input.Terminfo
|
2013-08-30 04:00:07 +04:00
|
|
|
|
2013-10-20 10:20:29 +04:00
|
|
|
import Control.Applicative
|
2013-09-15 10:56:06 +04:00
|
|
|
import Control.Concurrent
|
2013-10-05 11:30:38 +04:00
|
|
|
import Control.Exception
|
2014-01-31 13:13:24 +04:00
|
|
|
import Control.Lens ((^.))
|
2013-08-30 04:00:07 +04:00
|
|
|
import Control.Monad
|
|
|
|
|
2014-01-31 13:13:24 +04:00
|
|
|
import Data.Default
|
2013-11-11 08:38:47 +04:00
|
|
|
import Data.IORef
|
2014-05-31 12:52:29 +04:00
|
|
|
import Data.List (intersperse, reverse, nubBy)
|
2013-11-11 08:38:47 +04:00
|
|
|
|
2013-10-21 01:18:29 +04:00
|
|
|
import System.Console.Terminfo
|
2013-11-11 08:38:47 +04:00
|
|
|
import System.Posix.IO
|
2014-01-31 13:13:24 +04:00
|
|
|
import System.Posix.Terminal (openPseudoTerminal)
|
2013-11-11 08:38:47 +04:00
|
|
|
import System.Posix.Types
|
|
|
|
import System.Timeout
|
2013-08-30 04:00:07 +04:00
|
|
|
|
2013-10-20 10:20:29 +04:00
|
|
|
import Test.Framework.Providers.SmallCheck
|
|
|
|
import Test.Framework
|
|
|
|
import Test.SmallCheck
|
2013-10-20 11:21:51 +04:00
|
|
|
import Test.SmallCheck.Series
|
2013-10-05 11:30:38 +04:00
|
|
|
|
2013-11-17 12:28:21 +04:00
|
|
|
import Text.Printf
|
|
|
|
|
2013-10-05 11:30:38 +04:00
|
|
|
-- processing a block of 16 chars is the largest I can do without taking too long to run the test.
|
2014-04-12 04:51:13 +04:00
|
|
|
maxBlockSize :: Int
|
|
|
|
maxBlockSize = 16
|
2013-10-05 11:30:38 +04:00
|
|
|
|
2014-04-12 04:51:13 +04:00
|
|
|
maxTableSize :: Int
|
|
|
|
maxTableSize = 28
|
2013-11-14 11:23:08 +04:00
|
|
|
|
2013-10-25 01:40:48 +04:00
|
|
|
forEachOf :: (Show a, Testable m b) => [a] -> (a -> b) -> Property m
|
|
|
|
forEachOf l = over (generate (\n -> take n l))
|
|
|
|
|
2013-09-15 10:56:06 +04:00
|
|
|
data InputEvent
|
|
|
|
= Bytes String -- | input sequence encoded as a string. Regardless, the input is read a byte at a time.
|
2013-11-11 08:38:47 +04:00
|
|
|
| Delay Int -- | microsecond delay
|
2013-10-23 04:48:22 +04:00
|
|
|
deriving Show
|
2013-09-15 10:56:06 +04:00
|
|
|
|
|
|
|
type InputSpec = [InputEvent]
|
2013-09-01 12:08:27 +04:00
|
|
|
|
|
|
|
type ExpectedSpec = [Event]
|
|
|
|
|
2014-04-12 04:51:13 +04:00
|
|
|
synthesizeInput :: InputSpec -> Fd -> IO ()
|
|
|
|
synthesizeInput input outHandle = forM_ input f >> (void $ fdWrite outHandle "\xFFFD")
|
2013-09-15 10:56:06 +04:00
|
|
|
where
|
2014-04-12 04:51:13 +04:00
|
|
|
f (Bytes str) = void $ fdWrite outHandle str
|
2013-11-11 08:38:47 +04:00
|
|
|
f (Delay t) = threadDelay t
|
|
|
|
|
2014-04-12 04:51:13 +04:00
|
|
|
minDetectableDelay :: Int
|
|
|
|
minDetectableDelay = 4000
|
2013-11-11 08:38:47 +04:00
|
|
|
|
2014-04-12 04:51:13 +04:00
|
|
|
minTimout :: Int
|
|
|
|
minTimout = 4000000
|
2013-11-11 08:38:47 +04:00
|
|
|
|
2014-04-12 04:51:13 +04:00
|
|
|
testKeyDelay :: Int
|
|
|
|
testKeyDelay = minDetectableDelay * 4
|
2013-11-11 08:38:47 +04:00
|
|
|
|
2014-04-12 04:51:13 +04:00
|
|
|
testEscSampleDelay :: Int
|
|
|
|
testEscSampleDelay = minDetectableDelay * 2
|
2013-11-11 08:38:47 +04:00
|
|
|
|
2014-04-12 04:51:13 +04:00
|
|
|
genEventsUsingIoActions :: Int -> IO () -> IO () -> IO ()
|
|
|
|
genEventsUsingIoActions maxDuration inputAction outputAction = do
|
|
|
|
let maxDuration' = max minTimout maxDuration
|
|
|
|
readComplete <- newEmptyMVar
|
|
|
|
writeComplete <- newEmptyMVar
|
|
|
|
_ <- forkOS $ inputAction `finally` putMVar writeComplete ()
|
|
|
|
_ <- forkOS $ outputAction `finally` putMVar readComplete ()
|
|
|
|
Just () <- timeout maxDuration' $ takeMVar writeComplete
|
|
|
|
Just () <- timeout maxDuration' $ takeMVar readComplete
|
2013-11-11 08:38:47 +04:00
|
|
|
return ()
|
|
|
|
|
2014-04-12 04:51:13 +04:00
|
|
|
compareEvents :: (Show a1, Show a, Eq a1) => a -> [a1] -> [a1] -> IO Bool
|
|
|
|
compareEvents inputSpec expectedEvents outEvents = compareEvents' expectedEvents outEvents
|
2013-11-17 12:28:21 +04:00
|
|
|
where
|
2014-04-12 04:51:13 +04:00
|
|
|
compareEvents' [] [] = return True
|
|
|
|
compareEvents' [] outEvents' = do
|
|
|
|
printf "extra events %s\n" (show outEvents') :: IO ()
|
2013-11-17 12:28:21 +04:00
|
|
|
return False
|
2014-04-12 04:51:13 +04:00
|
|
|
compareEvents' expectedEvents' [] = do
|
|
|
|
printf "events %s were not produced for input %s\n" (show expectedEvents') (show inputSpec) :: IO ()
|
|
|
|
printf "expected events %s\n" (show expectedEvents) :: IO ()
|
|
|
|
printf "received events %s\n" (show outEvents) :: IO ()
|
2013-11-17 12:28:21 +04:00
|
|
|
return False
|
2014-04-12 04:51:13 +04:00
|
|
|
compareEvents' (e : expectedEvents') (o : outEvents')
|
|
|
|
| e == o = compareEvents' expectedEvents' outEvents'
|
2013-11-17 12:28:21 +04:00
|
|
|
| otherwise = do
|
2014-04-12 04:51:13 +04:00
|
|
|
printf "%s expected not %s for input %s\n" (show e) (show o) (show inputSpec) :: IO ()
|
|
|
|
printf "expected events %s\n" (show expectedEvents) :: IO ()
|
|
|
|
printf "received events %s\n" (show outEvents) :: IO ()
|
2013-11-17 12:28:21 +04:00
|
|
|
return False
|
|
|
|
|
2014-06-05 10:26:41 +04:00
|
|
|
assertEventsFromSynInput :: ClassifyMap -> InputSpec -> ExpectedSpec -> IO Bool
|
2014-04-12 04:51:13 +04:00
|
|
|
assertEventsFromSynInput table inputSpec expectedEvents = do
|
|
|
|
let maxDuration = sum [t | Delay t <- inputSpec] + minDetectableDelay
|
2014-04-12 07:54:00 +04:00
|
|
|
eventCount = length expectedEvents
|
2014-04-12 04:51:13 +04:00
|
|
|
(writeFd, readFd) <- openPseudoTerminal
|
|
|
|
(setTermAttr,_) <- attributeControl readFd
|
|
|
|
setTermAttr
|
2014-06-05 10:26:41 +04:00
|
|
|
input <- initInputForFd def "dummy" table readFd
|
2014-04-12 04:51:13 +04:00
|
|
|
eventsRef <- newIORef []
|
|
|
|
let writeWaitClose = do
|
|
|
|
synthesizeInput inputSpec writeFd
|
|
|
|
threadDelay minDetectableDelay
|
|
|
|
shutdownInput input
|
|
|
|
threadDelay minDetectableDelay
|
|
|
|
closeFd writeFd
|
|
|
|
closeFd readFd
|
2013-11-11 08:38:47 +04:00
|
|
|
-- drain output pipe
|
2014-04-12 07:54:00 +04:00
|
|
|
let readEvents = readLoop eventCount
|
2014-04-12 04:51:13 +04:00
|
|
|
readLoop 0 = return ()
|
|
|
|
readLoop n = do
|
|
|
|
e <- readChan $ input^.eventChannel
|
|
|
|
modifyIORef eventsRef ((:) e)
|
|
|
|
readLoop (n - 1)
|
|
|
|
genEventsUsingIoActions maxDuration writeWaitClose readEvents
|
|
|
|
outEvents <- reverse <$> readIORef eventsRef
|
|
|
|
compareEvents inputSpec expectedEvents outEvents
|
2013-09-15 10:56:06 +04:00
|
|
|
|
2013-10-25 01:40:48 +04:00
|
|
|
newtype InputBlocksUsingTable event
|
|
|
|
= InputBlocksUsingTable ([(String,event)] -> [(String, event)])
|
2013-10-21 01:18:29 +04:00
|
|
|
|
2013-10-25 01:40:48 +04:00
|
|
|
instance Show (InputBlocksUsingTable event) where
|
|
|
|
show (InputBlocksUsingTable _g) = "InputBlocksUsingTable"
|
2013-10-21 01:18:29 +04:00
|
|
|
|
2013-10-25 01:40:48 +04:00
|
|
|
instance Monad m => Serial m (InputBlocksUsingTable event) where
|
2013-10-21 01:18:29 +04:00
|
|
|
series = do
|
2014-04-12 04:51:13 +04:00
|
|
|
n :: Int <- localDepth (const maxTableSize) series
|
2014-05-31 12:52:29 +04:00
|
|
|
return $ InputBlocksUsingTable $ \raw_table ->
|
|
|
|
let table = reverse $ nubBy (\(s0,_) (s1,_) -> s0 == s1) $ reverse raw_table
|
|
|
|
in concat (take n (selections table))
|
2013-11-14 11:23:08 +04:00
|
|
|
where
|
|
|
|
selections [] = []
|
|
|
|
selections (x:xs) = let z = selections xs in [x] : (z ++ map ((:) x) z)
|
2013-10-20 10:20:29 +04:00
|
|
|
|
2014-04-12 04:51:13 +04:00
|
|
|
verifyVisibleSynInputToEvent :: Property IO
|
|
|
|
verifyVisibleSynInputToEvent = forAll $ \(InputBlocksUsingTable gen) -> monadic $ do
|
|
|
|
let table = visibleChars
|
|
|
|
inputSeq = gen table
|
|
|
|
events = map snd inputSeq
|
|
|
|
keydowns = map (Bytes . fst) inputSeq
|
|
|
|
input = intersperse (Delay testKeyDelay) keydowns ++ [Delay testKeyDelay]
|
|
|
|
assertEventsFromSynInput universalTable input events
|
|
|
|
|
|
|
|
verifyCapsSynInputToEvent :: Property IO
|
|
|
|
verifyCapsSynInputToEvent = forAll $ \(InputBlocksUsingTable gen) ->
|
|
|
|
forEachOf terminalsOfInterest $ \termName -> monadic $ do
|
|
|
|
term <- setupTerm termName
|
2014-06-05 10:26:41 +04:00
|
|
|
let table = capsClassifyMap term keysFromCapsTable
|
2014-05-31 12:52:29 +04:00
|
|
|
inputSeq = gen table
|
2014-04-12 04:51:13 +04:00
|
|
|
events = map snd inputSeq
|
|
|
|
keydowns = map (Bytes . fst) inputSeq
|
|
|
|
input = intersperse (Delay testKeyDelay) keydowns ++ [Delay testKeyDelay]
|
|
|
|
assertEventsFromSynInput table input events
|
|
|
|
|
|
|
|
verifySpecialSynInputToEvent :: Property IO
|
|
|
|
verifySpecialSynInputToEvent = forAll $ \(InputBlocksUsingTable gen) -> monadic $ do
|
|
|
|
let table = specialSupportKeys
|
2014-05-31 12:52:29 +04:00
|
|
|
inputSeq = gen table
|
2014-04-12 04:51:13 +04:00
|
|
|
events = map snd inputSeq
|
|
|
|
keydowns = map (Bytes . fst) inputSeq
|
|
|
|
input = intersperse (Delay testKeyDelay) keydowns ++ [Delay testKeyDelay]
|
|
|
|
assertEventsFromSynInput universalTable input events
|
|
|
|
|
|
|
|
verifyFullSynInputToEvent :: Property IO
|
|
|
|
verifyFullSynInputToEvent = forAll $ \(InputBlocksUsingTable gen) ->
|
|
|
|
forEachOf terminalsOfInterest $ \termName -> monadic $ do
|
|
|
|
term <- setupTerm termName
|
2014-06-05 10:26:41 +04:00
|
|
|
let table = classifyMapForTerm termName term
|
2014-05-31 12:52:29 +04:00
|
|
|
inputSeq = gen table
|
2014-04-12 04:51:13 +04:00
|
|
|
events = map snd inputSeq
|
|
|
|
keydowns = map (Bytes . fst) inputSeq
|
|
|
|
input = intersperse (Delay testKeyDelay) keydowns ++ [Delay testKeyDelay]
|
|
|
|
assertEventsFromSynInput table input events
|
|
|
|
|
|
|
|
verifyFullSynInputToEvent_2x :: Property IO
|
|
|
|
verifyFullSynInputToEvent_2x = forAll $ \(InputBlocksUsingTable gen) ->
|
|
|
|
forEachOf terminalsOfInterest $ \termName -> monadic $ do
|
|
|
|
term <- setupTerm termName
|
2014-06-05 10:26:41 +04:00
|
|
|
let table = classifyMapForTerm termName term
|
2014-05-31 12:52:29 +04:00
|
|
|
inputSeq = gen table
|
2014-04-12 04:51:13 +04:00
|
|
|
events = concatMap ((\s -> [s,s]) . snd) inputSeq
|
|
|
|
keydowns = map (Bytes . (\s -> s ++ s) . fst) inputSeq
|
|
|
|
input = intersperse (Delay testKeyDelay) keydowns ++ [Delay testKeyDelay]
|
|
|
|
assertEventsFromSynInput table input events
|
2014-01-31 13:26:53 +04:00
|
|
|
|
2013-10-25 01:40:48 +04:00
|
|
|
main :: IO ()
|
2013-10-20 10:20:29 +04:00
|
|
|
main = defaultMain
|
2014-01-31 13:26:53 +04:00
|
|
|
[ testProperty "synthesized typing of single visible chars translates to expected events"
|
2014-04-12 04:51:13 +04:00
|
|
|
verifyVisibleSynInputToEvent
|
2014-01-31 13:26:53 +04:00
|
|
|
, testProperty "synthesized typing of keys from capabilities tables translates to expected events"
|
2014-04-12 04:51:13 +04:00
|
|
|
verifyCapsSynInputToEvent
|
2014-01-31 13:26:53 +04:00
|
|
|
, testProperty "synthesized typing of hard coded special keys translates to expected events"
|
2014-04-12 04:51:13 +04:00
|
|
|
verifySpecialSynInputToEvent
|
2014-01-31 13:26:53 +04:00
|
|
|
, testProperty "synthesized typing of any key in the table translates to its paired event"
|
2014-04-12 04:51:13 +04:00
|
|
|
verifyFullSynInputToEvent
|
2014-01-31 13:26:53 +04:00
|
|
|
, testProperty "synthesized typing of 2x any key in the table translates to 2x paired event"
|
2014-04-12 04:51:13 +04:00
|
|
|
verifyFullSynInputToEvent_2x
|
2013-09-16 11:15:49 +04:00
|
|
|
]
|
2013-09-01 12:08:27 +04:00
|
|
|
|