Test the encoding and decoding
This commit is contained in:
		
							
								
								
									
										49
									
								
								test/Test/Data/Buuka.hs
									
									
									
									
									
										Normal file
									
								
							
							
						
						
									
										49
									
								
								test/Test/Data/Buuka.hs
									
									
									
									
									
										Normal file
									
								
							@@ -0,0 +1,49 @@
 | 
			
		||||
module Test.Data.Buuka where
 | 
			
		||||
 | 
			
		||||
import Hedgehog
 | 
			
		||||
import qualified Hedgehog.Gen as Gen
 | 
			
		||||
import qualified Hedgehog.Range as Range
 | 
			
		||||
import Test.Tasty
 | 
			
		||||
import Test.Tasty.Hedgehog
 | 
			
		||||
 | 
			
		||||
import qualified Data.Aeson as A
 | 
			
		||||
 | 
			
		||||
import Data.List
 | 
			
		||||
       (intercalate)
 | 
			
		||||
import qualified Data.Foldable as F
 | 
			
		||||
 | 
			
		||||
import Data.Buuka
 | 
			
		||||
 | 
			
		||||
genUrl :: Gen URL
 | 
			
		||||
genUrl = URL . concat <$> sequence go
 | 
			
		||||
  where
 | 
			
		||||
    go = [ Gen.element protocols, Gen.element domains, Gen.element tlds, pure "/", genPath ]
 | 
			
		||||
    protocols = ["http://", "https://"]
 | 
			
		||||
    domains = ["example", "foo", "bar"]
 | 
			
		||||
    tlds = ["com", "fi", "org", "net", "info"]
 | 
			
		||||
    genPath = intercalate "/" <$> Gen.list (Range.linear 0 10) (Gen.element paths)
 | 
			
		||||
    paths = ["foo", "bar", "asd", "xyzzy"]
 | 
			
		||||
 | 
			
		||||
genBuukaEntry :: Gen BuukaEntry
 | 
			
		||||
genBuukaEntry = BuukaEntry <$> genUrl <*> genTitle
 | 
			
		||||
  where
 | 
			
		||||
    genTitle = Gen.maybe (Gen.string (Range.linear 0 10) Gen.unicode)
 | 
			
		||||
 | 
			
		||||
genBuuka :: Gen Buuka
 | 
			
		||||
genBuuka = F.foldl' (flip insert) mempty <$> Gen.list (Range.linear 0 10) genBuukaEntry
 | 
			
		||||
 | 
			
		||||
prop_buukaentry_encode_decode :: Property
 | 
			
		||||
prop_buukaentry_encode_decode = property $ do
 | 
			
		||||
  x <- forAll genBuukaEntry
 | 
			
		||||
  tripping x A.encode A.eitherDecode
 | 
			
		||||
 | 
			
		||||
prop_buuka_encode_decode :: Property
 | 
			
		||||
prop_buuka_encode_decode = property $ do
 | 
			
		||||
  x <- forAll genBuuka
 | 
			
		||||
  tripping x A.encode A.eitherDecode
 | 
			
		||||
 | 
			
		||||
tests :: TestTree
 | 
			
		||||
tests = testGroup "Data.Buuka"
 | 
			
		||||
  [ testProperty "Entries can be encoded and decoded" prop_buukaentry_encode_decode
 | 
			
		||||
  , testProperty "Entire set can be encoded and decoded" prop_buuka_encode_decode
 | 
			
		||||
  ]
 | 
			
		||||
		Reference in New Issue
	
	Block a user