1 {-# LANGUAGE NamedFieldPuns #-}
2 {-# LANGUAGE OverloadedStrings #-}
3 {-# LANGUAGE ScopedTypeVariables #-}
4 {-# LANGUAGE TupleSections #-}
5 module Strict.Test where
7 import Data.Function (($), id, const)
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)
15 import Test.Tasty.HUnit
17 import qualified Data.TreeMap.Strict as TreeMap
20 tests = testGroup "Strict"
23 TreeMap.insert const ((0::Int):|[]) () TreeMap.empty
27 [ (0::Int, TreeMap.leaf ())
30 TreeMap.insert const ((0::Int):|[1]) () TreeMap.empty
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):|[]) ()
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 ->
48 Strict.fromMaybe undefined $
51 (Strict.fromMaybe [] value)
52 (TreeMap.nodes descendants)
54 (TreeMap.from_List const
55 [ ((0::Integer):|[], [0::Integer])
62 TreeMap.from_List const
63 [ ((0::Integer):|[], [0,0,1,0,1,2])
64 , (0:|[1], [0,1,0,1,2])
71 TreeMap.map_by_depth_first
72 (\descendants value ->
75 Strict.fromMaybe undefined $
78 (Strict.fromMaybe [] value)
79 (TreeMap.nodes descendants)
81 (TreeMap.from_List const
82 [ ((0::Integer):|[0], [0::Integer,0])
85 TreeMap.from_List const
86 [ ((0::Integer):|[], [0,0])
91 [ testCase "[0, 0/1, 0/1/2]" $
93 (TreeMap.from_List const
94 [ ((0::Integer):|[], ())
100 [ ((0::Integer):|[], ())
104 , testCase "[1, 1/2, 1/22, 1/2/3, 1/2/33, 11, 11/2, 11/2/3, 11/2/33]" $
106 (TreeMap.from_List const
107 [ ((1::Integer):|[], ())
119 [ ((1::Integer):|[], ())
130 , testGroup "find_along"
131 [ testCase "0/1/2/3 [0, 0/1, 0/1/2, 0/1/2/3]" $
134 (TreeMap.from_List const
135 [ ((0::Integer):|[], [0])
137 , (0:|[1,2], [0,1,2])
138 , (0:|[1,2,3], [0,1,2,3])
146 , testCase "0/1/2/3 [0, 0/1]" $
149 (TreeMap.from_List const
150 [ ((0::Integer):|[], [0])