Bring the addressbook back up to date
- bytestring-trie is not available - hls - modern shell.nix - base - Re-implement trie, with benchmarks - Realize my implementation of trie is slower than Data.Map, use that instead
This commit is contained in:
		
							
								
								
									
										45
									
								
								test/Test/Data/Trie.hs
									
									
									
									
									
										Normal file
									
								
							
							
						
						
									
										45
									
								
								test/Test/Data/Trie.hs
									
									
									
									
									
										Normal file
									
								
							@@ -0,0 +1,45 @@
 | 
			
		||||
module Test.Data.Trie where
 | 
			
		||||
 | 
			
		||||
import Test.Tasty
 | 
			
		||||
import Test.Tasty.Hedgehog (testProperty)
 | 
			
		||||
import Hedgehog
 | 
			
		||||
import Data.Monoid (Sum(..))
 | 
			
		||||
import Data.ByteString (ByteString)
 | 
			
		||||
import Data.Map (Map)
 | 
			
		||||
import qualified Hedgehog.Gen as Gen
 | 
			
		||||
import qualified Hedgehog.Range as Range
 | 
			
		||||
import qualified Data.Trie as T
 | 
			
		||||
import qualified Data.Map.Strict as M
 | 
			
		||||
 | 
			
		||||
genMap :: Gen (Map ByteString (Sum Int))
 | 
			
		||||
genMap = Gen.map (Range.linear 0 100) genT
 | 
			
		||||
  where
 | 
			
		||||
    genT = (,) <$> Gen.bytes (Range.linear 0 20) <*> fmap Sum (Gen.integral (Range.linear 0 10))
 | 
			
		||||
 | 
			
		||||
propIsomorphic :: Property
 | 
			
		||||
propIsomorphic = property $ do
 | 
			
		||||
  m <- forAll genMap
 | 
			
		||||
  let wanted = m
 | 
			
		||||
      got = M.fromList . T.toList . T.fromList . M.toList $ wanted
 | 
			
		||||
  wanted === got
 | 
			
		||||
 | 
			
		||||
propElems :: Property
 | 
			
		||||
propElems = property $ do
 | 
			
		||||
  m <- forAll genMap
 | 
			
		||||
  let wanted = M.elems m
 | 
			
		||||
      got = T.elems . T.fromList . M.toList $ m
 | 
			
		||||
  wanted === got
 | 
			
		||||
 | 
			
		||||
propKeys :: Property
 | 
			
		||||
propKeys = property $ do
 | 
			
		||||
  m <- forAll genMap
 | 
			
		||||
  let wanted = M.keys m
 | 
			
		||||
      got = T.keys . T.fromList . M.toList $ m
 | 
			
		||||
  wanted === got
 | 
			
		||||
 | 
			
		||||
tests :: TestTree
 | 
			
		||||
tests = testGroup "Data.Trie"
 | 
			
		||||
  [ testProperty "isomorphic to Map" $ propIsomorphic
 | 
			
		||||
  , testProperty "isomorphic elems" $ propElems
 | 
			
		||||
  , testProperty "isomorphic keys" $ propKeys
 | 
			
		||||
  ]
 | 
			
		||||
		Reference in New Issue
	
	Block a user