summaryrefslogtreecommitdiff
path: root/src/Data
diff options
context:
space:
mode:
authorJames Crayne <jim.crayne@gmail.com>2017-11-22 16:00:25 +0000
committerJames Crayne <jim.crayne@gmail.com>2017-11-22 16:01:04 +0000
commitb7b52d1495a1b7915eb19aeb3111e865727a3322 (patch)
tree262ddc0317a79d09174490339640f0063944c77a /src/Data
parent1bb9b44ede5ba315bfc5cab7af3ec391efec2c5d (diff)
Rangemap, for use with outgoing
Diffstat (limited to 'src/Data')
-rw-r--r--src/Data/Word64RangeMap.hs110
1 files changed, 110 insertions, 0 deletions
diff --git a/src/Data/Word64RangeMap.hs b/src/Data/Word64RangeMap.hs
new file mode 100644
index 00000000..141feb8c
--- /dev/null
+++ b/src/Data/Word64RangeMap.hs
@@ -0,0 +1,110 @@
1{-# LANGUAGE FlexibleContexts #-}
2{-# LANGUAGE ConstraintKinds #-}
3-- |
4-- A Word64RangeMap is actually a sorted array of arrays
5-- but lookup is done via binary search testing the range.
6-- One way of implementing a sparse array i suppose.
7module Word64RangeMap where
8
9import Data.Word
10import Data.Array.Unboxed
11import qualified Data.Array.MArray as MA
12import Data.Array.MArray (MArray(..))
13
14import Debug.Trace
15import Data.Array.IO
16
17type OuterIndex = Word64
18type Index = Word64
19type InnerArray b = UArray Index b
20-- convenient contraint kind
21type RangeArray rangeArray m b = (IArray UArray b, MArray rangeArray (InnerArray b) m)
22-- The RangeMap type, to be used with the above constraint
23type RangeMap rangeArray b = rangeArray Index (InnerArray b)
24
25-- | a sample RangeMap for easier debugging
26getM :: IO (RangeMap IOArray Word8)
27getM = newListArray (0,3) [ listArray (0,5) [0..5]
28 , listArray (15,20) [15..20]
29 , listArray (100,105) [100..105]
30 , listArray (106,107) [106..107]
31 ]
32
33lookupArray :: RangeArray ra m b => Index -> RangeMap ra b -> m (Either OuterIndex (OuterIndex,InnerArray b))
34lookupArray i r = do
35 (zr,nr) <- getBounds r -- bounds of mutable range array
36 let (dr,mr) = (nr+1 - zr) `divMod` 2
37 lookupArrayHelper i r (zr+dr+mr) zr nr
38
39lookupArrayHelper :: RangeArray ra m b => Index -> RangeMap ra b
40 -> OuterIndex{- current position -}
41 -> OuterIndex{- smallest possible -}
42 -> OuterIndex{- largest possible -}
43 -> m (Either OuterIndex (OuterIndex,InnerArray b))
44lookupArrayHelper i ra pos min max = do
45 {- trace ("lookupArrayHelper " ++ show i ++ " "
46 ++ "ra "
47 ++ show pos ++ " "
48 ++ show min ++ " "
49 ++ show max) (return ()) -}
50 ca <- MA.readArray ra pos -- current array
51 let beforeOrAfter i (x,y) | i < x = LT
52 beforeOrAfter i (x,y) | i > y = GT
53 beforeOrAfter _ _ = EQ
54 avg a b = (a + b) `divMod` 2
55 isUnequalMod2 a b = if a `mod` 2 /= b `mod` 2 then 1 else 0
56 f a b recurse finish
57 = let (pos',r) = avg a b
58 u = isUnequalMod2 r (max - min) {- trace ("u = " ++ show t
59 ++ " min=" ++ show min
60 ++ " max=" ++ show max
61 ++ " pos'=" ++ show pos'
62 ++ " r=" ++ show r
63 ) t -}
64 in if max - min + u > 1 && pos' /= pos then recurse pos' r else finish
65 s = "beforeOrAfter " ++ show i ++ " " ++ show (bounds ca) ++ " --> "
66 checkAndReturn pos = do
67 a <- MA.readArray ra pos
68 {- trace ("checkAndReturn " ++ show pos ++ " bounds a= " ++ show (bounds a)) (return ()) -}
69 case beforeOrAfter i (bounds a) of
70 EQ -> {- trace "EQ" $ -} return (Right (pos,a))
71 LT -> {- trace "LT" $ -} return (Left pos)
72 GT -> {- trace "GT" $ -} return (Left (pos+1))
73 case beforeOrAfter i (bounds ca) of
74 GT -> {- trace (s ++ "GT") $ -} f pos max (\pos' r -> lookupArrayHelper i ra (pos'+r) pos max) (checkAndReturn (pos + 1))
75 LT -> {- trace (s ++ "LT") $ -} f min pos (\pos' r -> lookupArrayHelper i ra pos' min pos) (checkAndReturn pos)
76 EQ -> {- trace (s ++ "EQ") $ -} return (Right (pos,ca))
77
78-- | up to the caller to ensure the inserted array does not overlap with others
79-- and also to ensure that sort is maintained
80-- TODO: Does not grow array!
81insertArrayNoCheck :: RangeArray ra m b => OuterIndex -> InnerArray b -> RangeMap ra b -> m ()
82insertArrayNoCheck pos e ra = do
83 (z,n) <- MA.getBounds ra
84 flip mapM_ [n .. pos + 1] $ \j -> do
85 x <- readArray ra (j-1)
86 writeArray ra j x
87 writeArray ra pos e
88
89
90insertWhereItGoes :: RangeArray ra m e => InnerArray e -> ra Index (InnerArray e) -> m (Either (OuterIndex, InnerArray e) ())
91insertWhereItGoes e ra = do
92 let (i,j) = bounds e
93 (z,n) <- MA.getBounds ra
94 let inside x (low,hi) = x >= low && x <= hi
95 r <- lookupArray i ra
96 case r of
97 Left ii -> if ii+1 <= n
98 then do
99 y <- MA.readArray ra (ii+1)
100 if j `inside` bounds y
101 then return (Left (ii+1,y)) -- TODO, actually could shrink y or e
102 else Right <$> insertArrayNoCheck ii e ra
103 else Right <$> insertArrayNoCheck ii e ra
104 Right x -> return (Left x)
105
106lookupInRangeMap k ra = do
107 b <- lookupArray k ra
108 case b of
109 Right (_,ar) -> return (Just (ar ! k))
110 Left _ -> return Nothing