Blocking.hs 2.6 KB

123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687
  1. {-# LANGUAGE OverloadedStrings #-}
  2. module Blocking where
  3. import Distribution.TestSuite
  4. import Base (simpleTest)
  5. import Control.Concurrent(forkIO)
  6. import System.IO.Uniform.Network
  7. import qualified System.IO.Uniform.Streamline as S
  8. import System.Timeout (timeout)
  9. import Data.ByteString (ByteString)
  10. import qualified Data.ByteString as BS
  11. import qualified Data.ByteString.Char8 as C8
  12. import qualified Data.Attoparsec.ByteString as A
  13. --import Control.Monad.IO.Class (liftIO)
  14. --import Debug.Trace
  15. tests :: IO [Test]
  16. tests = return [
  17. simpleTest "recieveLine"
  18. (successTimeout "A test\n" S.recieveLine),
  19. simpleTest "runAttoparsec with successful parser"
  20. (successTimeout "abcde" (parseBS (A.string "abcde"))),
  21. simpleTest "runAttoparsec with failed parser"
  22. (failTimeout "abcde" (parseBS (A.string "c"))),
  23. simpleTest "recieveTill"
  24. (failTimeout "abcde" (restoreLine $ S.recieveTill "de"))
  25. ]
  26. parseBS :: A.Parser ByteString -> S.Streamline IO ByteString
  27. parseBS p = do
  28. t <- S.runAttoparsec p
  29. case t of
  30. Left e -> return . C8.pack $ e
  31. Right s -> return s
  32. restoreLine :: S.Streamline IO ByteString -> S.Streamline IO ByteString
  33. restoreLine f = do
  34. l <- f
  35. return $ BS.concat [l, "\n"]
  36. concatLine :: S.Streamline IO [ByteString] -> S.Streamline IO ByteString
  37. concatLine f = do
  38. l <- f
  39. return . BS.concat $ l
  40. -- | Tests the given command, by sending a string to an echo and running the command.
  41. -- the command must not block.
  42. successTimeout :: ByteString -> S.Streamline IO ByteString -> IO Progress
  43. successTimeout txt f = do
  44. recv <- bindPort 8888
  45. forkIO $ S.withClient recv $ \_ _ ->
  46. do
  47. l <- f
  48. S.send l
  49. return ()
  50. r' <- timeout 1000000 $ S.withServer "127.0.0.1" 8888 $
  51. do
  52. S.send txt
  53. t <- f
  54. if t == txt
  55. then return . Finished $ Pass
  56. else return . Finished . Fail $ "Strings differ: " -- ++ show txt ++ " <> " ++ show t
  57. closePort recv
  58. case r' of
  59. Just r -> return r
  60. Nothing -> return . Finished . Fail $ "Execution blocked"
  61. -- | Tests the given command, by sending text trough the network and running it.
  62. -- Does not care about the result of the command, just wether it blocks.
  63. failTimeout :: ByteString -> S.Streamline IO ByteString -> IO Progress
  64. failTimeout txt f = do
  65. recv <- bindPort 8888
  66. forkIO $ S.withClient recv $ \_ _ ->
  67. do
  68. f
  69. S.send "\n"
  70. return ()
  71. r' <- timeout 1000000 $ S.withServer "127.0.0.1" 8888 $
  72. do
  73. S.send txt
  74. S.recieveLine
  75. return . Finished $ Pass
  76. closePort recv
  77. case r' of
  78. Just r -> return r
  79. Nothing -> return . Finished . Fail $ "Execution blocked"