{-# LANGUAGE CPP #-}#include "containers.h" moduleData.Map.Internal.DebugwhereimportData.Map.Internal (Map (..),size ,delta )importControl.Monad(guard)-- | /O(n)/. Show the tree that implements the map. The tree is shown-- in a compressed, hanging format. See 'showTreeWith'.showTree::(Showk ,Showa )=>Map k a ->StringshowTree m =showTreeWith showElem TrueFalsem whereshowElem k x =showk ++":="++showx {- | /O(n)/. The expression (@'showTreeWith' showelem hang wide map@) shows the tree that implements the map. Elements are shown using the @showElem@ function. If @hang@ is 'True', a /hanging/ tree is shown otherwise a rotated tree is shown. If @wide@ is 'True', an extra wide version is shown. > Map> let t = fromDistinctAscList [(x,()) | x <- [1..5]] > Map> putStrLn $ showTreeWith (\k x -> show (k,x)) True False t > (4,()) > +--(2,()) > | +--(1,()) > | +--(3,()) > +--(5,()) > > Map> putStrLn $ showTreeWith (\k x -> show (k,x)) True True t > (4,()) > | > +--(2,()) > | | > | +--(1,()) > | | > | +--(3,()) > | > +--(5,()) > > Map> putStrLn $ showTreeWith (\k x -> show (k,x)) False True t > +--(5,()) > | > (4,()) > | > | +--(3,()) > | | > +--(2,()) > | > +--(1,()) -}showTreeWith::(k ->a ->String)->Bool->Bool->Map k a ->StringshowTreeWith showelem hang wide t |hang =(showsTreeHang showelem wide []t )""|otherwise=(showsTree showelem wide [][]t )""showsTree::(k ->a ->String)->Bool->[String]->[String]->Map k a ->ShowSshowsTree showelem wide lbars rbars t =caset ofTip ->showsBars lbars .showString"|\n"Bin _kx x Tip Tip ->showsBars lbars .showString(showelem kx x ).showString"\n"Bin _kx x l r ->showsTree showelem wide (withBar rbars )(withEmpty rbars )r .showWide wide rbars .showsBars lbars .showString(showelem kx x ).showString"\n".showWide wide lbars .showsTree showelem wide (withEmpty lbars )(withBar lbars )l showsTreeHang::(k ->a ->String)->Bool->[String]->Map k a ->ShowSshowsTreeHang showelem wide bars t =caset ofTip ->showsBars bars .showString"|\n"Bin _kx x Tip Tip ->showsBars bars .showString(showelem kx x ).showString"\n"Bin _kx x l r ->showsBars bars .showString(showelem kx x ).showString"\n".showWide wide bars .showsTreeHang showelem wide (withBar bars )l .showWide wide bars .showsTreeHang showelem wide (withEmpty bars )r showWide::Bool->[String]->String->StringshowWide wide bars |wide =showString(concat(reversebars )).showString"|\n"|otherwise=idshowsBars::[String]->ShowSshowsBars bars =casebars of[]->id_->showString(concat(reverse(tailbars ))).showStringnode node::Stringnode ="+--"withBar,withEmpty::[String]->[String]withBar bars ="| ":bars withEmpty bars =" ":bars {-------------------------------------------------------------------- Assertions --------------------------------------------------------------------}-- | /O(n)/. Test if the internal map structure is valid.---- > valid (fromAscList [(3,"b"), (5,"a")]) == True-- > valid (fromAscList [(5,"a"), (3,"b")]) == Falsevalid::Ordk =>Map k a ->Boolvalid t =balanced t &&ordered t &&validsize t -- | Test if the keys are ordered correctly.ordered::Orda =>Map a b ->Boolordered t =bounded (constTrue)(constTrue)t wherebounded lo hi t' =caset' ofTip ->TrueBin _kx _l r ->(lo kx )&&(hi kx )&&bounded lo (<kx )l &&bounded (>kx )hi r -- | Test if a map obeys the balance invariants.balanced::Map k a ->Boolbalanced t =caset ofTip ->TrueBin ___l r ->(size l +size r <=1||(size l <=delta *size r &&size r <=delta *size l ))&&balanced l &&balanced r -- | Test if each node of a map reports its size correctly.validsize::Map a b ->Boolvalidsize t =caseslowSize t ofNothing->FalseJust_->TruewhereslowSize Tip =Just0slowSize(Bin sz __l r )=dols <-slowSize l rs <-slowSize r guard(sz ==ls +rs +1)returnsz