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
24 @?= (TreeMap.TreeMap $ Map.fromList [ (0::Int, TreeMap.leaf ()) ])
26 TreeMap.insert const ((0::Int):|[1]) () TreeMap.empty
30 [ (0::Int, TreeMap.Node
31 { TreeMap.node_value = Strict.Nothing
32 , TreeMap.node_size = 1
33 , TreeMap.node_descendants =
34 TreeMap.singleton ((1::Int):|[]) ()
38 , testGroup "map_by_depth_first"
39 [ testCase "[0, 0/1, 0/1/2, 1, 1/2/3]" $
40 TreeMap.map_by_depth_first
41 (\descendants value ->
44 Strict.fromMaybe undefined $
47 (Strict.fromMaybe [] value)
48 (TreeMap.nodes descendants)
50 (TreeMap.from_List const
51 [ ((0::Integer):|[], [0::Integer])
58 TreeMap.from_List const
59 [ ((0::Integer):|[], [0,0,1,0,1,2])
60 , (0:|[1], [0,1,0,1,2])
67 TreeMap.map_by_depth_first
68 (\descendants value ->
71 Strict.fromMaybe undefined $
74 (Strict.fromMaybe [] value)
75 (TreeMap.nodes descendants)
77 (TreeMap.from_List const
78 [ ((0::Integer):|[0], [0::Integer,0])
81 TreeMap.from_List const
82 [ ((0::Integer):|[], [0,0])
87 [ testCase "[0, 0/1, 0/1/2]" $
89 (TreeMap.from_List const
90 [ ((0::Integer):|[], ())
96 [ ((0::Integer):|[], ())
100 , testCase "[1, 1/2, 1/22, 1/2/3, 1/2/33, 11, 11/2, 11/2/3, 11/2/33]" $
102 (TreeMap.from_List const
103 [ ((1::Integer):|[], ())
115 [ ((1::Integer):|[], ())
126 , testGroup "find_along"
127 [ testCase "0/1/2/3 [0, 0/1, 0/1/2, 0/1/2/3]" $
130 (TreeMap.from_List const
131 [ ((0::Integer):|[], [0])
133 , (0:|[1,2], [0,1,2])
134 , (0:|[1,2,3], [0,1,2,3])
142 , testCase "0/1/2/3 [0, 0/1]" $
145 (TreeMap.from_List const
146 [ ((0::Integer):|[], [0])