merge
authornemo
Mon, 14 Feb 2011 08:31:45 -0500
changeset 4940 e247addb947c
parent 4939 6d512ba87f72 (diff)
parent 4919 2ba6a2315838 (current diff)
child 4941 90572c338e60
merge
--- a/QTfrontend/drawmapscene.cpp	Sat Feb 05 15:36:02 2011 +0100
+++ b/QTfrontend/drawmapscene.cpp	Mon Feb 14 08:31:45 2011 -0500
@@ -1,6 +1,7 @@
 #include <QGraphicsSceneMouseEvent>
 #include <QGraphicsPathItem>
 #include <QtEndian>
+#include <QDebug>
 
 #include "drawmapscene.h"
 
@@ -32,8 +33,18 @@
     if(m_currPath && (mouseEvent->buttons() & Qt::LeftButton))
     {
         QPainterPath path = m_currPath->path();
-        path.lineTo(mouseEvent->scenePos());
-        paths.first().append(mouseEvent->scenePos().toPoint());
+
+        if(mouseEvent->modifiers() & Qt::ControlModifier)
+        {
+            int c = path.elementCount();
+            QPointF pos = mouseEvent->scenePos();
+            path.setElementPositionAt(c - 1, pos.x(), pos.y());
+
+        } else
+        {
+            path.lineTo(mouseEvent->scenePos());
+            paths.first().append(mouseEvent->scenePos().toPoint());
+        }
         m_currPath->setPath(path);
 
         emit pathChanged();
--- a/QTfrontend/gamecfgwidget.cpp	Sat Feb 05 15:36:02 2011 +0100
+++ b/QTfrontend/gamecfgwidget.cpp	Mon Feb 14 08:31:45 2011 -0500
@@ -33,7 +33,9 @@
 #include "proto.h"
 
 GameCFGWidget::GameCFGWidget(QWidget* parent) :
-  QGroupBox(parent), mainLayout(this)
+  QGroupBox(parent)
+  , mainLayout(this)
+  , seedRegexp("\\{[0-9a-f]{8}-[0-9a-f]{4}-[0-9a-f]{4}-[0-9a-f]{4}-[0-9a-f]{12}\\}")
 {
     mainLayout.setMargin(0);
 //  mainLayout.setSizeConstraint(QLayout::SetMinimumSize);
@@ -332,7 +334,7 @@
         }
         if (param == "SEED") {
             pMapContainer->setSeed(value);
-            if (!QRegExp("\\{[0-9a-f]{8}-[0-9a-f]{4}-[0-9a-f]{4}-[0-9a-f]{4}-[0-9a-f]{12}\\}").exactMatch(value)) {
+            if (!seedRegexp.exactMatch(value)) {
                 pMapContainer->seedEdit->setVisible(true);
                 }
             return;
@@ -371,6 +373,19 @@
         }
     }
 
+    if (slValue.size() == 3)
+    {
+        if (param == "FULLGENCFG")
+        {
+            QString seed = slValue[2];
+            if (!seedRegexp.exactMatch(seed))
+                pMapContainer->seedEdit->setVisible(true);
+
+            pMapContainer->setMapMapgenSeed(slValue[0], (MapGenerator)slValue[1].toUInt(), seed);
+            return;
+        }
+    }
+
     qWarning("Got bad config param from net");
 }
 
--- a/QTfrontend/gamecfgwidget.h	Sat Feb 05 15:36:02 2011 +0100
+++ b/QTfrontend/gamecfgwidget.h	Mon Feb 14 08:31:45 2011 -0500
@@ -23,6 +23,7 @@
 #include <QStringList>
 #include <QGroupBox>
 #include <QSpinBox>
+#include <QRegExp>
 
 #include "mapContainer.h"
 
@@ -77,6 +78,7 @@
     QCheckBox * bindEntries;
     QString curNetAmmoName;
     QString curNetAmmo;
+    QRegExp seedRegexp;
 
     void setNetAmmo(const QString& name, const QString& ammo);
 
--- a/QTfrontend/mapContainer.cpp	Sat Feb 05 15:36:02 2011 +0100
+++ b/QTfrontend/mapContainer.cpp	Mon Feb 14 08:31:45 2011 -0500
@@ -425,16 +425,21 @@
   //imageButt->setIconSize(imageButt->size());
 }
 
-void HWMapContainer::setSeed(const QString & seed)
+void HWMapContainer::intSetSeed(const QString & seed)
 {
     m_seed = seed;
     if (seed != seedEdit->text())
         seedEdit->setText(seed);
+}
+
+void HWMapContainer::setSeed(const QString & seed)
+{
+    intSetSeed(seed);
     if (chooseMap->currentIndex() < MAPGEN_MAP)
         updatePreview();
 }
 
-void HWMapContainer::setMap(const QString & map)
+void HWMapContainer::intSetMap(const QString & map)
 {
     int id = 0;
     for(int i = 0; i < chooseMap->count(); i++)
@@ -452,10 +457,15 @@
             pMap = 0;
         }
         chooseMap->setCurrentIndex(id);
-        updatePreview();
     }
 }
 
+void HWMapContainer::setMap(const QString &map)
+{
+    intSetMap(map);
+    updatePreview();
+}
+
 void HWMapContainer::setTheme(const QString & theme)
 {
     QList<QListWidgetItem *> items = lwThemes->findItems(theme, Qt::MatchExactly);
@@ -543,11 +553,16 @@
     updatePreview();
 }
 
-void HWMapContainer::setMapgen(MapGenerator m)
+void HWMapContainer::intSetMapgen(MapGenerator m)
 {
     mapgen = m;
     chooseMap->setCurrentIndex(m);
     emit mapgenChanged(m);
+}
+
+void HWMapContainer::setMapgen(MapGenerator m)
+{
+    intSetMapgen(m);
     updatePreview();
 }
 
@@ -620,3 +635,12 @@
         addInfoToPreview(mapImage);
     }
 }
+
+void HWMapContainer::setMapMapgenSeed(const QString & map, MapGenerator m, const QString & seed)
+{
+    setMap(map);
+    setMapgen(m);
+    setSeed(seed);
+
+    updatePreview();
+}
--- a/QTfrontend/mapContainer.h	Sat Feb 05 15:36:02 2011 +0100
+++ b/QTfrontend/mapContainer.h	Mon Feb 14 08:31:45 2011 -0500
@@ -67,6 +67,7 @@
   void setMapgen(MapGenerator m);
   void setMaze_size(int size);
   void setDrawnMapData(const QByteArray & ar);
+  void setMapMapgenSeed(const QString & map, MapGenerator m, const QString & seed);
 
  signals:
   void seedChanged(const QString & seed);
@@ -116,6 +117,9 @@
   int numMissions;
   DrawMapScene drawMapScene;
 
+  void intSetSeed(const QString & seed);
+  void intSetMap(const QString & map);
+  void intSetMapgen(MapGenerator m);
   void updatePreview();
 };
 
--- a/gameServer/Actions.hs	Sat Feb 05 15:36:02 2011 +0100
+++ b/gameServer/Actions.hs	Mon Feb 14 08:31:45 2011 -0500
@@ -2,8 +2,6 @@
 module Actions where
 
 import Control.Concurrent
-import Control.Concurrent.Chan
-import qualified Data.IntSet as IntSet
 import qualified Data.Set as Set
 import qualified Data.Sequence as Seq
 import System.Log.Logger
@@ -14,9 +12,8 @@
 import Control.Monad.State.Strict
 import qualified Data.ByteString.Char8 as B
 import Control.DeepSeq
-import Data.Time
-import Text.Printf
 import Data.Unique
+import Control.Arrow
 -----------------------------
 import CoreTypes
 import Utils
@@ -65,6 +62,8 @@
 instance NFData B.ByteString
 instance NFData (Chan a)
 
+
+othersChans :: StateT ServerState IO [ClientChan]
 othersChans = do
     cl <- client's id
     ri <- clientRoomA
@@ -73,8 +72,8 @@
 processAction :: Action -> StateT ServerState IO ()
 
 
-processAction (AnswerClients chans msg) = do
-    io $ mapM_ (flip writeChan (msg `deepseq` msg)) (chans `deepseq` chans)
+processAction (AnswerClients chans msg) =
+    io $ mapM_ (`writeChan` (msg `deepseq` msg)) (chans `deepseq` chans)
 
 
 processAction SendServerMessage = do
@@ -115,7 +114,6 @@
 
 processAction (ByeClient msg) = do
     (Just ci) <- gets clientIndex
-    rnc <- gets roomsClients
     ri <- clientRoomA
 
     chan <- client's sendChan
@@ -126,8 +124,8 @@
         return ()
 
     clientsChans <- liftM (Prelude.map sendChan . Prelude.filter logonPassed) $! allClientsS
-    io $ do
-        infoM "Clients" (show ci ++ " quits: " ++ (B.unpack msg))
+    io $
+        infoM "Clients" (show ci ++ " quits: " ++ B.unpack msg)
 
     processAction $ AnswerClients [chan] ["BYE", msg]
     processAction $ AnswerClients clientsChans ["LOBBY:LEFT", clNick, msg]
@@ -171,7 +169,7 @@
 
     io $ do
         modifyClient rnc (\cl -> cl{teamsInGame = 0, isReady = False, isMaster = False}) ci
-        modifyRoom rnc (\r -> r{playersIn = (playersIn r) + 1}) ri
+        modifyRoom rnc (\r -> r{playersIn = playersIn r + 1}) ri
         moveClientToRoom rnc ri ci
 
     chans <- liftM (map sendChan) $ roomClientsS ri
@@ -184,7 +182,7 @@
     (Just ci) <- gets clientIndex
     ri <- clientRoomA
     rnc <- gets roomsClients
-    (gameProgress, playersNum) <- io $ room'sM rnc (\r -> (gameinprogress r, playersIn r)) ri
+    (gameProgress, playersNum) <- io $ room'sM rnc (gameinprogress &&& playersIn) ri
     ready <- client's isReady
     master <- client's isMaster
 --    client <- client's id
@@ -201,7 +199,7 @@
 
     io $ do
             modifyRoom rnc (\r -> r{
-                    playersIn = (playersIn r) - 1,
+                    playersIn = playersIn r - 1,
                     readyPlayers = if ready then readyPlayers r - 1 else readyPlayers r
                     }) ri
             moveClientToLobby rnc ci
@@ -223,14 +221,14 @@
     rnc <- gets roomsClients
     proto <- io $ client'sM rnc clientProto clId
 
-    let room = newRoom{
+    let rm = newRoom{
             masterID = clId,
             name = roomName,
             password = roomPassword,
             roomProto = proto
             }
 
-    rId <- io $ addRoom rnc room
+    rId <- io $ addRoom rnc rm
 
     processAction $ MoveToRoom rId
 
@@ -270,7 +268,6 @@
 
 processAction (RemoveTeam teamName) = do
     rnc <- gets roomsClients
-    cl <- client's id
     ri <- clientRoomA
     inGame <- io $ room'sM rnc gameinprogress ri
     chans <- othersChans
@@ -289,7 +286,7 @@
                     })
                 ]
     where
-        rmTeamMsg = toEngineMsg $ (B.singleton 'F') `B.append` teamName
+        rmTeamMsg = toEngineMsg $ B.singleton 'F' `B.append` teamName
 
 
 processAction (RemoveClientTeams clId) = do
@@ -325,11 +322,11 @@
     case info of
         HasAccount passwd isAdmin -> do
             chan <- client's sendChan
-            processAction $ AnswerClients [chan] ["ASKPASSWORD"]
-        Guest -> do
+            mapM_ processAction [AnswerClients [chan] ["ASKPASSWORD"], ModifyClient (\c -> c{webPassword = passwd, isAdministrator = isAdmin})]
+        Guest ->
             processAction JoinLobby
         Admin -> do
-            mapM processAction [ModifyClient (\cl -> cl{isAdministrator = True}), JoinLobby]
+            mapM_ processAction [ModifyClient (\cl -> cl{isAdministrator = True}), JoinLobby]
             chan <- client's sendChan
             processAction $ AnswerClients [chan] ["ADMIN_ACCESS"]
 
@@ -337,11 +334,11 @@
 processAction JoinLobby = do
     chan <- client's sendChan
     clientNick <- client's nick
-    (lobbyNicks, clientsChans) <- liftM (unzip . Prelude.map (\c -> (nick c, sendChan c)) . Prelude.filter logonPassed) $! allClientsS
+    (lobbyNicks, clientsChans) <- liftM (unzip . Prelude.map (nick &&& sendChan) . Prelude.filter logonPassed) $! allClientsS
     mapM_ processAction $
