diff options
Diffstat (limited to 'src/Data')
-rw-r--r-- | src/Data/Word64RangeMap.hs | 170 |
1 files changed, 121 insertions, 49 deletions
diff --git a/src/Data/Word64RangeMap.hs b/src/Data/Word64RangeMap.hs index 141feb8c..b5cbe9d1 100644 --- a/src/Data/Word64RangeMap.hs +++ b/src/Data/Word64RangeMap.hs | |||
@@ -1,52 +1,102 @@ | |||
1 | {-# LANGUAGE FlexibleContexts #-} | 1 | {-# LANGUAGE FlexibleContexts, FlexibleInstances #-} |
2 | {-# LANGUAGE ConstraintKinds #-} | 2 | {-# LANGUAGE ConstraintKinds #-} |
3 | {-# LANGUAGE MultiParamTypeClasses #-} | ||
4 | {-# LANGUAGE TupleSections #-} | ||
3 | -- | | 5 | -- | |
4 | -- A Word64RangeMap is actually a sorted array of arrays | 6 | -- A Word64RangeMap is actually a sorted array of arrays |
5 | -- but lookup is done via binary search testing the range. | 7 | -- but lookup is done via binary search testing the range. |
6 | -- One way of implementing a sparse array i suppose. | 8 | -- One way of implementing a sparse array i suppose. |
7 | module Word64RangeMap where | 9 | module Data.Word64RangeMap where |
8 | 10 | ||
9 | import Data.Word | 11 | import Data.Word |
10 | import Data.Array.Unboxed | 12 | import Data.Array.Unboxed |
11 | import qualified Data.Array.MArray as MA | 13 | import qualified Data.Array.MArray as MA |
12 | import Data.Array.MArray (MArray(..)) | 14 | import Data.Array.MArray (MArray(..)) |
13 | 15 | import qualified Data.Array.Base as Base | |
16 | import Data.Reference | ||
14 | import Debug.Trace | 17 | import Debug.Trace |
15 | import Data.Array.IO | 18 | import Data.Array.IO |
19 | import Data.IORef | ||
16 | 20 | ||
17 | type OuterIndex = Word64 | 21 | type OuterIndex = Int |
18 | type Index = Word64 | 22 | type Index = Word64 |
19 | type InnerArray b = UArray Index b | 23 | type InnerArray b = UArray Index b |
24 | |||
25 | -- | Although this type includes a parameter for index, the code assumes bounds start at 0 | ||
26 | -- and the index has 'Integral', and 'Num' instances. | ||
27 | newtype RefArray r ma i e = RefArray (r (ma i e)) | ||
28 | |||
20 | -- convenient contraint kind | 29 | -- convenient contraint kind |
21 | type RangeArray rangeArray m b = (IArray UArray b, MArray rangeArray (InnerArray b) m) | 30 | type RangeArray rangeArray m b ref = (IArray UArray b, MArray rangeArray (InnerArray b) m, Reference ref m) |
22 | -- The RangeMap type, to be used with the above constraint | 31 | -- The RangeMap type, to be used with the above constraint |
23 | type RangeMap rangeArray b = rangeArray Index (InnerArray b) | 32 | type RangeMap rangeArray b ref = RefArray ref rangeArray OuterIndex (InnerArray b) |
33 | |||
34 | insertArrayAt :: (MA.MArray ma e m, Reference r m, Ix i, Num i, Integral i) => RefArray r ma i e -> i -> e -> m () | ||
35 | insertArrayAt (RefArray ref) pos e = do | ||
36 | ma <- readRef ref | ||
37 | (0,n) <- MA.getBounds ma -- irrefutable pattern, assume array starts at 0 | ||
38 | (esBefore,esAt) <- splitAt (fromIntegral pos) <$> (getElems ma) | ||
39 | newMA <- MA.newListArray (0,n+1) (esBefore ++ [e] ++ esAt) | ||
40 | writeRef ref newMA | ||
24 | 41 | ||
42 | deleteArrayAt :: (MA.MArray ma e m, Reference r m, Ix i, Num i, Integral i) => RefArray r ma i e -> i -> m () | ||
43 | deleteArrayAt (RefArray ref) pos = do | ||
44 | ma <- readRef ref | ||
45 | (0,n) <- MA.getBounds ma -- irrefutable pattern, assume array starts at 0 | ||
46 | (esBefore,esAt) <- splitAt (fromIntegral pos) <$> getElems ma | ||
47 | newMA <- MA.newListArray (0,n-1) (esBefore ++ drop 1 esAt) | ||
48 | writeRef ref newMA | ||
49 | |||
50 | readRefArray (RefArray x) = readRef x | ||
51 | writeRefArray (RefArray x) y = writeRef x y | ||
52 | |||
53 | {- | ||
54 | instance (Reference r m, MArray ma e m) => MArray (RefArray r ma) e m where | ||
55 | getBounds (RefArray r) = readRef r >>= Base.getBounds | ||
56 | getNumElements (RefArray r) = readRef r >>= Base.getNumElements | ||
57 | unsafeRead (RefArray r) i = readRef r >>= \x -> Base.unsafeRead x i | ||
58 | unsafeWrite (RefArray r) i e = modifyRef r (\x -> Base.unsafeWrite x i e >> return (x,())) | ||
59 | -} | ||
60 | |||
61 | -- | a sample RangeMap for easier debugging | ||
62 | getX :: IO (RangeMap IOArray Word8 IORef) | ||
63 | getX = RefArray <$> | ||
64 | (newIORef =<< | ||
65 | newListArray (0,2) | ||
66 | [ listArray (15,20) [15..20] | ||
67 | , listArray (100,105) [100..105] | ||
68 | , listArray (106,107) [106..107] | ||
69 | ]) | ||
25 | -- | a sample RangeMap for easier debugging | 70 | -- | a sample RangeMap for easier debugging |
26 | getM :: IO (RangeMap IOArray Word8) | 71 | getY :: IO (RangeMap IOArray Word8 IORef) |
27 | getM = newListArray (0,3) [ listArray (0,5) [0..5] | 72 | getY = RefArray <$> |
73 | (newIORef =<< | ||
74 | newListArray (0,3) | ||
75 | [ listArray (0,5) [0..5] | ||
28 | , listArray (15,20) [15..20] | 76 | , listArray (15,20) [15..20] |
29 | , listArray (100,105) [100..105] | 77 | , listArray (100,105) [100..105] |
30 | , listArray (106,107) [106..107] | 78 | , listArray (106,107) [106..107] |
31 | ] | 79 | ]) |
32 | 80 | ||
33 | lookupArray :: RangeArray ra m b => Index -> RangeMap ra b -> m (Either OuterIndex (OuterIndex,InnerArray b)) | 81 | lookupArray :: RangeArray ra m b ref => Index -> RangeMap ra b ref -> m (Either OuterIndex (OuterIndex,InnerArray b)) |
34 | lookupArray i r = do | 82 | lookupArray i r = do |
35 | (zr,nr) <- getBounds r -- bounds of mutable range array | 83 | ra <- readRefArray r |
84 | (zr,nr) <- getBounds ra -- bounds of mutable range array | ||
36 | let (dr,mr) = (nr+1 - zr) `divMod` 2 | 85 | let (dr,mr) = (nr+1 - zr) `divMod` 2 |
37 | lookupArrayHelper i r (zr+dr+mr) zr nr | 86 | lookupArrayHelper i r (zr+dr+mr) zr nr |
38 | 87 | ||
39 | lookupArrayHelper :: RangeArray ra m b => Index -> RangeMap ra b | 88 | lookupArrayHelper :: RangeArray ra m b ref => Index -> RangeMap ra b ref |
40 | -> OuterIndex{- current position -} | 89 | -> OuterIndex{- current position -} |
41 | -> OuterIndex{- smallest possible -} | 90 | -> OuterIndex{- smallest possible -} |
42 | -> OuterIndex{- largest possible -} | 91 | -> OuterIndex{- largest possible -} |
43 | -> m (Either OuterIndex (OuterIndex,InnerArray b)) | 92 | -> m (Either OuterIndex (OuterIndex,InnerArray b)) |
44 | lookupArrayHelper i ra pos min max = do | 93 | lookupArrayHelper i r pos min max = do |
45 | {- trace ("lookupArrayHelper " ++ show i ++ " " | 94 | {- trace ("lookupArrayHelper " ++ show i ++ " " |
46 | ++ "ra " | 95 | ++ "ra " |
47 | ++ show pos ++ " " | 96 | ++ show pos ++ " " |
48 | ++ show min ++ " " | 97 | ++ show min ++ " " |
49 | ++ show max) (return ()) -} | 98 | ++ show max) (return ()) -} |
99 | ra <- readRefArray r | ||
50 | ca <- MA.readArray ra pos -- current array | 100 | ca <- MA.readArray ra pos -- current array |
51 | let beforeOrAfter i (x,y) | i < x = LT | 101 | let beforeOrAfter i (x,y) | i < x = LT |
52 | beforeOrAfter i (x,y) | i > y = GT | 102 | beforeOrAfter i (x,y) | i > y = GT |
@@ -55,8 +105,8 @@ lookupArrayHelper i ra pos min max = do | |||
55 | isUnequalMod2 a b = if a `mod` 2 /= b `mod` 2 then 1 else 0 | 105 | isUnequalMod2 a b = if a `mod` 2 /= b `mod` 2 then 1 else 0 |
56 | f a b recurse finish | 106 | f a b recurse finish |
57 | = let (pos',r) = avg a b | 107 | = let (pos',r) = avg a b |
58 | u = isUnequalMod2 r (max - min) {- trace ("u = " ++ show t | 108 | u = isUnequalMod2 r (max - min) {- trace ("u = " ++ show t |
59 | ++ " min=" ++ show min | 109 | ++ " min=" ++ show min |
60 | ++ " max=" ++ show max | 110 | ++ " max=" ++ show max |
61 | ++ " pos'=" ++ show pos' | 111 | ++ " pos'=" ++ show pos' |
62 | ++ " r=" ++ show r | 112 | ++ " r=" ++ show r |
@@ -64,47 +114,69 @@ lookupArrayHelper i ra pos min max = do | |||
64 | in if max - min + u > 1 && pos' /= pos then recurse pos' r else finish | 114 | in if max - min + u > 1 && pos' /= pos then recurse pos' r else finish |
65 | s = "beforeOrAfter " ++ show i ++ " " ++ show (bounds ca) ++ " --> " | 115 | s = "beforeOrAfter " ++ show i ++ " " ++ show (bounds ca) ++ " --> " |
66 | checkAndReturn pos = do | 116 | checkAndReturn pos = do |
67 | a <- MA.readArray ra pos | 117 | boundsRA <- getBounds ra |
68 | {- trace ("checkAndReturn " ++ show pos ++ " bounds a= " ++ show (bounds a)) (return ()) -} | 118 | case beforeOrAfter pos boundsRA of |
69 | case beforeOrAfter i (bounds a) of | 119 | EQ -> do |
70 | EQ -> {- trace "EQ" $ -} return (Right (pos,a)) | 120 | a <- MA.readArray ra pos |
121 | {- trace ("checkAndReturn " ++ show pos ++ " bounds a= " ++ show (bounds a)) (return ()) -} | ||
122 | case beforeOrAfter i (bounds a) of | ||
123 | EQ -> {- trace "EQ" $ -} return (Right (pos,a)) | ||
124 | LT -> {- trace "LT" $ -} return (Left pos) | ||
125 | GT -> {- trace "GT" $ -} return (Left (pos+1)) | ||
71 | LT -> {- trace "LT" $ -} return (Left pos) | 126 | LT -> {- trace "LT" $ -} return (Left pos) |
72 | GT -> {- trace "GT" $ -} return (Left (pos+1)) | 127 | GT -> {- trace "GT" $ -} return (Left (pos+1)) |
73 | case beforeOrAfter i (bounds ca) of | 128 | 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)) | 129 | GT -> {- trace (s ++ "GT") $ -} f pos max (\pos' r' -> lookupArrayHelper i r (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) | 130 | LT -> {- trace (s ++ "LT") $ -} f min pos (\pos' r' -> lookupArrayHelper i r pos' min pos) (checkAndReturn pos) |
76 | EQ -> {- trace (s ++ "EQ") $ -} return (Right (pos,ca)) | 131 | EQ -> {- trace (s ++ "EQ") $ -} return (Right (pos,ca)) |
77 | 132 | ||
78 | -- | up to the caller to ensure the inserted array does not overlap with others | 133 | insertWhereItGoes :: RangeArray ra m e ref => InnerArray e -> RangeMap ra e ref -> m (Either (OuterIndex, InnerArray e) ()) |
79 | -- and also to ensure that sort is maintained | 134 | insertWhereItGoes e r = do |
80 | -- TODO: Does not grow array! | ||
81 | insertArrayNoCheck :: RangeArray ra m b => OuterIndex -> InnerArray b -> RangeMap ra b -> m () | ||
82 | insertArrayNoCheck 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 | |||
90 | insertWhereItGoes :: RangeArray ra m e => InnerArray e -> ra Index (InnerArray e) -> m (Either (OuterIndex, InnerArray e) ()) | ||
91 | insertWhereItGoes e ra = do | ||
92 | let (i,j) = bounds e | 135 | let (i,j) = bounds e |
93 | (z,n) <- MA.getBounds ra | 136 | outerArray <- readRefArray r |
94 | let inside x (low,hi) = x >= low && x <= hi | 137 | (outerZ,outerN) <- MA.getBounds outerArray |
95 | r <- lookupArray i ra | 138 | let inside x (low,hi) = x >= low && x <= hi -- flip inRange |
96 | case r of | 139 | lr <- lookupArray i r |
97 | Left ii -> if ii+1 <= n | 140 | case lr of |
141 | Left ii -> | ||
142 | trace "(insertWhereItGoes) Left ii case" | ||
143 | $if ii <= outerN -- is there a next array? | ||
98 | then do | 144 | then do |
99 | y <- MA.readArray ra (ii+1) | 145 | y <- MA.readArray outerArray (ii) |
100 | if j `inside` bounds y | 146 | let boundsy = show (bounds y) |
101 | then return (Left (ii+1,y)) -- TODO, actually could shrink y or e | 147 | insideStr = show j ++ " inside " ++ boundsy |
102 | else Right <$> insertArrayNoCheck ii e ra | 148 | outsideStr = show j ++ " outside " ++ boundsy |
103 | else Right <$> insertArrayNoCheck ii e ra | 149 | if j `inside` bounds y -- does the final bound of inserted array overlap next array? |
104 | Right x -> return (Left x) | 150 | then trace insideStr $ return (Left (ii,y)) -- TODO, actually could shrink y or e |
105 | 151 | else trace outsideStr $ Right <$> insertArrayAt r ii e | |
106 | lookupInRangeMap k ra = do | 152 | else Right <$> insertArrayAt r ii e |
107 | b <- lookupArray k ra | 153 | Right x -> |
154 | trace "(insertWhereItGoes) Right x case" | ||
155 | $return (Left x) | ||
156 | |||
157 | lookupInRangeMap :: RangeArray ra m e ref => Index -> RangeMap ra e ref -> m (Maybe e) | ||
158 | lookupInRangeMap k r = do | ||
159 | b <- lookupArray k r | ||
108 | case b of | 160 | case b of |
109 | Right (_,ar) -> return (Just (ar ! k)) | 161 | Right (_,ar) -> return (Just (ar ! k)) |
110 | Left _ -> return Nothing | 162 | Left _ -> return Nothing |
163 | |||
164 | |||
165 | deleteRange :: RangeArray ra m e ref => (Index,Index) | ||
166 | -> RangeMap ra e ref | ||
167 | -> m (Either OuterIndex (OuterIndex,InnerArray e)) | ||
168 | |||
169 | deleteRange (z,n) r = do | ||
170 | result <- lookupArray z r | ||
171 | case result of | ||
172 | Left _ -> return result | ||
173 | Right (outerIndex,a) | bounds a /= (z,n) -> return (Left outerIndex) | ||
174 | Right (outerIndex,a) | bounds a == (z,n) -> do | ||
175 | outerArray <- readRefArray r | ||
176 | (zz,nn) <- getBounds outerArray | ||
177 | as <- map (\(i,e) -> (if i > outerIndex then i - 1 else i, e)) | ||
178 | . filter ((/=outerIndex) . fst) | ||
179 | <$> getAssocs outerArray | ||
180 | mutAr <- MA.newListArray (zz,nn-1) (map snd as) | ||
181 | writeRefArray r mutAr | ||
182 | return result | ||