3
3
{-# LANGUAGE Trustworthy #-}
4
4
module Network.Tox.C.ToxSpec where
5
5
6
+ import Control.Monad (when )
6
7
import qualified Data.ByteString as BS
7
8
import Test.Hspec
8
9
import Test.QuickCheck
@@ -46,6 +47,12 @@ must :: Show a => IO (Either a b) -> IO b
46
47
must = (getRight =<< )
47
48
48
49
50
+ shouldBeBetween :: (Show a , Ord a ) => a -> (a , a ) -> IO ()
51
+ shouldBeBetween v (lo, hi) = do
52
+ when (v < lo || v > hi) $
53
+ expectationFailure $ " value " <> show v <> " should be between " <> show lo <> " and " <> show hi
54
+
55
+
49
56
spec :: Spec
50
57
spec = do
51
58
describe " tox_version_is_compatible" $ do
@@ -61,12 +68,12 @@ spec = do
61
68
fromIntegral C. tox_public_key_size `shouldBe` boxPK
62
69
fromIntegral C. tox_secret_key_size `shouldBe` boxSK
63
70
C. tox_address_size `shouldBe` C. tox_public_key_size + 6
64
- C. tox_max_name_length `shouldBe` 128
65
- C. tox_max_status_message_length `shouldBe` 1007
66
- C. tox_max_friend_request_length `shouldBe` 1016
71
+ C. tox_max_name_length `shouldBeBetween` ( 100 , 200 )
72
+ C. tox_max_status_message_length `shouldBeBetween` ( 500 , 1400 )
73
+ C. tox_max_friend_request_length `shouldBeBetween` ( 500 , 1400 )
67
74
C. tox_max_message_length `shouldBe` C. tox_max_custom_packet_size - 1
68
- C. tox_max_custom_packet_size `shouldBe` 1373
69
- C. tox_max_filename_length `shouldBe` 255
75
+ C. tox_max_custom_packet_size `shouldBeBetween` ( 500 , 1400 )
76
+ C. tox_max_filename_length `shouldBeBetween` ( 100 , 255 )
70
77
C. tox_hash_length `shouldBe` C. tox_file_id_length
71
78
72
79
describe " Options" $ do
0 commit comments