-        (AnswerClients clientsChans ["LOBBY:JOINED", clientNick])
-        : [AnswerClients [chan] ("LOBBY:JOINED" : clientNick : lobbyNicks)]
-        ++ [ModifyClient (\cl -> cl{logonPassed = True}), SendServerMessage]
+        AnswerClients clientsChans ["LOBBY:JOINED", clientNick]
+        : AnswerClients [chan] ("LOBBY:JOINED" : clientNick : lobbyNicks)
+        : [ModifyClient (\cl -> cl{logonPassed = True}), SendServerMessage]
 
 {-
 processAction (clID, serverInfo, rnc) (RoomAddThisClient rID) =
@@ -367,10 +364,10 @@
 processAction (BanClient seconds reason banId) = do
     modify (\s -> s{clientIndex = Just banId})
     clHost <- client's host
-    currentTime <- io $ getCurrentTime
-    let msg = "Ban for " `B.append` (B.pack . show $ seconds) `B.append` "seconds (" `B.append` msg` B.append` ")"
+    currentTime <- io getCurrentTime
+    let msg = "Ban for " `B.append` (B.pack . show $ seconds) `B.append` "seconds (" `B.append` reason ` B.append` ")"
     mapM_ processAction [
-        ModifyServerInfo (\s -> s{lastLogins = (clHost, (addUTCTime seconds $ currentTime, msg)) : lastLogins s})
+        ModifyServerInfo (\s -> s{lastLogins = (clHost, (addUTCTime seconds currentTime, msg)) : lastLogins s})
         , KickClient banId
         ]
 
@@ -387,7 +384,7 @@
     newClId <- io $ do
         ci <- addClient rnc cl
         t <- forkIO $ clientRecvLoop (clientSocket cl) (coreChan si) ci
-        forkIO $ clientSendLoop (clientSocket cl) t (coreChan si) (sendChan cl) ci
+        _ <- forkIO $ clientSendLoop (clientSocket cl) t (coreChan si) (sendChan cl) ci
 
         infoM "Clients" (show ci ++ ": New client. Time: " ++ show (connectTime cl))
 
@@ -396,8 +393,7 @@
     modify (\s -> s{clientIndex = Just newClId})
     processAction $ AnswerClients [sendChan cl] ["CONNECTED", "Hedgewars server http://www.hedgewars.org/"]
 
-    si <- gets serverInfo
-    let newLogins = takeWhile (\(_ , (time, _)) -> (connectTime cl) `diffUTCTime` time <= 0) $ lastLogins si
+    let newLogins = takeWhile (\(_ , (time, _)) -> connectTime cl `diffUTCTime` time <= 0) $ lastLogins si
     let info = host cl `Prelude.lookup` newLogins
     if isJust info then
         mapM_ processAction [ModifyServerInfo (\s -> s{lastLogins = newLogins}), ByeClient (snd .  fromJust $ info)]
@@ -423,10 +419,10 @@
 processAction StatsAction = do
     rnc <- gets roomsClients
     si <- gets serverInfo
-    (roomsNum, clientsNum) <- io $ withRoomsAndClients rnc stats
+    (roomsNum, clientsNum) <- io $ withRoomsAndClients rnc st
     io $ writeChan (dbQueries si) $ SendStats clientsNum (roomsNum - 1)
     where
-          stats irnc = (length $ allRooms irnc, length $ allClients irnc)
+          st irnc = (length $ allRooms irnc, length $ allClients irnc)
 
-processAction (RestartServer useForce) = do
+processAction (RestartServer _) =
     return ()
\ No newline at end of file
--- a/gameServer/ClientIO.hs	Sat Feb 05 15:36:02 2011 +0100
+++ b/gameServer/ClientIO.hs	Mon Feb 14 08:31:45 2011 -0500
@@ -5,7 +5,6 @@
 import Control.Concurrent.Chan
 import Control.Concurrent
 import Control.Monad
-import System.IO
 import Network
 import Network.Socket.ByteString
 import qualified Data.ByteString.Char8 as B
@@ -19,10 +18,10 @@
 pDelim = B.pack "\n\n"
 
 bs2Packets :: B.ByteString -> ([[B.ByteString]], B.ByteString)
-bs2Packets buf = unfoldrE extractPackets buf
+bs2Packets = unfoldrE extractPackets
     where
     extractPackets :: B.ByteString -> Either B.ByteString ([B.ByteString], B.ByteString)
-    extractPackets buf = 
+    extractPackets buf =
         let buf' = until (not . B.isPrefixOf pDelim) (B.drop 2) buf in
             let (bsPacket, bufTail) = B.breakSubstring pDelim buf' in
                 if B.null bufTail then
@@ -58,23 +57,23 @@
 
 
 clientSendLoop :: Socket -> ThreadId -> Chan CoreMessage -> Chan [B.ByteString] -> ClientIndex -> IO ()
-clientSendLoop s tId coreChan chan ci = do
+clientSendLoop s tId cChan chan ci = do
     answer <- readChan chan
     Exception.handle
-        (\(e :: Exception.IOException) -> when (not $ isQuit answer) $ sendQuit e) $ do
-            sendAll s $ (B.unlines answer) `B.append` (B.singleton '\n')
+        (\(e :: Exception.IOException) -> unless (isQuit answer) $ sendQuit e) $
+            sendAll s $ B.unlines answer `B.append` B.singleton '\n'
 
-    if (isQuit answer) then
+    if isQuit answer then
         do
         Exception.handle (\(_ :: Exception.IOException) -> putStrLn "error on sClose") $ sClose s
         killThread tId
-        writeChan coreChan $ Remove ci
+        writeChan cChan $ Remove ci
         else
-        clientSendLoop s tId coreChan chan ci
+        clientSendLoop s tId cChan chan ci
 
     where
         sendQuit e = do
-            putStrLn $ show e
-            writeChan coreChan $ ClientMessage (ci, ["QUIT", B.pack $ show e])
-        isQuit ("BYE":xs) = True
+            print e
+            writeChan cChan $ ClientMessage (ci, ["QUIT", B.pack $ show e])
+        isQuit ("BYE":_) = True
         isQuit _ = False
--- a/gameServer/CoreTypes.hs	Sat Feb 05 15:36:02 2011 +0100
+++ b/gameServer/CoreTypes.hs	Mon Feb 14 08:31:45 2011 -0500
@@ -1,13 +1,10 @@
 {-# LANGUAGE OverloadedStrings #-}
 module CoreTypes where
 
-import System.IO
 import Control.Concurrent
-import Control.Concurrent.Chan
 import Control.Concurrent.STM
 import Data.Word
 import qualified Data.Map as Map
-import qualified Data.IntSet as IntSet
 import Data.Sequence(Seq, empty)
 import Data.Time
 import Network
@@ -41,7 +38,7 @@
     }
 
 instance Show ClientInfo where
-    show ci = " nick: " ++ (unpack $ nick ci) ++ " host: " ++ (unpack $ host ci)
+    show ci = " nick: " ++ unpack (nick ci) ++ " host: " ++ unpack (host ci)
 
 instance Eq ClientInfo where
     (==) = (==) `on` clientSocket
@@ -66,9 +63,9 @@
     }
 
 instance Show TeamInfo where
-    show ti = "owner: " ++ (unpack $ teamowner ti)
-            ++ "name: " ++ (unpack $ teamname ti)
-            ++ "color: " ++ (unpack $ teamcolor ti)
+    show ti = "owner: " ++ unpack (teamowner ti)
+            ++ "name: " ++ unpack (teamname ti)
+            ++ "color: " ++ unpack (teamcolor ti)
 
 data RoomInfo =
     RoomInfo
@@ -95,7 +92,7 @@
             ++ ", teams: " ++ show (teams ri)
 
 newRoom :: RoomInfo
-newRoom = (
+newRoom =
     RoomInfo
         undefined
         ""
@@ -111,7 +108,6 @@
         []
         []
         (Map.singleton "MAP" ["+rnd+"])
-    )
 
 data StatisticsInfo =
     StatisticsInfo
@@ -142,7 +138,7 @@
     show _ = "Server Info"
 
 newServerInfo :: TMVar StatisticsInfo -> Chan CoreMessage -> Chan DBQuery -> ServerInfo
-newServerInfo = (
+newServerInfo =
     ServerInfo
         True
         "<h2><p align=center><a href=\"http://www.hedgewars.org/\">http://www.hedgewars.org/</a></p></h2>"
@@ -154,7 +150,6 @@
         ""
         ""
         []
-    )
 
 data AccountInfo =
     HasAccount B.ByteString Bool
--- a/gameServer/HWProtoCore.hs	Sat Feb 05 15:36:02 2011 +0100
+++ b/gameServer/HWProtoCore.hs	Mon Feb 14 08:31:45 2011 -0500
@@ -50,7 +50,7 @@
     let clRoom = room rnc roomId
     let roomMasterSign = if isMaster cl then "@" else ""
     let adminSign = if isAdministrator cl then "@" else ""
-    let roomInfo = if roomId /= lobbyId then roomMasterSign `B.append` "room " `B.append` (name clRoom) else adminSign `B.append` "lobby"
+    let roomInfo = if roomId /= lobbyId then roomMasterSign `B.append` "room " `B.append` name clRoom else adminSign `B.append` "lobby"
     let roomStatus = if gameinprogress clRoom then
             if teamsInGame cl > 0 then "(playing)" else "(spectating)"
             else
--- a/gameServer/HWProtoInRoomState.hs	Sat Feb 05 15:36:02 2011 +0100
+++ b/gameServer/HWProtoInRoomState.hs	Mon Feb 14 08:31:45 2011 -0500
@@ -38,46 +38,46 @@
             else
             return [ProtocolError "Not room master"]
 
-handleCmd_inRoom ("ADD_TEAM" : name : color : grave : fort : voicepack : flag : difStr : hhsInfo)
+handleCmd_inRoom ("ADD_TEAM" : tName : color : grave : fort : voicepack : flag : difStr : hhsInfo)
     | length hhsInfo /= 16 = return [ProtocolError "Corrupted hedgehogs info"]
     | otherwise = do
-        (ci, rnc) <- ask
-        r <- thisRoom
+        (ci, _) <- ask
+        rm <- thisRoom
         clNick <- clientNick
         clChan <- thisClientChans
-        othersChans <- roomOthersChans
+        othChans <- roomOthersChans
         return $
-            if not . null . drop 5 $ teams r then
+            if not . null . drop 5 $ teams rm then
                 [Warning "too many teams"]
-            else if canAddNumber r <= 0 then
+            else if canAddNumber rm <= 0 then
                 [Warning "too many hedgehogs"]
-            else if isJust $ findTeam r then
+            else if isJust $ findTeam rm then
                 [Warning "There's already a team with same name in the list"]
-            else if gameinprogress r then
+            else if gameinprogress rm then
                 [Warning "round in progress"]
-            else if isRestrictedTeams r then
+            else if isRestrictedTeams rm then
                 [Warning "restricted"]
             else
                 [ModifyRoom (\r -> r{teams = teams r ++ [newTeam ci clNick r]}),
                 ModifyClient (\c -> c{teamsInGame = teamsInGame c + 1, clientClan = color}),
-                AnswerClients clChan ["TEAM_ACCEPTED", name],
-                AnswerClients othersChans $ teamToNet $ newTeam ci clNick r,
-                AnswerClients othersChans ["TEAM_COLOR", name, color]
+                AnswerClients clChan ["TEAM_ACCEPTED", tName],
+                AnswerClients othChans $ teamToNet $ newTeam ci clNick rm,
+                AnswerClients othChans ["TEAM_COLOR", tName, color]
                 ]
         where
         canAddNumber r = 48 - (sum . map hhnum $ teams r)
-        findTeam = find (\t -> name == teamname t) . teams
-        newTeam ci clNick r = (TeamInfo ci clNick name color grave fort voicepack flag difficulty (newTeamHHNum r) (hhsList hhsInfo))
-        difficulty = case B.readInt difStr of
-                           Just (i, t) | B.null t -> fromIntegral i
-                           otherwise -> 0
+        findTeam = find (\t -> tName == teamname t) . teams
+        newTeam ci clNick r = TeamInfo ci clNick tName color grave fort voicepack flag dif (newTeamHHNum r) (hhsList hhsInfo)
+        dif = case B.readInt difStr of
+                    Just (i, t) | B.null t -> fromIntegral i
+                    _ -> 0
         hhsList [] = []
         hhsList [_] = error "Hedgehogs list with odd elements number"
         hhsList (n:h:hhs) = HedgehogInfo n h : hhsList hhs
         newTeamHHNum r = min 4 (canAddNumber r)
 
-handleCmd_inRoom ["REMOVE_TEAM", name] = do
-        (ci, rnc) <- ask
+handleCmd_inRoom ["REMOVE_TEAM", tName] = do
+        (ci, _) <- ask
         r <- thisRoom
         clNick <- clientNick
 
@@ -90,7 +90,7 @@
             else if clNick /= teamowner team then
                 [ProtocolError "Not team owner!"]
             else
