]> Git — Sourcephile - haskell/treemap.git/blob - Data/TreeMap/Strict/Test.hs
init
[haskell/treemap.git] / Data / TreeMap / Strict / Test.hs
1 {-# LANGUAGE NamedFieldPuns #-}
2 {-# LANGUAGE OverloadedStrings #-}
3 {-# LANGUAGE ScopedTypeVariables #-}
4 {-# LANGUAGE TupleSections #-}
5 module Strict.Test where
6
7 import Data.Function (($), id, const)
8 import Data.Int (Int)
9 import Data.List.NonEmpty (NonEmpty(..))
10 import qualified Data.Map.Strict as Map
11 import Data.Monoid ((<>))
12 import qualified Data.Strict.Maybe as Strict
13 import Prelude (Integer, undefined)
14 import Test.Tasty
15 import Test.Tasty.HUnit
16
17 import qualified Data.TreeMap.Strict as TreeMap
18
19 tests :: TestTree
20 tests = testGroup "Strict"
21 [ testGroup "insert"
22 [ testCase "[] 0" $
23 TreeMap.insert const ((0::Int):|[]) () TreeMap.empty
24 @?=
25 (TreeMap.TreeMap $
26 Map.fromList
27 [ (0::Int, TreeMap.leaf ())
28 ])
29 , testCase "[] 0/1" $
30 TreeMap.insert const ((0::Int):|[1]) () TreeMap.empty
31 @?=
32 (TreeMap.TreeMap $
33 Map.fromList
34 [ (0::Int, TreeMap.Node
35 { TreeMap.node_value = Strict.Nothing
36 , TreeMap.node_size = 1
37 , TreeMap.node_descendants =
38 TreeMap.singleton ((1::Int):|[]) ()
39 })
40 ])
41 ]
42 , testGroup "map_by_depth_first"
43 [ testCase "[0, 0/1, 0/1/2, 1, 1/2/3]" $
44 TreeMap.map_by_depth_first
45 (\descendants value ->
46 Map.foldl'
47 (\acc v -> (<>) acc $
48 Strict.fromMaybe undefined $
49 TreeMap.node_value v
50 )
51 (Strict.fromMaybe [] value)
52 (TreeMap.nodes descendants)
53 )
54 (TreeMap.from_List const
55 [ ((0::Integer):|[], [0::Integer])
56 , (0:|[1], [0,1])
57 , (0:|[1,2], [0,1,2])
58 , (1:|[], [1])
59 , (1:|[2,3], [1,2,3])
60 ])
61 @?=
62 TreeMap.from_List const
63 [ ((0::Integer):|[], [0,0,1,0,1,2])
64 , (0:|[1], [0,1,0,1,2])
65 , (0:|[1,2], [0,1,2])
66 , (1:|[], [1,1,2,3])
67 , (1:|[2], [1,2,3])
68 , (1:|[2,3], [1,2,3])
69 ]
70 , testCase "[0/0]" $
71 TreeMap.map_by_depth_first
72 (\descendants value ->
73 Map.foldl'
74 (\acc v -> (<>) acc $
75 Strict.fromMaybe undefined $
76 TreeMap.node_value v
77 )
78 (Strict.fromMaybe [] value)
79 (TreeMap.nodes descendants)
80 )
81 (TreeMap.from_List const
82 [ ((0::Integer):|[0], [0::Integer,0])
83 ])
84 @?=
85 TreeMap.from_List const
86 [ ((0::Integer):|[], [0,0])
87 , (0:|[0], [0,0])
88 ]
89 ]
90 , testGroup "flatten"
91 [ testCase "[0, 0/1, 0/1/2]" $
92 TreeMap.flatten id
93 (TreeMap.from_List const
94 [ ((0::Integer):|[], ())
95 , (0:|[1], ())
96 , (0:|[1,2], ())
97 ])
98 @?=
99 Map.fromList
100 [ ((0::Integer):|[], ())
101 , (0:|[1], ())
102 , (0:|[1,2], ())
103 ]
104 , testCase "[1, 1/2, 1/22, 1/2/3, 1/2/33, 11, 11/2, 11/2/3, 11/2/33]" $
105 TreeMap.flatten id
106 (TreeMap.from_List const
107 [ ((1::Integer):|[], ())
108 , (1:|[2], ())
109 , (1:|[22], ())
110 , (1:|[2,3], ())
111 , (1:|[2,33], ())
112 , (11:|[], ())
113 , (11:|[2], ())
114 , (11:|[2,3], ())
115 , (11:|[2,33], ())
116 ])
117 @?=
118 Map.fromList
119 [ ((1::Integer):|[], ())
120 , (1:|[2], ())
121 , (1:|[22], ())
122 , (1:|[2,3], ())
123 , (1:|[2,33], ())
124 , (11:|[], ())
125 , (11:|[2], ())
126 , (11:|[2,3], ())
127 , (11:|[2,33], ())
128 ]
129 ]
130 , testGroup "find_along"
131 [ testCase "0/1/2/3 [0, 0/1, 0/1/2, 0/1/2/3]" $
132 TreeMap.find_along
133 (0:|[1,2,3])
134 (TreeMap.from_List const
135 [ ((0::Integer):|[], [0])
136 , (0:|[1], [0,1])
137 , (0:|[1,2], [0,1,2])
138 , (0:|[1,2,3], [0,1,2,3])
139 ])
140 @?=
141 [ [0::Integer]
142 , [0,1]
143 , [0,1,2]
144 , [0,1,2,3]
145 ]
146 , testCase "0/1/2/3 [0, 0/1]" $
147 TreeMap.find_along
148 (0:|[1,2,3])
149 (TreeMap.from_List const
150 [ ((0::Integer):|[], [0])
151 , (0:|[1], [0,1])
152 ])
153 @?=
154 [ [0::Integer]
155 , [0,1]
156 ]
157 ]
158 ]