1 module HUnit.Strict where
3 import Data.Function (($), id, const)
5 import Data.Monoid ((<>))
6 import Prelude (Integer, undefined)
7 import qualified Data.Map.Strict as Map
8 import qualified Data.Strict.Maybe as Strict
11 import Test.Tasty.HUnit
13 import Data.TreeMap.Strict (TreeMap(..), (<|))
14 import qualified Data.TreeMap.Strict as TreeMap
17 hunits = testGroup "Strict"
20 TreeMap.insert const ((0::Int)<|[]) () TreeMap.empty
21 @?= (TreeMap $ Map.fromList [ (0::Int, TreeMap.leaf ()) ])
23 TreeMap.insert const ((0::Int)<|[1]) () TreeMap.empty
27 [ (0::Int, TreeMap.Node
28 { TreeMap.node_value = Strict.Nothing
29 , TreeMap.node_size = 1
30 , TreeMap.node_descendants =
31 TreeMap.singleton ((1::Int)<|[]) ()
35 , testGroup "mapByDepthFirst"
36 [ testCase "[0, 0/1, 0/1/2, 1, 1/2/3]" $
37 TreeMap.mapByDepthFirst
38 (\descendants value ->
41 Strict.fromMaybe undefined $
44 (Strict.fromMaybe [] value)
45 (TreeMap.nodes descendants)
47 (TreeMap.fromList const
48 [ ((0::Integer)<|[], [0::Integer])
55 TreeMap.fromList const
56 [ ((0::Integer)<|[], [0,0,1,0,1,2])
57 , (0<|[1], [0,1,0,1,2])
64 TreeMap.mapByDepthFirst
65 (\descendants value ->
68 Strict.fromMaybe undefined $
71 (Strict.fromMaybe [] value)
72 (TreeMap.nodes descendants)
74 (TreeMap.fromList const
75 [ ((0::Integer)<|[0], [0::Integer,0])
78 TreeMap.fromList const
79 [ ((0::Integer)<|[], [0,0])
84 [ testCase "[0, 0/1, 0/1/2]" $
86 (TreeMap.fromList const
87 [ ((0::Integer)<|[], ())
93 [ ((0::Integer)<|[], ())
97 , testCase "[1, 1/2, 1/22, 1/2/3, 1/2/33, 11, 11/2, 11/2/3, 11/2/33]" $
99 (TreeMap.fromList const
100 [ ((1::Integer)<|[], ())
112 [ ((1::Integer)<|[], ())
123 , testGroup "lookupAlong"
124 [ testCase "0/1/2/3 [0, 0/1, 0/1/2, 0/1/2/3]" $
127 (TreeMap.fromList const
128 [ ((0::Integer)<|[], [0])
130 , (0<|[1,2], [0,1,2])
131 , (0<|[1,2,3], [0,1,2,3])
139 , testCase "0/1/2/3 [0, 0/1]" $
142 (TreeMap.fromList const
143 [ ((0::Integer)<|[], [0])