-                [RemoveTeam name,
+                [RemoveTeam tName,
                 ModifyClient
                     (\c -> c{
                         teamsInGame = teamsInGame c - 1,
@@ -99,7 +99,7 @@
                 ]
     where
         anotherTeamClan ci = teamcolor . fromJust . find (\t -> teamownerId t == ci) . teams
-        findTeam = find (\t -> name == teamname t) . teams
+        findTeam = find (\t -> tName == teamname t) . teams
 
 
 handleCmd_inRoom ["HH_NUM", teamName, numberStr] = do
@@ -113,7 +113,7 @@
     return $
         if not $ isMaster cl then
             [ProtocolError "Not room master"]
-        else if hhNumber < 1 || hhNumber > 8 || isNothing maybeTeam || hhNumber > (canAddNumber r) + (hhnum team) then
+        else if hhNumber < 1 || hhNumber > 8 || isNothing maybeTeam || hhNumber > canAddNumber r + hhnum team then
             []
         else
             [ModifyRoom $ modifyTeam team{hhnum = hhNumber},
@@ -121,7 +121,7 @@
     where
         hhNumber = case B.readInt numberStr of
                            Just (i, t) | B.null t -> fromIntegral i
-                           otherwise -> 0
+                           _ -> 0
         findTeam = find (\t -> teamName == teamname t) . teams
         canAddNumber = (-) 48 . sum . map hhnum . teams
 
@@ -159,11 +159,11 @@
 
 handleCmd_inRoom ["START_GAME"] = do
     cl <- thisClient
-    r <- thisRoom
+    rm <- thisRoom
     chans <- roomClientsChans
 
-    if isMaster cl && (playersIn r == readyPlayers r) && (not $ gameinprogress r) then
-        if enoughClans r then
+    if isMaster cl && playersIn rm == readyPlayers rm && not (gameinprogress rm) then
+        if enoughClans rm then
             return [
                 ModifyRoom
                     (\r -> r{
@@ -184,11 +184,11 @@
 
 handleCmd_inRoom ["EM", msg] = do
     cl <- thisClient
-    r <- thisRoom
+    rm <- thisRoom
     chans <- roomOthersChans
-    
-    if (teamsInGame cl > 0) && isLegal then
-        return $ (AnswerClients chans ["EM", msg]) : [ModifyRoom (\r -> r{roundMsgs = roundMsgs r |> msg}) | not isKeepAlive]
+
+    if teamsInGame cl > 0 && gameinprogress rm && isLegal then
+        return $ AnswerClients chans ["EM", msg] : [ModifyRoom (\r -> r{roundMsgs = roundMsgs r |> msg}) | not isKeepAlive]
         else
         return []
     where
@@ -197,20 +197,20 @@
 
 handleCmd_inRoom ["ROUNDFINISHED", _] = do
     cl <- thisClient
-    r <- thisRoom
+    rm <- thisRoom
     chans <- roomClientsChans
 
-    if isMaster cl && (gameinprogress r) then
-        return $ (ModifyRoom
+    if isMaster cl && gameinprogress rm then
+        return $ ModifyRoom
                 (\r -> r{
                     gameinprogress = False,
                     readyPlayers = 0,
                     roundMsgs = empty,
                     leftTeams = [],
                     teamsAtStart = []}
-                ))
+                )
             : UnreadyRoomClients
-            : answerRemovedTeams chans r
+            : answerRemovedTeams chans rm
         else
         return []
     where
@@ -239,7 +239,7 @@
     maybeClientId <- clientByNick kickNick
     master <- liftM isMaster thisClient
     let kickId = fromJust maybeClientId
-    let sameRoom = (clientRoom rnc thisClientId) == (clientRoom rnc kickId)
+    let sameRoom = clientRoom rnc thisClientId == clientRoom rnc kickId
     return
         [KickRoomClient kickId | master && isJust maybeClientId && (kickId /= thisClientId) && sameRoom]
 
@@ -249,6 +249,6 @@
     chans <- roomSameClanChans
     return [AnswerClients chans ["EM", engineMsg cl]]
     where
-        engineMsg cl = toEngineMsg $ "b" `B.append` (nick cl) `B.append` "(team): " `B.append` msg `B.append` "\x20\x20"
+        engineMsg cl = toEngineMsg $ "b" `B.append` nick cl `B.append` "(team): " `B.append` msg `B.append` "\x20\x20"
 
 handleCmd_inRoom _ = return [ProtocolError "Incorrect command (state: in room)"]
--- a/gameServer/HWProtoLobbyState.hs	Sat Feb 05 15:36:02 2011 +0100
+++ b/gameServer/HWProtoLobbyState.hs	Mon Feb 14 08:31:45 2011 -0500
@@ -2,14 +2,11 @@
 module HWProtoLobbyState where
 
 import qualified Data.Map as Map
-import qualified Data.IntSet as IntSet
 import qualified Data.Foldable as Foldable
 import Data.Maybe
 import Data.List
-import Data.Word
 import Control.Monad.Reader
 import qualified Data.ByteString.Char8 as B
-import Control.DeepSeq
 --------------------------------------
 import CoreTypes
 import Actions
@@ -17,6 +14,8 @@
 import HandlerUtils
 import RoomsAndClients
 
+
+answerAllTeams :: ClientInfo -> [TeamInfo] -> [Action]
 answerAllTeams cl = concatMap toAnswer
     where
         clChan = sendChan cl
@@ -35,15 +34,18 @@
     let roomsInfoList = concatMap (roomInfo irnc) . filter (\r -> (roomProto r == clientProto cl) && not (isRestrictedJoins r))
     return [AnswerClients [sendChan cl] ("ROOMS" : roomsInfoList rooms)]
     where
-        roomInfo irnc room = [
-                showB $ gameinprogress room,
-                name room,
-                showB $ playersIn room,
-                showB $ length $ teams room,
-                nick $ irnc `client` masterID room,
-                head (Map.findWithDefault ["+gen+"] "MAP" (params room)),
-                head (Map.findWithDefault ["Default"] "SCHEME" (params room)),
-                head (Map.findWithDefault ["Default"] "AMMO" (params room))
+        roomInfo irnc r = [
+                showB $ gameinprogress r,
+                name r,
+                showB $ playersIn r,
+                showB $ length $ teams r,
+                nick $ irnc `client` masterID r,
+                head (Map.findWithDefault ["+gen+"] "MAP" (params r)),
+                head (Map.findWithDefault ["Default"] "SCHEME" (params r)),
+                head (Map.findWithDefault ["Default"] "AMMO" (params r)),
+                head (Map.findWithDefault ["Default"] "SCHEME" (params r)),
+                head (Map.findWithDefault ["0"] "MAPGEN" (params r)),
+                head (Map.findWithDefault ["seed"] "SEED" (params r))
                 ]
 
 
@@ -52,26 +54,26 @@
     s <- roomOthersChans
     return [AnswerClients s ["CHAT", n, msg]]
 
-handleCmd_lobby ["CREATE_ROOM", newRoom, roomPassword]
-    | illegalName newRoom = return [Warning "Illegal room name"]
+handleCmd_lobby ["CREATE_ROOM", rName, roomPassword]
+    | illegalName rName = return [Warning "Illegal room name"]
     | otherwise = do
         rs <- allRoomInfos
         cl <- thisClient
-        return $ if isJust $ find (\room -> newRoom == name room) rs then 
+        return $ if isJust $ find (\r -> rName == name r) rs then
             [Warning "Room exists"]
             else
             [
-                AddRoom newRoom roomPassword,
+                AddRoom rName roomPassword,
                 AnswerClients [sendChan cl] ["CLIENT_FLAGS", "-r", nick cl]
             ]
 
 
-handleCmd_lobby ["CREATE_ROOM", newRoom] =
-    handleCmd_lobby ["CREATE_ROOM", newRoom, ""]
+handleCmd_lobby ["CREATE_ROOM", rName] =
+    handleCmd_lobby ["CREATE_ROOM", rName, ""]
 
 
 handleCmd_lobby ["JOIN_ROOM", roomName, roomPassword] = do
-    (ci, irnc) <- ask
+    (_, irnc) <- ask
     let ris = allRooms irnc
     cl <- thisClient
     let maybeRI = find (\ri -> roomName == name (irnc `room` ri)) ris
@@ -93,19 +95,20 @@
                 AnswerClients [sendChan cl] $ "JOINED" : nicks,
                 AnswerClients chans ["CLIENT_FLAGS", "-r", nick cl]
             ]
-            ++ (map (readynessMessage cl) jRoomClients)
-            ++ (answerFullConfig cl $ params jRoom)
-            ++ (answerTeams cl jRoom)
-            ++ (watchRound cl jRoom)
+            ++ map (readynessMessage cl) jRoomClients
+            ++ answerFullConfig cl (params jRoom)
+            ++ answerTeams cl jRoom
+            ++ watchRound cl jRoom
 
         where
         readynessMessage cl c = AnswerClients [sendChan cl] ["CLIENT_FLAGS", if isReady c then "+r" else "-r", nick c]
 
         toAnswer cl (paramName, paramStrs) = AnswerClients [sendChan cl] $ "CFG" : paramName : paramStrs
 
-        answerFullConfig cl params = map (toAnswer cl) (leftConfigPart ++ rightConfigPart)
-            where
-            (leftConfigPart, rightConfigPart) = partition (\(p, _) -> p /= "MAP") $ Map.toList params
+        answerFullConfig cl pr = map (toAnswer cl) $
+                 ("FULLMAPCONFIG", concatMap ((Map.!) pr) ["MAP", "MAPGEN", "SEED"])
+                 : ("SCHEME", pr Map.! "SCHEME")
+                 : (filter (\(p, _) -> p /= "SCHEME" && p /= "MAP" && p /= "MAPGEN" && p /= "SEED") $ Map.toList pr)
 
         answerTeams cl jRoom = let f = if gameinprogress jRoom then teamsAtStart else teams in answerAllTeams cl $ f jRoom
 
@@ -161,7 +164,7 @@
     where
         readNum = case B.readInt protoNum of
                        Just (i, t) | B.null t -> fromIntegral i
-                       otherwise -> 0
+                       _ -> 0
 
 handleCmd_lobby ["GET_SERVER_VAR"] = do
     cl <- thisClient
--- a/gameServer/HWProtoNEState.hs	Sat Feb 05 15:36:02 2011 +0100
+++ b/gameServer/HWProtoNEState.hs	Mon Feb 14 08:31:45 2011 -0500
@@ -1,10 +1,8 @@
 {-# LANGUAGE OverloadedStrings #-}
 module HWProtoNEState where
 
-import qualified Data.IntMap as IntMap
 import Data.Maybe
 import Data.List
-import Data.Word
 import Control.Monad.Reader
 import qualified Data.ByteString.Char8 as B
 --------------------------------------
@@ -45,7 +43,7 @@
     where
         parsedProto = case B.readInt protoNum of
                            Just (i, t) | B.null t -> fromIntegral i
-                           otherwise -> 0
+                           _ -> 0
 
 
 handleCmd_NotEntered ["PASSWORD", passwd] = do
--- a/gameServer/HandlerUtils.hs	Sat Feb 05 15:36:02 2011 +0100
+++ b/gameServer/HandlerUtils.hs	Mon Feb 14 08:31:45 2011 -0500
@@ -49,10 +49,10 @@
 thisClientChans :: Reader (ClientIndex, IRnC) [ClientChan]
 thisClientChans = do
     (ci, rnc) <- ask
-    return $ [sendChan (rnc `client` ci)]
+    return [sendChan (rnc `client` ci)]
 
 answerClient :: [B.ByteString] -> Reader (ClientIndex, IRnC) [Action]
-answerClient msg = thisClientChans >>= return . (: []) . flip AnswerClients msg
+answerClient msg = liftM ((: []) . flip AnswerClients msg) thisClientChans
 
 allRoomInfos :: Reader (a, IRnC) [RoomInfo]
 allRoomInfos = liftM ((\irnc -> map (room irnc) $ allRooms irnc) . snd) ask
--- a/gameServer/NetRoutines.hs	Sat Feb 05 15:36:02 2011 +0100
+++ b/gameServer/NetRoutines.hs	Mon Feb 14 08:31:45 2011 -0500
@@ -13,7 +13,7 @@
 import RoomsAndClients
 
 acceptLoop :: Socket -> Chan CoreMessage -> IO ()
-acceptLoop servSock chan = forever $ do
+acceptLoop servSock chan = forever $
     Exception.handle
         (\(_ :: Exception.IOException) -> putStrLn "exception on connect") $
         do
--- a/gameServer/OfficialServer/DBInteraction.hs	Sat Feb 05 15:36:02 2011 +0100
+++ b/gameServer/OfficialServer/DBInteraction.hs	Mon Feb 14 08:31:45 2011 -0500
@@ -5,59 +5,67 @@
 ) where
 
 import Prelude hiding (catch);
+import Control.Concurrent
+import Control.Monad
+import Data.List as L
+import Data.ByteString.Char8 as B
+#if defined(OFFICIAL_SERVER)
 import System.Process
-import System.IO
-import Control.Concurrent
+import System.IO as SIO
 import qualified Control.Exception as Exception
-import Control.Monad
 import qualified Data.Map as Map
 import Data.Maybe
+import Data.Time
 import System.Log.Logger
-import Data.Time
+#endif
 ------------------------
 import CoreTypes
+#if defined(OFFICIAL_SERVER)
 import Utils
+#endif
 
+localAddressList :: [B.ByteString]
 localAddressList = ["127.0.0.1", "0:0:0:0:0:0:0:1", "0:0:0:0:0:ffff:7f00:1"]
 
+fakeDbConnection :: forall b. ServerInfo -> IO b
 fakeDbConnection serverInfo = forever $ do
     q <- readChan $ dbQueries serverInfo
     case q of
-        CheckAccount clId clUid _ clHost -> do
-            writeChan (coreChan serverInfo) $ ClientAccountInfo clId clUid (if clHost `elem` localAddressList then Admin else Guest)
+        CheckAccount clId clUid _ clHost ->
+            writeChan (coreChan serverInfo) $ ClientAccountInfo clId clUid (if clHost `L.elem` localAddressList then Admin else Guest)
         ClearCache -> return ()
         SendStats {} -> return ()
 
-
+dbConnectionLoop :: forall b. ServerInfo -> IO b
 #if defined(OFFICIAL_SERVER)
 pipeDbConnectionLoop queries coreChan hIn hOut accountsCache =
     Exception.handle (\(e :: Exception.IOException) -> warningM "Database" (show e) >> return accountsCache) $
     do
     q <- readChan queries
     updatedCache <- case q of
-        CheckAccount clId clNick _ -> do
+        CheckAccount clId clUid clNick _ -> do
             let cacheEntry = clNick `Map.lookup` accountsCache
             currentTime <- getCurrentTime
             if (isNothing cacheEntry) || (currentTime `diffUTCTime` (fst . fromJust) cacheEntry > 2 * 24 * 60 * 60) then
                 do
-                    hPutStrLn hIn $ show q
+                    SIO.hPutStrLn hIn $ show q
                     hFlush hIn
 
-                    (clId', accountInfo) <- hGetLine hOut >>= (maybeException . maybeRead)
+                    (clId', clUid', accountInfo) <- SIO.hGetLine hOut >>= (maybeException . maybeRead)
 
-                    writeChan coreChan $ ClientAccountInfo (clId', accountInfo)
+                    writeChan coreChan $ ClientAccountInfo clId' clUid' accountInfo
 
                     return $ Map.insert clNick (currentTime, accountInfo) accountsCache
                 `Exception.onException`
                     (unGetChan queries q)
                 else
                 do
-                    writeChan coreChan $ ClientAccountInfo (clId, snd $ fromJust cacheEntry)
+                    writeChan coreChan $ ClientAccountInfo clId clUid (snd $ fromJust cacheEntry)
                     return accountsCache
 
         ClearCache -> return Map.empty
         SendStats {} -> (
-                (hPutStrLn hIn $ show q) >>
+                (SIO.hPutStrLn hIn $ show q) >>
                 hFlush hIn >>
                 return accountsCache)
                 `Exception.onException`
@@ -69,7 +77,7 @@
         maybeException Nothing = ioError (userError "Can't read")
 
 
-pipeDbConnection accountsCache serverInfo = do
+pipeDbConnection accountsCache si = do
     updatedCache <-
         Exception.handle (\(e :: Exception.IOException) -> warningM "Database" (show e) >> return accountsCache) $ do
             (Just hIn, Just hOut, _, _) <- createProcess (proc "./OfficialServer/extdbinterface" [])
@@ -78,22 +86,23 @@
             hSetBuffering hIn LineBuffering
             hSetBuffering hOut LineBuffering
 
-            hPutStrLn hIn $ dbHost serverInfo
-            hPutStrLn hIn $ dbLogin serverInfo
-            hPutStrLn hIn $ dbPassword serverInfo
-            pipeDbConnectionLoop (dbQueries serverInfo) (coreChan serverInfo) hIn hOut accountsCache
+            B.hPutStrLn hIn $ dbHost si
+            B.hPutStrLn hIn $ dbLogin si
+            B.hPutStrLn hIn $ dbPassword si
+            pipeDbConnectionLoop (dbQueries si) (coreChan si) hIn hOut accountsCache
 
     threadDelay (3 * 10^6)
-    pipeDbConnection updatedCache serverInfo
+    pipeDbConnection updatedCache si
 
-dbConnectionLoop serverInfo =
-        if (not . null $ dbHost serverInfo) then
-            pipeDbConnection Map.empty serverInfo
+dbConnectionLoop si =
+        if (not . B.null $ dbHost si) then
+            pipeDbConnection Map.empty si
         else
-            fakeDbConnection serverInfo
+            fakeDbConnection si
 #else
 dbConnectionLoop = fakeDbConnection
 #endif
 
+startDBConnection :: ServerInfo -> IO ()
 startDBConnection serverInfo =
-    forkIO $ dbConnectionLoop serverInfo
+    forkIO (dbConnectionLoop serverInfo) >> return ()
--- a/gameServer/OfficialServer/extdbinterface.hs	Sat Feb 05 15:36:02 2011 +0100
+++ b/gameServer/OfficialServer/extdbinterface.hs	Mon Feb 14 08:31:45 2011 -0500
@@ -6,7 +6,7 @@
 import Control.Monad
 import Control.Exception
 import System.IO
-import Maybe
+import Data.Maybe
 import Database.HDBC
 import Database.HDBC.MySQL
 --------------------------
@@ -20,26 +20,27 @@
     "UPDATE gameserver_stats SET players = ?, rooms = ?, last_update = UNIX_TIMESTAMP()"
 
 dbInteractionLoop dbConn = forever $ do
-    q <- (getLine >>= return . read)
+    q <- liftM read getLine
     hPutStrLn stderr $ show q
-    
+
     case q of
-        CheckAccount clUid clNick _ -> do
+        CheckAccount clId clUid clNick _ -> do
                 statement <- prepare dbConn dbQueryAccount
-                execute statement [SqlByteString $ clNick]
+                execute statement [SqlByteString clNick]
                 passAndRole <- fetchRow statement
                 finish statement
                 let response = 
                         if isJust passAndRole then
                         (
+                            clId,
                             clUid,
                             HasAccount
-                                (fromSql $ head $ fromJust $ passAndRole)
-                                ((fromSql $ last $ fromJust $ passAndRole) == (Just (3 :: Int)))
+                                (fromSql . head . fromJust $ passAndRole)
+                                (fromSql (last . fromJust $ passAndRole) == Just (3 :: Int))
                         )
                         else
-                        (clUid, Guest)
-                putStrLn (show response)
+                        (clId, clUid, Guest)
+                print response
                 hFlush stdout
 
         SendStats clients rooms ->
@@ -50,12 +51,12 @@
     Control.Exception.handle (\(e :: IOException) -> hPutStrLn stderr $ show e) $ handleSqlError $
         bracket
             (connectMySQL mySQLConnectionInfo)
-            (disconnect)
-            (dbInteractionLoop)
+            disconnect
+            dbInteractionLoop
 
 
-processRequest :: DBQuery -> IO String
-processRequest (CheckAccount clUid clNick clHost) = return $ show (clUid, Guest)
+--processRequest :: DBQuery -> IO String
+--processRequest (CheckAccount clId clUid clNick clHost) = return $ show (clclId, clUid, Guest)
 
 main = do
         dbHost <- getLine
--- a/gameServer/Opts.hs	Sat Feb 05 15:36:02 2011 +0100
+++ b/gameServer/Opts.hs	Mon Feb 14 08:31:45 2011 -0500
@@ -1,3 +1,4 @@
+{-# LANGUAGE CPP #-}
 module Opts
 (
     getOpts,
@@ -5,36 +6,44 @@
 
 import System.Environment
 import System.Console.GetOpt
+import Data.Maybe ( fromMaybe )
+#if defined(OFFICIAL_SERVER)
+import qualified Data.ByteString.Char8 as B
 import Network
-import Data.Maybe ( fromMaybe )
-import qualified Data.ByteString.Char8 as B
-
+#endif
+-------------------
 import CoreTypes
 import Utils
 
 options :: [OptDescr (ServerInfo -> ServerInfo)]
 options = [
-    Option ['p'] ["port"] (ReqArg readListenPort "PORT") "listen on PORT",
-    Option ['d'] ["dedicated"] (ReqArg readDedicated "BOOL") "start as dedicated (True or False)"
+    Option "p" ["port"] (ReqArg readListenPort "PORT") "listen on PORT",
+    Option "d" ["dedicated"] (ReqArg readDedicated "BOOL") "start as dedicated (True or False)"
     ]
 
-readListenPort,
-    readDedicated,
-    readDbLogin,
-    readDbPassword,
-    readDbHost :: String -> ServerInfo -> ServerInfo
+readListenPort
+    , readDedicated
+#if defined(OFFICIAL_SERVER)
+    , readDbLogin
+    , readDbPassword
+    readDbHost
+#endif
+    :: String -> ServerInfo -> ServerInfo
+
 
 readListenPort str opts = opts{listenPort = readPort}
     where
         readPort = fromInteger $ fromMaybe 46631 (maybeRead str :: Maybe Integer)
 
-readDedicated str opts = opts{isDedicated = readDedicated}
+readDedicated str opts = opts{isDedicated = readDed}
     where
-        readDedicated = fromMaybe True (maybeRead str :: Maybe Bool)
+        readDed = fromMaybe True (maybeRead str :: Maybe Bool)
 
+#if defined(OFFICIAL_SERVER)
 readDbLogin str opts = opts{dbLogin = B.pack str}
 readDbPassword str opts = opts{dbPassword = B.pack str}
 readDbHost str opts = opts{dbHost = B.pack str}
+#endif
 
 getOpts :: ServerInfo -> IO ServerInfo
 getOpts opts = do
--- a/gameServer/RoomsAndClients.hs	Sat Feb 05 15:36:02 2011 +0100
+++ b/gameServer/RoomsAndClients.hs	Mon Feb 14 08:31:45 2011 -0500
@@ -82,27 +82,27 @@
 
 
 roomAddClient :: ClientIndex -> Room r -> Room r
-roomAddClient cl room = let cls = cl : roomClients' room; nr = room{roomClients' = cls} in cls `seq` nr `seq` nr
+roomAddClient cl rm = let cls = cl : roomClients' rm; nr = rm{roomClients' = cls} in cls `seq` nr
 
 roomRemoveClient :: ClientIndex -> Room r -> Room r
-roomRemoveClient cl room = let cls = filter (/= cl) $ roomClients' room; nr = room{roomClients' = cls} in cls `seq` nr `seq` nr
+roomRemoveClient cl rm = let cls = filter (/= cl) $ roomClients' rm; nr = rm{roomClients' = cls} in cls `seq` nr
 
 
 addRoom :: MRoomsAndClients r c -> r -> IO RoomIndex
-addRoom (MRoomsAndClients (rooms, _)) room = do
-    i <- addElem rooms (Room  [] room)
+addRoom (MRoomsAndClients (rooms, _)) rm = do
+    i <- addElem rooms (Room  [] rm)
     return $ RoomIndex i
 
 
 addClient :: MRoomsAndClients r c -> c -> IO ClientIndex
-addClient (MRoomsAndClients (rooms, clients)) client = do
-    i <- addElem clients (Client lobbyId client)
+addClient (MRoomsAndClients (rooms, clients)) cl = do
+    i <- addElem clients (Client lobbyId cl)
     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"
+removeRoom rnc@(MRoomsAndClients (rooms, _)) rm@(RoomIndex ri)
+    | rm == lobbyId = error "Cannot delete lobby"
     | otherwise = do
         clIds <- liftM roomClients' $ readElem rooms ri
         forM_ clIds (moveClientToLobby rnc)
@@ -131,12 +131,12 @@
 
 moveClientToLobby :: MRoomsAndClients r c -> ClientIndex -> IO ()
 moveClientToLobby rnc ci = do
-    room <- clientRoomM rnc ci
-    moveClientInRooms rnc room lobbyId ci
+    rm <- clientRoomM rnc ci
+    moveClientInRooms rnc rm lobbyId ci
 
 
 moveClientToRoom :: MRoomsAndClients r c -> RoomIndex -> ClientIndex -> IO ()
-moveClientToRoom rnc ri ci = moveClientInRooms rnc lobbyId ri ci
+moveClientToRoom rnc = moveClientInRooms rnc lobbyId
 
 
 clientExists :: MRoomsAndClients r c -> ClientIndex -> IO Bool
@@ -155,10 +155,10 @@
 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)
+clientsM (MRoomsAndClients (_, clients)) = indicesM clients >>= mapM (liftM client' . readElem clients)
 
 roomClientsIndicesM :: MRoomsAndClients r c -> RoomIndex -> IO [ClientIndex]
-roomClientsIndicesM (MRoomsAndClients (rooms, clients)) (RoomIndex ri) = liftM roomClients' (rooms `readElem` ri)
+roomClientsIndicesM (MRoomsAndClients (rooms, _)) (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)
@@ -173,8 +173,8 @@
 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))
+    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]
@@ -193,4 +193,4 @@
 room (IRoomsAndClients (rooms, _)) (RoomIndex ri) = room' (rooms ! ri)
 
 roomClients :: IRoomsAndClients r c -> RoomIndex -> [ClientIndex]
-roomClients (IRoomsAndClients (rooms, _)) (RoomIndex ri) = roomClients' $ (rooms ! ri)
+roomClients (IRoomsAndClients (rooms, _)) (RoomIndex ri) = roomClients' (rooms ! ri)
--- a/gameServer/ServerCore.hs	Sat Feb 05 15:36:02 2011 +0100
+++ b/gameServer/ServerCore.hs	Mon Feb 14 08:31:45 2011 -0500
@@ -41,10 +41,10 @@
         Accept ci -> processAction (AddClient ci)
 
         ClientMessage (ci, cmd) -> do
-            liftIO $ debugM "Clients" $ (show ci) ++ ": " ++ (show cmd)
+            liftIO $ debugM "Clients" $ show ci ++ ": " ++ show cmd
 
             removed <- gets removedClients
-            when (not $ ci `Set.member` removed) $ do
+            unless (ci `Set.member` removed) $ do
                 as <- get
                 put $! as{clientIndex = Just ci}
                 reactCmd cmd
@@ -61,11 +61,11 @@
         ClientAccountInfo ci uid info -> do
             rnc <- gets roomsClients
             exists <- liftIO $ clientExists rnc ci
-            when (exists) $ do
+            when exists $ do
                 as <- get
                 put $! as{clientIndex = Just ci}
                 uid' <- client's clUID
-                when (uid == (hashUnique uid')) $ processAction (ProcessAccountInfo info)
+                when (uid == hashUnique uid') $ processAction (ProcessAccountInfo info)
                 return ()
 
         TimerAction tick ->
@@ -77,19 +77,19 @@
 startServer si serverSocket = do
     putStrLn $ "Listening on port " ++ show (listenPort si)
 
-    forkIO $
+    _ <- forkIO $
         acceptLoop
             serverSocket
             (coreChan si)
 
     return ()
 
-    forkIO $ timerLoop 0 $ coreChan si
+    _ <- forkIO $ timerLoop 0 $ coreChan si
 
     startDBConnection si
 
     rnc <- newRoomsAndClients newRoom
 
-    forkIO $ evalStateT mainLoop (ServerState Nothing si Set.empty rnc)
+    _ <- forkIO $ evalStateT mainLoop (ServerState Nothing si Set.empty rnc)
 
     forever $ threadDelay 3600000000 -- one hour
--- a/gameServer/Store.hs	Sat Feb 05 15:36:02 2011 +0100
+++ b/gameServer/Store.hs	Mon Feb 14 08:31:45 2011 -0500
@@ -56,7 +56,7 @@
     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)
+    writeIORef ref (busyElems, freeElems `IntSet.union` IntSet.fromAscList [m'+1..newM'], newArr)
 
 
 growIfNeeded :: MStore e -> IO ()
@@ -113,7 +113,7 @@
     c <- IOA.unsafeFreeze c'
     return $ IStore (a, c)
 
-i2m :: (MStore e) -> IStore e -> IO ()
+i2m :: MStore e -> IStore e -> IO ()
 i2m (MStore ref) (IStore (_, arr)) = do
     (b, e, _) <- readIORef ref
     a <- IOA.unsafeThaw arr
--- a/gameServer/Utils.hs	Sat Feb 05 15:36:02 2011 +0100
+++ b/gameServer/Utils.hs	Mon Feb 14 08:31:45 2011 -0500
@@ -1,21 +1,15 @@
 {-# LANGUAGE OverloadedStrings #-}
 module Utils where
 
-import Control.Concurrent
-import Control.Concurrent.STM
 import Data.Char
 import Data.Word
 import qualified Data.Map as Map
-import qualified Data.IntMap as IntMap
 import qualified Data.Set as Set
-import Data.ByteString.Internal (w2c)
 import Numeric
 import Network.Socket
 import System.IO
 import qualified Data.List as List
 import Control.Monad
-import Control.Monad.Trans
-import Data.Maybe
 -------------------------------------------------
 import qualified Codec.Binary.Base64 as Base64
 import qualified Data.ByteString.Char8 as B
@@ -27,14 +21,14 @@
 sockAddr2String (SockAddrInet _ hostAddr) = liftM B.pack $ inet_ntoa hostAddr
 sockAddr2String (SockAddrInet6 _ _ (a, b, c, d) _) =
     return $ B.pack $ (foldr1 (.)
-        $ List.intersperse (\a -> ':':a)
-        $ concatMap (\n -> (\(a, b) -> [showHex a, showHex b]) $ divMod n 65536) [a, b, c, d]) []
+        $ List.intersperse (':':)
+        $ concatMap (\n -> (\(a0, a1) -> [showHex a0, showHex a1]) $ divMod n 65536) [a, b, c, d]) []
 
 toEngineMsg :: B.ByteString -> B.ByteString
-toEngineMsg msg = B.pack $ Base64.encode (fromIntegral (BW.length msg) : (BW.unpack msg))
+toEngineMsg msg = B.pack $ Base64.encode (fromIntegral (BW.length msg) : BW.unpack msg)
 
 fromEngineMsg :: B.ByteString -> Maybe B.ByteString
-fromEngineMsg msg = Base64.decode (B.unpack msg) >>= removeLength >>= return . BW.pack
+fromEngineMsg msg = liftM BW.pack (Base64.decode (B.unpack msg) >>= removeLength)
     where
         removeLength (x:xs) = if length xs == fromIntegral x then Just xs else Nothing
         removeLength _ = Nothing
@@ -43,7 +37,7 @@
 checkNetCmd = check . liftM B.unpack . fromEngineMsg
     where
         check Nothing = (False, False)
-        check (Just (m:ms)) = (m `Set.member` legalMessages, m == '+')
+        check (Just (m:_)) = (m `Set.member` legalMessages, m == '+')
         check _ = (False, False)
         legalMessages = Set.fromList $ "M#+LlRrUuDdZzAaSjJ,sFNpPwtghb12345" ++ slotMessages
         slotMessages = "\128\129\130\131\132\133\134\135\136\137\138"
@@ -62,20 +56,20 @@
         : teamvoicepack team
         : teamflag team
         : teamowner team
-        : (B.pack $ show $ difficulty team)
+        : (B.pack . show $ difficulty team)
         : hhsInfo
     where
-        hhsInfo = concatMap (\(HedgehogInfo name hat) -> [name, hat]) $ hedgehogs team
+        hhsInfo = concatMap (\(HedgehogInfo n hat) -> [n, hat]) $ hedgehogs team
 
 modifyTeam :: TeamInfo -> RoomInfo -> RoomInfo
 modifyTeam team room = room{teams = replaceTeam team $ teams room}
     where
     replaceTeam _ [] = error "modifyTeam: no such team"
-    replaceTeam team (t:teams) =
-        if teamname team == teamname t then
-            team : teams
+    replaceTeam tm (t:ts) =
+        if teamname tm == teamname t then
+            tm : ts
         else
-            t : replaceTeam team teams
+            t : replaceTeam tm ts
 
 illegalName :: B.ByteString -> Bool
 illegalName b = null s || all isSpace s || isSpace (head s) || isSpace (last s)
@@ -86,32 +80,33 @@
 protoNumber2ver v = Map.findWithDefault "Unknown" v vermap
     where
         vermap = Map.fromList [
-            (17, "0.9.7-dev"),
-            (19, "0.9.7"),
-            (20, "0.9.8-dev"),
-            (21, "0.9.8"),
-            (22, "0.9.9-dev"),
-            (23, "0.9.9"),
-            (24, "0.9.10-dev"),
-            (25, "0.9.10"),
-            (26, "0.9.11-dev"),
-            (27, "0.9.11"),
-            (28, "0.9.12-dev"),
-            (29, "0.9.12"),
-            (30, "0.9.13-dev"),
-            (31, "0.9.13"),
-            (32, "0.9.14-dev"),
-            (33, "0.9.14"),
-            (34, "0.9.15-dev"),
-            (35, "0.9.14.1"),
-            (37, "0.9.15"),
-            (38, "0.9.16-dev")]
+            (17, "0.9.7-dev")
+            , (19, "0.9.7")
+            , (20, "0.9.8-dev")
+            , (21, "0.9.8")
+            , (22, "0.9.9-dev")
+            , (23, "0.9.9")
+            , (24, "0.9.10-dev")
+            , (25, "0.9.10")
+            , (26, "0.9.11-dev")
+            , (27, "0.9.11")
+            , (28, "0.9.12-dev")
+            , (29, "0.9.12")
+            , (30, "0.9.13-dev")
+            , (31, "0.9.13")
+            , (32, "0.9.14-dev")
+            , (33, "0.9.14")
+            , (34, "0.9.15-dev")
+            , (35, "0.9.14.1")
+            , (37, "0.9.15")
+            , (38, "0.9.16-dev")
+            ]
 
-askFromConsole :: String -> IO String
+askFromConsole :: B.ByteString -> IO B.ByteString
 askFromConsole msg = do
-    putStr msg
+    B.putStr msg
     hFlush stdout
-    getLine
+    B.getLine
 
 
 unfoldrE :: (b -> Either b (a, b)) -> b -> ([a], b)
--- a/gameServer/hedgewars-server.hs	Sat Feb 05 15:36:02 2011 +0100
+++ b/gameServer/hedgewars-server.hs	Mon Feb 14 08:31:45 2011 -0500
@@ -1,4 +1,4 @@
-{-# LANGUAGE CPP, ScopedTypeVariables #-}
+{-# LANGUAGE CPP, ScopedTypeVariables, OverloadedStrings #-}
 
 module Main where
 
@@ -12,6 +12,9 @@
 import Opts
 import CoreTypes
 import ServerCore
+#if defined(OFFICIAL_SERVER)
+import Utils
+#endif
 
 
 #if !defined(mingw32_HOST_OS)
@@ -27,8 +30,8 @@
 main :: IO ()
 main = withSocketsDo $ do
 #if !defined(mingw32_HOST_OS)
-    installHandler sigPIPE Ignore Nothing;
-    installHandler sigCHLD Ignore Nothing;
+    _ <- installHandler sigPIPE Ignore Nothing
+    _ <- installHandler sigCHLD Ignore Nothing
 #endif
 
     setupLoggers
--- a/gameServer/stresstest.hs	Sat Feb 05 15:36:02 2011 +0100
+++ b/gameServer/stresstest.hs	Mon Feb 14 08:31:45 2011 -0500
@@ -2,8 +2,8 @@
 
 module Main where
 
-import IO
 import System.IO
+import System.IO.Error
 import Control.Concurrent
 import Network
 import Control.OldException
--- a/gameServer/stresstest2.hs	Sat Feb 05 15:36:02 2011 +0100
+++ b/gameServer/stresstest2.hs	Mon Feb 14 08:31:45 2011 -0500
@@ -2,7 +2,6 @@
 
 module Main where
 
-import IO
 import System.IO
 import Control.Concurrent
 import Network
--- a/gameServer/stresstest3.hs	Sat Feb 05 15:36:02 2011 +0100
+++ b/gameServer/stresstest3.hs	Mon Feb 14 08:31:45 2011 -0500
@@ -2,8 +2,8 @@
 
 module Main where
 
-import IO
 import System.IO
+import System.IO.Error
 import Control.Concurrent
 import Network
 import Control.OldException
@@ -22,12 +22,11 @@
 readPacket :: StateT SState IO [String]
 readPacket = do
     h <- get
-    p <- io $ hGetPacket h []
-    return p
+    io $ hGetPacket h []
     where
     hGetPacket h buf = do
         l <- hGetLine h
-        if (not $ null l) then hGetPacket h (buf ++ [l]) else return buf
+        if not $ null l then hGetPacket h (buf ++ [l]) else return buf
 
 waitPacket :: String -> StateT SState IO Bool
 waitPacket s = do
@@ -46,7 +45,7 @@
 emulateSession = do
     n <- io $ randomRIO (100000::Int, 100100)
     waitPacket "CONNECTED"
-    sendPacket ["NICK", "test" ++ (show n)]
+    sendPacket ["NICK", "test" ++ show n]
     waitPacket "NICK"
     sendPacket ["PROTO", "31"]
     waitPacket "PROTO"
--- a/hedgewars/CMakeLists.txt	Sat Feb 05 15:36:02 2011 +0100
+++ b/hedgewars/CMakeLists.txt	Mon Feb 14 08:31:45 2011 -0500
@@ -34,6 +34,7 @@
 #SOURCE AND PROGRAMS SECTION
 set(fpc_tryexe fpc)
 set(hwengine_project ${hedgewars_SOURCE_DIR}/hedgewars/hwengine.pas)
+set(engine_output_name "hwengine")
 
 set(engine_sources
     ${hwengine_project}
@@ -93,10 +94,23 @@
     message(STATUS "Engine will be built as library (experimental)")
     set(hwengine_project ${hedgewars_SOURCE_DIR}/hedgewars/hwLibrary.pas)
     set(engine_sources ${hwengine_project} PascalExports.pas ${engine_sources})
-    set(pascal_compiler_flags_cmn "-dHWLIBRARY" "-k-no_order_inits" "-fPIC" ${pascal_compiler_flags_cmn})
+    set(pascal_compiler_flags_cmn "-dHWLIBRARY" ${pascal_compiler_flags_cmn})
+
+    # create position independent code, only required for x68_64 builds, similar to -fPIC
+    if(CMAKE_SIZEOF_VOID_P MATCHES "8")
+        set(pascal_compiler_flags_cmn "-Cg" ${pascal_compiler_flags_cmn})
+    endif(CMAKE_SIZEOF_VOID_P MATCHES "8")
+
+    # due to compiling/linker issues on Max OS X 10.6 -k-no_order_inits is needed to avoid linking fail
+    if(APPLE AND current_macosx_version MATCHES "10.6")
+        set(pascal_compiler_flags_cmn "-k-no_order_inits" ${pascal_compiler_flags_cmn})
+    endif(APPLE AND current_macosx_version MATCHES "10.6")
+
+    if (APPLE)
+        set(engine_output_name "hwengine.dylib")
+    endif (APPLE)
 endif(BUILD_ENGINE_LIBRARY)
 
-
 find_program(fpc_executable ${fpc_tryexe})
 
 if(fpc_executable)
@@ -152,9 +166,9 @@
 
 
 #DEPENDECIES AND EXECUTABLES SECTION
-IF(NOT APPLE OR BUILD_ENGINE_LIBRARY)
+IF(NOT APPLE)
     #here is the command for standard executables or for shared library
-    add_custom_command(OUTPUT "${EXECUTABLE_OUTPUT_PATH}/hwengine${CMAKE_EXECUTABLE_SUFFIX}"
+    add_custom_command(OUTPUT "${EXECUTABLE_OUTPUT_PATH}/${engine_output_name}${CMAKE_EXECUTABLE_SUFFIX}"
         COMMAND "${pascal_compiler}"
         ARGS ${pascal_compiler_flags}
         MAIN_DEPENDENCY ${hwengine_project}
@@ -182,15 +196,15 @@
         add_custom_target(hwengine.${build_arch} ALL DEPENDS "${EXECUTABLE_OUTPUT_PATH}/hwengine.${build_arch}")
     endforeach()
 
-    add_custom_command(OUTPUT "${EXECUTABLE_OUTPUT_PATH}/hwengine"
+    add_custom_command(OUTPUT "${EXECUTABLE_OUTPUT_PATH}/${engine_output_name}"
         COMMAND "lipo"
-        ARGS ${lipo_args_list} -create -output ${EXECUTABLE_OUTPUT_PATH}/hwengine
+        ARGS ${lipo_args_list} -create -output ${EXECUTABLE_OUTPUT_PATH}/${engine_output_name}
         DEPENDS ${lipo_args_list}
         )
 ENDIF()
 
 
-add_custom_target(hwengine ALL DEPENDS "${EXECUTABLE_OUTPUT_PATH}/hwengine${CMAKE_EXECUTABLE_SUFFIX}")
+add_custom_target(${engine_output_name} ALL DEPENDS "${EXECUTABLE_OUTPUT_PATH}/${engine_output_name}${CMAKE_EXECUTABLE_SUFFIX}")
 
-install(PROGRAMS "${EXECUTABLE_OUTPUT_PATH}/hwengine${CMAKE_EXECUTABLE_SUFFIX}" DESTINATION ${target_dir})
+install(PROGRAMS "${EXECUTABLE_OUTPUT_PATH}/${engine_output_name}${CMAKE_EXECUTABLE_SUFFIX}" DESTINATION ${target_dir})
 
--- a/hedgewars/PascalExports.pas	Sat Feb 05 15:36:02 2011 +0100
+++ b/hedgewars/PascalExports.pas	Mon Feb 14 08:31:45 2011 -0500
@@ -164,6 +164,11 @@
     KeyPressChat(13); // enter - removes chat
 end;
 
+procedure HW_screenshot; cdecl; export;
+begin
+    flagMakeCapture:= true;
+end;
+
 procedure HW_pause; cdecl; export;
 begin
     if isPaused = false then
@@ -199,6 +204,15 @@
     ParseCommand('forcequit', true);
 end;
 
+function HW_getSDLWindow: pointer; cdecl; export;
+begin
+{$IFDEF SDL13}
+    exit( SDLwindow );
+{$ELSE}
+    exit( nil );
+{$ENDIF}
+end;
+
 // cursor handling
 procedure HW_setCursor(x,y: LongInt); cdecl; export;
 begin
--- a/hedgewars/SDLh.pas	Sat Feb 05 15:36:02 2011 +0100
+++ b/hedgewars/SDLh.pas	Mon Feb 14 08:31:45 2011 -0500
@@ -358,6 +358,7 @@
 
 {$IFDEF SDL13}
     PSDL_Window = pointer;
+    PSDL_Renderer = pointer;
     PSDL_Texture = pointer;
 
     TSDL_WindowEvent = record
@@ -715,24 +716,23 @@
 
 {$IFDEF SDL13}
 function  SDL_CreateWindow(title: PChar; x,y,w,h, flags: LongInt): PSDL_Window; cdecl; external SDLLibName;
-function  SDL_CreateRenderer(window: PSDL_Window; index, flags: LongInt): LongInt; cdecl; external SDLLibName;
-function  SDL_SetRenderDrawColor(r,g,b,a: byte): LongInt; cdecl; external SDLLibName;
-function  SDL_DestroyRenderer(window: PSDL_Window): LongInt; cdecl; external SDLLibName;
+function  SDL_CreateRenderer(window: PSDL_Window; index, flags: LongInt): PSDL_Renderer; cdecl; external SDLLibName;
+function  SDL_DestroyRenderer(renderer: PSDL_Renderer): LongInt; cdecl; external SDLLibName;
 function  SDL_DestroyWindow(window: PSDL_Window): LongInt; cdecl; external SDLLibName;
+procedure SDL_VideoQuit; cdecl; external SDLLibName;
 function  SDL_SelectVideoDisplay(index: LongInt): LongInt; cdecl; external SDLLibName;
 function  SDL_GetNumVideoDisplays: LongInt; cdecl; external SDLLibName;
 
-function  SDL_RenderFill(rect: PSDL_Rect): LongInt;
-function  SDL_RenderFillRect(rect: PSDL_Rect): LongInt; cdecl; external SDLLibName;
-function  SDL_RenderClear: LongInt; cdecl; external SDLLibName;
-procedure SDL_RenderPresent; cdecl; external SDLLibName;
-procedure SDL_VideoQuit; cdecl; external SDLLibName;
+function  SDL_SetRenderDrawColor(renderer: PSDL_Renderer; r,g,b,a: byte): LongInt; cdecl; external SDLLibName;
+function  SDL_RenderFillRect(renderer: PSDL_Renderer; rect: PSDL_Rect): LongInt; cdecl; external SDLLibName;
+function  SDL_RenderClear(renderer: PSDL_Renderer): LongInt; cdecl; external SDLLibName;
+procedure SDL_RenderPresent(renderer: PSDL_Renderer); cdecl; external SDLLibName;
+function  SDL_RenderReadPixels(renderer: PSDL_Renderer; rect: PSDL_Rect; format: LongInt; pixels: pointer; pitch: LongInt): LongInt; cdecl; external SDLLibName;
 
 function  SDL_SelectMouse(index: LongInt): LongInt; cdecl; external SDLLibName;
 function  SDL_GetRelativeMouseState(x, y: PLongInt): Byte; cdecl; external SDLLibName;
 function  SDL_GetNumMice: LongInt; cdecl; external SDLLibName;
 function  SDL_PixelFormatEnumToMasks(format: TSDL_ArrayByteOrder; bpp: PLongInt; Rmask, Gmask, Bmask, Amask: PLongInt): boolean; cdecl; external SDLLibName;
-function  SDL_RenderReadPixels(rect: PSDL_Rect; format: LongInt; pixels: pointer; pitch: LongInt): LongInt; cdecl; external SDLLibName;
 {$ENDIF}
 
 function  SDL_GetKeyState(numkeys: PLongInt): PByteArray; cdecl; external SDLLibName {$IFDEF SDL13} name 'SDL_GetKeyboardState'{$ENDIF};
@@ -891,15 +891,5 @@
                   (PByteArray(buf)^[0] shl 24)
 end;
 
-{$IFDEF SDL13}
-function SDL_RenderFill(rect: PSDL_Rect): LongInt;
-var res: LongInt;
-begin
-    if (rect <> nil) then res:= SDL_RenderFillRect(rect)
-    else res:= SDL_RenderClear();
-    exit(res);
-end;
-{$ENDIF}
-
 end.
 
--- a/hedgewars/hwLibrary.pas	Sat Feb 05 15:36:02 2011 +0100
+++ b/hedgewars/hwLibrary.pas	Mon Feb 14 08:31:45 2011 -0500
@@ -1,18 +1,31 @@
-//  fptest
-//
-//  Created by Vittorio on 08/01/10.
-//  Copyright __MyCompanyName__ 2010. All rights reserved.
+(*
+ * Hedgewars, a free turn based strategy game
+ * Copyright (c) 2004-2011 Andrey Korotaev <unC0Rr@gmail.com>
+ *
+ * This program is free software; you can redistribute it and/or modify
+ * it under the terms of the GNU General Public License as published by
+ * the Free Software Foundation; version 2 of the License
+ *
+ * This program is distributed in the hope that it will be useful,
+ * but WITHOUT ANY WARRANTY; without even the implied warranty of
+ * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
+ * GNU General Public License for more details.
+ *
+ * You should have received a copy of the GNU General Public License
+ * along with this program; if not, write to the Free Software
+ * Foundation, Inc., 59 Temple Place - Suite 330, Boston, MA 02111-1307, USA
+ *)
 
 Library hwLibrary;
 
 // Add all your Pascal units to the "uses" clause below to add them to the program.
-
 // Mark all Pascal procedures/functions that you wish to call from C/C++/Objective-C code using
 // "cdecl; export;" (see the fpclogo.pas unit for an example), and then add C-declarations for
 // these procedures/functions to the PascalImports.h file (also in the "Pascal Sources" group)
 // to make these functions available in the C/C++/Objective-C source files
 // (add "#include PascalImports.h" near the top of these files if it's not there yet)
 uses PascalExports, hwengine;
+exports Game;
 begin
 
 end.
--- a/hedgewars/hwengine.pas	Sat Feb 05 15:36:02 2011 +0100
+++ b/hedgewars/hwengine.pas	Mon Feb 14 08:31:45 2011 -0500
@@ -36,6 +36,7 @@
 {$IFDEF HWLIBRARY}
 procedure initEverything(complete:boolean);
 procedure freeEverything(complete:boolean);
+procedure Game(gameArgs: PPChar); cdecl; export;
 
 implementation
 {$ELSE}
@@ -103,7 +104,7 @@
         end;
 
 {$IFDEF SDL13}
-    SDL_RenderPresent();
+    SDL_RenderPresent(SDLrender);
 {$ELSE}
     SDL_GL_SwapBuffers();
 {$ENDIF}
@@ -114,8 +115,7 @@
         s:= 'hw_' + FormatDateTime('YYYY-MM-DD_HH-mm-ss', Now()) + inttostr(GameTicks);
         WriteLnToConsole('Saving ' + s + '...');
         playSound(sndShutter);
-        MakeScreenshot(s);
-        //SDL_SaveBMP_RW(SDLPrimSurface, SDL_RWFromFile(Str2PChar(s), 'wb'), 1)
+        {$IFNDEF IPHONEOS}MakeScreenshot(s);{$ENDIF}
     end;
 end;
 
@@ -129,7 +129,8 @@
     CloseIPC();
     TTF_Quit();
 {$IFDEF SDL13}
-    SDL_DestroyRenderer(SDLwindow);
+    SDL_RenderClear(SDLrender);
+    SDL_DestroyRenderer(SDLrender);
     SDL_DestroyWindow(SDLwindow);
 {$ENDIF}
     SDL_Quit();
--- a/hedgewars/uChat.pas	Sat Feb 05 15:36:02 2011 +0100
+++ b/hedgewars/uChat.pas	Mon Feb 14 08:31:45 2011 -0500
@@ -68,7 +68,6 @@
 if cl.Tex <> nil then
     FreeTexture(cl.Tex);
 
-
 cl.s:= str;
 
 if isInput then
@@ -355,6 +354,7 @@
 end;
 
 procedure initModule;
+var i: ShortInt;
 begin
     RegisterVariable('chatmsg', vtCommand, @chChatMessage, true);
     RegisterVariable('say', vtCommand, @chSay, true);
@@ -367,6 +367,12 @@
     showAll:= false;
     ChatReady:= false;
     missedCount:= 0;
+
+    inputStr.Tex := nil;
+    for i:= 0 to MaxStrIndex do
+    begin
+        Strs[i].Tex := nil;
+    end;
 end;
 
 procedure freeModule;
--- a/hedgewars/uGears.pas	Sat Feb 05 15:36:02 2011 +0100
+++ b/hedgewars/uGears.pas	Mon Feb 14 08:31:45 2011 -0500
@@ -1262,13 +1262,14 @@
 
 procedure ShotgunShot(Gear: PGear);
 var t: PGear;
-    dmg: LongInt;
+    dmg, dist: LongInt;
 begin
 Gear^.Radius:= cShotgunRadius;
 t:= GearsList;
 while t <> nil do
     begin
-    dmg:= ModifyDamage(min(Gear^.Radius + t^.Radius - hwRound(Distance(Gear^.X - t^.X, Gear^.Y - t^.Y)), 25), t);
+    dist:= hwRound(Distance(Gear^.X - t^.X, Gear^.Y - t^.Y));
+    dmg:= ModifyDamage(min(Gear^.Radius + t^.Radius - dist, 25), t);
     if dmg > 0 then
     case t^.Kind of
         gtHedgehog,
@@ -1278,6 +1279,7 @@
             gtTarget,
             gtExplosives,
             gtStructure: begin
+addFileLog('ShotgunShot radius: ' + inttostr(Gear^.Radius) + ', t^.Radius = ' + inttostr(t^.Radius) + ', distance = ' + inttostr(dist) + ', dmg = ' + inttostr(dmg));
                     if (not t^.Invulnerable) then
                         ApplyDamage(t, Gear^.Hedgehog, dmg, dsBullet)
                     else
--- a/hedgewars/uStore.pas	Sat Feb 05 15:36:02 2011 +0100
+++ b/hedgewars/uStore.pas	Mon Feb 14 08:31:45 2011 -0500
@@ -689,7 +689,7 @@
 
     SDL_GL_SwapBuffers();
 {$IFDEF SDL13}
-    SDL_RenderPresent();
+    SDL_RenderPresent(SDLrender);
 {$ENDIF}
     inc(Step);
 
@@ -932,12 +932,12 @@
         SDLwindow:= SDL_CreateWindow('Hedgewars', 0, 0, cScreenWidth, cScreenHeight,
                         SDL_WINDOW_OPENGL or SDL_WINDOW_SHOWN
                         {$IFDEF IPHONEOS} or SDL_WINDOW_BORDERLESS{$ENDIF});
-        SDL_CreateRenderer(SDLwindow, -1, 0);
+        SDLrender:= SDL_CreateRenderer(SDLwindow, -1, 1 and 2);
     end;
 
-    SDL_SetRenderDrawColor(0, 0, 0, 255);
-    SDL_RenderFill(nil);
-    SDL_RenderPresent();
+    SDL_SetRenderDrawColor(SDLrender,0, 0, 0, 255);
+    SDL_RenderClear(SDLrender);
+    SDL_RenderPresent(SDLrender);
 {$ELSE}
     SDLPrimSurface:= SDL_SetVideoMode(cScreenWidth, cScreenHeight, cBits, flags);
     SDLTry(SDLPrimSurface <> nil, true);
@@ -949,6 +949,8 @@
 end;
 
 procedure initModule;
+var ai: TAmmoType;
+    i: LongInt;
 begin
     RegisterVariable('fullscr', vtCommand, @chFullScr, true);
 
@@ -964,6 +966,17 @@
     SupportNPOTT:= false;
     Step:= 0;
     ProgrTex:= nil;
+
+    // init all ammo name texture pointers
+    for ai:= Low(TAmmoType) to High(TAmmoType) do
+    begin
+        Ammoz[ai].NameTex := nil;
+    end;
+    // init all count texture pointers
+    for i:= Low(CountTexz) to High(CountTexz) do
+    begin
+        CountTexz[i] := nil;
+    end;
 end;
 
 procedure freeModule;
--- a/hedgewars/uVariables.pas	Sat Feb 05 15:36:02 2011 +0100
+++ b/hedgewars/uVariables.pas	Mon Feb 14 08:31:45 2011 -0500
@@ -141,6 +141,7 @@
 
 {$IFDEF SDL13}
     SDLwindow       : PSDL_Window;
+    SDLrender       : PSDL_Renderer;
 {$ENDIF}
 
     WorldDx: LongInt;
@@ -2337,6 +2338,7 @@
 
 {$IFDEF SDL13}
     SDLwindow       := nil;
+    SDLrender       := nil;
 {$ENDIF}
 
     // those values still are not perfect
--- a/misc/wrapper.c	Sat Feb 05 15:36:02 2011 +0100
+++ b/misc/wrapper.c	Mon Feb 14 08:31:45 2011 -0500
@@ -6,24 +6,28 @@
  - this executable expect a save file "Save.hws" and the data folder "Data" to be in the same launching directory
  */
 
-#import <stdio.h>
-#import <stdlib.h>
+#include <stdlib.h>
 
 extern void Game (const char **);
 
-int SDL_main (int argc, const char **argv) {
+int SDL_main (int argc, const char **argv)
+{
+    // Note: if you get a segfault or other unexpected crashes on startup
+    // make sure that these arguments are up-to-date with the ones actual needed
 
-    const char **gameArgs = (const char**) malloc(sizeof(char *) * 9);
+    const char **gameArgs = (const char**) malloc(sizeof(char *) * 11);
 
-    gameArgs[0] = "wrapper";    //UserNick
-	gameArgs[1] = "0";          //ipcPort
-	gameArgs[2] = "0";          //isSoundEnabled
-	gameArgs[3] = "0";          //isMusicEnabled
-	gameArgs[4] = "en.txt";     //cLocaleFName
-	gameArgs[5] = "0";          //cAltDamage
-	gameArgs[6] = "768";        //cScreenHeight
-    gameArgs[7] = "1024";       //cScreenHeight
-    gameArgs[8] = "Save.hws";   //recordFileName
+    gameArgs[ 0] = "0";          //ipcPort
+    gameArgs[ 1] = "1024";       //cScreenWidth
+    gameArgs[ 2] = "768";        //cScreenHeight
+    gameArgs[ 3] = "0";          //cReducedQuality
+    gameArgs[ 4] = "en.txt";     //cLocaleFName
+    gameArgs[ 5] = "wrapper";    //UserNick
+    gameArgs[ 6] = "1";          //isSoundEnabled
+    gameArgs[ 7] = "1";          //isMusicEnabled
+    gameArgs[ 8] = "1";          //cAltDamage
+    gameArgs[ 9] = "0.0";        //rotationQt
+    gameArgs[10] = "Save.hws";   //recordFileName
 
     Game(gameArgs);
     free(gameArgs);
--- a/project_files/HedgewarsMobile/Classes/GameSetup.m	Sat Feb 05 15:36:02 2011 +0100
+++ b/project_files/HedgewarsMobile/Classes/GameSetup.m	Mon Feb 14 08:31:45 2011 -0500
@@ -394,8 +394,10 @@
                 }
                 break;
             case 'q':
-                // game ended, can remove the savefile
+                // game ended, can remove the savefile and the trailing overlay (when dualhead)
                 [[NSFileManager defaultManager] removeItemAtPath:self.savePath error:nil];
+                if (IS_DUALHEAD())
+                    [[NSNotificationCenter defaultCenter] postNotificationName:@"remove overlay" object:nil];
                 break;
             case 'Q':
                 // game exited but not completed, nothing to do (just don't save the message)
--- a/project_files/HedgewarsMobile/Classes/InGameMenuViewController.h	Sat Feb 05 15:36:02 2011 +0100
+++ b/project_files/HedgewarsMobile/Classes/InGameMenuViewController.h	Mon Feb 14 08:31:45 2011 -0500
@@ -24,13 +24,13 @@
 
 @interface InGameMenuViewController : UITableViewController <UIActionSheetDelegate> {
     NSArray *menuList;
-    SDL_Window *sdlwindow;
+    BOOL shouldTakeScreenshot;
 }
 
 @property (nonatomic,retain) NSArray *menuList;
 
 -(void) present;
 -(void) dismiss;
--(void) removeChat;
+-(void) saveCurrentScreenToPhotoAlbum:(UIAlertView *)alert;
 
 @end
--- a/project_files/HedgewarsMobile/Classes/InGameMenuViewController.m	Sat Feb 05 15:36:02 2011 +0100
+++ b/project_files/HedgewarsMobile/Classes/InGameMenuViewController.m	Mon Feb 14 08:31:45 2011 -0500
@@ -25,6 +25,9 @@
 #import "CommodityFunctions.h"
 #import "SDL_sysvideo.h"
 #import "SDL_uikitkeyboard.h"
+#import "OpenGLES/ES1/gl.h"
+
+#define VIEW_HEIGHT 200
 
 @implementation InGameMenuViewController
 @synthesize menuList;
@@ -43,36 +46,17 @@
     NSArray *array = [[NSArray alloc] initWithObjects:
                       NSLocalizedString(@"Show Help", @""),
                       NSLocalizedString(@"Tag", @""),
+                      NSLocalizedString(@"Snapshot",@""),
                       NSLocalizedString(@"End Game", @""),
                       nil];
     self.menuList = array;
     [array release];
 
-    // save the sdl window (!= uikit window) for future reference
-    SDL_VideoDevice *videoDevice = SDL_GetVideoDevice();
-    if (videoDevice) {
-        SDL_VideoDisplay *display = &videoDevice->displays[0];
-        if (display)
-            sdlwindow = display->windows;
-    }
     [super viewDidLoad];
 }
 
--(void) viewWillAppear:(BOOL)animated {
-    if (sdlwindow == NULL) {
-        SDL_VideoDevice *_this = SDL_GetVideoDevice();
-        if (_this) {
-            SDL_VideoDisplay *display = &_this->displays[0];
-            if (display)
-                sdlwindow = display->windows;
-        }
-    }
-    [super viewWillAppear:animated];
-}
-
 -(void) viewDidUnload {
     self.menuList = nil;
-    sdlwindow = NULL;
     MSG_DIDUNLOAD();
     [super viewDidUnload];
 }
@@ -87,11 +71,11 @@
 -(void) present {
     CGRect screen = [[UIScreen mainScreen] bounds];
     self.view.backgroundColor = [UIColor clearColor];
-    self.view.frame = CGRectMake(screen.size.height, 0, 200, 170);
+    self.view.frame = CGRectMake(screen.size.height, 0, 200, VIEW_HEIGHT);
 
     [UIView beginAnimations:@"showing popover" context:NULL];
     [UIView setAnimationDuration:0.35];
-    self.view.frame = CGRectMake(screen.size.height-200, 0, 200, 170);
+    self.view.frame = CGRectMake(screen.size.height-200, 0, 200, VIEW_HEIGHT);
     [UIView commitAnimations];
 }
 
@@ -100,13 +84,33 @@
         CGRect screen = [[UIScreen mainScreen] bounds];
         [UIView beginAnimations:@"hiding popover" context:NULL];
         [UIView setAnimationDuration:0.35];
-        self.view.frame = CGRectMake(screen.size.height, 0, 200, 170);
+        self.view.frame = CGRectMake(screen.size.height, 0, 200, VIEW_HEIGHT);
         [UIView commitAnimations];
+        [self.view performSelector:@selector(removeFromSuperview) withObject:nil afterDelay:0.35];
     }
 
-    [self.view performSelector:@selector(removeFromSuperview) withObject:nil afterDelay:0.35];
+    HW_chatEnd();
+    SDL_iPhoneKeyboardHide((SDL_Window *)HW_getSDLWindow());
 
-    [self removeChat];
+    if (shouldTakeScreenshot) {
+        UIAlertView *alert = [[UIAlertView alloc] initWithTitle:@"Please wait"
+                                                        message:nil
+                                                       delegate:nil
+                                              cancelButtonTitle:nil
+                                              otherButtonTitles:nil];
+        [alert show];
+        UIActivityIndicatorView *indicator = [[UIActivityIndicatorView alloc]
+                                              initWithActivityIndicatorStyle:UIActivityIndicatorViewStyleWhiteLarge];
+        indicator.center = CGPointMake(alert.bounds.size.width / 2, alert.bounds.size.height - 45);
+        [indicator startAnimating];
+        [alert addSubview:indicator];
+        [indicator release];
+
+        // all these hacks because of the PAUSE caption on top of everything...
+        [self performSelector:@selector(saveCurrentScreenToPhotoAlbum:) withObject:alert afterDelay:0.3];
+    }
+    shouldTakeScreenshot = NO;
+
 }
 
 #pragma mark -
@@ -116,7 +120,7 @@
 }
 
 -(NSInteger) tableView:(UITableView *)tableView numberOfRowsInSection:(NSInteger)section {
-    return 3;
+    return 4;
 }
 
 -(UITableViewCell *)tableView:(UITableView *)aTableView cellForRowAtIndexPath:(NSIndexPath *)indexPath {
@@ -127,7 +131,7 @@
         cell = [[[UITableViewCell alloc] initWithStyle:UITableViewCellStyleDefault
                                        reuseIdentifier:cellIdentifier] autorelease];
     }
-    cell.textLabel.text = [menuList objectAtIndex:[indexPath row]];
+    cell.textLabel.text = [self.menuList objectAtIndex:[indexPath row]];
 
     if (IS_IPAD())
         cell.textLabel.textAlignment = UITextAlignmentCenter;
@@ -137,20 +141,30 @@
 
 -(void) tableView:(UITableView *)aTableView didSelectRowAtIndexPath:(NSIndexPath *)indexPath {
     UIActionSheet *actionSheet;
+    UIAlertView *alert;
 
     switch ([indexPath row]) {
         case 0:
             [[NSNotificationCenter defaultCenter] postNotificationName:@"show help ingame" object:nil];
+
             break;
         case 1:
-            if (SDL_iPhoneKeyboardIsShown(sdlwindow))
-                [self removeChat];
-            else {
-                HW_chat();
-                SDL_iPhoneKeyboardShow(sdlwindow);
-            }
+            HW_chat();
+            SDL_iPhoneKeyboardShow((SDL_Window *)HW_getSDLWindow());
+
             break;
         case 2:
+            alert = [[UIAlertView alloc] initWithTitle:NSLocalizedString(@"Going to take a screenshot",@"")
+                                               message:NSLocalizedString(@"The game snapshot will be placed in your Photo Album and it will be taken as soon as the pause menu is dismissed",@"")
+                                              delegate:nil
+                                     cancelButtonTitle:NSLocalizedString(@"Ok, got it",@"")
+                                     otherButtonTitles:nil];
+            [alert show];
+            [alert release];
+            shouldTakeScreenshot = YES;
+
+            break;
+        case 3:
             // expand the view (and table) so that the actionsheet can be selected on the iPhone
             if (IS_IPAD() == NO) {
                 CGRect screen = [[UIScreen mainScreen] bounds];
@@ -177,13 +191,6 @@
     [aTableView deselectRowAtIndexPath:indexPath animated:YES];
 }
 
--(void) removeChat {
-    if (SDL_iPhoneKeyboardIsShown(sdlwindow)) {
-        SDL_iPhoneKeyboardHide(sdlwindow);
-        HW_chatEnd();
-    }
-}
-
 #pragma mark -
 #pragma mark actionSheet methods
 -(void) actionSheet:(UIActionSheet *)actionSheet didDismissWithButtonIndex:(NSInteger) buttonIndex {
@@ -191,12 +198,70 @@
         CGRect screen = [[UIScreen mainScreen] bounds];
         [UIView beginAnimations:@"table width less" context:NULL];
         [UIView setAnimationDuration:0.2];
-        self.view.frame = CGRectMake(screen.size.height-200, 0, 200, 170);
+        self.view.frame = CGRectMake(screen.size.height-200, 0, 200, VIEW_HEIGHT);
         [UIView commitAnimations];
     }
 
-    if ([actionSheet cancelButtonIndex] != buttonIndex)
+    if ([actionSheet cancelButtonIndex] != buttonIndex) {
+        if (IS_DUALHEAD())
+            [[NSNotificationCenter defaultCenter] postNotificationName:@"remove overlay" object:nil];
         HW_terminate(NO);
+    }
+}
+
+#pragma mark save screenshot
+//by http://www.bit-101.com/blog/?p=1861
+// callback for CGDataProviderCreateWithData
+void releaseData(void *info, const void *data, size_t dataSize) {
+    DLog(@"freeing raw data\n");
+    free((void *)data);
+}
+
+// callback for UIImageWriteToSavedPhotosAlbum
+-(void) image:(UIImage *)image didFinishSavingWithError:(NSError *)error contextInfo:(void *)contextInfo {
+    DLog(@"Save finished\n");
+    [image release];
+    UIAlertView *alert = (UIAlertView *)contextInfo;
+    [alert dismissWithClickedButtonIndex:0 animated:YES];
+    [alert release];
 }
 
+// the resolution of the buffer is always equal to the hardware device even if scaled
+-(void) saveCurrentScreenToPhotoAlbum:(UIAlertView *)alert {
+    CGRect screenRect = [[UIScreen mainScreen] bounds];
+    int width = screenRect.size.width;
+    int height = screenRect.size.height;
+
+    NSInteger size = width * height * 4;
+    GLubyte *buffer = (GLubyte *) malloc(size * sizeof(GLubyte));
+    GLubyte *buffer_flipped = (GLubyte *) malloc(size * sizeof(GLubyte));
+
+    glReadPixels(0, 0, width, height, GL_RGBA, GL_UNSIGNED_BYTE, buffer);
+    HW_screenshot();
+    // flip the data as glReadPixels here reads upside down
+    for(int y = 0; y <height; y++)
+        for(int x = 0; x <width * 4; x++)
+            buffer_flipped[(int)((height - 1 - y) * width * 4 + x)] = buffer[(int)(y * 4 * width + x)];
+    free(buffer);
+
+    CGDataProviderRef provider = CGDataProviderCreateWithData(NULL, buffer_flipped, size, releaseData);
+    CGColorSpaceRef colorSpaceRef = CGColorSpaceCreateDeviceRGB();
+    CGBitmapInfo bitmapInfo = kCGBitmapByteOrderDefault;
+    CGColorRenderingIntent renderingIntent = kCGRenderingIntentDefault;
+    CGImageRef imageRef = CGImageCreate(width, height, 8, 32, 4 * width, colorSpaceRef, bitmapInfo, provider, NULL, NO, renderingIntent);
+
+    CGColorSpaceRelease(colorSpaceRef);
+    CGDataProviderRelease(provider);
+
+    UIImage *image;
+    if ([UIImage respondsToSelector:@selector(imageWithCGImage:scale:orientation:)])
+        image = [[UIImage alloc] initWithCGImage:imageRef scale:1 orientation:UIImageOrientationRight];
+    else
+        image = [[UIImage alloc] initWithCGImage:imageRef];
+    CGImageRelease(imageRef);
+
+    UIImageWriteToSavedPhotosAlbum(image, self, @selector(image:didFinishSavingWithError:contextInfo:), (void *)alert); // add callback for finish saving
+}
+
+
 @end
--- a/project_files/HedgewarsMobile/Classes/OverlayViewController.m	Sat Feb 05 15:36:02 2011 +0100
+++ b/project_files/HedgewarsMobile/Classes/OverlayViewController.m	Mon Feb 14 08:31:45 2011 -0500
@@ -180,12 +180,18 @@
     // add timer to runloop, otherwise it doesn't work
     [[NSRunLoop currentRunLoop] addTimer:dimTimer forMode:NSDefaultRunLoopMode];
 
-    // become listener of some notifications
+    // display the help page, required by the popover on ipad
     [[NSNotificationCenter defaultCenter] addObserver:self
                                              selector:@selector(showHelp:)
                                                  name:@"show help ingame"
                                                object:nil];
 
+    // remove the view, required by the dual head version
+    [[NSNotificationCenter defaultCenter] addObserver:self
+                                             selector:@selector(removeOverlay:)
+                                                 name:@"remove overlay"
+                                               object:nil];
+
     // for iOS >= 3.2
     if ([UIScreen respondsToSelector:@selector(screens)]) {
         [[NSNotificationCenter defaultCenter] addObserver:self
@@ -252,6 +258,13 @@
     doNotDim();
 }
 
+-(void) removeOverlay:(id) sender {
+    [self.popupMenu performSelectorOnMainThread:@selector(dismiss) withObject:nil waitUntilDone:YES];
+    [self.popoverController performSelectorOnMainThread:@selector(dismissPopoverAnimated:) withObject:nil waitUntilDone:YES];
+    [self.view performSelectorOnMainThread:@selector(removeFromSuperview) withObject:nil waitUntilDone:YES];
+    HW_terminate(NO);
+}
+
 -(void) didReceiveMemoryWarning {
     if (self.popupMenu.view.superview == nil)
         self.popupMenu = nil;
@@ -461,7 +474,7 @@
             self.popupMenu = [[InGameMenuViewController alloc] initWithStyle:UITableViewStylePlain];
         if (self.popoverController == nil) {
             self.popoverController = [[UIPopoverController alloc] initWithContentViewController:self.popupMenu];
-            [self.popoverController setPopoverContentSize:CGSizeMake(220, 170) animated:YES];
+            [self.popoverController setPopoverContentSize:CGSizeMake(220, 200) animated:YES];
             [self.popoverController setPassthroughViews:[NSArray arrayWithObject:self.view]];
         }
 
@@ -486,12 +499,10 @@
         if (HW_isPaused())
             HW_pauseToggle();
 
-        if (IS_IPAD()) {
-            [(InGameMenuViewController *)[[self popoverController] contentViewController] removeChat];
+        [self.popupMenu dismiss];
+        if (IS_IPAD())
             [self.popoverController dismissPopoverAnimated:YES];
-        } else {
-            [self.popupMenu dismiss];
-        }
+
         [self buttonReleased:nil];
     }
 }
--- a/project_files/HedgewarsMobile/Classes/PascalImports.h	Sat Feb 05 15:36:02 2011 +0100
+++ b/project_files/HedgewarsMobile/Classes/PascalImports.h	Mon Feb 14 08:31:45 2011 -0500
@@ -63,11 +63,13 @@
     void HW_chat(void);
     void HW_chatEnd(void);
     void HW_tab(void);
+    void HW_screenshot(void);
 
     void HW_pause(void);
     void HW_pauseToggle(void);
     BOOL HW_isPaused(void);
 
+    void *HW_getSDLWindow(void);
     void HW_terminate(BOOL andCloseFrontend);
     void HW_suspend(void);
     void HW_resume(void);
--- a/project_files/HedgewarsMobile/Classes/StatsPageViewController.m	Sat Feb 05 15:36:02 2011 +0100
+++ b/project_files/HedgewarsMobile/Classes/StatsPageViewController.m	Mon Feb 14 08:31:45 2011 -0500
@@ -141,8 +141,10 @@
 #pragma mark -
 #pragma mark Table view delegate
 -(void) tableView:(UITableView *)tableView didSelectRowAtIndexPath:(NSIndexPath *)indexPath {
-    if ([indexPath section] == 3)
+    if ([indexPath section] == 3) {
+        playSound(@"backSound");
         [self dismissModalViewControllerAnimated:YES];
+    }
 }
 
 #pragma mark -
--- a/project_files/HedgewarsMobile/Classes/TeamConfigViewController.m	Sat Feb 05 15:36:02 2011 +0100
+++ b/project_files/HedgewarsMobile/Classes/TeamConfigViewController.m	Mon Feb 14 08:31:45 2011 -0500
@@ -77,7 +77,9 @@
         selectedTeamsCount = [self.listOfSelectedTeams count];
         allTeamsCount = [self.listOfTeams count];
 
-        self.cachedContentsOfDir = [[NSArray alloc] initWithArray:contentsOfDir copyItems:YES];
+        NSArray *contents = [[NSArray alloc] initWithArray:contentsOfDir copyItems:YES];
+        self.cachedContentsOfDir = contents;
+        [contents release];
     }
     [self.tableView reloadData];
 }
--- a/project_files/HedgewarsMobile/Hedgewars.xcodeproj/project.pbxproj	Sat Feb 05 15:36:02 2011 +0100
+++ b/project_files/HedgewarsMobile/Hedgewars.xcodeproj/project.pbxproj	Mon Feb 14 08:31:45 2011 -0500
@@ -715,42 +715,42 @@
 			isa = PBXContainerItemProxy;
 			containerPortal = 617988D3114AAA3900BA94A9 /* SDLiPhoneOS.xcodeproj */;
 			proxyType = 2;
-			remoteGlobalIDString = FD6526630DE8FCCB002AD96B /* libSDLiPhoneOS.a */;
+			remoteGlobalIDString = FD6526630DE8FCCB002AD96B;
 			remoteInfo = StaticLibiPhoneOS;
 		};
 		61B7A54F12FA129F0051E14E /* PBXContainerItemProxy */ = {
 			isa = PBXContainerItemProxy;
 			containerPortal = 617988D3114AAA3900BA94A9 /* SDLiPhoneOS.xcodeproj */;
 			proxyType = 2;
-			remoteGlobalIDString = 006E982211955059001DE610 /* testsdl.app */;
+			remoteGlobalIDString = 006E982211955059001DE610;
 			remoteInfo = testsdl;
 		};
 		61B7A55712FA12AD0051E14E /* PBXContainerItemProxy */ = {
 			isa = PBXContainerItemProxy;
 			containerPortal = 6127232E117DF752005B90CF /* SDL_image.xcodeproj */;
 			proxyType = 2;
-			remoteGlobalIDString = BE1FA74107AF4C45004B6283 /* libSDL_image.a */;
+			remoteGlobalIDString = BE1FA74107AF4C45004B6283;
 			remoteInfo = "Static Library";
 		};
 		61B7A55F12FA12BF0051E14E /* PBXContainerItemProxy */ = {
 			isa = PBXContainerItemProxy;
 			containerPortal = 6179898B114AB3FA00BA94A9 /* SDL_mixer.xcodeproj */;
 			proxyType = 2;
-			remoteGlobalIDString = BE1FA95407AF96B2004B6283 /* libSDL_mixer.a */;
+			remoteGlobalIDString = BE1FA95407AF96B2004B6283;
 			remoteInfo = "Static Library";
 		};
 		61B7A56712FA12D00051E14E /* PBXContainerItemProxy */ = {
 			isa = PBXContainerItemProxy;
 			containerPortal = 618E27B612A2C30700C20EF0 /* SDL_net.xcodeproj */;
 			proxyType = 2;
-			remoteGlobalIDString = BE48FF6F07AFA9A900BB41DA /* libSDL_net.a */;
+			remoteGlobalIDString = BE48FF6F07AFA9A900BB41DA;
 			remoteInfo = "Static Library";
 		};
 		61B7A58F12FA13330051E14E /* PBXContainerItemProxy */ = {
 			isa = PBXContainerItemProxy;
 			containerPortal = 61798A0B114AB65600BA94A9 /* SDL_ttf.xcodeproj */;
 			proxyType = 2;
-			remoteGlobalIDString = BE48FD6E07AFA17000BB41DA /* libSDL_ttf.a */;
+			remoteGlobalIDString = BE48FD6E07AFA17000BB41DA;
 			remoteInfo = "Static Library";
 		};
 		928301590F10E41300CC5A3C /* PBXContainerItemProxy */ = {
@@ -1576,7 +1576,7 @@
 /* End PBXGroup section */
 
 /* Begin PBXNativeTarget section */
-		1D6058900D05DD3D006BFB54 /* Hedgewars */ = {
+		1D6058900D05DD3D006BFB54 /* Test Lua */ = {
 			isa = PBXNativeTarget;
 			buildConfigurationList = 1D6058960D05DD3E006BFB54 /* Build configuration list for PBXNativeTarget "Hedgewars" */;
 			buildPhases = (
@@ -1667,7 +1667,7 @@
 			);
 			projectRoot = "";
 			targets = (
-				1D6058900D05DD3D006BFB54 /* Hedgewars */,
+				1D6058900D05DD3D006BFB54 /* Test Lua */,
 				928301160F10CAFC00CC5A3C /* fpc */,
 				6179928B114AE0C800BA94A9 /* UpdateDataFolder */,
 			);
--- a/project_files/HedgewarsMobile/SDL.patch	Sat Feb 05 15:36:02 2011 +0100
+++ b/project_files/HedgewarsMobile/SDL.patch	Mon Feb 14 08:31:45 2011 -0500
@@ -1,7 +1,7 @@
-diff -r f2c2f0ecba5f Xcode-iPhoneOS/SDL/SDLiPhoneOS.xcodeproj/project.pbxproj
---- a/Xcode-iPhoneOS/SDL/SDLiPhoneOS.xcodeproj/project.pbxproj	Sun Jan 30 13:42:05 2011 -0800
-+++ b/Xcode-iPhoneOS/SDL/SDLiPhoneOS.xcodeproj/project.pbxproj	Mon Jan 31 23:57:58 2011 +0100
-@@ -1564,11 +1564,15 @@
+diff -r 1fbe1c202501 Xcode-iPhoneOS/SDL/SDLiPhoneOS.xcodeproj/project.pbxproj
+--- a/Xcode-iPhoneOS/SDL/SDLiPhoneOS.xcodeproj/project.pbxproj	Mon Feb 07 10:40:21 2011 -0800
++++ b/Xcode-iPhoneOS/SDL/SDLiPhoneOS.xcodeproj/project.pbxproj	Mon Feb 07 23:21:28 2011 +0100
+@@ -1603,11 +1603,15 @@
  			isa = XCBuildConfiguration;
  			buildSettings = {
  				ALWAYS_SEARCH_USER_PATHS = NO;
@@ -17,7 +17,7 @@
  				IPHONEOS_DEPLOYMENT_TARGET = 3.1;
  				ONLY_ACTIVE_ARCH = NO;
  				PREBINDING = NO;
-@@ -1581,12 +1585,18 @@
+@@ -1620,12 +1624,18 @@
  			isa = XCBuildConfiguration;
  			buildSettings = {
  				ALWAYS_SEARCH_USER_PATHS = NO;
@@ -37,20 +37,9 @@
  				PREBINDING = NO;
  				SDKROOT = iphoneos;
  				TARGETED_DEVICE_FAMILY = "1,2";
-diff -r f2c2f0ecba5f Xcode-iPhoneOS/SDL/testsdl-Info.plist
---- a/Xcode-iPhoneOS/SDL/testsdl-Info.plist	Sun Jan 30 13:42:05 2011 -0800
-+++ b/Xcode-iPhoneOS/SDL/testsdl-Info.plist	Mon Jan 31 23:57:58 2011 +0100
-@@ -16,7 +16,5 @@
- 	<string>????</string>
- 	<key>CFBundleVersion</key>
- 	<string>1.0</string>
--	<key>NSMainNibFile</key>
--	<string>MainWindow</string>
- </dict>
- </plist>
-diff -r f2c2f0ecba5f include/SDL_config_iphoneos.h
---- a/include/SDL_config_iphoneos.h	Sun Jan 30 13:42:05 2011 -0800
-+++ b/include/SDL_config_iphoneos.h	Mon Jan 31 23:57:58 2011 +0100
+diff -r 1fbe1c202501 include/SDL_config_iphoneos.h
+--- a/include/SDL_config_iphoneos.h	Mon Feb 07 10:40:21 2011 -0800
++++ b/include/SDL_config_iphoneos.h	Mon Feb 07 23:21:28 2011 +0100
 @@ -119,7 +119,7 @@
  /* enable iPhone version of Core Audio driver */
  #define SDL_AUDIO_DRIVER_COREAUDIOIPHONE 1
@@ -60,7 +49,7 @@
  
  /* Enable the stub haptic driver (src/haptic/dummy/\*.c) */
  #define SDL_HAPTIC_DISABLED	1
-@@ -140,14 +140,17 @@
+@@ -140,15 +140,18 @@
  
  /* Supported video drivers */
  #define SDL_VIDEO_DRIVER_UIKIT	1
@@ -70,6 +59,8 @@
  /* enable OpenGL ES */
  #define SDL_VIDEO_OPENGL_ES	1
  #define SDL_VIDEO_RENDER_OGL_ES	1
+-#define SDL_VIDEO_RENDER_OGL_ES2	1
++#define SDL_VIDEO_RENDER_OGL_ES2	0
  
  /* Enable system power support */
 -#define SDL_POWER_UIKIT 1
@@ -80,7 +71,7 @@
  
  /* enable iPhone keyboard support */
  #define SDL_IPHONE_KEYBOARD 1
-@@ -157,4 +160,7 @@
+@@ -158,4 +161,7 @@
   */
  #define SDL_IPHONE_MAX_GFORCE 5.0
  
@@ -88,182 +79,14 @@
 +#define SDL_VIEW_TAG 456987
 +
  #endif /* _SDL_config_iphoneos_h */
-diff -r f2c2f0ecba5f src/video/SDL_video.c
---- a/src/video/SDL_video.c	Sun Jan 30 13:42:05 2011 -0800
-+++ b/src/video/SDL_video.c	Mon Jan 31 23:57:58 2011 +0100
-@@ -1414,9 +1414,9 @@
-         SDL_MinimizeWindow(window);
-     }
- 
--    if (display->gamma && _this->SetDisplayGammaRamp) {
-+    /*if (display->gamma && _this->SetDisplayGammaRamp) {
-         _this->SetDisplayGammaRamp(_this, display, display->saved_gamma);
--    }
-+    }*/
-     if ((window->flags & (SDL_WINDOW_INPUT_GRABBED | SDL_WINDOW_FULLSCREEN))
-         && _this->SetWindowGrab) {
-         _this->SetWindowGrab(_this, window);
-diff -r f2c2f0ecba5f src/video/uikit/SDL_uikitopengles.m
---- a/src/video/uikit/SDL_uikitopengles.m	Sun Jan 30 13:42:05 2011 -0800
-+++ b/src/video/uikit/SDL_uikitopengles.m	Mon Jan 31 23:57:58 2011 +0100
-@@ -115,6 +115,7 @@
- 									aBits: _this->gl_config.alpha_size \
- 									depthBits: _this->gl_config.depth_size];
- 	
-+	view.tag = SDL_VIEW_TAG;
- 	data->view = view;
- 	
- 	/* add the view to our window */
-diff -r f2c2f0ecba5f src/video/uikit/SDL_uikitopenglview.m
---- a/src/video/uikit/SDL_uikitopenglview.m	Sun Jan 30 13:42:05 2011 -0800
-+++ b/src/video/uikit/SDL_uikitopenglview.m	Mon Jan 31 23:57:58 2011 +0100
-@@ -117,6 +117,8 @@
- 			return NO;
- 		}
- 		/* end create buffers */
-+            if ([[UIScreen mainScreen] respondsToSelector:@selector(scale)])
-+                self.contentScaleFactor = [UIScreen mainScreen].scale;
- 	}
- 	return self;
- }
-diff -r f2c2f0ecba5f src/video/uikit/SDL_uikitview.h
---- a/src/video/uikit/SDL_uikitview.h	Sun Jan 30 13:42:05 2011 -0800
-+++ b/src/video/uikit/SDL_uikitview.h	Mon Jan 31 23:57:58 2011 +0100
-@@ -23,11 +23,11 @@
- #include "SDL_stdinc.h"
- #include "SDL_events.h"
- 
--#define IPHONE_TOUCH_EFFICIENT_DANGEROUS
--#define FIXED_MULTITOUCH
-+#undef IPHONE_TOUCH_EFFICIENT_DANGEROUS
-+#undef FIXED_MULTITOUCH
- 
- #ifndef IPHONE_TOUCH_EFFICIENT_DANGEROUS
--#define MAX_SIMULTANEOUS_TOUCHES 5
-+#define MAX_SIMULTANEOUS_TOUCHES 0
- #endif
- 
- /* *INDENT-OFF* */
-diff -r f2c2f0ecba5f src/video/uikit/SDL_uikitview.m
---- a/src/video/uikit/SDL_uikitview.m	Sun Jan 30 13:42:05 2011 -0800
-+++ b/src/video/uikit/SDL_uikitview.m	Mon Jan 31 23:57:58 2011 +0100
-@@ -298,6 +298,7 @@
- 
- /* Terminates the editing session */
- - (BOOL)textFieldShouldReturn:(UITextField*)_textField {
-+	SDL_SendKeyboardKey(SDL_PRESSED, SDL_SCANCODE_RETURN);
- 	[self hideKeyboard];
- 	return YES;
- }
-@@ -312,7 +313,7 @@
- int SDL_iPhoneKeyboardShow(SDL_Window * window) {
- 	
- 	SDL_WindowData *data;
--	SDL_uikitview *view;
-+	SDL_uikitview *view = NULL;
- 	
- 	if (NULL == window) {
- 		SDL_SetError("Window does not exist");
-@@ -320,7 +321,8 @@
- 	}
- 	
- 	data = (SDL_WindowData *)window->driverdata;
--	view = data->view;
-+	if (data != NULL)
-+            view = data->view;
- 	
- 	if (nil == view) {
- 		SDL_SetError("Window has no view");
-@@ -335,7 +337,7 @@
- int SDL_iPhoneKeyboardHide(SDL_Window * window) {
- 	
- 	SDL_WindowData *data;
--	SDL_uikitview *view;
-+	SDL_uikitview *view = NULL;
- 	
- 	if (NULL == window) {
- 		SDL_SetError("Window does not exist");
-@@ -343,7 +345,8 @@
- 	}	
- 	
- 	data = (SDL_WindowData *)window->driverdata;
--	view = data->view;
-+	if (data != NULL)
-+            view = data->view;
- 	
- 	if (NULL == view) {
- 		SDL_SetError("Window has no view");
-@@ -358,7 +361,7 @@
- SDL_bool SDL_iPhoneKeyboardIsShown(SDL_Window * window) {
- 	
- 	SDL_WindowData *data;
--	SDL_uikitview *view;
-+	SDL_uikitview *view = NULL;
- 	
- 	if (NULL == window) {
- 		SDL_SetError("Window does not exist");
-@@ -366,7 +369,8 @@
- 	}	
- 	
- 	data = (SDL_WindowData *)window->driverdata;
--	view = data->view;
-+	if (data != NULL)
-+            view = data->view;
- 	
- 	if (NULL == view) {
- 		SDL_SetError("Window has no view");
-@@ -380,7 +384,7 @@
- int SDL_iPhoneKeyboardToggle(SDL_Window * window) {
- 	
- 	SDL_WindowData *data;
--	SDL_uikitview *view;
-+	SDL_uikitview *view = NULL;
- 	
- 	if (NULL == window) {
- 		SDL_SetError("Window does not exist");
-@@ -388,7 +392,8 @@
- 	}	
- 	
- 	data = (SDL_WindowData *)window->driverdata;
--	view = data->view;
-+	if (data != NULL)
-+            view = data->view;
- 	
- 	if (NULL == view) {
- 		SDL_SetError("Window has no view");
-diff -r f2c2f0ecba5f src/video/uikit/SDL_uikitwindow.m
---- a/src/video/uikit/SDL_uikitwindow.m	Sun Jan 30 13:42:05 2011 -0800
-+++ b/src/video/uikit/SDL_uikitwindow.m	Mon Jan 31 23:57:58 2011 +0100
-@@ -145,7 +145,10 @@
-     if (SDL_UIKit_supports_multiple_displays) {
-         [uiwindow setScreen:uiscreen];
-     }
--
-+    
-+    if ([UIScreen respondsToSelector:@selector(screens)] && [[UIScreen screens] count] > 1)
-+        uiwindow.screen = [[UIScreen screens] objectAtIndex:1];
-+    
-     if (SetupWindowData(_this, window, uiwindow, SDL_TRUE) < 0) {
-         [uiwindow release];
-         return -1;
-diff -r f2c2f0ecba5f src/video/uikit/keyinfotable.h
---- a/src/video/uikit/keyinfotable.h	Sun Jan 30 13:42:05 2011 -0800
-+++ b/src/video/uikit/keyinfotable.h	Mon Jan 31 23:57:58 2011 +0100
-@@ -54,7 +54,7 @@
- /*  10 */ {   SDL_SCANCODE_UNKNOWN, 0 },
- /*  11 */ {   SDL_SCANCODE_UNKNOWN, 0 },
- /*  12 */ {   SDL_SCANCODE_UNKNOWN, 0 },
--/*  13 */ {   SDL_SCANCODE_UNKNOWN, 0 },
-+/*  13 */ {   SDL_SCANCODE_RETURN, 0 },
- /*  14 */ {   SDL_SCANCODE_UNKNOWN, 0 },
- /*  15 */ {   SDL_SCANCODE_UNKNOWN, 0 },
- /*  16 */ {   SDL_SCANCODE_UNKNOWN, 0 },
-@@ -137,7 +137,7 @@
- /*  93 */ {   SDL_SCANCODE_RIGHTBRACKET, 0 },
- /*  94 */ {   SDL_SCANCODE_6,  KMOD_SHIFT },			/* plus shift modifier '^' */
- /*  95 */ {   SDL_SCANCODE_MINUS,  KMOD_SHIFT },		/* plus shift modifier '_' */
--/*  96 */ {   SDL_SCANCODE_GRAVE,  KMOD_SHIFT },		/* '`'
-+/*  96 */ {   SDL_SCANCODE_GRAVE,  KMOD_SHIFT },		/* '`' */
- /*  97 */ {   SDL_SCANCODE_A, 0	},	
- /*  98 */ {   SDL_SCANCODE_B, 0 },
- /*  99 */ {   SDL_SCANCODE_C, 0 },
+diff -r 1fbe1c202501 src/video/uikit/SDL_uikitopengles.m
+--- a/src/video/uikit/SDL_uikitopengles.m	Mon Feb 07 10:40:21 2011 -0800
++++ b/src/video/uikit/SDL_uikitopengles.m	Mon Feb 07 23:21:28 2011 +0100
+@@ -117,6 +117,7 @@
+                                     majorVersion: _this->gl_config.major_version];
+     
+     data->view = view;
++    view.tag = SDL_VIEW_TAG;
+     
+     /* add the view to our window */
+     [uiwindow addSubview: view ];