3425
|
1 |
module Store(
|
|
2 |
ElemIndex(),
|
|
3 |
MStore(),
|
|
4 |
IStore(),
|
|
5 |
newStore,
|
|
6 |
addElem,
|
|
7 |
removeElem,
|
|
8 |
readElem,
|
|
9 |
writeElem,
|
|
10 |
modifyElem,
|
|
11 |
firstIndex,
|
3501
|
12 |
indicesM,
|
3425
|
13 |
withIStore,
|
|
14 |
withIStore2,
|
|
15 |
(!),
|
|
16 |
indices
|
|
17 |
) where
|
|
18 |
|
|
19 |
import qualified Data.Array.IArray as IA
|
|
20 |
import qualified Data.Array.IO as IOA
|
|
21 |
import qualified Data.IntSet as IntSet
|
|
22 |
import Data.IORef
|
|
23 |
import Control.Monad
|
|
24 |
|
|
25 |
|
|
26 |
newtype ElemIndex = ElemIndex Int
|
3566
|
27 |
deriving (Eq, Show, Read, Ord)
|
3425
|
28 |
newtype MStore e = MStore (IORef (IntSet.IntSet, IntSet.IntSet, IOA.IOArray Int e))
|
|
29 |
newtype IStore e = IStore (IntSet.IntSet, IA.Array Int e)
|
|
30 |
|
|
31 |
|
|
32 |
firstIndex :: ElemIndex
|
|
33 |
firstIndex = ElemIndex 0
|
|
34 |
|
|
35 |
-- MStore code
|
|
36 |
initialSize :: Int
|
|
37 |
initialSize = 10
|
|
38 |
|
|
39 |
|
|
40 |
growFunc :: Int -> Int
|
|
41 |
growFunc a = a * 3 `div` 2
|
|
42 |
|
|
43 |
|
|
44 |
newStore :: IO (MStore e)
|
|
45 |
newStore = do
|
|
46 |
newar <- IOA.newArray_ (0, initialSize - 1)
|
|
47 |
new <- newIORef (IntSet.empty, IntSet.fromAscList [0..initialSize - 1], newar)
|
|
48 |
return (MStore new)
|
|
49 |
|
|
50 |
|
|
51 |
growStore :: MStore e -> IO ()
|
|
52 |
growStore (MStore ref) = do
|
|
53 |
(busyElems, freeElems, arr) <- readIORef ref
|
|
54 |
(_, m') <- IOA.getBounds arr
|
|
55 |
let newM' = growFunc (m' + 1) - 1
|
|
56 |
newArr <- IOA.newArray_ (0, newM')
|
|
57 |
sequence_ [IOA.readArray arr i >>= IOA.writeArray newArr i | i <- [0..m']]
|
|
58 |
writeIORef ref (busyElems, freeElems `IntSet.union` (IntSet.fromAscList [m'+1..newM']), newArr)
|
|
59 |
|
|
60 |
|
|
61 |
growIfNeeded :: MStore e -> IO ()
|
|
62 |
growIfNeeded m@(MStore ref) = do
|
|
63 |
(_, freeElems, _) <- readIORef ref
|
|
64 |
when (IntSet.null freeElems) $ growStore m
|
|
65 |
|
|
66 |
|
|
67 |
addElem :: MStore e -> e -> IO ElemIndex
|
|
68 |
addElem m@(MStore ref) element = do
|
|
69 |
growIfNeeded m
|
|
70 |
(busyElems, freeElems, arr) <- readIORef ref
|
|
71 |
let (n, freeElems') = IntSet.deleteFindMin freeElems
|
|
72 |
IOA.writeArray arr n element
|
|
73 |
writeIORef ref (IntSet.insert n busyElems, freeElems', arr)
|
|
74 |
return $ ElemIndex n
|
|
75 |
|
|
76 |
|
|
77 |
removeElem :: MStore e -> ElemIndex -> IO ()
|
|
78 |
removeElem (MStore ref) (ElemIndex n) = do
|
|
79 |
(busyElems, freeElems, arr) <- readIORef ref
|
|
80 |
IOA.writeArray arr n undefined
|
|
81 |
writeIORef ref (IntSet.delete n busyElems, IntSet.insert n freeElems, arr)
|
|
82 |
|
|
83 |
|
|
84 |
readElem :: MStore e -> ElemIndex -> IO e
|
|
85 |
readElem (MStore ref) (ElemIndex n) = readIORef ref >>= \(_, _, arr) -> IOA.readArray arr n
|
|
86 |
|
|
87 |
|
|
88 |
writeElem :: MStore e -> ElemIndex -> e -> IO ()
|
|
89 |
writeElem (MStore ref) (ElemIndex n) el = readIORef ref >>= \(_, _, arr) -> IOA.writeArray arr n el
|
|
90 |
|
|
91 |
|
|
92 |
modifyElem :: MStore e -> (e -> e) -> ElemIndex -> IO ()
|
|
93 |
modifyElem (MStore ref) f (ElemIndex n) = do
|
|
94 |
(_, _, arr) <- readIORef ref
|
|
95 |
IOA.readArray arr n >>= (IOA.writeArray arr n) . f
|
|
96 |
|
|
97 |
|
3501
|
98 |
indicesM :: MStore e -> IO [ElemIndex]
|
|
99 |
indicesM (MStore ref) = do
|
|
100 |
(busy, _, _) <- readIORef ref
|
|
101 |
return $ map ElemIndex $ IntSet.toList busy
|
|
102 |
|
|
103 |
|
3425
|
104 |
-- A way to use see MStore elements in pure code via IStore
|
|
105 |
m2i :: MStore e -> IO (IStore e)
|
|
106 |
m2i (MStore ref) = do
|
|
107 |
(a, _, c') <- readIORef ref
|
3566
|
108 |
c <- IOA.freeze c'
|
3425
|
109 |
return $ IStore (a, c)
|
|
110 |
|
3501
|
111 |
|
3425
|
112 |
withIStore :: MStore e -> (IStore e -> a) -> IO a
|
|
113 |
withIStore m f = liftM f (m2i m)
|
|
114 |
|
|
115 |
|
|
116 |
withIStore2 :: MStore e1 -> MStore e2 -> (IStore e1 -> IStore e2 -> a) -> IO a
|
|
117 |
withIStore2 m1 m2 f = do
|
|
118 |
i1 <- m2i m1
|
|
119 |
i2 <- m2i m2
|
|
120 |
return $ f i1 i2
|
|
121 |
|
|
122 |
|
|
123 |
-- IStore code
|
|
124 |
(!) :: IStore e -> ElemIndex -> e
|
|
125 |
(!) (IStore (_, arr)) (ElemIndex i) = (IA.!) arr i
|
|
126 |
|
|
127 |
indices :: IStore e -> [ElemIndex]
|
|
128 |
indices (IStore (busy, _)) = map ElemIndex $ IntSet.toList busy
|