Some more that were not native
authornemo
Fri, 20 Aug 2010 11:54:14 -0400
changeset 3747 76a197793b62
parent 3746 f227a6b69618
child 3748 daea2650a5aa
Some more that were not native
.hgignore
gameServer/RoomsAndClients.hs
gameServer/Store.hs
share/hedgewars/Data/Maps/FlightJoust/map.cfg
share/hedgewars/Data/Themes/Art/theme.cfg
share/hedgewars/Data/Themes/Stage/theme.cfg
--- a/.hgignore	Fri Aug 20 11:52:30 2010 -0400
+++ b/.hgignore	Fri Aug 20 11:54:14 2010 -0400
@@ -1,25 +1,25 @@
-glob:CMakeCache.txt
-glob:CMakeFiles
-glob:moc_*.cxx
-glob:qrc_*.cxx
-glob:*.o
-glob:Makefile
-glob:bin
-glob:*.hi
-glob:*.*~
-glob:*.core
-glob:hedgewars/config.inc
-glob:cmake_install.cmake
-glob:QTfrontend/hwconsts.cpp
-glob:CPackConfig.cmake
-glob:CPackSourceConfig.cmake
-glob:tools/cmake_uninstall.cmake
-glob:install_manifest.txt
-glob:.DS_Store
-glob:*.swp
-glob:*.orig
-glob:*.diff
-glob:project_files/HedgewarsMobile/Data/
-glob:project_files/HedgewarsMobile/build/
-glob:project_files/HedgewarsMobile/Hedgewars.xcodeproj/vittorio.*
-glob:moc_*.cxx_parameters
+glob:CMakeCache.txt
+glob:CMakeFiles
+glob:moc_*.cxx
+glob:qrc_*.cxx
+glob:*.o
+glob:Makefile
+glob:bin
+glob:*.hi
+glob:*.*~
+glob:*.core
+glob:hedgewars/config.inc
+glob:cmake_install.cmake
+glob:QTfrontend/hwconsts.cpp
+glob:CPackConfig.cmake
+glob:CPackSourceConfig.cmake
+glob:tools/cmake_uninstall.cmake
+glob:install_manifest.txt
+glob:.DS_Store
+glob:*.swp
+glob:*.orig
+glob:*.diff
+glob:project_files/HedgewarsMobile/Data/
+glob:project_files/HedgewarsMobile/build/
+glob:project_files/HedgewarsMobile/Hedgewars.xcodeproj/vittorio.*
+glob:moc_*.cxx_parameters
--- a/gameServer/RoomsAndClients.hs	Fri Aug 20 11:52:30 2010 -0400
+++ b/gameServer/RoomsAndClients.hs	Fri Aug 20 11:54:14 2010 -0400
@@ -1,197 +1,197 @@
-module RoomsAndClients(
-    RoomIndex(),
-    ClientIndex(),
-    MRoomsAndClients(),
-    IRoomsAndClients(),
-    newRoomsAndClients,
-    addRoom,
-    addClient,
-    removeRoom,
-    removeClient,
-    modifyRoom,
-    modifyClient,
-    lobbyId,
-    moveClientToLobby,
-    moveClientToRoom,
-    clientRoom,
-    clientRoomM,
-    clientExists,
-    client,
-    room,
-    client'sM,
-    room'sM,
-    allClientsM,
-    clientsM,
-    roomClientsM,
-    roomClientsIndicesM,
-    withRoomsAndClients,
-    allRooms,
-    allClients,
-    clientRoom,
-    showRooms,
-    roomClients
-    ) where
-
-
-import Store
-import Control.Monad
-
-
-data Room r = Room {
-    roomClients' :: [ClientIndex],
-    room' :: r
-    }
-
-
-data Client c = Client {
-    clientRoom' :: RoomIndex,
-    client' :: c
-    }
-
-
-newtype RoomIndex = RoomIndex ElemIndex
-    deriving (Eq)
-newtype ClientIndex = ClientIndex ElemIndex
-    deriving (Eq, Show, Read, Ord)
-
-instance Show RoomIndex where
-    show (RoomIndex i) = 'r' : show i
-
-unRoomIndex :: RoomIndex -> ElemIndex
-unRoomIndex (RoomIndex r) = r
-
-unClientIndex :: ClientIndex -> ElemIndex
-unClientIndex (ClientIndex c) = c
-
-
-newtype MRoomsAndClients r c = MRoomsAndClients (MStore (Room r), MStore (Client c))
-newtype IRoomsAndClients r c = IRoomsAndClients (IStore (Room r), IStore (Client c))
-
-
-lobbyId :: RoomIndex
-lobbyId = RoomIndex firstIndex
-
-
-newRoomsAndClients :: r -> IO (MRoomsAndClients r c)
-newRoomsAndClients r = do
-    rooms <- newStore
-    clients <- newStore
-    let rnc = MRoomsAndClients (rooms, clients)
-    ri <- addRoom rnc r
-    when (ri /= lobbyId) $ error "Empty struct inserts not at firstIndex index"
-    return rnc
-
-
-roomAddClient :: ClientIndex -> Room r -> Room r
-roomAddClient cl room = room{roomClients' = cl : roomClients' room}
-
-roomRemoveClient :: ClientIndex -> Room r -> Room r
-roomRemoveClient cl room = room{roomClients' = filter (/= cl) $ roomClients' room}
-
-
-addRoom :: MRoomsAndClients r c -> r -> IO RoomIndex
-addRoom (MRoomsAndClients (rooms, _)) room = do
-    i <- addElem rooms (Room  [] room)
-    return $ RoomIndex i
-
-
-addClient :: MRoomsAndClients r c -> c -> IO ClientIndex
-addClient (MRoomsAndClients (rooms, clients)) client = do
-    i <- addElem clients (Client lobbyId client)
-    modifyElem rooms (roomAddClient (ClientIndex i)) (unRoomIndex lobbyId)
-    return $ ClientIndex i
-
-removeRoom :: MRoomsAndClients r c -> RoomIndex -> IO ()
-removeRoom rnc@(MRoomsAndClients (rooms, _)) room@(RoomIndex ri) 
-    | room == lobbyId = error "Cannot delete lobby"
-    | otherwise = do
-        clIds <- liftM roomClients' $ readElem rooms ri
-        forM_ clIds (moveClientToLobby rnc)
-        removeElem rooms ri
-
-
-removeClient :: MRoomsAndClients r c -> ClientIndex -> IO ()
-removeClient (MRoomsAndClients (rooms, clients)) cl@(ClientIndex ci) = do
-    RoomIndex ri <- liftM clientRoom' $ readElem clients ci
-    modifyElem rooms (roomRemoveClient cl) ri
-    removeElem clients ci
-
-
-modifyRoom :: MRoomsAndClients r c -> (r -> r) -> RoomIndex -> IO ()
-modifyRoom (MRoomsAndClients (rooms, _)) f (RoomIndex ri) = modifyElem rooms (\r -> r{room' = f $ room' r}) ri
-
-modifyClient :: MRoomsAndClients r c -> (c -> c) -> ClientIndex -> IO ()
-modifyClient (MRoomsAndClients (_, clients)) f (ClientIndex ci) = modifyElem clients (\c -> c{client' = f $ client' c}) ci
-
-moveClientInRooms :: MRoomsAndClients r c -> RoomIndex -> RoomIndex -> ClientIndex -> IO ()
-moveClientInRooms (MRoomsAndClients (rooms, clients)) (RoomIndex riFrom) rt@(RoomIndex riTo) cl@(ClientIndex ci) = do
-    modifyElem rooms (roomRemoveClient cl) riFrom
-    modifyElem rooms (roomAddClient cl) riTo
-    modifyElem clients (\c -> c{clientRoom' = rt}) ci
-
-
-moveClientToLobby :: MRoomsAndClients r c -> ClientIndex -> IO ()
-moveClientToLobby rnc ci = do
-    room <- clientRoomM rnc ci
-    moveClientInRooms rnc room lobbyId ci
-
-
-moveClientToRoom :: MRoomsAndClients r c -> RoomIndex -> ClientIndex -> IO ()
-moveClientToRoom rnc ri ci = moveClientInRooms rnc lobbyId ri ci
-
-
-clientExists :: MRoomsAndClients r c -> ClientIndex -> IO Bool
-clientExists (MRoomsAndClients (_, clients)) (ClientIndex ci) = elemExists clients ci
-
-clientRoomM :: MRoomsAndClients r c -> ClientIndex -> IO RoomIndex
-clientRoomM (MRoomsAndClients (_, clients)) (ClientIndex ci) = liftM clientRoom' (clients `readElem` ci)
-
-client'sM :: MRoomsAndClients r c -> (c -> a) -> ClientIndex -> IO a
-client'sM (MRoomsAndClients (_, clients)) f (ClientIndex ci) = liftM (f . client') (clients `readElem` ci)
-
-room'sM :: MRoomsAndClients r c -> (r -> a) -> RoomIndex -> IO a
-room'sM (MRoomsAndClients (rooms, _)) f (RoomIndex ri) = liftM (f . room') (rooms `readElem` ri)
-
-allClientsM :: MRoomsAndClients r c -> IO [ClientIndex]
-allClientsM (MRoomsAndClients (_, clients)) = liftM (map ClientIndex) $ indicesM clients
-
-clientsM :: MRoomsAndClients r c -> IO [c]
-clientsM (MRoomsAndClients (_, clients)) = indicesM clients >>= mapM (\ci -> liftM client' $ readElem clients ci)
-
-roomClientsIndicesM :: MRoomsAndClients r c -> RoomIndex -> IO [ClientIndex]
-roomClientsIndicesM (MRoomsAndClients (rooms, clients)) (RoomIndex ri) = liftM roomClients' (rooms `readElem` ri)
-
-roomClientsM :: MRoomsAndClients r c -> RoomIndex -> IO [c]
-roomClientsM (MRoomsAndClients (rooms, clients)) (RoomIndex ri) = liftM roomClients' (rooms `readElem` ri) >>= mapM (\(ClientIndex ci) -> liftM client' $ readElem clients ci)
-
-withRoomsAndClients :: MRoomsAndClients r c -> (IRoomsAndClients r c -> a) -> IO a
-withRoomsAndClients (MRoomsAndClients (rooms, clients)) f =
-    withIStore2 rooms clients (\r c -> f $ IRoomsAndClients (r, c))
-
-----------------------------------------
------------ IRoomsAndClients -----------
-
-showRooms :: (Show r, Show c) => IRoomsAndClients r c -> String
-showRooms rnc@(IRoomsAndClients (rooms, clients)) = concatMap showRoom (allRooms rnc)
-    where
-    showRoom r = unlines $ ((show r) ++ ": " ++ (show $ room' $ rooms ! (unRoomIndex r))) : (map showClient (roomClients' $ rooms ! (unRoomIndex r)))
-    showClient c = "    " ++ (show c) ++ ": " ++ (show $ client' $ clients ! (unClientIndex c))
-
-
-allRooms :: IRoomsAndClients r c -> [RoomIndex]
-allRooms (IRoomsAndClients (rooms, _)) = map RoomIndex $ indices rooms
-
-allClients :: IRoomsAndClients r c -> [ClientIndex]
-allClients (IRoomsAndClients (_, clients)) = map ClientIndex $ indices clients
-
-clientRoom :: IRoomsAndClients r c -> ClientIndex -> RoomIndex
-clientRoom (IRoomsAndClients (_, clients)) (ClientIndex ci) = clientRoom' (clients ! ci)
-
-client :: IRoomsAndClients r c -> ClientIndex -> c
-client (IRoomsAndClients (_, clients)) (ClientIndex ci) = client' (clients ! ci)
-
-room :: IRoomsAndClients r c -> RoomIndex -> r
-room (IRoomsAndClients (rooms, _)) (RoomIndex ri) = room' (rooms ! ri)
-
-roomClients :: IRoomsAndClients r c -> RoomIndex -> [ClientIndex]
-roomClients (IRoomsAndClients (rooms, _)) (RoomIndex ri) = roomClients' $ (rooms ! ri)
+module RoomsAndClients(
+    RoomIndex(),
+    ClientIndex(),
+    MRoomsAndClients(),
+    IRoomsAndClients(),
+    newRoomsAndClients,
+    addRoom,
+    addClient,
+    removeRoom,
+    removeClient,
+    modifyRoom,
+    modifyClient,
+    lobbyId,
+    moveClientToLobby,
+    moveClientToRoom,
+    clientRoom,
+    clientRoomM,
+    clientExists,
+    client,
+    room,
+    client'sM,
+    room'sM,
+    allClientsM,
+    clientsM,
+    roomClientsM,
+    roomClientsIndicesM,
+    withRoomsAndClients,
+    allRooms,
+    allClients,
+    clientRoom,
+    showRooms,
+    roomClients
+    ) where
+
+
+import Store
+import Control.Monad
+
+
+data Room r = Room {
+    roomClients' :: [ClientIndex],
+    room' :: r
+    }
+
+
+data Client c = Client {
+    clientRoom' :: RoomIndex,
+    client' :: c
+    }
+
+
+newtype RoomIndex = RoomIndex ElemIndex
+    deriving (Eq)
+newtype ClientIndex = ClientIndex ElemIndex
+    deriving (Eq, Show, Read, Ord)
+
+instance Show RoomIndex where
+    show (RoomIndex i) = 'r' : show i
+
+unRoomIndex :: RoomIndex -> ElemIndex
+unRoomIndex (RoomIndex r) = r
+
+unClientIndex :: ClientIndex -> ElemIndex
+unClientIndex (ClientIndex c) = c
+
+
+newtype MRoomsAndClients r c = MRoomsAndClients (MStore (Room r), MStore (Client c))
+newtype IRoomsAndClients r c = IRoomsAndClients (IStore (Room r), IStore (Client c))
+
+
+lobbyId :: RoomIndex
+lobbyId = RoomIndex firstIndex
+
+
+newRoomsAndClients :: r -> IO (MRoomsAndClients r c)
+newRoomsAndClients r = do
+    rooms <- newStore
+    clients <- newStore
+    let rnc = MRoomsAndClients (rooms, clients)
+    ri <- addRoom rnc r
+    when (ri /= lobbyId) $ error "Empty struct inserts not at firstIndex index"
+    return rnc
+
+
+roomAddClient :: ClientIndex -> Room r -> Room r
+roomAddClient cl room = room{roomClients' = cl : roomClients' room}
+
+roomRemoveClient :: ClientIndex -> Room r -> Room r
+roomRemoveClient cl room = room{roomClients' = filter (/= cl) $ roomClients' room}
+
+
+addRoom :: MRoomsAndClients r c -> r -> IO RoomIndex
+addRoom (MRoomsAndClients (rooms, _)) room = do
+    i <- addElem rooms (Room  [] room)
+    return $ RoomIndex i
+
+
+addClient :: MRoomsAndClients r c -> c -> IO ClientIndex
+addClient (MRoomsAndClients (rooms, clients)) client = do
+    i <- addElem clients (Client lobbyId client)
+    modifyElem rooms (roomAddClient (ClientIndex i)) (unRoomIndex lobbyId)
+    return $ ClientIndex i
+
+removeRoom :: MRoomsAndClients r c -> RoomIndex -> IO ()
+removeRoom rnc@(MRoomsAndClients (rooms, _)) room@(RoomIndex ri) 
+    | room == lobbyId = error "Cannot delete lobby"
+    | otherwise = do
+        clIds <- liftM roomClients' $ readElem rooms ri
+        forM_ clIds (moveClientToLobby rnc)
+        removeElem rooms ri
+
+
+removeClient :: MRoomsAndClients r c -> ClientIndex -> IO ()
+removeClient (MRoomsAndClients (rooms, clients)) cl@(ClientIndex ci) = do
+    RoomIndex ri <- liftM clientRoom' $ readElem clients ci
+    modifyElem rooms (roomRemoveClient cl) ri
+    removeElem clients ci
+
+
+modifyRoom :: MRoomsAndClients r c -> (r -> r) -> RoomIndex -> IO ()
+modifyRoom (MRoomsAndClients (rooms, _)) f (RoomIndex ri) = modifyElem rooms (\r -> r{room' = f $ room' r}) ri
+
+modifyClient :: MRoomsAndClients r c -> (c -> c) -> ClientIndex -> IO ()
+modifyClient (MRoomsAndClients (_, clients)) f (ClientIndex ci) = modifyElem clients (\c -> c{client' = f $ client' c}) ci
+
+moveClientInRooms :: MRoomsAndClients r c -> RoomIndex -> RoomIndex -> ClientIndex -> IO ()
+moveClientInRooms (MRoomsAndClients (rooms, clients)) (RoomIndex riFrom) rt@(RoomIndex riTo) cl@(ClientIndex ci) = do
+    modifyElem rooms (roomRemoveClient cl) riFrom
+    modifyElem rooms (roomAddClient cl) riTo
+    modifyElem clients (\c -> c{clientRoom' = rt}) ci
+
+
+moveClientToLobby :: MRoomsAndClients r c -> ClientIndex -> IO ()
+moveClientToLobby rnc ci = do
+    room <- clientRoomM rnc ci
+    moveClientInRooms rnc room lobbyId ci
+
+
+moveClientToRoom :: MRoomsAndClients r c -> RoomIndex -> ClientIndex -> IO ()
+moveClientToRoom rnc ri ci = moveClientInRooms rnc lobbyId ri ci
+
+
+clientExists :: MRoomsAndClients r c -> ClientIndex -> IO Bool
+clientExists (MRoomsAndClients (_, clients)) (ClientIndex ci) = elemExists clients ci
+
+clientRoomM :: MRoomsAndClients r c -> ClientIndex -> IO RoomIndex
+clientRoomM (MRoomsAndClients (_, clients)) (ClientIndex ci) = liftM clientRoom' (clients `readElem` ci)
+
+client'sM :: MRoomsAndClients r c -> (c -> a) -> ClientIndex -> IO a
+client'sM (MRoomsAndClients (_, clients)) f (ClientIndex ci) = liftM (f . client') (clients `readElem` ci)
+
+room'sM :: MRoomsAndClients r c -> (r -> a) -> RoomIndex -> IO a
+room'sM (MRoomsAndClients (rooms, _)) f (RoomIndex ri) = liftM (f . room') (rooms `readElem` ri)
+
+allClientsM :: MRoomsAndClients r c -> IO [ClientIndex]
+allClientsM (MRoomsAndClients (_, clients)) = liftM (map ClientIndex) $ indicesM clients
+
+clientsM :: MRoomsAndClients r c -> IO [c]
+clientsM (MRoomsAndClients (_, clients)) = indicesM clients >>= mapM (\ci -> liftM client' $ readElem clients ci)
+
+roomClientsIndicesM :: MRoomsAndClients r c -> RoomIndex -> IO [ClientIndex]
+roomClientsIndicesM (MRoomsAndClients (rooms, clients)) (RoomIndex ri) = liftM roomClients' (rooms `readElem` ri)
+
+roomClientsM :: MRoomsAndClients r c -> RoomIndex -> IO [c]
+roomClientsM (MRoomsAndClients (rooms, clients)) (RoomIndex ri) = liftM roomClients' (rooms `readElem` ri) >>= mapM (\(ClientIndex ci) -> liftM client' $ readElem clients ci)
+
+withRoomsAndClients :: MRoomsAndClients r c -> (IRoomsAndClients r c -> a) -> IO a
+withRoomsAndClients (MRoomsAndClients (rooms, clients)) f =
+    withIStore2 rooms clients (\r c -> f $ IRoomsAndClients (r, c))
+
+----------------------------------------
+----------- IRoomsAndClients -----------
+
+showRooms :: (Show r, Show c) => IRoomsAndClients r c -> String
+showRooms rnc@(IRoomsAndClients (rooms, clients)) = concatMap showRoom (allRooms rnc)
+    where
+    showRoom r = unlines $ ((show r) ++ ": " ++ (show $ room' $ rooms ! (unRoomIndex r))) : (map showClient (roomClients' $ rooms ! (unRoomIndex r)))
+    showClient c = "    " ++ (show c) ++ ": " ++ (show $ client' $ clients ! (unClientIndex c))
+
+
+allRooms :: IRoomsAndClients r c -> [RoomIndex]
+allRooms (IRoomsAndClients (rooms, _)) = map RoomIndex $ indices rooms
+
+allClients :: IRoomsAndClients r c -> [ClientIndex]
+allClients (IRoomsAndClients (_, clients)) = map ClientIndex $ indices clients
+
+clientRoom :: IRoomsAndClients r c -> ClientIndex -> RoomIndex
+clientRoom (IRoomsAndClients (_, clients)) (ClientIndex ci) = clientRoom' (clients ! ci)
+
+client :: IRoomsAndClients r c -> ClientIndex -> c
+client (IRoomsAndClients (_, clients)) (ClientIndex ci) = client' (clients ! ci)
+
+room :: IRoomsAndClients r c -> RoomIndex -> r
+room (IRoomsAndClients (rooms, _)) (RoomIndex ri) = room' (rooms ! ri)
+
+roomClients :: IRoomsAndClients r c -> RoomIndex -> [ClientIndex]
+roomClients (IRoomsAndClients (rooms, _)) (RoomIndex ri) = roomClients' $ (rooms ! ri)
--- a/gameServer/Store.hs	Fri Aug 20 11:52:30 2010 -0400
+++ b/gameServer/Store.hs	Fri Aug 20 11:54:14 2010 -0400
@@ -1,145 +1,145 @@
-module Store(
-    ElemIndex(),
-    MStore(),
-    IStore(),
-    newStore,
-    addElem,
-    removeElem,
-    readElem,
-    writeElem,
-    modifyElem,
-    elemExists,
-    firstIndex,
-    indicesM,
-    withIStore,
-    withIStore2,
-    (!),
-    indices
-    ) where
-
-import qualified Data.Array.IArray as IA
-import qualified Data.Array.IO as IOA
-import qualified Data.IntSet as IntSet
-import Data.IORef
-import Control.Monad
-
-
-newtype ElemIndex = ElemIndex Int
-    deriving (Eq, Show, Read, Ord)
-newtype MStore e = MStore (IORef (IntSet.IntSet, IntSet.IntSet, IOA.IOArray Int e))
-newtype IStore e = IStore (IntSet.IntSet, IA.Array Int e)
-
-
-firstIndex :: ElemIndex
-firstIndex = ElemIndex 0
-
--- MStore code
-initialSize :: Int
-initialSize = 10
-
-
-growFunc :: Int -> Int
-growFunc a = a * 3 `div` 2
-
-
-newStore :: IO (MStore e)
-newStore = do
-    newar <- IOA.newArray_ (0, initialSize - 1)
-    new <- newIORef (IntSet.empty, IntSet.fromAscList [0..initialSize - 1], newar)
-    return (MStore new)
-
-
-growStore :: MStore e -> IO ()
-growStore (MStore ref) = do
-    (busyElems, freeElems, arr) <- readIORef ref
-    (_, m') <- IOA.getBounds arr
-    let newM' = growFunc (m' + 1) - 1
-    newArr <- IOA.newArray_ (0, newM')
-    sequence_ [IOA.readArray arr i >>= IOA.writeArray newArr i | i <- [0..m']]
-    writeIORef ref (busyElems, freeElems `IntSet.union` (IntSet.fromAscList [m'+1..newM']), newArr)
-
-
-growIfNeeded :: MStore e -> IO ()
-growIfNeeded m@(MStore ref) = do
-    (_, freeElems, _) <- readIORef ref
-    when (IntSet.null freeElems) $ growStore m
-
-
-addElem :: MStore e -> e -> IO ElemIndex
-addElem m@(MStore ref) element = do
-    growIfNeeded m
-    (busyElems, freeElems, arr) <- readIORef ref
-    let (n, freeElems') = IntSet.deleteFindMin freeElems
-    IOA.writeArray arr n element
-    writeIORef ref (IntSet.insert n busyElems, freeElems', arr)
-    return $ ElemIndex n
-
-
-removeElem :: MStore e -> ElemIndex -> IO ()
-removeElem (MStore ref) (ElemIndex n) = do
-    (busyElems, freeElems, arr) <- readIORef ref
-    IOA.writeArray arr n (error $ "Store: no element " ++ show n)
-    writeIORef ref (IntSet.delete n busyElems, IntSet.insert n freeElems, arr)
-
-
-readElem :: MStore e -> ElemIndex -> IO e
-readElem (MStore ref) (ElemIndex n) = readIORef ref >>= \(_, _, arr) -> IOA.readArray arr n
-
-
-writeElem :: MStore e -> ElemIndex -> e -> IO ()
-writeElem (MStore ref) (ElemIndex n) el = readIORef ref >>= \(_, _, arr) -> IOA.writeArray arr n el
-
-
-modifyElem :: MStore e -> (e -> e) -> ElemIndex -> IO ()
-modifyElem (MStore ref) f (ElemIndex n) = do
-    (_, _, arr) <- readIORef ref
-    IOA.readArray arr n >>= (IOA.writeArray arr n) . f
-
-elemExists :: MStore e -> ElemIndex -> IO Bool
-elemExists (MStore ref) (ElemIndex n) = do
-    (_, free, _) <- readIORef ref
-    return $ n `IntSet.notMember` free
-
-indicesM :: MStore e -> IO [ElemIndex]
-indicesM (MStore ref) = do
-    (busy, _, _) <- readIORef ref
-    return $ map ElemIndex $ IntSet.toList busy
-
-
--- A way to see MStore elements in pure code via IStore
-m2i :: MStore e -> IO (IStore e)
-m2i (MStore ref) = do
-    (a, _, c') <- readIORef ref
-    c <- IOA.unsafeFreeze c'
-    return $ IStore (a, c)
-
-i2m :: (MStore e) -> IStore e -> IO ()
-i2m (MStore ref) (IStore (_, arr)) = do
-    (b, e, _) <- readIORef ref
-    a <- IOA.unsafeThaw arr
-    writeIORef ref (b, e, a)
-
-withIStore :: MStore e -> (IStore e -> a) -> IO a
-withIStore m f = do
-    i <- m2i m
-    let res = f i
-    res `seq` i2m m i
-    return res
-
-
-withIStore2 :: MStore e1 -> MStore e2 -> (IStore e1 -> IStore e2 -> a) -> IO a
-withIStore2 m1 m2 f = do
-    i1 <- m2i m1
-    i2 <- m2i m2
-    let res = f i1 i2
-    res `seq` i2m m1 i1
-    i2m m2 i2
-    return res
-
-
--- IStore code
-(!) :: IStore e -> ElemIndex -> e
-(!) (IStore (_, arr)) (ElemIndex i) = (IA.!) arr i
-
-indices :: IStore e -> [ElemIndex]
-indices (IStore (busy, _)) = map ElemIndex $ IntSet.toList busy
+module Store(
+    ElemIndex(),
+    MStore(),
+    IStore(),
+    newStore,
+    addElem,
+    removeElem,
+    readElem,
+    writeElem,
+    modifyElem,
+    elemExists,
+    firstIndex,
+    indicesM,
+    withIStore,
+    withIStore2,
+    (!),
+    indices
+    ) where
+
+import qualified Data.Array.IArray as IA
+import qualified Data.Array.IO as IOA
+import qualified Data.IntSet as IntSet
+import Data.IORef
+import Control.Monad
+
+
+newtype ElemIndex = ElemIndex Int
+    deriving (Eq, Show, Read, Ord)
+newtype MStore e = MStore (IORef (IntSet.IntSet, IntSet.IntSet, IOA.IOArray Int e))
+newtype IStore e = IStore (IntSet.IntSet, IA.Array Int e)
+
+
+firstIndex :: ElemIndex
+firstIndex = ElemIndex 0
+
+-- MStore code
+initialSize :: Int
+initialSize = 10
+
+
+growFunc :: Int -> Int
+growFunc a = a * 3 `div` 2
+
+
+newStore :: IO (MStore e)
+newStore = do
+    newar <- IOA.newArray_ (0, initialSize - 1)
+    new <- newIORef (IntSet.empty, IntSet.fromAscList [0..initialSize - 1], newar)
+    return (MStore new)
+
+
+growStore :: MStore e -> IO ()
+growStore (MStore ref) = do
+    (busyElems, freeElems, arr) <- readIORef ref
+    (_, m') <- IOA.getBounds arr
+    let newM' = growFunc (m' + 1) - 1
+    newArr <- IOA.newArray_ (0, newM')
+    sequence_ [IOA.readArray arr i >>= IOA.writeArray newArr i | i <- [0..m']]
+    writeIORef ref (busyElems, freeElems `IntSet.union` (IntSet.fromAscList [m'+1..newM']), newArr)
+
+
+growIfNeeded :: MStore e -> IO ()
+growIfNeeded m@(MStore ref) = do
+    (_, freeElems, _) <- readIORef ref
+    when (IntSet.null freeElems) $ growStore m
+
+
+addElem :: MStore e -> e -> IO ElemIndex
+addElem m@(MStore ref) element = do
+    growIfNeeded m
+    (busyElems, freeElems, arr) <- readIORef ref
+    let (n, freeElems') = IntSet.deleteFindMin freeElems
+    IOA.writeArray arr n element
+    writeIORef ref (IntSet.insert n busyElems, freeElems', arr)
+    return $ ElemIndex n
+
+
+removeElem :: MStore e -> ElemIndex -> IO ()
+removeElem (MStore ref) (ElemIndex n) = do
+    (busyElems, freeElems, arr) <- readIORef ref
+    IOA.writeArray arr n (error $ "Store: no element " ++ show n)
+    writeIORef ref (IntSet.delete n busyElems, IntSet.insert n freeElems, arr)
+
+
+readElem :: MStore e -> ElemIndex -> IO e
+readElem (MStore ref) (ElemIndex n) = readIORef ref >>= \(_, _, arr) -> IOA.readArray arr n
+
+
+writeElem :: MStore e -> ElemIndex -> e -> IO ()
+writeElem (MStore ref) (ElemIndex n) el = readIORef ref >>= \(_, _, arr) -> IOA.writeArray arr n el
+
+
+modifyElem :: MStore e -> (e -> e) -> ElemIndex -> IO ()
+modifyElem (MStore ref) f (ElemIndex n) = do
+    (_, _, arr) <- readIORef ref
+    IOA.readArray arr n >>= (IOA.writeArray arr n) . f
+
+elemExists :: MStore e -> ElemIndex -> IO Bool
+elemExists (MStore ref) (ElemIndex n) = do
+    (_, free, _) <- readIORef ref
+    return $ n `IntSet.notMember` free
+
+indicesM :: MStore e -> IO [ElemIndex]
+indicesM (MStore ref) = do
+    (busy, _, _) <- readIORef ref
+    return $ map ElemIndex $ IntSet.toList busy
+
+
+-- A way to see MStore elements in pure code via IStore
+m2i :: MStore e -> IO (IStore e)
+m2i (MStore ref) = do
+    (a, _, c') <- readIORef ref
+    c <- IOA.unsafeFreeze c'
+    return $ IStore (a, c)
+
+i2m :: (MStore e) -> IStore e -> IO ()
+i2m (MStore ref) (IStore (_, arr)) = do
+    (b, e, _) <- readIORef ref
+    a <- IOA.unsafeThaw arr
+    writeIORef ref (b, e, a)
+
+withIStore :: MStore e -> (IStore e -> a) -> IO a
+withIStore m f = do
+    i <- m2i m
+    let res = f i
+    res `seq` i2m m i
+    return res
+
+
+withIStore2 :: MStore e1 -> MStore e2 -> (IStore e1 -> IStore e2 -> a) -> IO a
+withIStore2 m1 m2 f = do
+    i1 <- m2i m1
+    i2 <- m2i m2
+    let res = f i1 i2
+    res `seq` i2m m1 i1
+    i2m m2 i2
+    return res
+
+
+-- IStore code
+(!) :: IStore e -> ElemIndex -> e
+(!) (IStore (_, arr)) (ElemIndex i) = (IA.!) arr i
+
+indices :: IStore e -> [ElemIndex]
+indices (IStore (busy, _)) = map ElemIndex $ IntSet.toList busy
--- a/share/hedgewars/Data/Maps/FlightJoust/map.cfg	Fri Aug 20 11:52:30 2010 -0400
+++ b/share/hedgewars/Data/Maps/FlightJoust/map.cfg	Fri Aug 20 11:54:14 2010 -0400
@@ -1,2 +1,2 @@
-Nature
+Nature
 4
\ No newline at end of file
--- a/share/hedgewars/Data/Themes/Art/theme.cfg	Fri Aug 20 11:52:30 2010 -0400
+++ b/share/hedgewars/Data/Themes/Art/theme.cfg	Fri Aug 20 11:54:14 2010 -0400
@@ -1,18 +1,18 @@
-7 13 40
-13 17 22
-$01 $3b $66
-$01 $3b $66 $80
-Art.ogg
-0
-4
-Soup
-3 3 220 130 18 1 0 0 142 150
-Mona
-2 0 190 191 8 1 0 0 191  150
-Schrei
-1 0 345 130 1 1 0 0 160 175
-Zeit
-2 0 153 45 5 1 90 20 106 105
-0
-0
-30 0 0 0
+7 13 40
+13 17 22
+$01 $3b $66
+$01 $3b $66 $80
+Art.ogg
+0
+4
+Soup
+3 3 220 130 18 1 0 0 142 150
+Mona
+2 0 190 191 8 1 0 0 191  150
+Schrei
+1 0 345 130 1 1 0 0 160 175
+Zeit
+2 0 153 45 5 1 90 20 106 105
+0
+0
+30 0 0 0
--- a/share/hedgewars/Data/Themes/Stage/theme.cfg	Fri Aug 20 11:52:30 2010 -0400
+++ b/share/hedgewars/Data/Themes/Stage/theme.cfg	Fri Aug 20 11:54:14 2010 -0400
@@ -1,30 +1,30 @@
-0 0 0
-106 106 106
-72 105 127
-37 76 91 128
-Rock.ogg
-0
-6
-MicR
-1 0 28 7 24 1 25 0 125 52
-MicL
-1 145 27 5 25 1 0 0 110 52
-Bass
-1 243 373 20 5 1 0 0 330 310
-Light
-1 10 0 65 10 1 0 42 140 122
-Box
-1 0 170 150 8 1 0 0 150 145
-drum
-1 0 202 239 4 1 39 0 200 150
-4
-poster1
-2
-poster2
-2
-poster3
-2
-poster4
-2
-100
-3 99999999 10 20
+0 0 0
+106 106 106
+72 105 127
+37 76 91 128
+Rock.ogg
+0
+6
+MicR
+1 0 28 7 24 1 25 0 125 52
+MicL
+1 145 27 5 25 1 0 0 110 52
+Bass
+1 243 373 20 5 1 0 0 330 310
+Light
+1 10 0 65 10 1 0 42 140 122
+Box
+1 0 170 150 8 1 0 0 150 145
+drum
+1 0 202 239 4 1 39 0 200 150
+4
+poster1
+2
+poster2
+2
+poster3
+2
+poster4
+2
+100
+3 99999999 10 20