module Test.Map where import qualified Data.NonEmpty.Map as NonEmptyMap import qualified Data.NonEmpty as NonEmpty import qualified Data.Map as Map import qualified Test.QuickCheck as QC insert :: (Int,Char) -> [(Int,Char)] -> Bool insert (k,a) xs = let m = Map.fromList xs in Map.insert k a m == NonEmptyMap.flatten (NonEmptyMap.insert k a m) insertWith :: (Int,String) -> [(Int,String)] -> Bool insertWith (k,a) xs = let m = Map.fromList xs in Map.insertWith (++) k a m == NonEmptyMap.flatten (NonEmptyMap.insertWith (++) k a m) delete :: Int -> NonEmpty.T [] (Int,Char) -> Bool delete k xs = let m = NonEmptyMap.fromList xs in Map.delete k (NonEmptyMap.flatten m) == NonEmptyMap.delete k m fromList :: NonEmpty.T [] (Int,Char) -> Bool fromList xs = Map.fromList (NonEmpty.flatten xs) == NonEmptyMap.flatten (NonEmptyMap.fromList xs) fromListWith :: NonEmpty.T [] (Int,String) -> Bool fromListWith xs = Map.fromListWith (++) (NonEmpty.flatten xs) == NonEmptyMap.flatten (NonEmptyMap.fromListWith (++) xs) fromAscList :: NonEmpty.T [] (Int,Char) -> Bool fromAscList xs = let m = NonEmptyMap.fromList xs in NonEmptyMap.fromAscList (NonEmptyMap.toAscList m) == m toAscList :: NonEmpty.T [] (Int,Char) -> Bool toAscList xs = let m = NonEmptyMap.fromList xs in NonEmpty.flatten (NonEmptyMap.toAscList m) == Map.toAscList (NonEmptyMap.flatten m) union :: NonEmpty.T [] (Int,Char) -> NonEmpty.T [] (Int,Char) -> Bool union xs ys = Map.union (Map.fromList (NonEmpty.flatten xs)) (Map.fromList (NonEmpty.flatten ys)) == NonEmptyMap.flatten (NonEmptyMap.union (NonEmptyMap.fromList xs) (NonEmptyMap.fromList ys)) unionWith :: NonEmpty.T [] (Int,String) -> NonEmpty.T [] (Int,String) -> Bool unionWith xs ys = Map.unionWith (++) (Map.fromList (NonEmpty.flatten xs)) (Map.fromList (NonEmpty.flatten ys)) == NonEmptyMap.flatten (NonEmptyMap.unionWith (++) (NonEmptyMap.fromList xs) (NonEmptyMap.fromList ys)) unionLeft :: [] (Int,Char) -> NonEmpty.T [] (Int,Char) -> Bool unionLeft xs ys = let xm = Map.fromList xs in Map.union xm (Map.fromList (NonEmpty.flatten ys)) == NonEmptyMap.flatten (NonEmptyMap.unionLeft xm (NonEmptyMap.fromList ys)) unionLeftWith :: [] (Int,String) -> NonEmpty.T [] (Int,String) -> Bool unionLeftWith xs ys = let xm = Map.fromList xs in Map.unionWith (++) xm (Map.fromList (NonEmpty.flatten ys)) == NonEmptyMap.flatten (NonEmptyMap.unionLeftWith (++) xm (NonEmptyMap.fromList ys)) unionRight :: NonEmpty.T [] (Int,Char) -> [] (Int,Char) -> Bool unionRight xs ys = let ym = Map.fromList ys in Map.union (Map.fromList (NonEmpty.flatten xs)) ym == NonEmptyMap.flatten (NonEmptyMap.unionRight (NonEmptyMap.fromList xs) ym) unionRightWith :: NonEmpty.T [] (Int,String) -> [] (Int,String) -> Bool unionRightWith xs ys = let ym = Map.fromList ys in Map.unionWith (++) (Map.fromList (NonEmpty.flatten xs)) ym == NonEmptyMap.flatten (NonEmptyMap.unionRightWith (++) (NonEmptyMap.fromList xs) ym) tests :: [(String, QC.Property)] tests = ("insert", QC.property insert) : ("insertWith", QC.property insertWith) : ("delete", QC.property delete) : ("fromList", QC.property fromList) : ("fromListWith", QC.property fromListWith) : ("fromAscList", QC.property fromAscList) : ("toAscList", QC.property toAscList) : ("union", QC.property union) : ("unionWith", QC.property unionWith) : ("unionLeft", QC.property unionLeft) : ("unionLeftWith", QC.property unionLeftWith) : ("unionRight", QC.property unionRight) : ("unionRightWith", QC.property unionRightWith) : []