Merge default qmlfrontend
authorunc0rr
Mon, 14 Mar 2016 22:08:27 +0300
branchqmlfrontend
changeset 11606 99966b4a6e1e
parent 11544 b69f5f22a3ba (current diff)
parent 11605 dc8de75747f9 (diff)
child 11607 f0dcdbb9b2fe
Merge default
.hgignore
gameServer/OfficialServer/checker.hs
hedgewars/hwengine.pas
--- a/.hgignore	Tue Feb 09 21:11:16 2016 +0300
+++ b/.hgignore	Mon Mar 14 22:08:27 2016 +0300
@@ -23,7 +23,6 @@
 glob:.DS_Store
 glob:*.swp
 glob:*.orig
-glob:*.diff
 glob:vittorio.*
 glob:project_files/HedgewarsMobile/Data/
 glob:project_files/HedgewarsMobile/Build/
@@ -35,7 +34,6 @@
 relre:^release\/
 glob:*.log
 glob:*.cmd
-glob:*.diff
 glob:*.patch
 glob:*.orig
 glob:*.bak
--- a/.travis.yml	Tue Feb 09 21:11:16 2016 +0300
+++ b/.travis.yml	Mon Mar 14 22:08:27 2016 +0300
@@ -14,15 +14,33 @@
   - BUILD_ARGS="-DNOSERVER=1 -DBUILD_ENGINE_C=1"
   - BUILD_ARGS="-DNOSERVER=1 -DNOVIDEOREC=1 -DNOPNG=1"
   - BUILD_ARGS="-DNOSERVER=1 -DLUA_SYSTEM=0 -DPHYSFS_SYSTEM=0"
+matrix:
+  include:
+  - language: objective-c
+    os: osx
+    compiler:
+    env: BUILD_ARGS="IOS" SDL_LIB_PATH="$TRAVIS_BUILD_DIR/../Library"
+    osx_image: xcode7.2
+    sudo: required
 before_install: |
-  if [ "$TRAVIS_OS_NAME" == "linux" ]; then
+  if [ "$BUILD_ARGS" == "IOS" ]; then
+    hg clone http://hg.libsdl.org/SDL $SDL_LIB_PATH/SDL/
+    hg clone http://hg.libsdl.org/SDL_image $SDL_LIB_PATH/SDL_image/
+    hg clone http://hg.libsdl.org/SDL_net $SDL_LIB_PATH/SDL_net/
+    hg clone http://hg.libsdl.org/SDL_ttf $SDL_LIB_PATH/SDL_ttf/
+    hg clone http://hg.libsdl.org/SDL_mixer $SDL_LIB_PATH/SDL_mixer/
+  elif [ "$TRAVIS_OS_NAME" == "linux" ]; then
     sudo add-apt-repository -y ppa:zoogie/sdl2-snapshots
     sudo apt-get update -qq
   elif [ "$TRAVIS_OS_NAME" == "osx" ]; then
     brew update --all
   fi
 install: |
-  if [ "$TRAVIS_OS_NAME" == "linux" ]; then
+  if [ "$BUILD_ARGS" == "IOS" ]; then
+    # FPC 3.0.0 required for using FPC 3.0.1 which contains rtl for ios
+    sudo bash tools/dmg_pkg_install.sh ftp://freepascal.stack.nl/pub/fpc/dist/3.0.0/i386-macosx/fpc-3.0.0.intel-macosx.dmg
+    sudo bash tools/dmg_pkg_install.sh ftp://freepascal.stack.nl/pub/fpc/dist/3.0.0/i386-macosx/fpc-3.0.1.intel-macosx.cross.ios.dmg
+  elif [ "$TRAVIS_OS_NAME" == "linux" ]; then
     sudo apt-get install debhelper cmake dpkg-dev libqt4-dev qt4-qmake libphysfs-dev libsdl2-dev libsdl2-ttf-dev libsdl2-mixer-dev libsdl2-image-dev libsdl2-net-dev bzip2 ghc libghc-mtl-dev libghc-parsec3-dev libghc-bytestring-show-dev libghc-vector-dev libghc-zlib-dev libghc-random-dev libghc-stm-dev libghc-network-dev libghc-dataenc-dev libghc-hslogger-dev libghc-utf8-string-dev libghc-sha-dev libghc-entropy-dev liblua5.1-0-dev imagemagick fpc fp-compiler fp-units-misc libpng-dev fp-units-gfx libavcodec-dev libavformat-dev libglew1.6-dev
   elif [ "$TRAVIS_OS_NAME" == "osx" ]; then
     brew install fpc glew qt physfs lua51 sdl2 sdl2_image sdl2_net sdl2_ttf ffmpeg ghc cabal-install
@@ -39,12 +57,25 @@
     # avoid installing Sparkle, add default unit path
     export BUILD_ARGS="$BUILD_ARGS -DNOAUTOUPDATE=1 -DCMAKE_Pascal_FLAGS=-Fu/usr/local/lib/fpc/$(fpc -iW)/units/x86_64-darwin/*/"
   fi
-before_script:
-  - mkdir build && cd build && cmake $BUILD_ARGS ..
-script:
-  - make VERBOSE=1
+before_script: |
+  if [ "$BUILD_ARGS" == "IOS" ]; then
+    # More or less stable hw iOS version can be compiled with FPC 3.1.1, btw there are no (easy?) way to build it from sources,
+    # so we just temporary switch Xcode project to use FPC 3.0.1
+    git apply tools/fix_fpc_ios_build_patch.diff
+    xctool -project ./project_files/HedgewarsMobile/Hedgewars.xcodeproj -scheme UpdateDataFolder build
+  else
+    mkdir build && cd build && cmake $BUILD_ARGS ..
+  fi
+script: |
+  if [ "$BUILD_ARGS" == "IOS" ]; then
+    xctool -project ./project_files/HedgewarsMobile/Hedgewars.xcodeproj -scheme Hedgewars -configuration Release build CODE_SIGN_IDENTITY="" CODE_SIGNING_REQUIRED=NO
+  else
+    make VERBOSE=1
+  fi
 after_success: |
-  if [ "$TRAVIS_OS_NAME" == "linux" ]; then
+  if [ "$BUILD_ARGS" == "IOS" ]; then
+    :
+  elif [ "$TRAVIS_OS_NAME" == "linux" ]; then
     make test_verbose
   elif [ "$TRAVIS_OS_NAME" == "osx" ]; then
     make install
--- a/gameServer/Actions.hs	Tue Feb 09 21:11:16 2016 +0300
+++ b/gameServer/Actions.hs	Mon Mar 14 22:08:27 2016 +0300
@@ -728,6 +728,31 @@
     processAction $ AnswerClients chans ["CHAT", "[random]", i !! n]
 
 
+processAction (LoadGhost location) = do
+    ri <- clientRoomA
+    rnc <- gets roomsClients
+    thisRoomChans <- liftM (map sendChan) $ roomClientsS ri
+#if defined(OFFICIAL_SERVER)
+    rm <- io $ room'sM rnc id ri
+    points <- io $ loadFile (B.unpack $ "ghosts/" `B.append` sanitizeName location)
+    when (roomProto rm > 51) $ do
+        processAction $ ModifyRoom $ \r -> r{params = Map.insert "DRAWNMAP" [prependGhostPoints (toP points) $ head $ (params r) Map.! "DRAWNMAP"] (params r)}
+#endif
+    cl <- client's id
+    rm <- io $ room'sM rnc id ri
+    mapM_ processAction $ map (replaceChans thisRoomChans) $ answerFullConfigParams cl (mapParams rm) (params rm)
+    where
+    loadFile :: String -> IO [Int]
+    loadFile fileName = E.handle (\(e :: SomeException) -> return []) $ do
+        points <- liftM read $ readFile fileName
+        return (points `deepseq` points)
+    replaceChans chans (AnswerClients _ msg) = AnswerClients chans msg
+    replaceChans _ a = a
+    toP [] = []
+    toP (p1:p2:ps) = (fromIntegral p1, fromIntegral p2) : toP ps
+{-
+        let a = map (replaceChans chans) $ answerFullConfigParams cl mp p
+-}
 #if defined(OFFICIAL_SERVER)
 processAction SaveReplay = do
     ri <- clientRoomA
@@ -846,4 +871,4 @@
     forM_ (actions `deepseq` actions) processAction
 
 processAction CheckVotes =
-    checkVotes >>= mapM_ processAction
\ No newline at end of file
+    checkVotes >>= mapM_ processAction
--- a/gameServer/CoreTypes.hs	Tue Feb 09 21:11:16 2016 +0300
+++ b/gameServer/CoreTypes.hs	Mon Mar 14 22:08:27 2016 +0300
@@ -93,6 +93,7 @@
     | CheckFailed B.ByteString
     | CheckSuccess [B.ByteString]
     | Random [ClientChan] [B.ByteString]
+    | LoadGhost B.ByteString
     | QueryReplay B.ByteString
     | ShowReplay B.ByteString
     | Cleanup
@@ -154,6 +155,7 @@
         eiEM,
         eiJoin :: !EventsInfo,
         teamsInGame :: !Word,
+        teamIndexes :: ![Word8],
         pendingActions :: ![Action]
     }
 
@@ -236,7 +238,7 @@
         roomBansList :: ![B.ByteString],
         mapParams :: !(Map.Map B.ByteString B.ByteString),
         params :: !(Map.Map B.ByteString [B.ByteString]),
-        roomSaves :: !(Map.Map B.ByteString (Map.Map B.ByteString B.ByteString, Map.Map B.ByteString [B.ByteString]))
+        roomSaves :: !(Map.Map B.ByteString (B.ByteString, Map.Map B.ByteString B.ByteString, Map.Map B.ByteString [B.ByteString]))
     }
 
 newRoom :: RoomInfo
--- a/gameServer/EngineInteraction.hs	Tue Feb 09 21:11:16 2016 +0300
+++ b/gameServer/EngineInteraction.hs	Mon Mar 14 22:08:27 2016 +0300
@@ -19,7 +19,7 @@
 {-# LANGUAGE CPP, OverloadedStrings #-}
 
 #if defined(OFFICIAL_SERVER)
-module EngineInteraction(replayToDemo, checkNetCmd, toEngineMsg, drawnMapData) where
+module EngineInteraction(replayToDemo, checkNetCmd, toEngineMsg, drawnMapData, prependGhostPoints) where
 #else
 module EngineInteraction(checkNetCmd, toEngineMsg) where
 #endif
@@ -33,9 +33,12 @@
 import qualified Data.Map as Map
 import qualified Data.List as L
 import Data.Word
+import Data.Int
 import Data.Bits
 import Control.Arrow
 import Data.Maybe
+import Data.Binary
+import Data.Binary.Put
 -------------
 import CoreTypes
 import Utils
@@ -45,12 +48,13 @@
     this is snippet from http://stackoverflow.com/questions/10043102/how-to-catch-the-decompress-ioerror
     because standard 'catch' doesn't seem to catch decompression errors for some reason
 -}
-import qualified Codec.Compression.Zlib.Internal as Z
+import qualified Codec.Compression.Zlib.Internal as ZI
+import qualified Codec.Compression.Zlib as Z
 
 decompressWithoutExceptions :: BL.ByteString -> Either String BL.ByteString
 decompressWithoutExceptions = finalise
-                            . Z.foldDecompressStream cons nil err
-                            . Z.decompressWithErrors Z.zlibFormat Z.defaultDecompressParams
+                            . ZI.foldDecompressStream cons nil err
+                            . ZI.decompressWithErrors ZI.zlibFormat ZI.defaultDecompressParams
   where err _ msg = Left msg
         nil = Right []
         cons chunk = right (chunk :)
@@ -78,22 +82,25 @@
 splitMessages = L.unfoldr (\b -> if B.null b then Nothing else Just $ B.splitAt (1 + fromIntegral (BW.head b)) b)
 
 
-checkNetCmd :: B.ByteString -> (B.ByteString, B.ByteString, Maybe (Maybe B.ByteString))
-checkNetCmd msg = check decoded
+checkNetCmd :: [Word8] -> B.ByteString -> (B.ByteString, B.ByteString, Maybe (Maybe B.ByteString))
+checkNetCmd teamsIndexes msg = check decoded
     where
         decoded = liftM (splitMessages . BW.pack) $ Base64.decode $ B.unpack msg
         check Nothing = (B.empty, B.empty, Nothing)
         check (Just msgs) = let (a, b) = (filter isLegal msgs, filter isNonEmpty a) in (encode a, encode b, lft a)
         encode = B.pack . Base64.encode . BW.unpack . B.concat
-        isLegal m = (B.length m > 1) && (flip Set.member legalMessages . B.head . B.tail $ m)
+        isLegal m = (B.length m > 1) && (flip Set.member legalMessages . B.head . B.tail $ m) && not (isMalformed (B.head m) (B.tail m))
         lft = foldr l Nothing
         l m n = let m' = B.head $ B.tail m; tst = flip Set.member in
                       if not $ tst timedMessages m' then n
                         else if '+' /= m' then Just Nothing else Just . Just . B.pack . Base64.encode . BW.unpack $ m
         isNonEmpty = (/=) '+' . B.head . B.tail
-        legalMessages = Set.fromList $ "M#+LlRrUuDdZzAaSjJ,sNpPwtgfhbc12345" ++ slotMessages
+        legalMessages = Set.fromList $ "M#+LlRrUuDdZzAaSjJ,NpPwtgfhbc12345" ++ slotMessages
         slotMessages = "\128\129\130\131\132\133\134\135\136\137\138"
         timedMessages = Set.fromList $ "+LlRrUuDdZzAaSjJ,NpPwtgfc12345" ++ slotMessages
+        isMalformed 'h' m | B.length m >= 3 = let hognum = m `B.index` 1; teamnum = m `BW.index` 2 in hognum < '1' || hognum > '8' || teamnum `L.notElem` teamsIndexes
+                          | otherwise = True
+        isMalformed _ _ = False
 
 #if defined(OFFICIAL_SERVER)
 replayToDemo :: [TeamInfo]
@@ -144,7 +151,7 @@
         schemeFlags = map (\(v, (n, m)) -> eml [n, " ", showB $ (readInt_ v) * m])
             $ filter (\(_, (n, _)) -> not $ B.null n)
             $ zip (drop (length gameFlagConsts) scheme) schemeParams
-        schemeAdditional = let scriptParam = B.tail $ scheme !! 41 in [eml ["e$scriptparam ", scriptParam] | not $ B.null scriptParam]
+        schemeAdditional = let scriptParam = B.tail $ scheme !! 42 in [eml ["e$scriptparam ", scriptParam] | not $ B.null scriptParam]
         ammoStr :: B.ByteString
         ammoStr = head . tail $ prms Map.! "AMMO"
         ammo = let l = B.length ammoStr `div` 4; ((a, b), (c, d)) = (B.splitAt l . fst &&& B.splitAt l . snd) . B.splitAt (l * 2) $ ammoStr in
@@ -173,17 +180,35 @@
           L.map (\m -> eml ["edraw ", BW.pack m])
         . L.unfoldr by200
         . BL.unpack
-        . either (const BL.empty) id
+        . unpackDrawnMap
+    where
+        by200 :: [a] -> Maybe ([a], [a])
+        by200 [] = Nothing
+        by200 m = Just $ L.splitAt 200 m
+
+unpackDrawnMap :: B.ByteString -> BL.ByteString
+unpackDrawnMap = either (const BL.empty) id
         . decompressWithoutExceptions
         . BL.pack
         . L.drop 4
         . fromMaybe []
         . Base64.decode
         . B.unpack
-    where
-        by200 :: [a] -> Maybe ([a], [a])
-        by200 [] = Nothing
-        by200 m = Just $ L.splitAt 200 m
+
+compressWithLength :: BL.ByteString -> BL.ByteString
+compressWithLength b = BL.drop 8 . encode . runPut $ do
+    put $ ((fromIntegral $ BL.length b)::Word32)
+    mapM_ putWord8 $ BW.unpack $ BL.toStrict $ Z.compress b
+
+packDrawnMap :: BL.ByteString -> B.ByteString
+packDrawnMap = B.pack
+    . Base64.encode
+    . BW.unpack
+    . BL.toStrict
+    . compressWithLength
+
+prependGhostPoints :: [(Int16, Int16)] -> B.ByteString -> B.ByteString
+prependGhostPoints pts dm = packDrawnMap $ (runPut $ forM_ pts $ \(x, y) -> put x >> put y >> putWord8 99) `BL.append` unpackDrawnMap dm
 
 schemeParams :: [(B.ByteString, Int)]
 schemeParams = [
--- a/gameServer/HWProtoCore.hs	Tue Feb 09 21:11:16 2016 +0300
+++ b/gameServer/HWProtoCore.hs	Mon Mar 14 22:08:27 2016 +0300
@@ -67,7 +67,7 @@
         h "DELEGATE" n | not $ B.null n = handleCmd ["DELEGATE", n]
         h "SAVEROOM" n | not $ B.null n = handleCmd ["SAVEROOM", n]
         h "LOADROOM" n | not $ B.null n = handleCmd ["LOADROOM", n]
-        h "SAVE" n | not $ B.null n = handleCmd ["SAVE", n]
+        h "SAVE" n | not $ B.null n = let (sn, ln) = B.break (== ' ') n in if B.null ln then return [] else handleCmd ["SAVE", sn, B.tail ln]
         h "DELETE" n | not $ B.null n = handleCmd ["DELETE", n]
         h "STATS" _ = handleCmd ["STATS"]
         h "PART" m | not $ B.null m = handleCmd ["PART", m]
--- a/gameServer/HWProtoInRoomState.hs	Tue Feb 09 21:11:16 2016 +0300
+++ b/gameServer/HWProtoInRoomState.hs	Mon Mar 14 22:08:27 2016 +0300
@@ -54,7 +54,7 @@
                 , AnswerClients chans ["RUN_GAME"]
                 , SendUpdateOnThisRoom
                 , AnswerClients chans $ "CLIENT_FLAGS" : "+g" : nicks
-                , ModifyRoomClients (\c -> c{isInGame = True})
+                , ModifyRoomClients (\c -> c{isInGame = True, teamIndexes = map snd . filter (\(t, _) -> teamowner t == nick c) $ zip (teams rm) [0..]})
                 ]
             else
             return [Warning $ loc "Less than two clans!"]
@@ -260,6 +260,8 @@
     rm <- thisRoom
     chans <- roomOthersChans
 
+    let (legalMsgs, nonEmptyMsgs, lastFTMsg) = checkNetCmd (teamIndexes cl) msg
+
     if teamsInGame cl > 0 && (isJust $ gameInfo rm) && (not $ B.null legalMsgs) then
         return $ AnswerClients chans ["EM", legalMsgs]
             : [ModifyRoom (\r -> r{gameInfo = liftM
@@ -269,8 +271,6 @@
                 $ gameInfo r}), RegisterEvent EngineMessage]
         else
         return []
-    where
-        (legalMsgs, nonEmptyMsgs, lastFTMsg) = checkNetCmd msg
 
 
 handleCmd_inRoom ["ROUNDFINISHED", _] = do
@@ -492,8 +492,8 @@
         return [AnswerClients [sendChan cl] ["CHAT", "[server]", "vote: 'yes' or 'no'"]]
 
 
-handleCmd_inRoom ["SAVE", stateName] = serverAdminOnly $ do
-    return [ModifyRoom $ \r -> r{roomSaves = Map.insert stateName (mapParams r, params r) (roomSaves r)}]
+handleCmd_inRoom ["SAVE", stateName, location] = serverAdminOnly $ do
+    return [ModifyRoom $ \r -> r{roomSaves = Map.insert stateName (location, mapParams r, params r) (roomSaves r)}]
 
 handleCmd_inRoom ["DELETE", stateName] = serverAdminOnly $ do
     return [ModifyRoom $ \r -> r{roomSaves = Map.delete stateName (roomSaves r)}]
--- a/gameServer/NetRoutines.hs	Tue Feb 09 21:11:16 2016 +0300
+++ b/gameServer/NetRoutines.hs	Mon Mar 14 22:08:27 2016 +0300
@@ -81,6 +81,7 @@
                     newEventsInfo
                     0
                     []
+                    []
                     )
 
         writeChan chan $ Accept newClient
--- a/gameServer/OfficialServer/checker.hs	Tue Feb 09 21:11:16 2016 +0300
+++ b/gameServer/OfficialServer/checker.hs	Mon Mar 14 22:08:27 2016 +0300
@@ -83,6 +83,7 @@
         start = flip L.elem ["WINNERS", "DRAW"]
         ps ("DRAW" : bs) = "DRAW" : ps bs
         ps ("WINNERS" : n : bs) = let c = readInt_ n in "WINNERS" : n : take c bs ++ (ps $ drop c bs)
+        ps ("GHOST_POINTS" : n : bs) = let c = 2 * (readInt_ n) in "GHOST_POINTS" : n : take c bs ++ (ps $ drop c bs)
         ps ("ACHIEVEMENT" : typ : teamname : location : value : bs) =
             "ACHIEVEMENT" : typ : teamname : location : value : ps bs
         ps _ = []
--- a/gameServer/OfficialServer/extdbinterface.hs	Tue Feb 09 21:11:16 2016 +0300
+++ b/gameServer/OfficialServer/extdbinterface.hs	Mon Mar 14 22:08:27 2016 +0300
@@ -23,6 +23,7 @@
 import Prelude hiding (catch)
 import Control.Monad
 import Control.Exception
+import Control.Monad.State
 import System.IO
 import Data.Maybe
 import Database.MySQL.Simple
@@ -36,6 +37,7 @@
 import CoreTypes
 import Utils
 
+io = liftIO
 
 dbQueryAccount =
     "SELECT CASE WHEN users.status = 1 THEN users.pass ELSE '' END, \
@@ -62,6 +64,7 @@
 
 dbQueryReplayFilename = "SELECT filename FROM achievements WHERE id = ?"
 
+dbQueryBestTime = "SELECT MIN(value) FROM achievements WHERE location = ? AND id <> (SELECT MAX(id) FROM achievements)"
 
 dbInteractionLoop dbConn = forever $ do
     q <- liftM read getLine
@@ -94,7 +97,7 @@
         SendStats clients rooms ->
                 void $ execute dbConn dbQueryStats (clients, rooms)
         StoreAchievements p fileName teams g info ->
-            sequence_ $ parseStats dbConn p fileName teams g info
+            parseStats dbConn p fileName teams g info
 
 
 --readTime = read . B.unpack . B.take 19 . B.drop 8
@@ -107,28 +110,47 @@
     -> [(B.ByteString, B.ByteString)] 
     -> GameDetails
     -> [B.ByteString]
-    -> [IO Int64]
-parseStats dbConn p fileName teams (GameDetails script infRopes vamp infAttacks) = ps
+    -> IO ()
+parseStats dbConn p fileName teams (GameDetails script infRopes vamp infAttacks) d = evalStateT (ps d) ("", maxBound)
     where
     time = readTime fileName
-    ps :: [B.ByteString] -> [IO Int64]
-    ps [] = []
-    ps ("DRAW" : bs) = execute dbConn dbQueryGamesHistory (script, (fromIntegral p) :: Int, fileName, time, vamp, infRopes, infAttacks)
-        : places (map drawParams teams)
-        : ps bs
-    ps ("WINNERS" : n : bs) = let winNum = readInt_ n in execute dbConn dbQueryGamesHistory (script, (fromIntegral p) :: Int, fileName, time, vamp, infRopes, infAttacks)
-        : places (map (placeParams (take winNum bs)) teams)
-        : ps (drop winNum bs)
-    ps ("ACHIEVEMENT" : typ : teamname : location : value : bs) = execute dbConn dbQueryAchievement
-        ( time
-        , typ
-        , fromMaybe "" (lookup teamname teams)
-        , (readInt_ value) :: Int
-        , fileName
-        , location
-        , (fromIntegral p) :: Int
-        ) : ps bs
+    ps :: [B.ByteString] -> StateT (B.ByteString, Int) IO ()
+    ps [] = return ()
+    ps ("DRAW" : bs) = do
+        io $ execute dbConn dbQueryGamesHistory (script, (fromIntegral p) :: Int, fileName, time, vamp, infRopes, infAttacks)
+        io $ places (map drawParams teams)
+        ps bs
+    ps ("WINNERS" : n : bs) = do
+        let winNum = readInt_ n
+        io $ execute dbConn dbQueryGamesHistory (script, (fromIntegral p) :: Int, fileName, time, vamp, infRopes, infAttacks)
+        io $ places (map (placeParams (take winNum bs)) teams)
+        ps (drop winNum bs)
+    ps ("ACHIEVEMENT" : typ : teamname : location : value : bs) = do
+        let result = readInt_ value
+        io $ execute dbConn dbQueryAchievement
+            ( time
+            , typ
+            , fromMaybe "" (lookup teamname teams)
+            , result
+            , fileName
+            , location
+            , (fromIntegral p) :: Int
+            )
+        modify $ \st@(l, s) -> if result < s then (location, result) else st
+        ps bs
+    ps ("GHOST_POINTS" : n : bs) = do
+        let pointsNum = readInt_ n
+        (location, time) <- get
+        res <- io $ query dbConn dbQueryBestTime $ Only location
+        let bestTime = case res of
+                [Only a] -> a
+                _ -> maxBound :: Int
+        when (time < bestTime) $ do
+            io $ writeFile (B.unpack $ "ghosts/" `B.append` sanitizeName location) $ show (map readInt_ $ take (2 * pointsNum) bs)
+            return ()
+        ps (drop (2 * pointsNum) bs)
     ps (b:bs) = ps bs
+
     drawParams t = (snd t, 0 :: Int)
     placeParams winners t = (snd t, if (fst t) `elem` winners then 1 else 2 :: Int)
     places :: [(B.ByteString, Int)] -> IO Int64
--- a/gameServer/Utils.hs	Tue Feb 09 21:11:16 2016 +0300
+++ b/gameServer/Utils.hs	Mon Mar 14 22:08:27 2016 +0300
@@ -241,3 +241,8 @@
 deleteFirstsBy2          :: (a -> b -> Bool) -> [a] -> [b] -> [a]
 deleteFirstsBy2 eq       =  foldl (flip (deleteBy2 (flip eq)))
 
+sanitizeName :: B.ByteString -> B.ByteString
+sanitizeName = B.map sc
+    where
+        sc c | isAlphaNum c = c
+             | otherwise = '_'
--- a/gameServer/Votes.hs	Tue Feb 09 21:11:16 2016 +0300
+++ b/gameServer/Votes.hs	Mon Mar 14 22:08:27 2016 +0300
@@ -95,17 +95,14 @@
         let rs = Map.lookup roomSave (roomSaves rm)
         case rs of
              Nothing -> return []
-             Just (mp, p) -> do
+             Just (location, mp, p) -> do
                  cl <- thisClient
                  chans <- roomClientsChans
-                 let a = map (replaceChans chans) $ answerFullConfigParams cl mp p
-                 return $ 
-                    (ModifyRoom $ \r -> r{params = p, mapParams = mp})
-                    : SendUpdateOnThisRoom
-                    : a
-        where
-            replaceChans chans (AnswerClients _ msg) = AnswerClients chans msg
-            replaceChans _ a = a
+                 return $
+                    [ModifyRoom $ \r -> r{params = p, mapParams = mp}
+                    , AnswerClients chans ["CHAT", "[server]", location]
+                    , SendUpdateOnThisRoom
+                    , LoadGhost location]
     act (VotePause) = do
         rm <- thisRoom
         chans <- roomClientsChans
--- a/hedgewars/avwrapper/avwrapper.c	Tue Feb 09 21:11:16 2016 +0300
+++ b/hedgewars/avwrapper/avwrapper.c	Mon Mar 14 22:08:27 2016 +0300
@@ -518,11 +518,10 @@
             return FatalError("Could not open output file (%s)", g_pContainer->filename);
     }
 
-    // write the stream header, if any
-    avformat_write_header(g_pContainer, NULL);
+    g_pVFrame->pts = -1;
 
-    g_pVFrame->pts = -1;
-    return 0;
+    // write the stream header, if any
+    return avformat_write_header(g_pContainer, NULL);
 }
 
 AVWRAP_DECL int AVWrapper_Close()
--- a/hedgewars/hwengine.pas	Tue Feb 09 21:11:16 2016 +0300
+++ b/hedgewars/hwengine.pas	Mon Mar 14 22:08:27 2016 +0300
@@ -173,21 +173,6 @@
                     if (GameState <> gsChat) and (GameState >= gsGame) then
                         ProcessKey(event.key);
 
-                SDL_MOUSEBUTTONDOWN:
-                    if GameState = gsConfirm then
-                        ParseCommand('quit', true)
-                    else
-                        if (GameState >= gsGame) then ProcessMouse(event.button, true);
-
-                SDL_MOUSEBUTTONUP:
-                    if (GameState >= gsGame) then ProcessMouse(event.button, false);
-
-                SDL_MOUSEWHEEL:
-                    begin
-                    wheelEvent:= true;
-                    ProcessMouseWheel(event.wheel.x, event.wheel.y);
-                    end;
-
                 SDL_TEXTINPUT: if GameState = gsChat then uChat.TextInput(event.text);
 
                 SDL_WINDOWEVENT:
@@ -234,7 +219,23 @@
 
                 SDL_FINGERUP:
                     onTouchUp(event.tfinger.x, event.tfinger.y, event.tfinger.fingerId);
+{$ELSE}
+                SDL_MOUSEBUTTONDOWN:
+                    if GameState = gsConfirm then
+                        ParseCommand('quit', true)
+                    else
+                        if (GameState >= gsGame) then ProcessMouse(event.button, true);
+
+                SDL_MOUSEBUTTONUP:
+                    if (GameState >= gsGame) then ProcessMouse(event.button, false);
+
+                SDL_MOUSEWHEEL:
+                    begin
+                    wheelEvent:= true;
+                    ProcessMouseWheel(event.wheel.x, event.wheel.y);
+                    end;
 {$ENDIF}
+
                 SDL_JOYAXISMOTION:
                     ControllerAxisEvent(event.jaxis.which, event.jaxis.axis, event.jaxis.value);
                 SDL_JOYHATMOTION:
--- a/hedgewars/uCollisions.pas	Tue Feb 09 21:11:16 2016 +0300
+++ b/hedgewars/uCollisions.pas	Mon Mar 14 22:08:27 2016 +0300
@@ -85,7 +85,7 @@
     X:= hwRound(Gear^.X);
     Y:= hwRound(Gear^.Y);
     Radius:= Gear^.Radius;
-    ChangeRoundInLand(X, Y, Radius - 1, true, (Gear = CurrentHedgehog^.Gear) or ((Gear^.Kind = gtCase) and (Gear^.State and gstFrozen = 0)));
+    ChangeRoundInLand(X, Y, Radius - 1, true,  ((CurrentHedgehog <> nil) and (Gear = CurrentHedgehog^.Gear)) or ((Gear^.Kind = gtCase) and (Gear^.State and gstFrozen = 0)), Gear^.Kind = gtHedgehog);
     cGear:= Gear
     end;
 Gear^.CollisionIndex:= Count;
@@ -97,7 +97,7 @@
 if Gear^.CollisionIndex >= 0 then
     begin
     with cinfos[Gear^.CollisionIndex] do
-        ChangeRoundInLand(X, Y, Radius - 1, false, ((CurrentHedgehog <> nil) and (Gear = CurrentHedgehog^.Gear)) or ((Gear^.Kind = gtCase) and (Gear^.State and gstFrozen = 0)));
+        ChangeRoundInLand(X, Y, Radius - 1, false, ((CurrentHedgehog <> nil) and (Gear = CurrentHedgehog^.Gear)) or ((Gear^.Kind = gtCase) and (Gear^.State and gstFrozen = 0)), Gear^.Kind = gtHedgehog);
     cinfos[Gear^.CollisionIndex]:= cinfos[Pred(Count)];
     cinfos[Gear^.CollisionIndex].cGear^.CollisionIndex:= Gear^.CollisionIndex;
     Gear^.CollisionIndex:= -1;
--- a/hedgewars/uConsts.pas	Tue Feb 09 21:11:16 2016 +0300
+++ b/hedgewars/uConsts.pas	Mon Mar 14 22:08:27 2016 +0300
@@ -115,13 +115,24 @@
 
     lfCurrentHog     = $0080;  // CurrentHog.  It is also used to flag crates, for convenience of AI.  Since an active hog would instantly collect the crate, this does not impact play
     lfNotCurrentMask = $FF7F;  // inverse of above. frequently used
-    lfObjMask        = $007F;  // lower 7 bits used for hogs
+    lfObjMask        = $007F;  // lower 7 bits used for hogs and explosives and mines 
     lfNotObjMask     = $FF80;  // inverse of above.
+
+// breaking up hogs would makes it easier to differentiate 
+// colliding with a hog from colliding with other things
+// if overlapping hogs are less common than objects, the division can be altered.
+// 3 bits for objects, 4 for hogs, that is, overlap 7 barrels/mines before possible dents, and 15 hogs.
+    lfHHMask         = $000F;  // lower 4 bits used only for hogs
+    lfNotHHObjMask   = $0070;  // next 3 bits used for non-hog things
+    lfNotHHObjShift  = 4;
+    lfNotHHObjSize   = lfNotHHObjMask shr lfNotHHObjShift;  
+
     // lower byte is for objects.
     // consists of 0-127 counted for object checkins and $80 as a bit flag for current hog.
     lfAllObjMask     = $00FF;  // lfCurrentHog or lfObjMask
 
 
+
     cMaxPower     = 1500;
     cMaxAngle     = 2048;
     cPowerDivisor = 1500;
--- a/hedgewars/uGame.pas	Tue Feb 09 21:11:16 2016 +0300
+++ b/hedgewars/uGame.pas	Mon Mar 14 22:08:27 2016 +0300
@@ -31,6 +31,7 @@
      {$IFDEF USE_TOUCH_INTERFACE}, uTouch{$ENDIF}, uDebug;
 
 procedure DoGameTick(Lag: LongInt);
+const maxCheckedGameDuration = 3*60*60*1000;
 var i,j : LongInt;
     s: ansistring;
 begin
@@ -63,7 +64,15 @@
             else Lag:= Lag*80;
             end
         else if cOnlyStats then
-            Lag:= High(LongInt)
+            begin
+                if GameTicks >= maxCheckedGameDuration then
+                begin
+                    gameState:= gsExit;
+                    exit;
+                end;
+
+            Lag:= maxCheckedGameDuration + 60000;
+            end;
     end;
 
 if cTestLua then
--- a/hedgewars/uGearsHandlersMess.pas	Tue Feb 09 21:11:16 2016 +0300
+++ b/hedgewars/uGearsHandlersMess.pas	Mon Mar 14 22:08:27 2016 +0300
@@ -1337,10 +1337,15 @@
 
 procedure doStepDEagleShot(Gear: PGear);
 begin
+    Gear^.Data:= nil;
+    // remember who fired this
+    if (Gear^.Hedgehog <> nil) and (Gear^.Hedgehog^.Gear <> nil) then
+        Gear^.Data:= Pointer(Gear^.Hedgehog^.Gear);
+
     PlaySound(sndGun);
-    // add 3 initial steps to avoid problem with ammoshove related to calculation of radius + 1 radius as gear widths, and also just plain old weird angles
-    Gear^.X := Gear^.X + Gear^.dX * 3;
-    Gear^.Y := Gear^.Y + Gear^.dY * 3;
+    // add 2 initial steps to avoid problem with ammoshove related to calculation of radius + 1 radius as gear widths, and also just plain old weird angles
+    Gear^.X := Gear^.X + Gear^.dX * 2;
+    Gear^.Y := Gear^.Y + Gear^.dY * 2;
     Gear^.doStep := @doStepBulletWork
 end;
 
@@ -1349,6 +1354,7 @@
     HHGear: PGear;
     shell: PVisualGear;
 begin
+
     cArtillery := true;
     HHGear := Gear^.Hedgehog^.Gear;
 
@@ -1358,6 +1364,9 @@
         exit
         end;
 
+    // remember who fired this
+    Gear^.Data:= Pointer(Gear^.Hedgehog^.Gear);
+
     HHGear^.State := HHGear^.State or gstNotKickable;
     HedgehogChAngle(HHGear);
     if not cLaserSighting then
@@ -1382,9 +1391,9 @@
         Gear^.dX := SignAs(AngleSin(HHGear^.Angle), HHGear^.dX) * _0_5;
         Gear^.dY := -AngleCos(HHGear^.Angle) * _0_5;
         PlaySound(sndGun);
-        // add 3 initial steps to avoid problem with ammoshove related to calculation of radius + 1 radius as gear widths, and also just weird angles
-        Gear^.X := Gear^.X + Gear^.dX * 3;
-        Gear^.Y := Gear^.Y + Gear^.dY * 3;
+        // add 2 initial steps to avoid problem with ammoshove related to calculation of radius + 1 radius as gear widths, and also just weird angles
+        Gear^.X := Gear^.X + Gear^.dX * 2;
+        Gear^.Y := Gear^.Y + Gear^.dY * 2;
         Gear^.doStep := @doStepBulletWork;
         end
     else
@@ -2646,7 +2655,7 @@
     AllInactive := false;
     Gear^.X := Gear^.X + cAirPlaneSpeed * Gear^.Tag;
 
-    if (Gear^.Health > 0)and(not (Gear^.X < Gear^.dX))and(Gear^.X < Gear^.dX + cAirPlaneSpeed) then
+    if (Gear^.Health > 0) and (not (Gear^.X < Gear^.dX)) and (Gear^.X < Gear^.dX + cAirPlaneSpeed) then
         begin
         dec(Gear^.Health);
             case Gear^.State of
@@ -2690,7 +2699,7 @@
         end;
 
     Gear^.Y := int2hwFloat(topY-300);
-    Gear^.dX := int2hwFloat(Gear^.Target.X) - int2hwFloat(Gear^.Tag * Gear^.Health * Gear^.Damage) / 2;
+    Gear^.dX := int2hwFloat(Gear^.Target.X) - int2hwFloat(Gear^.Tag * (Gear^.Health-1) * Gear^.Damage) / 2;
 
     // calcs for Napalm Strike, so that it will hit the target (without wind at least :P)
     if (Gear^.State = 2) then
@@ -4357,9 +4366,13 @@
                 continue;
             end;
 
-        // draw bullet trail
-        if isbullet then
+        if (iterator^.Kind = gtDEagleShot) or (iterator^.Kind = gtSniperRifleShot) then
+            begin
+            // draw bullet trail
             spawnBulletTrail(iterator);
+            // the bullet can now hurt the hog that fired it
+            iterator^.Data:= nil;
+            end;
 
         // calc gear offset in portal vector direction
         ox := (iterator^.X - Gear^.X);
@@ -5006,15 +5019,18 @@
 begin
     PlaySound(sndSineGun);
 
-    // push the shooting Hedgehog back
-    HHGear := CurrentHedgehog^.Gear;
-    Gear^.dX.isNegative := not Gear^.dX.isNegative;
-    Gear^.dY.isNegative := not Gear^.dY.isNegative;
-    HHGear^.dX := Gear^.dX;
-    HHGear^.dY := Gear^.dY;
-    AmmoShove(Gear, 0, 80);
-    Gear^.dX.isNegative := not Gear^.dX.isNegative;
-    Gear^.dY.isNegative := not Gear^.dY.isNegative;
+    if (Gear^.Hedgehog <> nil) and (Gear^.Hedgehog^.Gear <> nil) then
+        begin
+        HHGear := Gear^.Hedgehog^.Gear;
+        // push the shooting Hedgehog back
+        Gear^.dX.isNegative := not Gear^.dX.isNegative;
+        Gear^.dY.isNegative := not Gear^.dY.isNegative;
+        HHGear^.dX := Gear^.dX;
+        HHGear^.dY := Gear^.dY;
+        AmmoShove(Gear, 0, 80);
+        Gear^.dX.isNegative := not Gear^.dX.isNegative;
+        Gear^.dY.isNegative := not Gear^.dY.isNegative;
+        end;
 
     Gear^.doStep := @doStepSineGunShotWork;
     {$IFNDEF PAS2C}
--- a/hedgewars/uGearsHandlersRope.pas	Tue Feb 09 21:11:16 2016 +0300
+++ b/hedgewars/uGearsHandlersRope.pas	Mon Mar 14 22:08:27 2016 +0300
@@ -498,7 +498,7 @@
         end;
 
     if Gear^.Elasticity < _20 then Gear^.CollisionMask:= lfLandMask
-    else Gear^.CollisionMask:= lfNotCurrentMask;
+    else Gear^.CollisionMask:= lfNotObjMask or lfNotHHObjMask;
     CheckCollision(Gear);
 
     if (Gear^.State and gstCollision) <> 0 then
--- a/hedgewars/uGearsList.pas	Tue Feb 09 21:11:16 2016 +0300
+++ b/hedgewars/uGearsList.pas	Mon Mar 14 22:08:27 2016 +0300
@@ -376,6 +376,7 @@
                 gear^.nImpactSounds:= 1;
                 gear^.Radius:= 10;
                 gear^.Elasticity:= _0_6;
+                gear^.Z:= 1;
                 end;
          gtBee: begin
                 gear^.Radius:= 5;
@@ -406,6 +407,7 @@
                 RopePoints.Count:= 0;
                 gear^.Tint:= $D8D8D8FF;
                 gear^.Tag:= 0; // normal rope render
+                gear^.CollisionMask:= lfNotObjMask or lfNotHHObjMask;
                 end;
         gtMine: begin
                 gear^.ImpactSound:= sndMineImpact;
--- a/hedgewars/uGearsUtils.pas	Tue Feb 09 21:11:16 2016 +0300
+++ b/hedgewars/uGearsUtils.pas	Mon Mar 14 22:08:27 2016 +0300
@@ -1170,6 +1170,8 @@
     begin
     dec(i);
     Gear:= t^.ar[i];
+    if (Ammo^.Data <> nil) and (Ammo^.Kind in [gtDEagleShot, gtSniperRifleShot]) and (PGear(Ammo^.Data) = Gear) then
+        continue;
     if ((Ammo^.Kind = gtFlame) or (Ammo^.Kind = gtBlowTorch)) and
        (Gear^.Kind = gtHedgehog) and (Gear^.Hedgehog^.Effects[heFrozen] > 255) then
         Gear^.Hedgehog^.Effects[heFrozen]:= max(255,Gear^.Hedgehog^.Effects[heFrozen]-10000);
@@ -1510,6 +1512,9 @@
 if (hwRound(Gear^.X) < LongInt(leftX)) or
    (hwRound(Gear^.X) > LongInt(rightX)) then
     begin
+    // bullets can now hurt the hog that fired them
+    if (WorldEdge <> weSea) and (Gear^.Kind in [gtDEagleShot, gtSniperRifleShot]) then
+        Gear^.Data:= nil;
     if WorldEdge = weWrap then
         begin
         if (hwRound(Gear^.X) < LongInt(leftX)) then
--- a/hedgewars/uLandGraphics.pas	Tue Feb 09 21:11:16 2016 +0300
+++ b/hedgewars/uLandGraphics.pas	Mon Mar 14 22:08:27 2016 +0300
@@ -23,7 +23,7 @@
 uses uFloat, uConsts, uTypes, Math, uRenderUtils;
 
 type
-    fillType = (nullPixel, backgroundPixel, ebcPixel, icePixel, setNotCurrentMask, changePixelSetNotCurrent, setCurrentHog, changePixelNotSetNotCurrent);
+    fillType = (nullPixel, backgroundPixel, ebcPixel, icePixel, addNotHHObj, removeNotHHObj, addHH, removeHH, setCurrentHog, removeCurrentHog);
 
 type TRangeArray = array[0..31] of record
                                    Left, Right: LongInt;
@@ -41,7 +41,7 @@
 procedure DrawTunnel(X, Y, dX, dY: hwFloat; ticks, HalfWidth: LongInt);
 function FillRoundInLand(X, Y, Radius: LongInt; Value: Longword): Longword;
 function FillRoundInLandFT(X, Y, Radius: LongInt; fill: fillType): Longword;
-procedure ChangeRoundInLand(X, Y, Radius: LongInt; doSet, isCurrent: boolean);
+procedure ChangeRoundInLand(X, Y, Radius: LongInt; doSet, isCurrent, isHH: boolean);
 function  LandBackPixel(x, y: LongInt): LongWord;
 procedure DrawLine(X1, Y1, X2, Y2: LongInt; Color: Longword);
 function  DrawThickLine(X1, Y1, X2, Y2, radius: LongInt; color: Longword): Longword;
@@ -209,15 +209,28 @@
             calculatePixelsCoordinates(i, y, px, py);
             DrawPixelIce(i, y, px, py);
             end;
-    setNotCurrentMask:
+    addNotHHObj:
+        for i:= fromPix to toPix do
+            begin
+            if Land[y, i] and lfNotHHObjMask shr lfNotHHObjShift < lfNotHHObjSize then
+                Land[y, i]:= (Land[y, i] and (not lfNotHHObjMask)) or ((Land[y, i] and lfNotHHObjMask shr lfNotHHObjShift + 1) shl lfNotHHObjShift);
+            end;
+    removeNotHHObj:
         for i:= fromPix to toPix do
             begin
-            Land[y, i]:= Land[y, i] and lfNotCurrentMask;
+            if Land[y, i] and lfNotHHObjMask <> 0 then
+                Land[y, i]:= (Land[y, i] and (not lfNotHHObjMask)) or ((Land[y, i] and lfNotHHObjMask shr lfNotHHObjShift - 1) shl lfNotHHObjShift);
             end;
-    changePixelSetNotCurrent:
+    addHH:
         for i:= fromPix to toPix do
             begin
-            if Land[y, i] and lfObjMask > 0 then
+            if Land[y, i] and lfHHMask < lfHHMask then
+                Land[y, i]:= Land[y, i] + 1
+            end;
+    removeHH:
+        for i:= fromPix to toPix do
+            begin
+            if Land[y, i] and lfHHMask > 0 then
                 Land[y, i]:= Land[y, i] - 1;
             end;
     setCurrentHog:
@@ -225,11 +238,10 @@
             begin
             Land[y, i]:= Land[y, i] or lfCurrentHog
             end;
-    changePixelNotSetNotCurrent:
+    removeCurrentHog:
         for i:= fromPix to toPix do
             begin
-            if Land[y, i] and lfObjMask < lfObjMask then
-                Land[y, i]:= Land[y, i] + 1
+            Land[y, i]:= Land[y, i] and lfNotCurrentMask;
             end;
     end;
 end;
@@ -360,16 +372,20 @@
     inc(FillRoundInLand, FillCircleLines(x, y, dx, dy, Value));
 end;
 
-procedure ChangeRoundInLand(X, Y, Radius: LongInt; doSet, isCurrent: boolean);
+procedure ChangeRoundInLand(X, Y, Radius: LongInt; doSet, isCurrent, isHH: boolean);
 begin
 if not doSet and isCurrent then
-    FillRoundInLandFT(X, Y, Radius, setNotCurrentMask)
-else if not doSet and (not IsCurrent) then
-    FillRoundInLandFT(X, Y, Radius, changePixelSetNotCurrent)
+    FillRoundInLandFT(X, Y, Radius, removeCurrentHog)
+else if (not doSet) and (not IsCurrent) and isHH then
+    FillRoundInLandFT(X, Y, Radius, removeHH)
+else if (not doSet) and (not IsCurrent) and (not isHH) then
+    FillRoundInLandFT(X, Y, Radius, removeNotHHObj)
 else if doSet and IsCurrent then
     FillRoundInLandFT(X, Y, Radius, setCurrentHog)
-else if doSet and (not IsCurrent) then
-    FillRoundInLandFT(X, Y, Radius, changePixelNotSetNotCurrent);
+else if doSet and (not IsCurrent) and isHH then
+    FillRoundInLandFT(X, Y, Radius, addHH)
+else if doSet and (not IsCurrent) and (not isHH) then
+    FillRoundInLandFT(X, Y, Radius, addNotHHObj);
 end;
 
 procedure DrawIceBreak(x, y, iceRadius, iceHeight: Longint);
@@ -693,7 +709,6 @@
 begin
     ForcePlaceOnLand:= TryPlaceOnLand(cpX, cpY, Obj, Frame, true, false, true, behind, flipHoriz, flipVert, LandFlags, Tint)
 end;
-
 function TryPlaceOnLand(cpX, cpY: LongInt; Obj: TSprite; Frame: LongInt; doPlace, outOfMap, force, behind, flipHoriz, flipVert: boolean; LandFlags: Word; Tint: LongWord): boolean;
 var X, Y, bpp, h, w, row, col, gx, gy, numFramesFirstCol: LongInt;
     p: PByteArray;
@@ -765,7 +780,7 @@
         begin
         for x:= 0 to Pred(w) do
             if ((PLongword(@(p^[x * 4]))^) and AMask) <> 0 then
-                   begin
+                begin
                 if (cReducedQuality and rqBlurryLand) = 0 then
                     begin
                     gX:= cpX + x;
@@ -776,15 +791,15 @@
                     gX:= (cpX + x) div 2;
                     gY:= (cpY + y) div 2;
                     end;
-		if not behind or (Land[cpY + y, cpX + x] and lfLandMask = 0) then
+                if (not behind) or (Land[cpY + y, cpX + x] and lfLandMask = 0) then
                     begin
                     if (LandFlags and lfBasic <> 0) or 
-                       (((LandPixels[gY, gX] and AMask) shr AShift = 255) and  // This test assumes lfBasic and lfObject differ only graphically
-                         (LandFlags or lfObject = 0)) then
+                       ((LandPixels[gY, gX] and AMask shr AShift > 128) and  // This test assumes lfBasic and lfObject differ only graphically
+                         (LandFlags and lfObject = 0)) then
                          Land[cpY + y, cpX + x]:= lfBasic or LandFlags
                     else Land[cpY + y, cpX + x]:= lfObject or LandFlags
                     end;
-		if not behind or (LandPixels[gY, gX] = 0) then
+                if (not behind) or (LandPixels[gY, gX] = 0) then
                     begin
                     if tint = $FFFFFFFF then
                         LandPixels[gY, gX]:= PLongword(@(p^[x * 4]))^
@@ -998,7 +1013,7 @@
         yy:= Y div 2;
     end;
 
-    pixelsweep:= (Land[Y, X] <= lfAllObjMask) and ((LandPixels[yy, xx] and AMASK) <> 0);
+    pixelsweep:= (Land[Y, X] <= lfAllObjMask) and ((LandPixels[yy, xx] and AMask) <> 0);
     if (((Land[Y, X] and lfDamaged) <> 0) and ((Land[Y, X] and lfIndestructible) = 0)) or pixelsweep then
     begin
         c:= 0;
--- a/hedgewars/uScript.pas	Tue Feb 09 21:11:16 2016 +0300
+++ b/hedgewars/uScript.pas	Mon Mar 14 22:08:27 2016 +0300
@@ -2211,24 +2211,6 @@
     lc_setwind:= 0
 end;
 
-function lc_getdatapath(L : Plua_State) : LongInt; Cdecl;
-begin
-    if CheckLuaParamCount(L, 0, 'GetDataPath', '') then
-        lua_pushstring(L, str2pchar(cPathz[ptData]))
-    else
-        lua_pushnil(L);
-    lc_getdatapath:= 1
-end;
-
-function lc_getuserdatapath(L : Plua_State) : LongInt; Cdecl;
-begin
-    if CheckLuaParamCount(L, 0, 'GetUserDataPath', '') then
-        lua_pushstring(L, str2pchar(cPathz[ptData]))
-    else
-        lua_pushnil(L);
-    lc_getuserdatapath:= 1
-end;
-
 function lc_maphasborder(L : Plua_State) : LongInt; Cdecl;
 begin
     if CheckLuaParamCount(L, 0, 'MapHasBorder', '') then
@@ -2544,6 +2526,20 @@
     lc_declareachievement:= 0
 end;
 
+function lc_startghostpoints(L : Plua_State) : LongInt; Cdecl;
+begin
+    if CheckLuaParamCount(L, 1, 'StartGhostPoints', 'count') then
+        startGhostPoints(lua_tointeger(L, 1));
+    lc_startghostpoints:= 0
+end;
+
+function lc_dumppoint(L : Plua_State) : LongInt; Cdecl;
+begin
+    if CheckLuaParamCount(L, 2, 'DumpPoint', 'x, y') then
+        dumpPoint(lua_tointeger(L, 1), lua_tointeger(L, 2));
+    lc_dumppoint:= 0
+end;
+
 
 procedure ScriptFlushPoints();
 begin
@@ -3338,8 +3334,6 @@
 lua_register(luaState, _P'SetGearCollisionMask', @lc_setgearcollisionmask);
 lua_register(luaState, _P'GetRandom', @lc_getrandom);
 lua_register(luaState, _P'SetWind', @lc_setwind);
-lua_register(luaState, _P'GetDataPath', @lc_getdatapath);
-lua_register(luaState, _P'GetUserDataPath', @lc_getuserdatapath);
 lua_register(luaState, _P'MapHasBorder', @lc_maphasborder);
 lua_register(luaState, _P'GetHogHat', @lc_gethoghat);
 lua_register(luaState, _P'SetHogHat', @lc_sethoghat);
@@ -3362,6 +3356,8 @@
 lua_register(luaState, _P'SetGearAIHints', @lc_setgearaihints);
 lua_register(luaState, _P'HedgewarsScriptLoad', @lc_hedgewarsscriptload);
 lua_register(luaState, _P'DeclareAchievement', @lc_declareachievement);
+lua_register(luaState, _P'StartGhostPoints', @lc_startghostpoints);
+lua_register(luaState, _P'DumpPoint', @lc_dumppoint);
 
 ScriptSetInteger('TEST_SUCCESSFUL'   , HaltTestSuccess);
 ScriptSetInteger('TEST_FAILED'       , HaltTestFailed);
--- a/hedgewars/uStats.pas	Tue Feb 09 21:11:16 2016 +0300
+++ b/hedgewars/uStats.pas	Mon Mar 14 22:08:27 2016 +0300
@@ -36,6 +36,8 @@
 procedure SendStats;
 procedure hedgehogFlight(Gear: PGear; time: Longword);
 procedure declareAchievement(id, teamname, location: shortstring; value: LongInt);
+procedure startGhostPoints(n: LongInt);
+procedure dumpPoint(x, y: LongInt);
 
 implementation
 uses uSound, uLocale, uVariables, uUtils, uIO, uCaptions, uMisc, uConsole, uScript;
@@ -323,8 +325,32 @@
     WriteLnToConsole(inttostr(value));
 end;
 
+procedure startGhostPoints(n: LongInt);
+begin
+    WriteLnToConsole('GHOST_POINTS');
+    WriteLnToConsole(inttostr(n));
+end;
+
+procedure dumpPoint(x, y: LongInt);
+begin
+    WriteLnToConsole(inttostr(x));
+    WriteLnToConsole(inttostr(y));
+end;
+
 procedure initModule;
 begin
+    DamageClan  := 0;
+    DamageTotal := 0;
+    DamageTurn  := 0;
+    KillsClan   := 0;
+    Kills       := 0;
+    KillsTotal  := 0;
+    AmmoUsedCount := 0;
+    AmmoDamagingUsed := false;
+    SkippedTurns:= 0;
+    isTurnSkipped:= false;
+    vpHurtSameClan:= nil;
+    vpHurtEnemy:= nil;
     TotalRounds:= -1;
     FinishedTurnsTotal:= -1;
 end;
--- a/hedgewars/uTouch.pas	Tue Feb 09 21:11:16 2016 +0300
+++ b/hedgewars/uTouch.pas	Mon Mar 14 22:08:27 2016 +0300
@@ -423,6 +423,7 @@
                 fingers[index].historicalX := fingers[pointerCount].historicalX;
                 fingers[index].historicalY := fingers[pointerCount].historicalY;
                 fingers[index].timeSinceDown := fingers[pointerCount].timeSinceDown;
+                fingers[index].pressedWidget := fingers[pointerCount].pressedWidget;
 
                 fingers[pointerCount].id := 0;
             end
--- a/project_files/HedgewarsMobile/Classes/AboutViewController.m	Tue Feb 09 21:11:16 2016 +0300
+++ b/project_files/HedgewarsMobile/Classes/AboutViewController.m	Mon Mar 14 22:08:27 2016 +0300
@@ -128,7 +128,7 @@
 
     UILabel *label = [[UILabel alloc] initWithFrame:CGRectMake(0, 0, self.tableView.frame.size.width*80/100, 90)];
     label.center = CGPointMake(self.tableView.frame.size.width/2, 45);
-    label.textAlignment = UITextAlignmentCenter;
+    label.textAlignment = NSTextAlignmentCenter;
     label.font = [UIFont systemFontOfSize:16];
     label.textColor = [UIColor lightGrayColor];
     label.numberOfLines = 5;
--- /dev/null	Thu Jan 01 00:00:00 1970 +0000
+++ b/project_files/HedgewarsMobile/Classes/CampaignViewController-iPad.xib	Mon Mar 14 22:08:27 2016 +0300
@@ -0,0 +1,25 @@
+<?xml version="1.0" encoding="UTF-8" standalone="no"?>
+<document type="com.apple.InterfaceBuilder3.CocoaTouch.iPad.XIB" version="3.0" toolsVersion="9531" systemVersion="15D21" targetRuntime="iOS.CocoaTouch.iPad" propertyAccessControl="none">
+    <dependencies>
+        <deployment identifier="iOS"/>
+        <plugIn identifier="com.apple.InterfaceBuilder.IBCocoaTouchPlugin" version="9529"/>
+    </dependencies>
+    <objects>
+        <placeholder placeholderIdentifier="IBFilesOwner" id="-1" userLabel="File's Owner" customClass="CampaignViewController">
+            <connections>
+                <outlet property="view" destination="BGY-i4-0hN" id="Dvn-DY-Coe"/>
+            </connections>
+        </placeholder>
+        <placeholder placeholderIdentifier="IBFirstResponder" id="-2" customClass="UIResponder"/>
+        <tableView clipsSubviews="YES" contentMode="scaleToFill" alwaysBounceVertical="YES" style="plain" separatorStyle="default" rowHeight="44" sectionHeaderHeight="28" sectionFooterHeight="28" id="BGY-i4-0hN">
+            <rect key="frame" x="0.0" y="0.0" width="768" height="1024"/>
+            <autoresizingMask key="autoresizingMask" flexibleMaxX="YES" flexibleMaxY="YES"/>
+            <color key="backgroundColor" white="1" alpha="1" colorSpace="calibratedWhite"/>
+            <connections>
+                <outlet property="dataSource" destination="-1" id="ziw-0v-GnE"/>
+                <outlet property="delegate" destination="-1" id="xbG-8w-TF1"/>
+            </connections>
+            <point key="canvasLocation" x="514" y="414"/>
+        </tableView>
+    </objects>
+</document>
--- /dev/null	Thu Jan 01 00:00:00 1970 +0000
+++ b/project_files/HedgewarsMobile/Classes/CampaignViewController-iPhone.xib	Mon Mar 14 22:08:27 2016 +0300
@@ -0,0 +1,25 @@
+<?xml version="1.0" encoding="UTF-8" standalone="no"?>
+<document type="com.apple.InterfaceBuilder3.CocoaTouch.XIB" version="3.0" toolsVersion="9531" systemVersion="15D21" targetRuntime="iOS.CocoaTouch" propertyAccessControl="none">
+    <dependencies>
+        <deployment identifier="iOS"/>
+        <plugIn identifier="com.apple.InterfaceBuilder.IBCocoaTouchPlugin" version="9529"/>
+    </dependencies>
+    <objects>
+        <placeholder placeholderIdentifier="IBFilesOwner" id="-1" userLabel="File's Owner" customClass="CampaignViewController">
+            <connections>
+                <outlet property="view" destination="i5M-Pr-FkT" id="sfx-zR-JGt"/>
+            </connections>
+        </placeholder>
+        <placeholder placeholderIdentifier="IBFirstResponder" id="-2" customClass="UIResponder"/>
+        <tableView opaque="NO" clipsSubviews="YES" clearsContextBeforeDrawing="NO" contentMode="scaleToFill" bouncesZoom="NO" style="plain" separatorStyle="default" rowHeight="44" sectionHeaderHeight="22" sectionFooterHeight="22" id="i5M-Pr-FkT">
+            <rect key="frame" x="0.0" y="0.0" width="320" height="568"/>
+            <autoresizingMask key="autoresizingMask" widthSizable="YES" heightSizable="YES"/>
+            <color key="backgroundColor" white="1" alpha="1" colorSpace="calibratedWhite"/>
+            <connections>
+                <outlet property="dataSource" destination="-1" id="Tng-2m-Rnh"/>
+                <outlet property="delegate" destination="-1" id="9aC-8N-iBw"/>
+            </connections>
+            <point key="canvasLocation" x="781" y="482"/>
+        </tableView>
+    </objects>
+</document>
--- /dev/null	Thu Jan 01 00:00:00 1970 +0000
+++ b/project_files/HedgewarsMobile/Classes/CampaignViewController.h	Mon Mar 14 22:08:27 2016 +0300
@@ -0,0 +1,25 @@
+/*
+ * Hedgewars-iOS, a Hedgewars port for iOS devices
+ * Copyright (c) 2015-2016 Anton Malmygin <antonc27@mail.ru>
+ *
+ * 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., 51 Franklin St, Fifth Floor, Boston, MA  02110-1301  USA.
+ */
+
+#import <UIKit/UIKit.h>
+
+@interface CampaignViewController : UITableViewController
+
+@property (nonatomic, retain) NSString *campaignName;
+
+@end
--- /dev/null	Thu Jan 01 00:00:00 1970 +0000
+++ b/project_files/HedgewarsMobile/Classes/CampaignViewController.m	Mon Mar 14 22:08:27 2016 +0300
@@ -0,0 +1,104 @@
+/*
+ * Hedgewars-iOS, a Hedgewars port for iOS devices
+ * Copyright (c) 2015-2016 Anton Malmygin <antonc27@mail.ru>
+ *
+ * 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., 51 Franklin St, Fifth Floor, Boston, MA  02110-1301  USA.
+ */
+
+#import "CampaignViewController.h"
+#import "IniParser.h"
+#import "GameInterfaceBridge.h"
+
+@interface CampaignViewController ()
+@property (nonatomic, retain) NSArray *campaignMissions;
+@end
+
+@implementation CampaignViewController
+
+#pragma mark - Lazy instantiation
+
+- (NSArray *)campaignMissions {
+    if (!_campaignMissions) {
+        _campaignMissions = [self newParsedMissionsForCurrentCampaign];
+    }
+    return _campaignMissions;
+}
+
+- (NSArray *)newParsedMissionsForCurrentCampaign {
+    NSString *campaignIniPath = [CAMPAIGNS_DIRECTORY() stringByAppendingFormat:@"%@/campaign.ini", self.campaignName];
+    
+    IniParser *iniParser = [[IniParser alloc] initWithIniFilePath:campaignIniPath];
+    NSArray *parsedMissions = [iniParser newParsedSections];
+    [iniParser release];
+    
+    return parsedMissions;
+}
+
+#pragma mark - View lifecycle
+
+- (void)viewDidLoad {
+    [super viewDidLoad];
+    
+    UIBarButtonItem *doneButton = [[UIBarButtonItem alloc] initWithBarButtonSystemItem:UIBarButtonSystemItemDone target:self action:@selector(dismiss)];
+    self.navigationItem.rightBarButtonItem = doneButton;
+    [doneButton release];
+    
+    [self.tableView registerClass:[UITableViewCell class] forCellReuseIdentifier:@"campaignMissionCell"];
+}
+
+- (void)dismiss {
+    [self.navigationController.presentingViewController dismissViewControllerAnimated:YES completion:nil];
+}
+
+- (void)didReceiveMemoryWarning {
+    [super didReceiveMemoryWarning];
+    // Dispose of any resources that can be recreated.
+}
+
+#pragma mark - Table view data source
+
+- (NSInteger)numberOfSectionsInTableView:(UITableView *)tableView {
+    return 1;
+}
+
+- (NSInteger)tableView:(UITableView *)tableView numberOfRowsInSection:(NSInteger)section {
+    return [self.campaignMissions count];
+}
+
+- (UITableViewCell *)tableView:(UITableView *)tableView cellForRowAtIndexPath:(NSIndexPath *)indexPath {
+    UITableViewCell *cell = [tableView dequeueReusableCellWithIdentifier:@"campaignMissionCell" forIndexPath:indexPath];
+    
+    cell.textLabel.text = self.campaignMissions[indexPath.row][@"Name"];
+    
+    return cell;
+}
+
+#pragma mark - Table view delegate
+
+- (void)tableView:(UITableView *)tableView didSelectRowAtIndexPath:(NSIndexPath *)indexPath {
+    NSString *campaignMissionScript = self.campaignMissions[indexPath.row][@"Script"];
+    
+    [GameInterfaceBridge registerCallingController:self];
+    [GameInterfaceBridge startCampaignMissionGameWithScript:campaignMissionScript forCampaign:self.campaignName];
+}
+
+#pragma mark - Dealloc
+
+- (void)dealloc {
+    [_campaignName release];
+    [_campaignMissions release];
+    [super dealloc];
+}
+
+@end
--- /dev/null	Thu Jan 01 00:00:00 1970 +0000
+++ b/project_files/HedgewarsMobile/Classes/CampaignsViewController-iPad.xib	Mon Mar 14 22:08:27 2016 +0300
@@ -0,0 +1,25 @@
+<?xml version="1.0" encoding="UTF-8" standalone="no"?>
+<document type="com.apple.InterfaceBuilder3.CocoaTouch.iPad.XIB" version="3.0" toolsVersion="9531" systemVersion="15D21" targetRuntime="iOS.CocoaTouch.iPad" propertyAccessControl="none">
+    <dependencies>
+        <deployment identifier="iOS"/>
+        <plugIn identifier="com.apple.InterfaceBuilder.IBCocoaTouchPlugin" version="9529"/>
+    </dependencies>
+    <objects>
+        <placeholder placeholderIdentifier="IBFilesOwner" id="-1" userLabel="File's Owner" customClass="CampaignsViewController">
+            <connections>
+                <outlet property="view" destination="zXe-Y5-nDC" id="Xzl-t1-QHC"/>
+            </connections>
+        </placeholder>
+        <placeholder placeholderIdentifier="IBFirstResponder" id="-2" customClass="UIResponder"/>
+        <tableView clipsSubviews="YES" contentMode="scaleToFill" alwaysBounceVertical="YES" style="plain" separatorStyle="default" rowHeight="44" sectionHeaderHeight="28" sectionFooterHeight="28" id="zXe-Y5-nDC">
+            <rect key="frame" x="0.0" y="0.0" width="768" height="1024"/>
+            <autoresizingMask key="autoresizingMask" flexibleMaxX="YES" flexibleMaxY="YES"/>
+            <color key="backgroundColor" white="1" alpha="1" colorSpace="calibratedWhite"/>
+            <connections>
+                <outlet property="dataSource" destination="-1" id="UCr-h4-2sD"/>
+                <outlet property="delegate" destination="-1" id="sba-bd-bdf"/>
+            </connections>
+            <point key="canvasLocation" x="513" y="343"/>
+        </tableView>
+    </objects>
+</document>
--- /dev/null	Thu Jan 01 00:00:00 1970 +0000
+++ b/project_files/HedgewarsMobile/Classes/CampaignsViewController-iPhone.xib	Mon Mar 14 22:08:27 2016 +0300
@@ -0,0 +1,27 @@
+<?xml version="1.0" encoding="UTF-8" standalone="no"?>
+<document type="com.apple.InterfaceBuilder3.CocoaTouch.XIB" version="3.0" toolsVersion="9531" systemVersion="15D21" targetRuntime="iOS.CocoaTouch" propertyAccessControl="none">
+    <dependencies>
+        <deployment identifier="iOS"/>
+        <plugIn identifier="com.apple.InterfaceBuilder.IBCocoaTouchPlugin" version="9529"/>
+    </dependencies>
+    <objects>
+        <placeholder placeholderIdentifier="IBFilesOwner" id="-1" userLabel="File's Owner" customClass="CampaignsViewController">
+            <connections>
+                <outlet property="view" destination="i5M-Pr-FkT" id="sfx-zR-JGt"/>
+            </connections>
+        </placeholder>
+        <placeholder placeholderIdentifier="IBFirstResponder" id="-2" customClass="UIResponder"/>
+        <tableView opaque="NO" clipsSubviews="YES" clearsContextBeforeDrawing="NO" contentMode="scaleToFill" bouncesZoom="NO" style="plain" separatorStyle="default" rowHeight="44" sectionHeaderHeight="22" sectionFooterHeight="22" id="i5M-Pr-FkT">
+            <rect key="frame" x="0.0" y="0.0" width="480" height="320"/>
+            <autoresizingMask key="autoresizingMask" widthSizable="YES" heightSizable="YES"/>
+            <color key="backgroundColor" white="1" alpha="1" colorSpace="calibratedWhite"/>
+            <simulatedOrientationMetrics key="simulatedOrientationMetrics" orientation="landscapeRight"/>
+            <simulatedScreenMetrics key="simulatedDestinationMetrics"/>
+            <connections>
+                <outlet property="dataSource" destination="-1" id="Tng-2m-Rnh"/>
+                <outlet property="delegate" destination="-1" id="9aC-8N-iBw"/>
+            </connections>
+            <point key="canvasLocation" x="520" y="350"/>
+        </tableView>
+    </objects>
+</document>
--- /dev/null	Thu Jan 01 00:00:00 1970 +0000
+++ b/project_files/HedgewarsMobile/Classes/CampaignsViewController.h	Mon Mar 14 22:08:27 2016 +0300
@@ -0,0 +1,23 @@
+/*
+ * Hedgewars-iOS, a Hedgewars port for iOS devices
+ * Copyright (c) 2015-2016 Anton Malmygin <antonc27@mail.ru>
+ *
+ * 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., 51 Franklin St, Fifth Floor, Boston, MA  02110-1301  USA.
+ */
+
+#import <UIKit/UIKit.h>
+
+@interface CampaignsViewController : UITableViewController
+
+@end
--- /dev/null	Thu Jan 01 00:00:00 1970 +0000
+++ b/project_files/HedgewarsMobile/Classes/CampaignsViewController.m	Mon Mar 14 22:08:27 2016 +0300
@@ -0,0 +1,113 @@
+/*
+ * Hedgewars-iOS, a Hedgewars port for iOS devices
+ * Copyright (c) 2015-2016 Anton Malmygin <antonc27@mail.ru>
+ *
+ * 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., 51 Franklin St, Fifth Floor, Boston, MA  02110-1301  USA.
+ */
+
+#import "CampaignsViewController.h"
+#import "CampaignViewController.h"
+
+@interface CampaignsViewController ()
+@property (nonatomic, retain) NSArray *campaigns;
+@end
+
+@implementation CampaignsViewController
+
+#pragma mark - Lazy instantiation
+
+- (NSArray *)campaigns {
+    if (!_campaigns) {
+        _campaigns = [self newListOfCampaigns];
+    }
+    return _campaigns;
+}
+
+- (NSArray *)newListOfCampaigns {
+    NSFileManager *fileManager = [NSFileManager defaultManager];
+    NSArray *contents = [fileManager contentsOfDirectoryAtPath:CAMPAIGNS_DIRECTORY() error:nil];
+    
+    NSMutableArray *tempCampaigns = [[NSMutableArray alloc] init];
+    for (NSString *item in contents) {
+        NSString *fullItemPath = [CAMPAIGNS_DIRECTORY() stringByAppendingString:item];
+        BOOL isDirectory;
+        if ([fileManager fileExistsAtPath:fullItemPath isDirectory:&isDirectory] && isDirectory) {
+            [tempCampaigns addObject:item];
+        }
+    }
+    
+    NSArray *campaigns = [tempCampaigns copy];
+    [tempCampaigns release];
+    return campaigns;
+}
+
+#pragma mark - View lifecycle
+
+- (void)viewDidLoad {
+    [super viewDidLoad];
+    
+    UIBarButtonItem *doneButton = [[UIBarButtonItem alloc] initWithBarButtonSystemItem:UIBarButtonSystemItemDone target:self action:@selector(dismiss)];
+    self.navigationItem.rightBarButtonItem = doneButton;
+    [doneButton release];
+    
+    [self.tableView registerClass:[UITableViewCell class] forCellReuseIdentifier:@"campaignCell"];
+}
+
+- (void)dismiss {
+    [self.navigationController.presentingViewController dismissViewControllerAnimated:YES completion:nil];
+}
+
+- (void)didReceiveMemoryWarning {
+    [super didReceiveMemoryWarning];
+    // Dispose of any resources that can be recreated.
+}
+
+#pragma mark - Table view data source
+
+- (NSInteger)numberOfSectionsInTableView:(UITableView *)tableView {
+    return 1;
+}
+
+- (NSInteger)tableView:(UITableView *)tableView numberOfRowsInSection:(NSInteger)section {
+    return [self.campaigns count];
+}
+
+- (UITableViewCell *)tableView:(UITableView *)tableView cellForRowAtIndexPath:(NSIndexPath *)indexPath {
+    UITableViewCell *cell = [tableView dequeueReusableCellWithIdentifier:@"campaignCell" forIndexPath:indexPath];
+    
+    cell.textLabel.text = self.campaigns[indexPath.row];
+    
+    return cell;
+}
+
+#pragma mark - Table view delegate
+
+- (void)tableView:(UITableView *)tableView didSelectRowAtIndexPath:(NSIndexPath *)indexPath {
+    NSString *xib = IS_IPAD() ? @"CampaignViewController-iPad" : @"CampaignViewController-iPhone";
+    CampaignViewController *campaign = [[CampaignViewController alloc] initWithNibName:xib bundle:nil];
+    
+    campaign.campaignName = self.campaigns[indexPath.row];
+    
+    [self.navigationController pushViewController:campaign animated:YES];
+    [campaign release];
+}
+
+#pragma mark - Dealloc
+
+- (void)dealloc {
+    [_campaigns release];
+    [super dealloc];
+}
+
+@end
--- a/project_files/HedgewarsMobile/Classes/DefinesAndMacros.h	Tue Feb 09 21:11:16 2016 +0300
+++ b/project_files/HedgewarsMobile/Classes/DefinesAndMacros.h	Mon Mar 14 22:08:27 2016 +0300
@@ -66,6 +66,7 @@
 #define MAPS_DIRECTORY()        [[[NSBundle mainBundle] resourcePath] stringByAppendingString:@"/Data/Maps/"]
 #define MISSIONS_DIRECTORY()    [[[NSBundle mainBundle] resourcePath] stringByAppendingString:@"/Data/Missions/Maps/"]
 #define TRAININGS_DIRECTORY()   [[[NSBundle mainBundle] resourcePath] stringByAppendingString:@"/Data/Missions/Training/"]
+#define CAMPAIGNS_DIRECTORY()   [[[NSBundle mainBundle] resourcePath] stringByAppendingString:@"/Data/Missions/Campaign/"]
 #define LOCALE_DIRECTORY()      [[[NSBundle mainBundle] resourcePath] stringByAppendingString:@"/Data/Locale/"]
 #define SCRIPTS_DIRECTORY()     [[[NSBundle mainBundle] resourcePath] stringByAppendingString:@"/Data/Scripts/Multiplayer/"]
 
--- a/project_files/HedgewarsMobile/Classes/EditableCellView.m	Tue Feb 09 21:11:16 2016 +0300
+++ b/project_files/HedgewarsMobile/Classes/EditableCellView.m	Mon Mar 14 22:08:27 2016 +0300
@@ -43,7 +43,7 @@
         //[textField release];
 
         titleLabel = [[UILabel alloc] init];
-        titleLabel.textAlignment = UITextAlignmentLeft;
+        titleLabel.textAlignment = NSTextAlignmentLeft;
         titleLabel.backgroundColor = [UIColor clearColor];
         titleLabel.font = [UIFont boldSystemFontOfSize:[UIFont labelFontSize]];
         [self.contentView addSubview:titleLabel];
--- a/project_files/HedgewarsMobile/Classes/EngineProtocolNetwork.m	Tue Feb 09 21:11:16 2016 +0300
+++ b/project_files/HedgewarsMobile/Classes/EngineProtocolNetwork.m	Mon Mar 14 22:08:27 2016 +0300
@@ -273,13 +273,15 @@
                 NSString *script = [gameConfig objectForKey:@"mission_command"];
                 if ([script length] != 0)
                     [self sendToEngine:script];
-                // missions/tranings only need the script configuration set
-                if ([gameConfig count] == 1)
-                    break;
-
+                
                 // seed info
                 [self sendToEngine:[gameConfig objectForKey:@"seed_command"]];
 
+                // missions/tranings/campaign only need the script configuration set and seed
+                TGameType currentGameType = [HWUtils gameType];
+                if (currentGameType == gtMission || currentGameType == gtCampaign)
+                    break;
+                
                 // dimension of the map
                 [self sendToEngine:[gameConfig objectForKey:@"templatefilter_command"]];
                 [self sendToEngine:[gameConfig objectForKey:@"mapgen_command"]];
--- a/project_files/HedgewarsMobile/Classes/ExtraCategories.m	Tue Feb 09 21:11:16 2016 +0300
+++ b/project_files/HedgewarsMobile/Classes/ExtraCategories.m	Mon Mar 14 22:08:27 2016 +0300
@@ -161,7 +161,7 @@
     if (title != nil) {
         theLabel.text = title;
         theLabel.textColor = [UIColor lightYellowColor];
-        theLabel.textAlignment = UITextAlignmentCenter;
+        theLabel.textAlignment = NSTextAlignmentCenter;
         theLabel.font = [UIFont boldSystemFontOfSize:[UIFont labelFontSize]*80/100];
     }
 
--- a/project_files/HedgewarsMobile/Classes/GameConfigViewController.m	Tue Feb 09 21:11:16 2016 +0300
+++ b/project_files/HedgewarsMobile/Classes/GameConfigViewController.m	Mon Mar 14 22:08:27 2016 +0300
@@ -349,7 +349,7 @@
                                            withBorderWidth:2.0f];
         maxLabel.font = [UIFont italicSystemFontOfSize:[UIFont labelFontSize]];
         maxLabel.textColor = [UIColor whiteColor];
-        maxLabel.textAlignment = UITextAlignmentCenter;
+        maxLabel.textAlignment = NSTextAlignmentCenter;
         [self.view addSubview:maxLabel];
         self.mapConfigViewController.maxLabel = maxLabel;
         [maxLabel release];
--- a/project_files/HedgewarsMobile/Classes/GameInterfaceBridge.h	Tue Feb 09 21:11:16 2016 +0300
+++ b/project_files/HedgewarsMobile/Classes/GameInterfaceBridge.h	Mon Mar 14 22:08:27 2016 +0300
@@ -34,6 +34,7 @@
 +(void) startLocalGame:(NSDictionary *)withOptions;
 +(void) startSaveGame:(NSString *)atPath;
 +(void) startMissionGame:(NSString *)withScript;
++(void) startCampaignMissionGameWithScript:(NSString *)missionScriptName forCampaign:(NSString *)campaignName;
 +(void) startSimpleGame;
 
 +(void) registerCallingController:(UIViewController *)controller;
--- a/project_files/HedgewarsMobile/Classes/GameInterfaceBridge.m	Tue Feb 09 21:11:16 2016 +0300
+++ b/project_files/HedgewarsMobile/Classes/GameInterfaceBridge.m	Mon Mar 14 22:08:27 2016 +0300
@@ -241,21 +241,37 @@
 }
 
 +(void) startMissionGame:(NSString *)withScript {
+    NSString *seedCmd = [self seedCommand];
     NSString *missionPath = [[NSString alloc] initWithFormat:@"escript Missions/Training/%@.lua",withScript];
-    NSDictionary *missionLine = [[NSDictionary alloc] initWithObjectsAndKeys:missionPath,@"mission_command",nil];
+    NSDictionary *missionDict = [[NSDictionary alloc] initWithObjectsAndKeys:missionPath, @"mission_command", seedCmd, @"seed_command", nil];
     [missionPath release];
+    [seedCmd release];
 
-    [self startGame:gtMission atPath:nil withOptions:missionLine];
-    [missionLine release];
+    [self startGame:gtMission atPath:nil withOptions:missionDict];
+    [missionDict release];
+}
+
++(NSString *) seedCommand {
+    // generate a seed
+    NSString *seed = [HWUtils seed];
+    NSString *seedCmd = [[NSString alloc] initWithFormat:@"eseed {%@}", seed];
+    [seed release];
+    return seedCmd;
+}
+
++(void) startCampaignMissionGameWithScript:(NSString *)missionScriptName forCampaign:(NSString *)campaignName {
+    NSString *seedCmd = [self seedCommand];
+    NSString *campaignMissionPath = [[NSString alloc] initWithFormat:@"escript Missions/Campaign/%@/%@", campaignName, missionScriptName];
+    NSDictionary *campaignMissionDict = [[NSDictionary alloc] initWithObjectsAndKeys:campaignMissionPath, @"mission_command", seedCmd, @"seed_command", nil];
+    [campaignMissionPath release];
+    [seedCmd release];
+    
+    [self startGame:gtCampaign atPath:nil withOptions:campaignMissionDict];
+    [campaignMissionDict release];
 }
 
 +(void) startSimpleGame {
-    // generate a seed
-    CFUUIDRef uuid = CFUUIDCreate(kCFAllocatorDefault);
-    NSString *seed = (NSString *)CFUUIDCreateString(kCFAllocatorDefault, uuid);
-    CFRelease(uuid);
-    NSString *seedCmd = [[NSString alloc] initWithFormat:@"eseed {%@}", seed];
-    [seed release];
+    NSString *seedCmd = [self seedCommand];
 
     // pick a random static map
     NSArray *listOfMaps = [[NSFileManager defaultManager] contentsOfDirectoryAtPath:MAPS_DIRECTORY() error:NULL];
--- a/project_files/HedgewarsMobile/Classes/HWUtils.h	Tue Feb 09 21:11:16 2016 +0300
+++ b/project_files/HedgewarsMobile/Classes/HWUtils.h	Mon Mar 14 22:08:27 2016 +0300
@@ -20,7 +20,7 @@
 #import <Foundation/Foundation.h>
 
 
-typedef enum {gtNone, gtLocal, gtSave, gtMission, gtNet} TGameType;
+typedef enum {gtNone, gtLocal, gtSave, gtMission, gtCampaign, gtNet} TGameType;
 typedef enum {gsNone, gsLoading, gsInGame, gsInterrupted, gsEnded} TGameStatus;
 
 @interface HWUtils : NSObject {
@@ -43,6 +43,7 @@
 +(BOOL) isNetworkReachable;
 +(NSString *) languageID;
 //+(UIView *)mainSDLViewInstance;
++(NSString *) seed;
 
 @end
 
--- a/project_files/HedgewarsMobile/Classes/HWUtils.m	Tue Feb 09 21:11:16 2016 +0300
+++ b/project_files/HedgewarsMobile/Classes/HWUtils.m	Mon Mar 14 22:08:27 2016 +0300
@@ -174,4 +174,12 @@
 }
 */
 
++ (NSString *)seed
+{
+    CFUUIDRef uuid = CFUUIDCreate(kCFAllocatorDefault);
+    NSString *seed = (NSString *)CFUUIDCreateString(kCFAllocatorDefault, uuid);
+    CFRelease(uuid);
+    return seed;
+}
+
 @end
--- /dev/null	Thu Jan 01 00:00:00 1970 +0000
+++ b/project_files/HedgewarsMobile/Classes/IniParser.h	Mon Mar 14 22:08:27 2016 +0300
@@ -0,0 +1,27 @@
+/*
+ * Hedgewars-iOS, a Hedgewars port for iOS devices
+ * Copyright (c) 2015-2016 Anton Malmygin <antonc27@mail.ru>
+ *
+ * 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., 51 Franklin St, Fifth Floor, Boston, MA  02110-1301  USA.
+ */
+
+#import <Foundation/Foundation.h>
+
+@interface IniParser : NSObject
+
+- (instancetype)initWithIniFilePath:(NSString *)iniFilePath;
+
+- (NSArray *)newParsedSections;
+
+@end
--- /dev/null	Thu Jan 01 00:00:00 1970 +0000
+++ b/project_files/HedgewarsMobile/Classes/IniParser.m	Mon Mar 14 22:08:27 2016 +0300
@@ -0,0 +1,122 @@
+/*
+ * Hedgewars-iOS, a Hedgewars port for iOS devices
+ * Copyright (c) 2015-2016 Anton Malmygin <antonc27@mail.ru>
+ *
+ * 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., 51 Franklin St, Fifth Floor, Boston, MA  02110-1301  USA.
+ */
+
+#import "IniParser.h"
+
+#define COMMENTS_START_CHAR ';'
+#define  SECTION_START_CHAR '['
+
+@interface IniParser ()
+@property (nonatomic, retain) NSString *iniFilePath;
+
+@property (nonatomic, retain) NSMutableArray *mutableSections;
+@property (nonatomic, retain) NSMutableDictionary *currentSection;
+@end
+
+@implementation IniParser
+
+#pragma mark - Initilisation
+
+- (instancetype)initWithIniFilePath:(NSString *)iniFilePath {
+    self = [super init];
+    if (self) {
+        _iniFilePath = [iniFilePath copy];
+    }
+    return self;
+}
+
+#pragma mark - Parse sections
+
+- (NSArray *)newParsedSections {
+    NSString *iniFileContents = [NSString stringWithContentsOfFile:self.iniFilePath encoding:NSUTF8StringEncoding error:nil];
+    
+    [self prepareForParsing];
+    [iniFileContents enumerateLinesUsingBlock:^(NSString *line, BOOL *stop) {
+        if (![self isNeedToSkipLine:line]) {
+            [self parseLine:line];
+        }
+    }];
+    [self addLastParsedSectionToSections];
+    
+    return [self copyParsedSections];
+}
+
+- (void)prepareForParsing {
+    self.mutableSections = [[NSMutableArray alloc] init];
+    self.currentSection = nil;
+}
+
+- (BOOL)isNeedToSkipLine:(NSString *)line {
+    return ([line length] < 1 || [self isLineAComment:line]);
+}
+
+- (BOOL)isLineAComment:(NSString *)line {
+    return ([line characterAtIndex:0] == COMMENTS_START_CHAR);
+}
+
+- (void)parseLine:(NSString *)line {
+    if ([self isLineASectionStart:line]) {
+        [self addPreviousSectionToSectionsIfNecessary];
+        [self createCurrentSection];
+    } else {
+        [self parseAssignmentForCurrentSectionInLine:line];
+    }
+}
+
+- (BOOL)isLineASectionStart:(NSString *)line {
+    return ([line characterAtIndex:0] == SECTION_START_CHAR);
+}
+
+- (void)addPreviousSectionToSectionsIfNecessary {
+    if (self.currentSection != nil) {
+        [self.mutableSections addObject:self.currentSection];
+        [self.currentSection release];
+    }
+}
+
+- (void)createCurrentSection {
+    self.currentSection = [[NSMutableDictionary alloc] init];
+}
+
+- (void)parseAssignmentForCurrentSectionInLine:(NSString *)line {
+    NSArray *components = [line componentsSeparatedByString:@"="];
+    if (components.count > 1) {
+        NSString *key = components[0];
+        NSString *value = components[1];
+        [self.currentSection setObject:value forKey:key];
+    }
+}
+
+- (void)addLastParsedSectionToSections {
+    [self addPreviousSectionToSectionsIfNecessary];
+}
+
+- (NSArray *)copyParsedSections {
+    return [self.mutableSections copy];
+}
+
+#pragma mark - Dealloc
+
+- (void)dealloc {
+    [_iniFilePath release];
+    [_mutableSections release];
+    [_currentSection release];
+    [super dealloc];
+}
+
+@end
--- a/project_files/HedgewarsMobile/Classes/MNEValueTrackingSlider.m	Tue Feb 09 21:11:16 2016 +0300
+++ b/project_files/HedgewarsMobile/Classes/MNEValueTrackingSlider.m	Mon Mar 14 22:08:27 2016 +0300
@@ -81,7 +81,7 @@
         [_text drawInRect:textRect
                  withFont:self.font
             lineBreakMode:UILineBreakModeWordWrap
-                alignment:UITextAlignmentCenter];
+                alignment:NSTextAlignmentCenter];
     }
 }
 
--- a/project_files/HedgewarsMobile/Classes/MainMenuViewController-iPad.xib	Tue Feb 09 21:11:16 2016 +0300
+++ b/project_files/HedgewarsMobile/Classes/MainMenuViewController-iPad.xib	Mon Mar 14 22:08:27 2016 +0300
@@ -1,12 +1,13 @@
 <?xml version="1.0" encoding="UTF-8" standalone="no"?>
-<document type="com.apple.InterfaceBuilder3.CocoaTouch.iPad.XIB" version="3.0" toolsVersion="9059" systemVersion="15B42" targetRuntime="iOS.CocoaTouch.iPad" propertyAccessControl="none">
+<document type="com.apple.InterfaceBuilder3.CocoaTouch.iPad.XIB" version="3.0" toolsVersion="9531" systemVersion="15D21" targetRuntime="iOS.CocoaTouch.iPad" propertyAccessControl="none">
     <dependencies>
         <deployment identifier="iOS"/>
-        <plugIn identifier="com.apple.InterfaceBuilder.IBCocoaTouchPlugin" version="9049"/>
+        <plugIn identifier="com.apple.InterfaceBuilder.IBCocoaTouchPlugin" version="9529"/>
     </dependencies>
     <objects>
         <placeholder placeholderIdentifier="IBFilesOwner" id="-1" userLabel="File's Owner" customClass="MainMenuViewController">
             <connections>
+                <outlet property="campaignButton" destination="m3U-KE-tbo" id="iAM-Xf-PsP"/>
                 <outlet property="missionsButton" destination="91" id="96"/>
                 <outlet property="simpleGameButton" destination="93" id="95"/>
                 <outlet property="view" destination="1" id="3"/>
@@ -20,12 +21,10 @@
                 <imageView userInteractionEnabled="NO" contentMode="scaleToFill" image="background.png" id="37">
                     <rect key="frame" x="0.0" y="0.0" width="1024" height="768"/>
                     <autoresizingMask key="autoresizingMask" widthSizable="YES" heightSizable="YES"/>
-                    <animations/>
                 </imageView>
                 <button opaque="NO" contentMode="scaleToFill" contentHorizontalAlignment="center" contentVerticalAlignment="center" lineBreakMode="middleTruncation" id="39" userLabel="local">
                     <rect key="frame" x="383" y="389" width="271" height="244"/>
                     <autoresizingMask key="autoresizingMask" flexibleMinX="YES" flexibleMaxX="YES" flexibleMinY="YES" flexibleMaxY="YES"/>
-                    <animations/>
                     <fontDescription key="fontDescription" name="Helvetica-Bold" family="Helvetica" pointSize="15"/>
                     <inset key="titleEdgeInsets" minX="0.0" minY="215" maxX="0.0" maxY="0.0"/>
                     <state key="normal" image="localplayButton.png">
@@ -42,7 +41,6 @@
                 <button opaque="NO" clipsSubviews="YES" alpha="0.69999999999999996" tag="3" contentMode="scaleToFill" contentHorizontalAlignment="center" contentVerticalAlignment="center" buttonType="infoLight" showsTouchWhenHighlighted="YES" lineBreakMode="middleTruncation" id="45">
                     <rect key="frame" x="984" y="20" width="22" height="22"/>
                     <autoresizingMask key="autoresizingMask" flexibleMinX="YES" flexibleMaxY="YES"/>
-                    <animations/>
                     <fontDescription key="fontDescription" name="Helvetica-Bold" family="Helvetica" pointSize="15"/>
                     <color key="tintColor" red="0.99607843137254903" green="0.85098039215686272" blue="0.039215686274509803" alpha="1" colorSpace="calibratedRGB"/>
                     <state key="normal">
@@ -59,7 +57,6 @@
                 <button opaque="NO" tag="2" contentMode="scaleToFill" contentHorizontalAlignment="center" contentVerticalAlignment="center" lineBreakMode="middleTruncation" id="52">
                     <rect key="frame" x="940" y="686" width="64" height="64"/>
                     <autoresizingMask key="autoresizingMask" flexibleMinX="YES" flexibleMinY="YES"/>
-                    <animations/>
                     <fontDescription key="fontDescription" name="Helvetica-Bold" family="Helvetica" pointSize="15"/>
                     <state key="normal" image="settingsButton.png">
                         <color key="titleColor" red="0.19607843459999999" green="0.30980393290000002" blue="0.52156865600000002" alpha="1" colorSpace="calibratedRGB"/>
@@ -75,7 +72,6 @@
                 <button opaque="NO" tag="4" contentMode="scaleToFill" contentHorizontalAlignment="center" contentVerticalAlignment="center" lineBreakMode="middleTruncation" id="88">
                     <rect key="frame" x="20" y="686" width="64" height="64"/>
                     <autoresizingMask key="autoresizingMask" flexibleMaxX="YES" flexibleMinY="YES"/>
-                    <animations/>
                     <fontDescription key="fontDescription" name="Helvetica-Bold" family="Helvetica" pointSize="15"/>
                     <state key="normal" image="savesButton.png">
                         <color key="titleColor" red="0.19607843459999999" green="0.30980393290000002" blue="0.52156865600000002" alpha="1" colorSpace="calibratedRGB"/>
@@ -91,12 +87,32 @@
                 <imageView userInteractionEnabled="NO" contentMode="scaleToFill" image="title.png" id="90">
                     <rect key="frame" x="242" y="43" width="540" height="300"/>
                     <autoresizingMask key="autoresizingMask" flexibleMinX="YES" flexibleMaxX="YES" flexibleMinY="YES" flexibleMaxY="YES"/>
-                    <animations/>
                 </imageView>
+                <button opaque="NO" tag="6" contentMode="scaleToFill" contentHorizontalAlignment="center" contentVerticalAlignment="center" buttonType="roundedRect" lineBreakMode="middleTruncation" id="93">
+                    <rect key="frame" x="242" y="686" width="100" height="37"/>
+                    <autoresizingMask key="autoresizingMask" flexibleMinX="YES" flexibleMaxX="YES" flexibleMinY="YES"/>
+                    <fontDescription key="fontDescription" name="Helvetica-Bold" family="Helvetica" pointSize="15"/>
+                    <state key="normal" title="Simple">
+                        <color key="titleShadowColor" white="0.5" alpha="1" colorSpace="calibratedWhite"/>
+                    </state>
+                    <connections>
+                        <action selector="switchViews:" destination="-1" eventType="touchUpInside" id="94"/>
+                    </connections>
+                </button>
+                <button opaque="NO" tag="7" contentMode="scaleToFill" contentHorizontalAlignment="center" contentVerticalAlignment="center" buttonType="roundedRect" lineBreakMode="middleTruncation" id="m3U-KE-tbo">
+                    <rect key="frame" x="682" y="686" width="100" height="37"/>
+                    <autoresizingMask key="autoresizingMask" flexibleMinX="YES" flexibleMaxX="YES" flexibleMinY="YES"/>
+                    <fontDescription key="fontDescription" name="Helvetica-Bold" family="Helvetica" pointSize="15"/>
+                    <state key="normal" title="Campaign">
+                        <color key="titleShadowColor" white="0.5" alpha="1" colorSpace="calibratedWhite"/>
+                    </state>
+                    <connections>
+                        <action selector="switchViews:" destination="-1" eventType="touchUpInside" id="OmQ-ow-2f5"/>
+                    </connections>
+                </button>
                 <button opaque="NO" tag="5" contentMode="scaleToFill" contentHorizontalAlignment="center" contentVerticalAlignment="center" buttonType="roundedRect" lineBreakMode="middleTruncation" id="91">
-                    <rect key="frame" x="565" y="686" width="89" height="37"/>
+                    <rect key="frame" x="462" y="686" width="100" height="37"/>
                     <autoresizingMask key="autoresizingMask" flexibleMinX="YES" flexibleMaxX="YES" flexibleMinY="YES"/>
-                    <animations/>
                     <fontDescription key="fontDescription" name="Helvetica-Bold" family="Helvetica" pointSize="15"/>
                     <state key="normal" title="Missions">
                         <color key="titleShadowColor" white="0.5" alpha="1" colorSpace="calibratedWhite"/>
@@ -105,20 +121,7 @@
                         <action selector="switchViews:" destination="-1" eventType="touchUpInside" id="92"/>
                     </connections>
                 </button>
-                <button opaque="NO" tag="6" contentMode="scaleToFill" contentHorizontalAlignment="center" contentVerticalAlignment="center" buttonType="roundedRect" lineBreakMode="middleTruncation" id="93">
-                    <rect key="frame" x="383" y="686" width="89" height="37"/>
-                    <autoresizingMask key="autoresizingMask" flexibleMinX="YES" flexibleMaxX="YES" flexibleMinY="YES"/>
-                    <animations/>
-                    <fontDescription key="fontDescription" name="Helvetica-Bold" family="Helvetica" pointSize="15"/>
-                    <state key="normal" title="Simple">
-                        <color key="titleShadowColor" white="0.5" alpha="1" colorSpace="calibratedWhite"/>
-                    </state>
-                    <connections>
-                        <action selector="switchViews:" destination="-1" eventType="touchUpInside" id="94"/>
-                    </connections>
-                </button>
             </subviews>
-            <animations/>
             <color key="backgroundColor" red="0.0" green="0.0" blue="0.0" alpha="1" colorSpace="calibratedRGB"/>
             <nil key="simulatedStatusBarMetrics"/>
             <simulatedOrientationMetrics key="simulatedOrientationMetrics" orientation="landscapeRight"/>
--- a/project_files/HedgewarsMobile/Classes/MainMenuViewController-iPhone.xib	Tue Feb 09 21:11:16 2016 +0300
+++ b/project_files/HedgewarsMobile/Classes/MainMenuViewController-iPhone.xib	Mon Mar 14 22:08:27 2016 +0300
@@ -1,12 +1,13 @@
 <?xml version="1.0" encoding="UTF-8" standalone="no"?>
-<document type="com.apple.InterfaceBuilder3.CocoaTouch.XIB" version="3.0" toolsVersion="9059" systemVersion="15B42" targetRuntime="iOS.CocoaTouch" propertyAccessControl="none">
+<document type="com.apple.InterfaceBuilder3.CocoaTouch.XIB" version="3.0" toolsVersion="9531" systemVersion="15D21" targetRuntime="iOS.CocoaTouch" propertyAccessControl="none">
     <dependencies>
         <deployment identifier="iOS"/>
-        <plugIn identifier="com.apple.InterfaceBuilder.IBCocoaTouchPlugin" version="9049"/>
+        <plugIn identifier="com.apple.InterfaceBuilder.IBCocoaTouchPlugin" version="9529"/>
     </dependencies>
     <objects>
         <placeholder placeholderIdentifier="IBFilesOwner" id="-1" userLabel="File's Owner" customClass="MainMenuViewController">
             <connections>
+                <outlet property="campaignButton" destination="bc4-Vx-1l9" id="BxT-Y6-DvJ"/>
                 <outlet property="missionsButton" destination="52" id="54"/>
                 <outlet property="simpleGameButton" destination="51" id="56"/>
                 <outlet property="view" destination="1" id="3"/>
@@ -20,18 +21,15 @@
                 <imageView userInteractionEnabled="NO" contentMode="scaleAspectFill" image="background.png" id="22">
                     <rect key="frame" x="0.0" y="0.0" width="480" height="320"/>
                     <autoresizingMask key="autoresizingMask" widthSizable="YES" heightSizable="YES"/>
-                    <animations/>
                     <color key="backgroundColor" white="0.0" alpha="0.0" colorSpace="calibratedWhite"/>
                 </imageView>
                 <imageView opaque="NO" clearsContextBeforeDrawing="NO" userInteractionEnabled="NO" contentMode="center" image="title.png" id="23">
                     <rect key="frame" x="105" y="20" width="270" height="150"/>
                     <autoresizingMask key="autoresizingMask" flexibleMinX="YES" flexibleMaxX="YES" flexibleMaxY="YES"/>
-                    <animations/>
                 </imageView>
                 <button opaque="NO" tag="5" contentMode="scaleToFill" contentHorizontalAlignment="center" contentVerticalAlignment="center" buttonType="roundedRect" lineBreakMode="middleTruncation" id="52">
-                    <rect key="frame" x="376" y="14" width="89" height="31"/>
+                    <rect key="frame" x="376" y="14" width="96" height="31"/>
                     <autoresizingMask key="autoresizingMask" flexibleMinX="YES" flexibleMaxY="YES"/>
-                    <animations/>
                     <fontDescription key="fontDescription" name="Helvetica-Bold" family="Helvetica" pointSize="15"/>
                     <state key="normal" title="Missions">
                         <color key="titleShadowColor" white="0.5" alpha="1" colorSpace="calibratedWhite"/>
@@ -43,7 +41,6 @@
                 <button opaque="NO" clearsContextBeforeDrawing="NO" contentMode="scaleToFill" contentHorizontalAlignment="center" contentVerticalAlignment="center" lineBreakMode="middleTruncation" id="24">
                     <rect key="frame" x="190" y="200" width="100" height="100"/>
                     <autoresizingMask key="autoresizingMask" flexibleMinX="YES" flexibleMaxX="YES" flexibleMinY="YES"/>
-                    <animations/>
                     <color key="backgroundColor" red="0.0" green="0.0" blue="0.0" alpha="0.0" colorSpace="calibratedRGB"/>
                     <fontDescription key="fontDescription" name="Helvetica-Bold" family="Helvetica" pointSize="15"/>
                     <state key="normal" image="localplayButton.png">
@@ -60,7 +57,6 @@
                 <button opaque="NO" clearsContextBeforeDrawing="NO" tag="2" contentMode="scaleToFill" contentHorizontalAlignment="center" contentVerticalAlignment="center" lineBreakMode="middleTruncation" id="28">
                     <rect key="frame" x="396" y="236" width="64" height="64"/>
                     <autoresizingMask key="autoresizingMask" flexibleMinX="YES" flexibleMinY="YES"/>
-                    <animations/>
                     <fontDescription key="fontDescription" name="Helvetica-Bold" family="Helvetica" pointSize="15"/>
                     <state key="normal" image="settingsButton.png">
                         <color key="titleColor" red="0.19607843" green="0.30980393000000001" blue="0.52156866000000002" alpha="1" colorSpace="calibratedRGB"/>
@@ -76,7 +72,6 @@
                 <button opaque="NO" clearsContextBeforeDrawing="NO" tag="4" contentMode="scaleToFill" contentHorizontalAlignment="center" contentVerticalAlignment="center" lineBreakMode="middleTruncation" id="43">
                     <rect key="frame" x="20" y="236" width="64" height="64"/>
                     <autoresizingMask key="autoresizingMask" flexibleMaxX="YES" flexibleMinY="YES"/>
-                    <animations/>
                     <fontDescription key="fontDescription" name="Helvetica-Bold" family="Helvetica" pointSize="15"/>
                     <state key="normal" image="savesButton.png">
                         <color key="titleColor" red="0.19607843" green="0.30980393000000001" blue="0.52156866000000002" alpha="1" colorSpace="calibratedRGB"/>
@@ -92,7 +87,6 @@
                 <button opaque="NO" alpha="0.69999999999999996" tag="3" contentMode="scaleToFill" contentHorizontalAlignment="center" contentVerticalAlignment="center" buttonType="infoLight" showsTouchWhenHighlighted="YES" lineBreakMode="middleTruncation" id="41">
                     <rect key="frame" x="20" y="20" width="22" height="22"/>
                     <autoresizingMask key="autoresizingMask" flexibleMaxX="YES" flexibleMaxY="YES"/>
-                    <animations/>
                     <fontDescription key="fontDescription" name="Helvetica-Bold" family="Helvetica" pointSize="15"/>
                     <color key="tintColor" red="0.99607843137254903" green="0.85098039215686272" blue="0.039215686274509803" alpha="1" colorSpace="calibratedRGB"/>
                     <state key="normal">
@@ -107,9 +101,8 @@
                     </connections>
                 </button>
                 <button opaque="NO" tag="6" contentMode="scaleToFill" contentHorizontalAlignment="center" contentVerticalAlignment="center" buttonType="roundedRect" lineBreakMode="middleTruncation" id="51">
-                    <rect key="frame" x="376" y="57" width="89" height="31"/>
+                    <rect key="frame" x="376" y="57" width="96" height="31"/>
                     <autoresizingMask key="autoresizingMask" flexibleMinX="YES" flexibleMaxY="YES"/>
-                    <animations/>
                     <fontDescription key="fontDescription" name="Helvetica-Bold" family="Helvetica" pointSize="15"/>
                     <state key="normal" title="Simple">
                         <color key="titleShadowColor" white="0.5" alpha="1" colorSpace="calibratedWhite"/>
@@ -118,13 +111,23 @@
                         <action selector="switchViews:" destination="-1" eventType="touchUpInside" id="55"/>
                     </connections>
                 </button>
+                <button opaque="NO" tag="7" contentMode="scaleToFill" contentHorizontalAlignment="center" contentVerticalAlignment="center" buttonType="roundedRect" lineBreakMode="middleTruncation" id="bc4-Vx-1l9">
+                    <rect key="frame" x="376" y="100" width="96" height="31"/>
+                    <autoresizingMask key="autoresizingMask" flexibleMinX="YES" flexibleMaxY="YES"/>
+                    <fontDescription key="fontDescription" name="Helvetica-Bold" family="Helvetica" pointSize="15"/>
+                    <state key="normal" title="Campaign">
+                        <color key="titleShadowColor" white="0.5" alpha="1" colorSpace="calibratedWhite"/>
+                    </state>
+                    <connections>
+                        <action selector="switchViews:" destination="-1" eventType="touchUpInside" id="11r-ZZ-mUo"/>
+                    </connections>
+                </button>
             </subviews>
-            <animations/>
-            <color key="backgroundColor" cocoaTouchSystemColor="darkTextColor"/>
+            <color key="backgroundColor" red="0.0" green="0.0" blue="0.0" alpha="1" colorSpace="calibratedRGB"/>
             <nil key="simulatedStatusBarMetrics"/>
             <simulatedOrientationMetrics key="simulatedOrientationMetrics" orientation="landscapeRight"/>
             <freeformSimulatedSizeMetrics key="simulatedDestinationMetrics"/>
-            <point key="canvasLocation" x="567" y="470"/>
+            <point key="canvasLocation" x="310" y="551"/>
         </view>
     </objects>
     <resources>
--- a/project_files/HedgewarsMobile/Classes/MainMenuViewController.m	Tue Feb 09 21:11:16 2016 +0300
+++ b/project_files/HedgewarsMobile/Classes/MainMenuViewController.m	Mon Mar 14 22:08:27 2016 +0300
@@ -26,6 +26,7 @@
 #import "SavedGamesViewController.h"
 #import "RestoreViewController.h"
 #import "MissionTrainingViewController.h"
+#import "CampaignsViewController.h"
 #import "Appirater.h"
 #import "ServerProtocolNetwork.h"
 #import "GameInterfaceBridge.h"
@@ -44,6 +45,7 @@
 @interface MainMenuViewController ()
 @property (retain, nonatomic) IBOutlet UIButton *simpleGameButton;
 @property (retain, nonatomic) IBOutlet UIButton *missionsButton;
+@property (retain, nonatomic) IBOutlet UIButton *campaignButton;
 @end
 
 @implementation MainMenuViewController
@@ -59,9 +61,11 @@
     
     [self.simpleGameButton setTitle:NSLocalizedString(@"Simple", nil) forState:UIControlStateNormal];
     [self.missionsButton setTitle:NSLocalizedString(@"Missions", nil) forState:UIControlStateNormal];
+    [self.campaignButton setTitle:NSLocalizedString(@"Campaign", nil) forState:UIControlStateNormal];
     
     [self.simpleGameButton applyDarkBlueQuickStyle];
     [self.missionsButton applyDarkBlueQuickStyle];
+    [self.campaignButton applyDarkBlueQuickStyle];
     
     // get the app's version
     NSString *version = [[[NSBundle mainBundle] infoDictionary] objectForKey:(NSString*)kCFBundleVersionKey];
@@ -86,8 +90,7 @@
     {
         NSString *xibName = [@"RestoreViewController-" stringByAppendingString:(IS_IPAD() ? @"iPad" : @"iPhone")];
         RestoreViewController *restored = [[RestoreViewController alloc] initWithNibName:xibName bundle:nil];
-        if ([restored respondsToSelector:@selector(setModalPresentationStyle:)])
-            restored.modalPresentationStyle = UIModalPresentationFormSheet;
+        restored.modalPresentationStyle = UIModalPresentationFormSheet;
 
         [self performSelector:@selector(presentViewController:) withObject:restored afterDelay:0.25];
     }
@@ -216,8 +219,7 @@
             {
                 AboutViewController *about = [[AboutViewController alloc] initWithNibName:@"AboutViewController" bundle:nil];
                 about.modalTransitionStyle = UIModalTransitionStyleCoverVertical;
-                if ([about respondsToSelector:@selector(setModalPresentationStyle:)])
-                     about.modalPresentationStyle = UIModalPresentationFormSheet;
+                about.modalPresentationStyle = UIModalPresentationFormSheet;
                 
                 [self presentViewController:about animated:YES completion:nil];
                 [about release];
@@ -228,8 +230,7 @@
             {
                 SavedGamesViewController *savedgames = [[SavedGamesViewController alloc] initWithNibName:@"SavedGamesViewController" bundle:nil];
                 savedgames.modalTransitionStyle = UIModalTransitionStyleCoverVertical;
-                if ([savedgames respondsToSelector:@selector(setModalPresentationStyle:)])
-                    savedgames.modalPresentationStyle = UIModalPresentationPageSheet;
+                savedgames.modalPresentationStyle = UIModalPresentationPageSheet;
                 
                 [self presentViewController:savedgames animated:YES completion:nil];
                 [savedgames release];
@@ -240,8 +241,7 @@
                 xib = IS_IPAD() ? @"MissionTrainingViewController-iPad" : @"MissionTrainingViewController-iPhone";
                 MissionTrainingViewController *missions = [[MissionTrainingViewController alloc] initWithNibName:xib bundle:nil];
                 missions.modalTransitionStyle = IS_IPAD() ? UIModalTransitionStyleCoverVertical : UIModalTransitionStyleCrossDissolve;
-                if ([missions respondsToSelector:@selector(setModalPresentationStyle:)])
-                    missions.modalPresentationStyle = UIModalPresentationPageSheet;
+                missions.modalPresentationStyle = UIModalPresentationPageSheet;
                 
                 [self presentViewController:missions animated:YES completion:nil];
                 [missions release];
@@ -251,6 +251,20 @@
             [GameInterfaceBridge registerCallingController:self];
             [GameInterfaceBridge startSimpleGame];
             break;
+        case 7:
+            {
+                xib = IS_IPAD() ? @"CampaignsViewController-iPad" : @"CampaignsViewController-iPhone";
+                CampaignsViewController *campaigns = [[CampaignsViewController alloc] initWithNibName:xib bundle:nil];
+                UINavigationController *campaignNavigationController = [[UINavigationController alloc] initWithRootViewController:campaigns];
+                [campaigns release];
+                
+                campaignNavigationController.modalTransitionStyle = IS_IPAD() ? UIModalTransitionStyleCoverVertical : UIModalTransitionStyleCrossDissolve;
+                campaignNavigationController.modalPresentationStyle = UIModalPresentationPageSheet;
+                
+                [self presentViewController:campaignNavigationController animated:YES completion:nil];
+                [campaignNavigationController release];
+            }
+            break;
         default:
             alert = [[UIAlertView alloc] initWithTitle:@"Not Yet Implemented"
                                                message:@"Sorry, this feature is not yet implemented"
@@ -286,6 +300,7 @@
 -(void) dealloc {
     [_simpleGameButton release];
     [_missionsButton release];
+    [_campaignButton release];
     [super dealloc];
 }
 
--- a/project_files/HedgewarsMobile/Classes/MapConfigViewController.m	Tue Feb 09 21:11:16 2016 +0300
+++ b/project_files/HedgewarsMobile/Classes/MapConfigViewController.m	Mon Mar 14 22:08:27 2016 +0300
@@ -45,9 +45,7 @@
         return;
 
     // generate a seed
-    CFUUIDRef uuid = CFUUIDCreate(kCFAllocatorDefault);
-    NSString *seed = (NSString *)CFUUIDCreateString(kCFAllocatorDefault, uuid);
-    CFRelease(uuid);
+    NSString *seed = [HWUtils seed];
     NSString *seedCmd = [[NSString alloc] initWithFormat:@"eseed {%@}", seed];
     self.seedCommand = seedCmd;
     [seedCmd release];
--- a/project_files/HedgewarsMobile/Classes/MissionTrainingViewController.m	Tue Feb 09 21:11:16 2016 +0300
+++ b/project_files/HedgewarsMobile/Classes/MissionTrainingViewController.m	Mon Mar 14 22:08:27 2016 +0300
@@ -226,7 +226,7 @@
     
     cell.textLabel.textColor = [UIColor lightYellowColor];
     //cell.textLabel.font = [UIFont fontWithName:@"Bradley Hand Bold" size:[UIFont labelFontSize]];
-    cell.textLabel.textAlignment = (IS_IPAD()) ? UITextAlignmentCenter : UITextAlignmentLeft;
+    cell.textLabel.textAlignment = (IS_IPAD()) ? NSTextAlignmentCenter : NSTextAlignmentLeft;
     cell.textLabel.backgroundColor = [UIColor clearColor];
     cell.textLabel.adjustsFontSizeToFitWidth = YES;
     cell.detailTextLabel.text = (IS_IPAD()) ? nil : self.dictOfMissions[missionID][@"desc"];
--- a/project_files/HedgewarsMobile/Classes/SavedGamesViewController.m	Tue Feb 09 21:11:16 2016 +0300
+++ b/project_files/HedgewarsMobile/Classes/SavedGamesViewController.m	Mon Mar 14 22:08:27 2016 +0300
@@ -144,7 +144,7 @@
 
     UILabel *label = [[UILabel alloc] initWithFrame:CGRectMake(0, 0, self.tableView.frame.size.width*60/100, 60)];
     label.center = CGPointMake(self.tableView.frame.size.width/2, 30);
-    label.textAlignment = UITextAlignmentCenter;
+    label.textAlignment = NSTextAlignmentCenter;
     label.font = [UIFont italicSystemFontOfSize:16];
     label.textColor = [UIColor lightGrayColor];
     label.numberOfLines = 5;
--- a/project_files/HedgewarsMobile/Classes/SchemeWeaponConfigViewController.m	Tue Feb 09 21:11:16 2016 +0300
+++ b/project_files/HedgewarsMobile/Classes/SchemeWeaponConfigViewController.m	Mon Mar 14 22:08:27 2016 +0300
@@ -270,7 +270,7 @@
 
     UILabel *label = [[UILabel alloc] initWithFrame:CGRectMake(0, 0, aTableView.frame.size.width*90/100, height)];
     label.center = CGPointMake(aTableView.frame.size.width/2, height/2);
-    label.textAlignment = UITextAlignmentCenter;
+    label.textAlignment = NSTextAlignmentCenter;
     label.font = [UIFont italicSystemFontOfSize:12];
     label.textColor = [UIColor whiteColor];
     label.numberOfLines = 2;
--- a/project_files/HedgewarsMobile/Classes/StatsPageViewController.m	Tue Feb 09 21:11:16 2016 +0300
+++ b/project_files/HedgewarsMobile/Classes/StatsPageViewController.m	Mon Mar 14 22:08:27 2016 +0300
@@ -124,7 +124,7 @@
     cell.accessoryView = imgView;
     [imgView release];
 
-    cell.textLabel.textAlignment = UITextAlignmentCenter;
+    cell.textLabel.textAlignment = NSTextAlignmentCenter;
     cell.textLabel.adjustsFontSizeToFitWidth = YES;
     cell.backgroundColor = [UIColor blackColor];
     cell.selectionStyle = UITableViewCellSelectionStyleNone;
--- a/project_files/HedgewarsMobile/Classes/SupportViewController.m	Tue Feb 09 21:11:16 2016 +0300
+++ b/project_files/HedgewarsMobile/Classes/SupportViewController.m	Mon Mar 14 22:08:27 2016 +0300
@@ -74,10 +74,10 @@
 
     if (section == 0) {
         imgName = @"star";
-        cell.textLabel.textAlignment = UITextAlignmentCenter;
+        cell.textLabel.textAlignment = NSTextAlignmentCenter;
         cell.imageView.image = nil;
     } else {
-        cell.textLabel.textAlignment = UITextAlignmentLeft;
+        cell.textLabel.textAlignment = NSTextAlignmentLeft;
         switch (row) {
             case 0:
                 imgName = @"fb";
@@ -160,7 +160,7 @@
 
         UILabel *label = [[UILabel alloc] initWithFrame:CGRectMake(0, 0, self.tableView.frame.size.width, 20)];
         label.autoresizingMask = UIViewAutoresizingFlexibleLeftMargin | UIViewAutoresizingFlexibleRightMargin;
-        label.textAlignment = UITextAlignmentCenter;
+        label.textAlignment = NSTextAlignmentCenter;
         label.text = NSLocalizedString(@" ♥ THANK YOU ♥ ", nil);
         label.backgroundColor = [UIColor clearColor];
         label.center = CGPointMake(self.tableView.frame.size.width/2, 250);
--- a/project_files/HedgewarsMobile/Classes/TeamConfigViewController.m	Tue Feb 09 21:11:16 2016 +0300
+++ b/project_files/HedgewarsMobile/Classes/TeamConfigViewController.m	Mon Mar 14 22:08:27 2016 +0300
@@ -205,7 +205,7 @@
 
     UILabel *label = [[UILabel alloc] initWithFrame:CGRectMake(0, 0, aTableView.frame.size.width*90/100, height)];
     label.center = CGPointMake(aTableView.frame.size.width/2, height/2);
-    label.textAlignment = UITextAlignmentCenter;
+    label.textAlignment = NSTextAlignmentCenter;
     label.font = [UIFont italicSystemFontOfSize:12];
     label.textColor = [UIColor whiteColor];
     label.numberOfLines = 2;
--- a/project_files/HedgewarsMobile/Classes/WeaponCellView.m	Tue Feb 09 21:11:16 2016 +0300
+++ b/project_files/HedgewarsMobile/Classes/WeaponCellView.m	Mon Mar 14 22:08:27 2016 +0300
@@ -81,27 +81,27 @@
         initialLab = [[UILabel alloc] init];
         initialLab.backgroundColor = [UIColor clearColor];
         initialLab.textColor = [UIColor grayColor];
-        initialLab.textAlignment = UITextAlignmentCenter;
+        initialLab.textAlignment = NSTextAlignmentCenter;
 
         probabilityLab = [[UILabel alloc] init];
         probabilityLab.backgroundColor = [UIColor clearColor];
         probabilityLab.textColor = [UIColor grayColor];
-        probabilityLab.textAlignment = UITextAlignmentCenter;
+        probabilityLab.textAlignment = NSTextAlignmentCenter;
 
         delayLab = [[UILabel alloc] init];
         delayLab.backgroundColor = [UIColor clearColor];
         delayLab.textColor = [UIColor grayColor];
-        delayLab.textAlignment = UITextAlignmentCenter;
+        delayLab.textAlignment = NSTextAlignmentCenter;
 
         crateLab = [[UILabel alloc] init];
         crateLab.backgroundColor = [UIColor clearColor];
         crateLab.textColor = [UIColor grayColor];
-        crateLab.textAlignment = UITextAlignmentCenter;
+        crateLab.textAlignment = NSTextAlignmentCenter;
 
         helpLabel = [[UILabel alloc] init];
         helpLabel.backgroundColor = [UIColor clearColor];
         helpLabel.textColor = [UIColor darkGrayColor];
-        helpLabel.textAlignment = UITextAlignmentRight;
+        helpLabel.textAlignment = NSTextAlignmentRight;
         helpLabel.font = [UIFont italicSystemFontOfSize:[UIFont systemFontSize]];
         helpLabel.adjustsFontSizeToFitWidth = YES;
 
--- a/project_files/HedgewarsMobile/Hedgewars.xcodeproj/project.pbxproj	Tue Feb 09 21:11:16 2016 +0300
+++ b/project_files/HedgewarsMobile/Hedgewars.xcodeproj/project.pbxproj	Mon Mar 14 22:08:27 2016 +0300
@@ -242,6 +242,7 @@
 		61F9040B11DF59370068B24D /* background.png in Resources */ = {isa = PBXBuildFile; fileRef = 61F9040A11DF59370068B24D /* background.png */; };
 		61F904D711DF7DA30068B24D /* WeaponCellView.m in Sources */ = {isa = PBXBuildFile; fileRef = 61F904D611DF7DA30068B24D /* WeaponCellView.m */; };
 		922F64900F10F53100DC6EC0 /* libfpc.a in Frameworks */ = {isa = PBXBuildFile; fileRef = 928301170F10CAFC00CC5A3C /* libfpc.a */; };
+		F60ACBB71C7BC08B00385701 /* IniParser.m in Sources */ = {isa = PBXBuildFile; fileRef = F60ACBB61C7BC08B00385701 /* IniParser.m */; };
 		F60D04771BD137B5003ACB00 /* bullet_filled.png in Resources */ = {isa = PBXBuildFile; fileRef = F60D04631BD137B5003ACB00 /* bullet_filled.png */; };
 		F60D04781BD137B5003ACB00 /* bullet_filled@2x.png in Resources */ = {isa = PBXBuildFile; fileRef = F60D04641BD137B5003ACB00 /* bullet_filled@2x.png */; };
 		F60D04791BD137B5003ACB00 /* bullet.png in Resources */ = {isa = PBXBuildFile; fileRef = F60D04651BD137B5003ACB00 /* bullet.png */; };
@@ -262,6 +263,12 @@
 		F60D04881BD137B5003ACB00 /* teams_filled@2x.png in Resources */ = {isa = PBXBuildFile; fileRef = F60D04741BD137B5003ACB00 /* teams_filled@2x.png */; };
 		F60D04891BD137B5003ACB00 /* teams.png in Resources */ = {isa = PBXBuildFile; fileRef = F60D04751BD137B5003ACB00 /* teams.png */; };
 		F60D048A1BD137B5003ACB00 /* teams@2x.png in Resources */ = {isa = PBXBuildFile; fileRef = F60D04761BD137B5003ACB00 /* teams@2x.png */; };
+		F6338CC81C7A53C100353945 /* CampaignsViewController.m in Sources */ = {isa = PBXBuildFile; fileRef = F6338CC61C7A53C100353945 /* CampaignsViewController.m */; };
+		F6338CC91C7A53C100353945 /* CampaignsViewController-iPhone.xib in Resources */ = {isa = PBXBuildFile; fileRef = F6338CC71C7A53C100353945 /* CampaignsViewController-iPhone.xib */; };
+		F6338CCC1C7A542C00353945 /* CampaignsViewController-iPad.xib in Resources */ = {isa = PBXBuildFile; fileRef = F6338CCB1C7A542C00353945 /* CampaignsViewController-iPad.xib */; };
+		F6338CD81C7A702B00353945 /* CampaignViewController.m in Sources */ = {isa = PBXBuildFile; fileRef = F6338CD61C7A702B00353945 /* CampaignViewController.m */; };
+		F6338CD91C7A702B00353945 /* CampaignViewController-iPhone.xib in Resources */ = {isa = PBXBuildFile; fileRef = F6338CD71C7A702B00353945 /* CampaignViewController-iPhone.xib */; };
+		F6338CDB1C7A709600353945 /* CampaignViewController-iPad.xib in Resources */ = {isa = PBXBuildFile; fileRef = F6338CDA1C7A709600353945 /* CampaignViewController-iPad.xib */; };
 		F6448CE31BD2E00500C31C8C /* TableViewControllerWithDoneButton.m in Sources */ = {isa = PBXBuildFile; fileRef = F6448CE21BD2E00500C31C8C /* TableViewControllerWithDoneButton.m */; };
 		F65724FD1B7E784700A86262 /* helpabove.png in Resources */ = {isa = PBXBuildFile; fileRef = F65724F81B7E784700A86262 /* helpabove.png */; };
 		F65724FE1B7E784700A86262 /* helpbottom.png in Resources */ = {isa = PBXBuildFile; fileRef = F65724F91B7E784700A86262 /* helpbottom.png */; };
@@ -731,6 +738,8 @@
 		61F904D611DF7DA30068B24D /* WeaponCellView.m */ = {isa = PBXFileReference; fileEncoding = 4; lastKnownFileType = sourcecode.c.objc; name = WeaponCellView.m; path = Classes/WeaponCellView.m; sourceTree = "<group>"; };
 		8D1107310486CEB800E47090 /* Info.plist */ = {isa = PBXFileReference; fileEncoding = 4; lastKnownFileType = text.plist.xml; path = Info.plist; sourceTree = "<group>"; };
 		928301170F10CAFC00CC5A3C /* libfpc.a */ = {isa = PBXFileReference; explicitFileType = archive.ar; includeInIndex = 0; path = libfpc.a; sourceTree = BUILT_PRODUCTS_DIR; };
+		F60ACBB51C7BC08B00385701 /* IniParser.h */ = {isa = PBXFileReference; fileEncoding = 4; lastKnownFileType = sourcecode.c.h; name = IniParser.h; path = Classes/IniParser.h; sourceTree = "<group>"; };
+		F60ACBB61C7BC08B00385701 /* IniParser.m */ = {isa = PBXFileReference; fileEncoding = 4; lastKnownFileType = sourcecode.c.objc; name = IniParser.m; path = Classes/IniParser.m; sourceTree = "<group>"; };
 		F60D04631BD137B5003ACB00 /* bullet_filled.png */ = {isa = PBXFileReference; lastKnownFileType = image.png; name = bullet_filled.png; path = Resources/Icons/bullet_filled.png; sourceTree = "<group>"; };
 		F60D04641BD137B5003ACB00 /* bullet_filled@2x.png */ = {isa = PBXFileReference; lastKnownFileType = image.png; name = "bullet_filled@2x.png"; path = "Resources/Icons/bullet_filled@2x.png"; sourceTree = "<group>"; };
 		F60D04651BD137B5003ACB00 /* bullet.png */ = {isa = PBXFileReference; lastKnownFileType = image.png; name = bullet.png; path = Resources/Icons/bullet.png; sourceTree = "<group>"; };
@@ -751,6 +760,14 @@
 		F60D04741BD137B5003ACB00 /* teams_filled@2x.png */ = {isa = PBXFileReference; lastKnownFileType = image.png; name = "teams_filled@2x.png"; path = "Resources/Icons/teams_filled@2x.png"; sourceTree = "<group>"; };
 		F60D04751BD137B5003ACB00 /* teams.png */ = {isa = PBXFileReference; lastKnownFileType = image.png; name = teams.png; path = Resources/Icons/teams.png; sourceTree = "<group>"; };
 		F60D04761BD137B5003ACB00 /* teams@2x.png */ = {isa = PBXFileReference; lastKnownFileType = image.png; name = "teams@2x.png"; path = "Resources/Icons/teams@2x.png"; sourceTree = "<group>"; };
+		F6338CC51C7A53C100353945 /* CampaignsViewController.h */ = {isa = PBXFileReference; fileEncoding = 4; lastKnownFileType = sourcecode.c.h; path = CampaignsViewController.h; sourceTree = "<group>"; };
+		F6338CC61C7A53C100353945 /* CampaignsViewController.m */ = {isa = PBXFileReference; fileEncoding = 4; lastKnownFileType = sourcecode.c.objc; path = CampaignsViewController.m; sourceTree = "<group>"; };
+		F6338CC71C7A53C100353945 /* CampaignsViewController-iPhone.xib */ = {isa = PBXFileReference; fileEncoding = 4; lastKnownFileType = file.xib; path = "CampaignsViewController-iPhone.xib"; sourceTree = "<group>"; };
+		F6338CCB1C7A542C00353945 /* CampaignsViewController-iPad.xib */ = {isa = PBXFileReference; fileEncoding = 4; lastKnownFileType = file.xib; path = "CampaignsViewController-iPad.xib"; sourceTree = "<group>"; };
+		F6338CD51C7A702B00353945 /* CampaignViewController.h */ = {isa = PBXFileReference; fileEncoding = 4; lastKnownFileType = sourcecode.c.h; path = CampaignViewController.h; sourceTree = "<group>"; };
+		F6338CD61C7A702B00353945 /* CampaignViewController.m */ = {isa = PBXFileReference; fileEncoding = 4; lastKnownFileType = sourcecode.c.objc; path = CampaignViewController.m; sourceTree = "<group>"; };
+		F6338CD71C7A702B00353945 /* CampaignViewController-iPhone.xib */ = {isa = PBXFileReference; fileEncoding = 4; lastKnownFileType = file.xib; path = "CampaignViewController-iPhone.xib"; sourceTree = "<group>"; };
+		F6338CDA1C7A709600353945 /* CampaignViewController-iPad.xib */ = {isa = PBXFileReference; fileEncoding = 4; lastKnownFileType = file.xib; path = "CampaignViewController-iPad.xib"; sourceTree = "<group>"; };
 		F6448CE11BD2E00500C31C8C /* TableViewControllerWithDoneButton.h */ = {isa = PBXFileReference; fileEncoding = 4; lastKnownFileType = sourcecode.c.h; path = TableViewControllerWithDoneButton.h; sourceTree = "<group>"; };
 		F6448CE21BD2E00500C31C8C /* TableViewControllerWithDoneButton.m */ = {isa = PBXFileReference; fileEncoding = 4; lastKnownFileType = sourcecode.c.objc; path = TableViewControllerWithDoneButton.m; sourceTree = "<group>"; };
 		F65724F81B7E784700A86262 /* helpabove.png */ = {isa = PBXFileReference; lastKnownFileType = image.png; path = helpabove.png; sourceTree = "<group>"; };
@@ -970,6 +987,7 @@
 				61915D59143A4E2C00299991 /* MissionTrainingViewController.m */,
 				61915D5A143A4E2C00299991 /* MissionTrainingViewController-iPhone.xib */,
 				61077E86143FB09800645B29 /* MissionTrainingViewController-iPad.xib */,
+				F6338CDC1C7A721B00353945 /* Campaigns */,
 			);
 			name = "Satellite Controllers";
 			sourceTree = "<group>";
@@ -1256,6 +1274,8 @@
 				6165922611CA9BD500D6E256 /* HWUtils.m */,
 				6165922C11CA9BD500D6E256 /* UIImageExtra.h */,
 				6165922D11CA9BD500D6E256 /* UIImageExtra.m */,
+				F60ACBB51C7BC08B00385701 /* IniParser.h */,
+				F60ACBB61C7BC08B00385701 /* IniParser.m */,
 			);
 			name = Helpers;
 			sourceTree = "<group>";
@@ -1394,6 +1414,21 @@
 			name = Tabbar;
 			sourceTree = "<group>";
 		};
+		F6338CDC1C7A721B00353945 /* Campaigns */ = {
+			isa = PBXGroup;
+			children = (
+				F6338CC51C7A53C100353945 /* CampaignsViewController.h */,
+				F6338CC61C7A53C100353945 /* CampaignsViewController.m */,
+				F6338CC71C7A53C100353945 /* CampaignsViewController-iPhone.xib */,
+				F6338CCB1C7A542C00353945 /* CampaignsViewController-iPad.xib */,
+				F6338CD51C7A702B00353945 /* CampaignViewController.h */,
+				F6338CD61C7A702B00353945 /* CampaignViewController.m */,
+				F6338CD71C7A702B00353945 /* CampaignViewController-iPhone.xib */,
+				F6338CDA1C7A709600353945 /* CampaignViewController-iPad.xib */,
+			);
+			name = Campaigns;
+			sourceTree = "<group>";
+		};
 		F65724F71B7E784700A86262 /* Help Bubbles */ = {
 			isa = PBXGroup;
 			children = (
@@ -1608,6 +1643,7 @@
 				61370653117B1D50004EE44A /* Entitlements-Distribution.plist in Resources */,
 				611E12FF117BBBDA0044B62F /* Entitlements-Development.plist in Resources */,
 				6165925311CA9CB400D6E256 /* MainMenuViewController-iPad.xib in Resources */,
+				F6338CCC1C7A542C00353945 /* CampaignsViewController-iPad.xib in Resources */,
 				6165925511CA9CB400D6E256 /* MapConfigViewController-iPad.xib in Resources */,
 				F60D04791BD137B5003ACB00 /* bullet.png in Resources */,
 				61F9040911DF58B00068B24D /* settingsButton.png in Resources */,
@@ -1629,6 +1665,7 @@
 				61F2E7EC12060E31005734F7 /* checkbox.png in Resources */,
 				F60D04821BD137B5003ACB00 /* heart@2x.png in Resources */,
 				615AD96212073B4D00F2FF04 /* startGameButton.png in Resources */,
+				F6338CDB1C7A709600353945 /* CampaignViewController-iPad.xib in Resources */,
 				F60D048A1BD137B5003ACB00 /* teams@2x.png in Resources */,
 				F6D7E09F1B76884E004F3BCF /* Default-568h@2x.png in Resources */,
 				F60D047E1BD137B5003ACB00 /* flower@2x.png in Resources */,
@@ -1652,6 +1689,7 @@
 				61E2F7451283752C00E12521 /* tw.png in Resources */,
 				61808A5D128C930A005D0E2F /* backSound.caf in Resources */,
 				61D3D2A51290E03A003CE7C3 /* irc.png in Resources */,
+				F6338CC91C7A53C100353945 /* CampaignsViewController-iPhone.xib in Resources */,
 				6172FED91298CF9800D73365 /* background~iphone.png in Resources */,
 				6172FEEF1298D25D00D73365 /* mediumBackground~ipad.png in Resources */,
 				F65E1DBF1B9B95A400A78ADF /* Icon-60@2x.png in Resources */,
@@ -1683,6 +1721,7 @@
 				F67FC8161BEC17AC00A9DC75 /* Appirater.bundle in Resources */,
 				F65724FD1B7E784700A86262 /* helpabove.png in Resources */,
 				F6F07BDE1B7E72D40010E48F /* HelpPageLobbyViewController-iPad.xib in Resources */,
+				F6338CD91C7A702B00353945 /* CampaignViewController-iPhone.xib in Resources */,
 				61188C0712A6FE960026C5DA /* settingsButton@2x.png in Resources */,
 				61188C0812A6FE9A0026C5DA /* title@2x~iphone.png in Resources */,
 				F65724FF1B7E784700A86262 /* helpleft.png in Resources */,
@@ -1846,6 +1885,7 @@
 				61798838114AA34C00BA94A9 /* uStats.pas in Sources */,
 				61798839114AA34C00BA94A9 /* uStore.pas in Sources */,
 				6179883A114AA34C00BA94A9 /* uTeams.pas in Sources */,
+				F6338CD81C7A702B00353945 /* CampaignViewController.m in Sources */,
 				6179883C114AA34C00BA94A9 /* uVisualGears.pas in Sources */,
 				6179883D114AA34C00BA94A9 /* uWorld.pas in Sources */,
 				611F4D4B11B27A9900F9759A /* uScript.pas in Sources */,
@@ -1865,6 +1905,7 @@
 				6165921C11CA9BA200D6E256 /* SingleSchemeViewController.m in Sources */,
 				6165921D11CA9BA200D6E256 /* SingleTeamViewController.m in Sources */,
 				6165921F11CA9BA200D6E256 /* TeamConfigViewController.m in Sources */,
+				F60ACBB71C7BC08B00385701 /* IniParser.m in Sources */,
 				6165922011CA9BA200D6E256 /* TeamSettingsViewController.m in Sources */,
 				6165922111CA9BA200D6E256 /* VoicesViewController.m in Sources */,
 				6165922211CA9BA200D6E256 /* WeaponSettingsViewController.m in Sources */,
@@ -1883,6 +1924,7 @@
 				619C5AF4124F7E3100D041AE /* LuaPas.pas in Sources */,
 				619C5BA2124FA59000D041AE /* MapPreviewButtonView.m in Sources */,
 				61D205A1127CDD1100ABD83E /* ObjcExports.m in Sources */,
+				F6338CC81C7A53C100353945 /* CampaignsViewController.m in Sources */,
 				61006F95128DE31F00EBA7F7 /* CreationChamber.m in Sources */,
 				61A4A39412A5CCC2004D81E6 /* uCommandHandlers.pas in Sources */,
 				61A4A39512A5CCC2004D81E6 /* uCommands.pas in Sources */,
--- /dev/null	Thu Jan 01 00:00:00 1970 +0000
+++ b/project_files/HedgewarsMobile/Hedgewars.xcodeproj/xcshareddata/xcschemes/Hedgewars.xcscheme	Mon Mar 14 22:08:27 2016 +0300
@@ -0,0 +1,92 @@
+<?xml version="1.0" encoding="UTF-8"?>
+<Scheme
+   LastUpgradeVersion = "0710"
+   version = "1.3">
+   <BuildAction
+      parallelizeBuildables = "YES"
+      buildImplicitDependencies = "YES">
+      <BuildActionEntries>
+         <BuildActionEntry
+            buildForTesting = "YES"
+            buildForRunning = "YES"
+            buildForProfiling = "YES"
+            buildForArchiving = "YES"
+            buildForAnalyzing = "YES">
+            <BuildableReference
+               BuildableIdentifier = "primary"
+               BlueprintIdentifier = "1D6058900D05DD3D006BFB54"
+               BuildableName = "Hedgewars.app"
+               BlueprintName = "Hedgewars"
+               ReferencedContainer = "container:Hedgewars.xcodeproj">
+            </BuildableReference>
+         </BuildActionEntry>
+      </BuildActionEntries>
+   </BuildAction>
+   <TestAction
+      buildConfiguration = "Debug"
+      selectedDebuggerIdentifier = "Xcode.DebuggerFoundation.Debugger.LLDB"
+      selectedLauncherIdentifier = "Xcode.DebuggerFoundation.Launcher.LLDB"
+      shouldUseLaunchSchemeArgsEnv = "YES">
+      <Testables>
+      </Testables>
+      <MacroExpansion>
+         <BuildableReference
+            BuildableIdentifier = "primary"
+            BlueprintIdentifier = "1D6058900D05DD3D006BFB54"
+            BuildableName = "Hedgewars.app"
+            BlueprintName = "Hedgewars"
+            ReferencedContainer = "container:Hedgewars.xcodeproj">
+         </BuildableReference>
+      </MacroExpansion>
+      <AdditionalOptions>
+      </AdditionalOptions>
+   </TestAction>
+   <LaunchAction
+      buildConfiguration = "Release"
+      selectedDebuggerIdentifier = "Xcode.DebuggerFoundation.Debugger.LLDB"
+      selectedLauncherIdentifier = "Xcode.DebuggerFoundation.Launcher.LLDB"
+      launchStyle = "0"
+      useCustomWorkingDirectory = "NO"
+      ignoresPersistentStateOnLaunch = "NO"
+      debugDocumentVersioning = "YES"
+      debugServiceExtension = "internal"
+      allowLocationSimulation = "YES"
+      language = "ru">
+      <BuildableProductRunnable
+         runnableDebuggingMode = "0">
+         <BuildableReference
+            BuildableIdentifier = "primary"
+            BlueprintIdentifier = "1D6058900D05DD3D006BFB54"
+            BuildableName = "Hedgewars.app"
+            BlueprintName = "Hedgewars"
+            ReferencedContainer = "container:Hedgewars.xcodeproj">
+         </BuildableReference>
+      </BuildableProductRunnable>
+      <AdditionalOptions>
+      </AdditionalOptions>
+   </LaunchAction>
+   <ProfileAction
+      buildConfiguration = "Debug"
+      shouldUseLaunchSchemeArgsEnv = "YES"
+      savedToolIdentifier = ""
+      useCustomWorkingDirectory = "NO"
+      debugDocumentVersioning = "YES">
+      <BuildableProductRunnable
+         runnableDebuggingMode = "0">
+         <BuildableReference
+            BuildableIdentifier = "primary"
+            BlueprintIdentifier = "1D6058900D05DD3D006BFB54"
+            BuildableName = "Hedgewars.app"
+            BlueprintName = "Hedgewars"
+            ReferencedContainer = "container:Hedgewars.xcodeproj">
+         </BuildableReference>
+      </BuildableProductRunnable>
+   </ProfileAction>
+   <AnalyzeAction
+      buildConfiguration = "Debug">
+   </AnalyzeAction>
+   <ArchiveAction
+      buildConfiguration = "Distro AppStore"
+      revealArchiveInOrganizer = "YES">
+   </ArchiveAction>
+</Scheme>
--- /dev/null	Thu Jan 01 00:00:00 1970 +0000
+++ b/project_files/HedgewarsMobile/Hedgewars.xcodeproj/xcshareddata/xcschemes/UpdateDataFolder.xcscheme	Mon Mar 14 22:08:27 2016 +0300
@@ -0,0 +1,80 @@
+<?xml version="1.0" encoding="UTF-8"?>
+<Scheme
+   LastUpgradeVersion = "0710"
+   version = "1.3">
+   <BuildAction
+      parallelizeBuildables = "YES"
+      buildImplicitDependencies = "YES">
+      <BuildActionEntries>
+         <BuildActionEntry
+            buildForTesting = "YES"
+            buildForRunning = "YES"
+            buildForProfiling = "YES"
+            buildForArchiving = "YES"
+            buildForAnalyzing = "YES">
+            <BuildableReference
+               BuildableIdentifier = "primary"
+               BlueprintIdentifier = "6179928B114AE0C800BA94A9"
+               BuildableName = "UpdateDataFolder"
+               BlueprintName = "UpdateDataFolder"
+               ReferencedContainer = "container:Hedgewars.xcodeproj">
+            </BuildableReference>
+         </BuildActionEntry>
+      </BuildActionEntries>
+   </BuildAction>
+   <TestAction
+      buildConfiguration = "Debug"
+      selectedDebuggerIdentifier = "Xcode.DebuggerFoundation.Debugger.LLDB"
+      selectedLauncherIdentifier = "Xcode.DebuggerFoundation.Launcher.LLDB"
+      shouldUseLaunchSchemeArgsEnv = "YES">
+      <Testables>
+      </Testables>
+      <AdditionalOptions>
+      </AdditionalOptions>
+   </TestAction>
+   <LaunchAction
+      buildConfiguration = "Debug"
+      selectedDebuggerIdentifier = "Xcode.DebuggerFoundation.Debugger.LLDB"
+      selectedLauncherIdentifier = "Xcode.DebuggerFoundation.Launcher.LLDB"
+      launchStyle = "0"
+      useCustomWorkingDirectory = "NO"
+      ignoresPersistentStateOnLaunch = "NO"
+      debugDocumentVersioning = "YES"
+      debugServiceExtension = "internal"
+      allowLocationSimulation = "YES">
+      <MacroExpansion>
+         <BuildableReference
+            BuildableIdentifier = "primary"
+            BlueprintIdentifier = "6179928B114AE0C800BA94A9"
+            BuildableName = "UpdateDataFolder"
+            BlueprintName = "UpdateDataFolder"
+            ReferencedContainer = "container:Hedgewars.xcodeproj">
+         </BuildableReference>
+      </MacroExpansion>
+      <AdditionalOptions>
+      </AdditionalOptions>
+   </LaunchAction>
+   <ProfileAction
+      buildConfiguration = "Release"
+      shouldUseLaunchSchemeArgsEnv = "YES"
+      savedToolIdentifier = ""
+      useCustomWorkingDirectory = "NO"
+      debugDocumentVersioning = "YES">
+      <MacroExpansion>
+         <BuildableReference
+            BuildableIdentifier = "primary"
+            BlueprintIdentifier = "6179928B114AE0C800BA94A9"
+            BuildableName = "UpdateDataFolder"
+            BlueprintName = "UpdateDataFolder"
+            ReferencedContainer = "container:Hedgewars.xcodeproj">
+         </BuildableReference>
+      </MacroExpansion>
+   </ProfileAction>
+   <AnalyzeAction
+      buildConfiguration = "Debug">
+   </AnalyzeAction>
+   <ArchiveAction
+      buildConfiguration = "Release"
+      revealArchiveInOrganizer = "YES">
+   </ArchiveAction>
+</Scheme>
Binary file project_files/HedgewarsMobile/Locale/English.lproj/Localizable.strings has changed
Binary file project_files/HedgewarsMobile/Locale/ru.lproj/Localizable.strings has changed
--- a/share/Info.plist.in	Tue Feb 09 21:11:16 2016 +0300
+++ b/share/Info.plist.in	Mon Mar 14 22:08:27 2016 +0300
@@ -1,5 +1,5 @@
 <?xml version="1.0" encoding="UTF-8"?>
-<!DOCTYPE plist PUBLIC "-//Apple//DTD PLIST 1.0//EN" "http://www.apple.com/DTDs/PropertyList-1.0.dtd">
+<!DOCTYPE plist PUBLIC "-//Apple//DTD PLIST 1.0//EN" "https://www.apple.com/DTDs/PropertyList-1.0.dtd">
 <plist version="1.0">
 <dict>
     <key>LSApplicationCategoryType</key>
@@ -9,7 +9,7 @@
     <key>CFBundleExecutable</key>
     <string>hedgewars</string>
     <key>CFBundleGetInfoString</key>
-    <string>http://www.hedgewars.org</string>
+    <string>https://www.hedgewars.org</string>
     <key>CFBundleIconFile</key>
     <string>Icon.icns</string>
     <key>CFBundleIdentifier</key>
@@ -50,7 +50,7 @@
     <key>SUPublicDSAKeyFile</key>
     <string>dsa_pub.pem</string>
     <key>SUFeedURL</key>
-    <string>http://www.hedgewars.org/download/appcast.xml</string>
+    <string>https://www.hedgewars.org/download/appcast.xml</string>
     <key>CFBundleLocalizations</key>
     <array>
         <string>ar</string>
@@ -88,7 +88,7 @@
             <key>UTTypeIdentifier</key>
             <string>org.hedgewars.desktop.hws</string>
             <key>UTTypeReferenceURL</key>
-            <string>http://www.hedgewars.org/demos/</string>
+            <string>https://www.hedgewars.org/demos/</string>
             <key>UTTypeDescription</key>
             <string>Hedgewars Save Game</string>
             <key>UTTypeIconFile</key>
@@ -111,7 +111,7 @@
             <key>UTTypeIdentifier</key>
             <string>org.hedgewars.desktop.hwd</string>
             <key>UTTypeReferenceURL</key>
-            <string>http://www.hedgewars.org/demos/</string>
+            <string>https://www.hedgewars.org/demos/</string>
             <key>UTTypeIconFile</key>
             <string>public.text.icns</string>
             <key>UTTypeDescription</key>
--- a/share/hedgewars/Data/Locale/de.lua	Tue Feb 09 21:11:16 2016 +0300
+++ b/share/hedgewars/Data/Locale/de.lua	Mon Mar 14 22:08:27 2016 +0300
@@ -316,7 +316,7 @@
 ["We'll give you a problem then!"]="Dann geben wir euch ein Problem!",
 ["Nicely done, meatbags!"]="Gut gemacht, Fleischkugeln!",
 ["You have won the game by proving true cooperative skills!"]="Ihr hab das Spiel gewonnen, indem ihr wahre kooperative Fähigkeiten gezeigt habt!",
-["You have proven yourselves worthy!"]="Du hast dich bewährt.",
+["You have proven yourselves worthy!"]="Ihr habt euch bewährt.",
 ["Game? Was this a game to you?!"]="Spiel? War das ein Spiel für dich?!",
 ["Well, yes. This was a cyborg television show."]="Ähm, ja. Es war eine Cyborg-Fernsehsendung.",
 ["It is called 'Hogs of Steel'."]="Sie heißt »Igel aus Stahl«.",
--- a/share/hedgewars/Data/Locale/fr.lua	Tue Feb 09 21:11:16 2016 +0300
+++ b/share/hedgewars/Data/Locale/fr.lua	Mon Mar 14 22:08:27 2016 +0300
@@ -7,8 +7,8 @@
 --      ["011101001"] = "",
 --      ["+1 to a Bottom Feeder for killing anyone"] = "", -- Mutant
 --      ["+1 to a Mutant for killing anyone"] = "", -- Mutant
---      ["-1 to anyone for a suicide"] = "", -- Mutant
---      ["+2 for becoming a Mutant"] = "", -- Mutant
+      ["-1 to anyone for a suicide"] = "-1 pour cause de suicide",
+      ["+2 for becoming a Mutant"] = "+2 pour être devenu un Mutant",
       ["30 minutes later..."] = "30 minutes plus tard...",
       ["About a month ago, a cyborg came and told us that you're the cannibals!"] = "Il y a un mois, un cyborg est venu et nous a dit que vous étiez des cannibales !",
       ["Accuracy Bonus!"] = "Bonus précision",
@@ -17,29 +17,29 @@
       ["A Classic Fairytale"] = "Un conte classique de fée",
       ["Actually, you aren't worthy of life! Take this..."] = "En fait, tu n'es pas digne de vivre ! Prends ça....",
       ["A cy-what?"] = "Un cy-quoi ?",
---      ["Advanced Repositioning Mode"] = "", -- Construction_Mode
+      ["Advanced Repositioning Mode"] = "Mode de repositionnement avancé"
       ["Adventurous"] = "Aventurier",
---      ["a frenetic Hedgewars mini-game"] = "", -- Frenzy
---      ["Africa"] = "", -- Continental_supplies
+      ["a frenetic Hedgewars mini-game"] = "un mini-jeu frénétique d'HedgeWars", -- Frenzy
+      ["Africa"] = "Afrique", -- Continental_supplies
       ["After Leaks A Lot betrayed his tribe, he joined the cannibals..."] = "Après que Grosse Fuite ait trahit sa tribu, il rejoignât les cannibales... ",
       ["After the shock caused by the enemy spy, Leaks A Lot and Dense Cloud went hunting to relax."] = "Après le choc causé par l'espion ennemi, Grosse Fuite et Nuage Dense partirent chasser pour se détendre.",
       ["Again with the 'cannibals' thing!"] = "Encore avec votre 'cannibale' truc",
 --      ["Aggressively removes enemy hedgehogs."] = "", -- Construction_Mode
---      ["a Hedgewars challenge"] = "", -- User_Mission_-_RCPlane_Challenge, User_Mission_-_Rope_Knock_Challenge
+      ["a Hedgewars challenge"] = "un challenge d'Hegdewars", -- User_Mission_-_RCPlane_Challenge, User_Mission_-_Rope_Knock_Challenge
       ["a Hedgewars mini-game"] = "Un mini jeux d'Hedgewars", -- Space_Invasion, The_Specialists
 --      ["a Hedgewars tag game"] = "", -- Mutant
---      ["AHHh, home sweet home.  Made it in %d seconds."] = "", -- ClimbHome
+      ["AHHh, home sweet home.  Made it in %d seconds."] = "AHHh qu'il est bon d'être à la maison. Fait en %d secondes.", -- ClimbHome
       ["Aiming Practice"] = "Entraînement de tir", --Bazooka, Shotgun, SniperRifle
---      ["Air Attack"] = "", -- Construction_Mode
-	  ["A leap in a leap"] = "Un bond dans un bond",
+      ["Air Attack"] = "Attaque Aérienne", -- Construction_Mode
+      ["A leap in a leap"] = "Un bond dans un bond",
       ["A little gift from the cyborgs"] = "Un petit cadeau de la part des cyborgs",
       ["All gone...everything!"] = "Évaporé...plus rien !",
---      ["Allows free teleportation between other nodes."] = "", -- Construction_Mode
---      ["Allows placement of girders, rubber-bands, mines, sticky mines and barrels."] = "", -- Construction_Mode
---      ["Allows placement of structures."] = "", -- Construction_Mode
---      ["Allows the placement of weapons, utiliites, and health crates."] = "", -- Construction_Mode
+      ["Allows free teleportation between other nodes."] = "Autorise gratuitement une téléportation vers d'autres noeuds", -- Construction_Mode
+      ["Allows placement of girders, rubber-bands, mines, sticky mines and barrels."] = "Autorise le placement de poutres, d'élastiques, de mines, de mines collantes et de tonneaux", -- Construction_Mode
+      ["Allows placement of structures."] = "Autorise le placement de structures", -- Construction_Mode
+      ["Allows the placement of weapons, utiliites, and health crates."] = "Autorise le placement d'armes, d'utilitaires et de caisse de soin", -- Construction_Mode
       ["All right, we just need to get to the other side of the island!"] = "Très bien, nous devons juste rejoindre l'autre côté de l'île !",
---      ["All walls touched!"] = "", -- WxW
+      ["All walls touched!"] = "Tous les murs sont touchés", -- WxW
       ["Ammo Depleted!"] = "Munitions épuisées !",
       ["ammo extended!"] = "Munitions en plus !",
       ["Ammo is reset at the end of your turn."] = "Les munitions sont réinitialisées à la fin du tour",
@@ -54,53 +54,53 @@
       ["And you believed me? Oh, god, that's cute!"] = "Et tu m'as cru ? Oh mon dieu, c'est mignon !",
 --      ["Anno 1032: [The explosion will make a strong push ~ Wide range, wont affect hogs close to the target]"] = "", -- Continental_supplies
 
---      ["Antarctica"] = "", -- Continental_supplies
+      ["Antarctica"] = "Antarctique", -- Continental_supplies
 --      ["Antarctic summer: - Will give you one girder/mudball and two sineguns/portals every fourth turn."] = "", -- Continental_supplies
---      ["Area"] = "", -- Continental_supplies
+      ["Area"] = "Zone", -- Continental_supplies
       ["Are we there yet?"] = "Sommes-nous toujours là ?",
       ["Are you accusing me of something?"] = "Es-tu en train de m'accuser de quelque chose ? ",
       ["Are you saying that many of us have died for your entertainment?"] = "Vous dites que beaucoup d'entre nous sont morts pour votre divertissement ? ",
---      ["Artur Detour"] = "",
+      ["Artur Detour"] = "Arthur Detour",
       ["As a reward for your performance, here's some new technology!"] = "Comme récompense, voici une nouvelle technologie !",
 --      ["a shoppa minigame"] = "", -- WxW
---      ["Asia"] = "", -- Continental_supplies
---      ["Assault Team"] = "",
+      ["Asia"] = "Asie", -- Continental_supplies
+      ["Assault Team"] = "Equipe d'assault",
       ["As the ammo is sparse, you might want to reuse ropes while mid-air.|"] = "Vu que les munitions sont éparpillées tu devrais relancer le grappin en plein vol",
       ["As the challenge was completed, Leaks A Lot set foot on the ground..."] = "Comme le défi était accompli, Grosse Fuite posa les pieds sur le sol...",
       ["As you can see, there is no way to get on the other side!"] = "Comme tu peux le voir, il n'y a pas de moyen d'atteindre l'autre côté !",
---      ["Attack From Rope"] = "", -- WxW
---      ["Australia"] = "", -- Continental_supplies
-      ["Available points remaining: "] = "Points restant disponibles",  -- need the situation of when this sentence is used
+      ["Attack From Rope"] = "Attaquer d'une corde", -- WxW
+      ["Australia"] = "Australie", -- Continental_supplies
+      ["Available points remaining: "] = "Points restants disponibles",  -- need the situation of when this sentence is used
 --      ["Back Breaker"] = "",
       ["Back in the village, after telling the villagers about the threat..."] = "De retour au village, après avoir averti les villageois de la menace...",
 --      ["[Backspace]"] = "effacement arrière",  --maybe the original name is better...
       ["Backstab"] = "Coup de poignard dans le dos",
---      ["Bad Team"] = "", -- User_Mission_-_The_Great_Escape
+      ["Bad Team"] = "Mauvaise équipe", -- User_Mission_-_The_Great_Escape
 --      ["Ballgun"] = "", -- Construction_Mode
 --      ["Bamboo Thicket"] = "", --really, i don't know the good translation for this
-      ["Barrel Eater!"] = "Mangeur de barrils",
-      ["Barrel Launcher"] = "Lanceur de barrils", --need the situation for me to understand sens of sentence
---      ["Barrel Placement Mode"] = "", -- Construction_Mode
---      ["Baseball Bat"] = "", -- Construction_Mode
+      ["Barrel Eater!"] = "Mangeur de barile",
+      ["Barrel Launcher"] = "Lanceur de barile", --need the situation for me to understand sens of sentence
+      ["Barrel Placement Mode"] = "Mode de placement de barile", -- Construction_Mode
+      ["Baseball Bat"] = "Batte de Baseball", -- Construction_Mode
 --      ["Baseballbat"] = "", -- Continental_supplies
       ["Bat balls at your enemies and|push them into the sea!"] = "Frappez vos ennemis à la batte|et envoyez-les à la mer !",
       ["Bat your opponents through the|baskets and out of the map!"] = "Frappez vos ennemis à la batte|, marquez des paniers ou envoyez-les à la mer !",
 --      ["Bazooka"] = "", -- Construction_Mode, Frenzy, A_Space_Adventure:death02
       ["Bazooka Training"] = "Entraînement au Bazooka",
 --      ["Beep Loopers"] = "",
-      ["Best laps per team: "] = "Meilleur temps par équipe",
---      ["Best Team Times: "] = "",
-      ["Beware, though! If you are slow, you die!"] = "Attention tout de même ! si tu es lent, tu meurt !",
---      ["Bio-Filter"] = "", -- Construction_Mode
+      ["Best laps per team: "] = "Meilleurs tours par équipe",
+      ["Best Team Times: "] = "Meilleurs temps d'équipe",
+      ["Beware, though! If you are slow, you die!"] = "Attention tout de même ! Si tu es lent, tu meurs !",
+      ["Bio-Filter"] = "Filtre Biologique", -- Construction_Mode
 --      ["Biomechanic Team"] = "",
 --      ["Birdy"] = "", -- Construction_Mode
---      ["Blender"] = "",
+      ["Blender"] = "Mixeur",
 --      ["Bloodpie"] = "",
 --      ["Bloodrocutor"] = "",
---      ["Bloodsucker"] = "",
+      ["Bloodsucker"] = "Sangsue",
       ["Bloody Rookies"] = "Nouvelles recrues", -- 01#Boot_Çamp, User_Mission_-_Dangerous_Ducklings, User_Mission_-_Diver, User_Mission_-_Spooky_Tree
---      ["Blowtorch"] = "", -- Construction_Mode, Frenzy
---      ["Blue Team"] = "", -- User_Mission_-_Dangerous_Ducklings
+      ["Blowtorch"] = "Chalumeau", -- Construction_Mode, Frenzy
+      ["Blue Team"] = "Team Bleue", -- User_Mission_-_Dangerous_Ducklings
 --      ["Bone Jackson"] = "",
       ["Bonely"] = "Bonely",
 --      ["BOOM!"] = "",
@@ -114,7 +114,7 @@
 --      ["Brain Teaser"] = "",
 --      ["Brutal Lily"] = "",
 --      ["Brutus"] = "",
---      ["Build a fortress and destroy your enemy."] = "", -- Construction_Mode
+      ["Build a fortress and destroy your enemy."] = "Cronstruit une forteresse et décime ton ennemi", -- Construction_Mode
       ["Build a track and race."] = "Construisez un parcours et faites la course.",
       ["Bullseye"] = "Dans le mille",
       ["But it proved to be no easy task!"] = "Mais cela ne s'avéra pas être une tâche facile !",
@@ -125,74 +125,74 @@
       ["But why would they help us?"] = "Mais pourquoi nous aideraient-ils ? ",
       ["But you're cannibals. It's what you do."] = "Mais vous êtes cannibales. C'est ce que vous faites.",
       ["But you said you'd let her go!"] = "Mais vous aviez dit que vous la laisseriez partir !",
---      ["Cake"] = "", -- Construction_Mode
+      ["Cake"] = "Gâteau", -- Construction_Mode
       ["Çall me Beep! Well, 'cause I'm such a nice...person!"] = "Appelle-moi Beep ! Hum, parce que je suis du genre sympa !",
       ["Çannibals"] = "Çannibales",
       ["Çannibal Sentry"] = "Sentinelle cannibale",
       ["Çannibals?! You're the cannibals!"] = "Çannibales ? C'est vous les cannibales !",
       ["CAPTURE THE FLAG"] = "Çapturez le drapeau !",
       ["Çareless"] = "Imprudent",
---      ["Careless"] = "", -- User_Mission_-_That_Sinking_Feeling
+      ["Careless"] = "Imprudent", -- User_Mission_-_That_Sinking_Feeling
 --      ["Çarol"] = "",
---      ["CHALLENGE COMPLETE"] = "", -- User_Mission_-_RCPlane_Challenge
+      ["CHALLENGE COMPLETE"] = "Challenge Réussi", -- User_Mission_-_RCPlane_Challenge
       ["Change Weapon"] = "Changez d'arme",
---      ["changing range from %i%% to %i%% with period of %i msec"] = "", -- Gravity
+      ["changing range from %i%% to %i%% with period of %i msec"] = "modification de la portée de %i%% à %i%% à une période de %i msec", -- Gravity
       ["Choose your side! If you want to join the strange man, walk up to him.|Otherwise, walk away from him. If you decide to att...nevermind..."] = "Choisis ton côté ! Si tu veux rejoindre l'étranger, marche vers lui. |Dans le cas contraire, éloigne toi de lui. Si tu décide de l'att...non laisse tomber...",
---      ["Cleaver"] = "", -- Construction_Mode
---      ["Cleaver Placement Mode"] = "", -- Construction_Mode
---      ["Climber"] = "", -- ClimbHome
+      ["Cleaver"] = "Couperet", -- Construction_Mode
+      ["Cleaver Placement Mode"] = "Mode de placement de couperet", -- Construction_Mode
+      ["Climber"] = "Escaladeur", -- ClimbHome
 --      ["Climb Home"] = "", -- ClimbHome
 --      ["Clowns"] = "", -- User_Mission_-_Nobody_Laugh
       ["Clumsy"] = "Maladroit",
---      ["Cluster Bomb"] = "", -- Construction_Mode
---      ["Cluster Bomb MASTER!"] = "", -- Basic_Training_-_Cluster_Bomb
---      ["Cluster Bomb Training"] = "", -- Basic_Training_-_Cluster_Bomb
+      ["Cluster Bomb"] = "Bombe à fragmentation", -- Construction_Mode
+      ["Cluster Bomb MASTER!"] = "Maitre de la bombe à fragmentation", -- Basic_Training_-_Cluster_Bomb
+      ["Cluster Bomb Training"] = "Entrainement à la bombe à fragmentation", -- Basic_Training_-_Cluster_Bomb
       ["Codename: Teamwork"] = "Nom de code : Travail d'équipe",
       ["Collateral Damage"] = "Dommages collatéraux",
       ["Collateral Damage II"] = "Dommages collatéraux II",
 	  ["Collect all the crates, but remember, our time in this life is limited!"] = "Collecte toutes les caisses mais souviens toi, notre temps dans cette vie est limité !",
---      ["Collect or destroy all the health crates."] = "", -- User_Mission_-_RCPlane_Challenge
+      ["Collect or destroy all the health crates."] = "Récupère ou détruit toutes les caisses de soin", -- User_Mission_-_RCPlane_Challenge
 	  ["Collect the crate on the right.|Hint: Select the rope, [Up] or [Down] to aim, [Space] to fire, directional keys to move.|Ropes can be fired again in the air!"] = "Collecte les caisses à droite. |Astuce : sélectionne le grappin, [haut] ou [bas] pour viser, flèches directionnelles pour bouger. |Le grappin peut etre relancé en plein vol !",
 	  ["Collect the crates within the time limit!|If you fail, you'll have to try again."] = "Collecte les caisses dans le temps imparti ! |Si tu rates, tu devras réessayer.",
 	  ["Come closer, so that your training may continue!"] = "Rapproche-toi, ainsi ton entraînement pourra continuer !",
 --      ["Compete to use as few planes as possible!"] = "", -- User_Mission_-_RCPlane_Challenge
       ["Complete the track as fast as you can!"] = "Finissez la course aussi vite que possible !",
---      ["COMPLETION TIME"] = "", -- User_Mission_-_Rope_Knock_Challenge
---      ["Configuration accepted."] = "", -- WxW
---      ["Congratulations"] = "", -- Basic_Training_-_Rope
-      ["Congratulations!"] = "Félicitations !",
---      ["Congratulations! You needed only half of time|to eliminate all targets."] = "", -- Basic_Training_-_Cluster_Bomb
---      ["Congratulations! You've completed the Rope tutorial! |- Tutorial ends in 10 seconds!"] = "", -- Basic_Training_-_Rope
+      ["COMPLETION TIME"] = "Temps d'achèvement", -- User_Mission_-_Rope_Knock_Challenge
+      ["Configuration accepted."] = "Configuration acceptée", -- WxW
+      ["Congratulations"] = "Félicitations", -- Basic_Training_-_Rope
+      ["Congratulations!"] = "Félicitations!",
+      ["Congratulations! You needed only half of time|to eliminate all targets."] = "Félicitations! Tu n'as eu besoin que de la moitié du temps pour éliminer toutes tes cibles.", -- Basic_Training_-_Cluster_Bomb
+      ["Congratulations! You've completed the Rope tutorial! |- Tutorial ends in 10 seconds!"] = "Félicitations! Vous avez complété le tutoriel de la corde ! |- Tutoriel terminé en 10 secondes!", -- Basic_Training_-_Rope
       ["Congratulations! You've eliminated all targets|within the allowed time frame."] = "Félicitations ! Vous avez éliminé toutes les cibles|dans le temps alloué.", --Bazooka, Shotgun, SniperRifle
---      ["CONSTRUCTION MODE"] = "", -- Construction_Mode
---      ["Construction Station"] = "", -- Construction_Mode
+      ["CONSTRUCTION MODE"] = "MODE DE CONSTRUCTION", -- Construction_Mode
+      ["Construction Station"] = "Station de construction", -- Construction_Mode
 --      ["Continental supplies"] = "", -- Continental_supplies
       ["Control pillars to score points."] = "Contrôlez les piliers pour marquer des points",
---      ["Core"] = "", -- Construction_Mode
---      ["Corporationals"] = "",
+      ["Core"] = "Noyau", -- Construction_Mode
+      ["Corporationals"] = "Organismes",
 --      ["Corpsemonger"] = "",
 --      ["Corpse Thrower"] = "",
---      ["Cost"] = "", -- Construction_Mode
---      ["Crate Placement Tool"] = "", -- Construction_Mode
---      ["Crates Left:"] = "", -- User_Mission_-_RCPlane_Challenge
+      ["Cost"] = "Coût", -- Construction_Mode
+      ["Crate Placement Tool"] = "Outil de placement de caisse", -- Construction_Mode
+      ["Crates Left:"] = "Caisses restantes:", -- User_Mission_-_RCPlane_Challenge
 --      ["Cricket time: [Drop a fireable mine! ~ Will work if fired close to your hog & far away from enemy ~ 1 sec]"] = "", -- Continental_supplies
---      ["Current setting is "] = "", -- Gravity
+      ["Current setting is "] = "Le paramètre actuel est ", -- Gravity
       ["Cybernetic Empire"] = "Empire cybernétique",
       ["Cyborg. It's what the aliens call themselves."] = "Cyborg. C'est ainsi que s'appellent les aliens entre eux.",
 --      ["Dahmer"] = "",
       ["DAMMIT, ROOKIE!"] = "Et merde, recrue",
       ["DAMMIT, ROOKIE! GET OFF MY HEAD!"] = "Et merde, recrue ! Dégage de ma tête !",
       ["Dangerous Ducklings"] = "Çanetons dangereux",
---      ["Deadweight"] = "poids mort/boulet", 
---      ["Decrease"] = "", -- Continental_supplies
-      ["Defeat the cannibals!|"] = "Bats les cannibales",
+      ["Deadweight"] = "poids mort", 
+      ["Decrease"] = "Diminuer", -- Continental_supplies
+      ["Defeat the cannibals!|"] = "Décime les cannibales",
       ["Defeat the cannibals!|Grenade hint: set the timer with [1-5], aim with [Up]/[Down] and hold [Space] to set power"] = "Bat les cannibales ! |Astuce Grenade : règles le compte à rebour avec [1-5], vises avec [haut]/[bas] et maintiens [Espace] pour la puissance",
       ["Defeat the cyborgs!"] = "Bats les cyborgs !",
---      ["Defend your core from the enemy."] = "", -- Construction_Mode
+      ["Defend your core from the enemy."] = "Prôtège ton noyau des ennemis", -- Construction_Mode
       ["Defend yourself!|Hint: You can get tips on using weapons by moving your mouse over them in the weapon sélection menu"] = "Défends toi ! |Conseil : Tu peux obtenir des astuces sur l'utilisation des armes en plaçant ta souris dessus dans le menu de sélection des armes",
---      ["Dematerializes weapons and equipment carried by enemy hedgehogs."] = "", -- Construction_Mode
+      ["Dematerializes weapons and equipment carried by enemy hedgehogs."] = "Dématérialise les armes et l'équipement portés par les hedgehogs ennemis", -- Construction_Mode
       ["Demolition is fun!"] = "La démolition c'est marrant",
---      ["Dense Cloud"] = "",
+      ["Dense Cloud"] = "Nuage épais",
       ["Dense Cloud must have already told them everything..."] = "Nuage Dense leur a sûrement déjà tout raconté...",
 --      ["Depleted Kamikaze!"] = "Kamikaze ... !", 
 --      ["Desert Eagle"] = "", -- Construction_Mode, A_Space_Adventure:death02
@@ -209,13 +209,13 @@
       ["Do not laugh, inexperienced one, for he speaks the truth!"] = "Ne ris pas le bleu, car il dit la vérité ! ",
       ["Do not let his words fool you, young one! He will stab you in the back as soon as you turn away!"] = "Ne laisses pas ses mots te distraire, petit scarabée ! Il te poignardera dès que tu auras le dos tourné !",
 	  ["Do the deed"] = "Accomplir l'acte",
-      ["Double Kill!"] = "Double meurtre",
---      ["DOUBLE KILL"] = "", -- Mutant
+      ["Double Kill!"] = "Double meurtre !",
+      ["DOUBLE KILL"] = "DOUBLE MEURTRE", -- Mutant
       ["Do you have any idea how valuable grass is?"] = "Est-ce que vous avez une idée de la valeur de votre herbe ?",
       ["Do you think you're some kind of god?"] = "Vous vous prenez pour un genre de dieu ?",
       ["Dragon's Lair"] = "La tanière du dragon",
---      ["Drill Rocket"] = "", -- Construction_Mode
---      ["Drills"] = "",
+      ["Drill Rocket"] = "Missile forant", -- Construction_Mode
+      ["Drills"] = "Perce",
 --      ["Drill Strike"] = "", -- Construction_Mode
       ["Drone Hunter!"] = "Chasseur de drône",
 --      ["Drop a bomb: [Drop some heroic wind that will turn into a bomb on impact]"] = "", -- Continental_supplies
@@ -228,22 +228,22 @@
       ["Dude, what's this place?!"] = "Mec, quel est cet endroit?",
       ["Dude, where are we?"] = "Mec, on est où ? ",
 --      ["Dude, wow! I just had the weirdest high!"] = "",
---      ["Duration"] = "", -- Continental_supplies
---      ["Dust storm: [Deals 15 damage to all enemies in the circle]"] = "", -- Continental_supplies
+      ["Duration"] = "Durée", -- Continental_supplies
+      ["Dust storm: [Deals 15 damage to all enemies in the circle]"] = "Tempête de sable: [Inflige 15 dégâts à tous les ennemis dans le cercle]", -- Continental_supplies
 
 --      ["Dynamite"] = "", -- Construction_Mode
---      ["Each turn is only ONE SECOND!"] = "", -- Frenzy
+      ["Each turn is only ONE SECOND!"] = "Chaque tour dure seulement UNE SECONDE!", -- Frenzy
       ["Each turn you get 1-3 random weapons"] = "À chaque tour, tu as 1 à 3 armes aléatoires",
       ["Each turn you get one random weapon"] = "À chaque tour, tu as une arme aléatoire",
---      ["Eagle Eye"] = "",
+      ["Eagle Eye"] = "Oeil d'aigle",
 --      ["Eagle Eye: [Blink to the impact ~ One shot]"] = "", -- Continental_supplies
 
 --      ["Ear Sniffer"] = "",
 --      ["Elderbot"] = "",
---      ["Elimate your captor."] = "", -- User_Mission_-_The_Great_Escape
+      ["Eliminate your captor."] = "Éliminez votre capteur", -- User_Mission_-_The_Great_Escape
       ["Eliminate all enemies"] = "Éliminez tous les ennemis",
       ["Eliminate all targets before your time runs out.|You have unlimited ammo for this mission."] = "Éliminez toutes les cibles avant d'être à cours de temps.|Vos munitions sont illimitées pour cette mission.", --Bazooka, Shotgun, SniperRifle
---      ["Eliminate enemy hogs and take their weapons."] = "", -- Highlander
+      ["Eliminate enemy hogs and take their weapons."] = "Éliminez les hogs ennemis and prenez leurs armes.", -- Highlander
       ["Eliminate Poison before the time runs out"] = "Éliminez tout le Poison avant d'être à cours de temps.",
       ["Eliminate the Blue Team"] = "Éliminez l'équipe bleue",
       ["Eliminate the enemy before the time runs out"] = "Eliminez les ennemis avant que le temps ne soit épuisé", -- User_Mission_-_Bamboo_Thicket, User_Mission_-_Newton_and_the_Hammock
@@ -251,7 +251,7 @@
       ["Eliminate the enemy specialists."] = "Eliminez les spécialists ennemis",
       ["- Eliminate Unit 3378 |- Feeble Resistance must survive"] = "Éliminez l'unité 3378|- Résistance Futile doit survivre",
 --      ["Elmo"] = "",
---      ["Energetic Engineer"] = "",
+      ["Energetic Engineer"] = "Ingénieur énergique",
       ["Enjoy the swim..."] = "Profitez du bain ...",
 --      ["[Enter]"] = "",
 --      ["Europe"] = "", -- Continental_supplies
@@ -260,42 +260,42 @@
       ["Every single time!"] = "À chaque fois !",
       ["Everything looks OK..."] = "Tout a l'air d'être OK ...",
       ["Exactly, man! That was my dream."] = "Exactement, mec ! C'était mon rêve.",
---      ["Extra Damage"] = "", -- Construction_Mode
---      ["Extra Time"] = "", -- Construction_Mode
-      ["Eye Chewer"] = "Mâcheur d'oeilr",
+      ["Extra Damage"] = "Dégâts supplémentaires", -- Construction_Mode
+      ["Extra Time"] = "Temps Supplémentaire", -- Construction_Mode
+      ["Eye Chewer"] = "Mâcheur d'oeil",
       ["Family Reunion"] = "Réunion de famille ",
       ["Fastest lap: "] = "Meilleur tour : ",
       ["Feeble Resistance"] = "Résistance Futile",
 --      ["Fell From Grace"] = "",
---      ["Fell From Heaven"] = "",
+      ["Fell From Heaven"] = "Est tombé du Ciel",
       ["Fell From Heaven is the best! Fell From Heaven is the greatest!"] = "Tombée de l'Enfer est la meilleure ! Tombée de l'Enfer est la meilleure !",
---      ["Femur Lover"] = "",
---      ["Fierce Competition!"] = "", -- Space_Invasion
---      ["Fiery Water"] = "",
---      ["Filthy Blue"] = "", -- User_Mission_-_Dangerous_Ducklings
+      ["Femur Lover"] = "Amoureux du fémur",
+      ["Fierce Competition!"] = "Compétition féroce!", -- Space_Invasion
+      ["Fiery Water"] = "Eau bouillante",
+      ["Filthy Blue"] = "Bleu dégueulasse", -- User_Mission_-_Dangerous_Ducklings
       ["Find your tribe!|Cross the lake!"] = "Trouve ta tribue ! |Traverse le lac !",
       ["Finish your training|Hint: Animations can be skipped with the [Precise] key."] = "Finis ton entraînement ! |Astuce : Les animations peuvent être passées en appuyant sur la touche [Precise]",
---      ["Fire"] = "",
+      ["Fire"] = "Feu",
 --      ["Fire a mine: [Does what it says ~ Çant be dropped close to an enemy ~ 1 sec]"] = "", -- Continental_supplies
       ["First aid kits?!"] = "Des kits de premiers secours ?!",
 --      ["FIRST BLOOD MUTATES"] = "", -- Mutant
       ["First Blood"] = "Premier sang",
-	  ["First Steps"] = "Premiers pas",
+      ["First Steps"] = "Premiers pas",
       ["Flag captured!"] = "Drapeau capturé !",
       ["Flag respawned!"] = "Drapeau réapparu",
       ["Flag returned!"] = "Drapeau récupéré",
       ["Flags, and their home base will be placed where each team ends their first turn."] = "Les drapeaux et leur base seront placés là où chaque équipe finit son premier tour",
---      ["Flamer"] = "",
---      ["Flamethrower"] = "", -- Construction_Mode
---      ["Flaming Worm"] = "",
+      ["Flamer"] = "Flambeur",
+      ["Flamethrower"] = "Lance-flammes", -- Construction_Mode
+      ["Flaming Worm"] = "Ver flamboyant",
 
       ["Flesh for Brainz"] = "Flesh for Brainz",
---      ["Flying Saucer"] = "", -- Construction_Mode, Frenzy
---      ["For improved features/stability, play 0.9.18+"] = "", -- WxW
+      ["Flying Saucer"] = "Soucoupe volante", -- Construction_Mode, Frenzy
+      ["For improved features/stability, play 0.9.18+"] = "Pour de meilleurs fonctionnalités/stabilité, jouez en 0.9.18+", -- WxW
       ["Free Dense Cloud and continue the mission!"] = "Libérez Nuage Dense et continuez la mission !",
 --      ["Freezer"] = "", -- Construction_Mode
 --      ["FRENZY"] = "", -- Frenzy
---      ["Friendly Fire!"] = "",
+      ["Friendly Fire!"] = "Feu allié!",
       ["fuel extended!"] = "Le plein d'essence !",
       ["GAME BEGUN!!!"] = "Le jeu a commencé !!!",
 --      ["Game Modifiers: "] = "",
@@ -304,67 +304,67 @@
       ["Game? Was this a game to you?!"] = "Jeu ? Etait-ce un jeu pour vous ?!",
 --      ["GasBomb"] = "", -- Continental_supplies
 --      ["Gas Gargler"] = "",
---      ["General information"] = "", -- Continental_supplies
---      ["Generates power."] = "", -- Construction_Mode
---      ["Generator"] = "", -- Construction_Mode
+      ["General information"] = "Informations générales", -- Continental_supplies
+      ["Generates power."] = "Génère de l'énergie", -- Construction_Mode
+      ["Generator"] = "Générateur", -- Construction_Mode
       ["Get Dense Cloud out of the pit!"] = "Sortez Nuage Dense de la fosse",
       ["Get on over there and take him out!"] = "Viens par ici et débarrasse-toi de lui ! ",
 	  ["Get on the head of the mole"] = "Va sur la tête de la taupe",
---      ["Get out of there!"] = "", -- User_Mission_-_The_Great_Escape
+      ["Get out of there!"] = "Sors d'ici !", -- User_Mission_-_The_Great_Escape
 	  ["Get that crate!"] = "Prends cette caisse",
       ["Get the crate on the other side of the island!|"] = "Prends la caisse de l'autre côté de l'île !",
 --      ["Get to the target using your rope! |Controls: Left & Right to swing the rope - Up & Down to Contract and Expand!"] = "", -- Basic_Training_-_Rope
 --      ["Get your teammates out of their natural prison and save the princess!|Hint: Drilling holes should solve everything.|Hint: It might be a good idea to place a girder before starting to drill. Just saying.|Hint: All your hedgehogs need to be above the marked height!|Hint: Leaks A Lot needs to get really close to the princess!"] = "", -- A_Classic_Fairytale:family
 	 ["Get your teammates out of their natural prison and save the princess!|Hint: Drilling holes should solve everything.|Hint: It might be a good idea to place a girder before starting to drill. Just saying.|Hint: All your hedgehogs need to be above the marked height!|Hint: Leaks A Lot needs to get really close to the princess!"] = "Fais sortir tes coéquipiers de leur prison naturelle et sauve la princesse ! |Percer des trous résoudrait tout. |Ce serait une bonne idée de placer quelques poutres avant de commencer à percer. Moi j'dis ça mais j'dis rien. |Tous vos hérissons doivent être au dessus de la hauteur marquée ! | Grosse Fuite doit être très proche de la princesse !  ",
---      ["GG!"] = "", -- User_Mission_-_Rope_Knock_Challenge
+      ["GG!"] = "Bien joué!", -- User_Mission_-_Rope_Knock_Challenge
 --      ["Gimme Bones"] = "",
 --      ["Girder"] = "", -- Construction_Mode
 --      ["Girder Placement Mode"] = "", -- Construction_Mode
 --      ["Glark"] = "",
---      ["Goal"] = "",
---      ["GO! GO! GO!"] = "",
+      ["Goal"] = "But",
+      ["GO! GO! GO!"] = "Allez! Allez! Allez!",
       ["Good birdy......"] = "Gentil oiseau ...",
---      ["Good Dude"] = "", -- User_Mission_-_The_Great_Escape
+      ["Good Dude"] = "Bravo !", -- User_Mission_-_The_Great_Escape
       ["Good idea, they'll never find us there!"] = "Bonne idée, ils ne nous trouverons jamais là bas !",
       ["Good luck...or else!"] = "Bonne chance.... ou pas !",
       ["Good luck out there!"] = "Bonne chance pour sortir d'ici",
---      ["Good so far!"] = "",
---      ["Good to go!"] = "",
+      ["Good so far!"] = "Pas mal jusqu'ici!",
+      ["Good to go!"] = "C'est pret!",
 	  ["Go on top of the flower"] = "Atteins le dessus de la fleur",
       ["Go, quick!"] = "Va ! Vite !",
       ["Gorkij"] = "Gorkij",
---      ["Go surf!"] = "", -- WxW
---      ["GOTCHA!"] = "je t'ai eu !",  is this good ? 
+      ["Go surf!"] = "Va faire du surf", -- WxW
+      ["GOTCHA!"] = "je t'ai eu !", 
       ["Grab Mines/Explosives"] = "Emparez vous des Mines/Explosifs",
---      ["Grants nearby hogs life-regeneration."] = "", -- Construction_Mode
---      ["Gravity"] = "", -- Gravity
+      ["Grants nearby hogs life-regeneration."] = "Confère de la régénération de vie aux hogs proches", -- Construction_Mode
+      ["Gravity"] = "Gravité", -- Gravity
       ["Great choice, Steve! Mind if I call you that?"] = "Bon choix, Steve ! Ça t'ennuie si je t'appele comme ça ?",
---      ["Great work! Now hit it with your Baseball Bat! |Tip: You can change weapon with 'Right Click'!"] = "", -- Basic_Training_-_Rope
+      ["Great work! Now hit it with your Baseball Bat! |Tip: You can change weapon with 'Right Click'!"] = "Bien joué! Maintenant, fracasse le avec une batte de baseball ! Astuce: Tu peux changer d'arme avec un 'clique droit'!", -- Basic_Training_-_Rope
       ["Great! You will be contacted soon for assistance."] = "Super ! Tu seras bientot contacté pour de l'aide.",
 
 --      ["Green lipstick bullet: [Poisonous, deals no damage]"] = "", -- Continental_supplies
       ["Greetings, cloudy one!"] = "Salutation, le nuageux !",
       ["Greetings, "] = "Salutations, ",
 --      ["Grenade"] = "", -- Construction_Mode, Frenzy, A_Space_Adventure:death02
---      ["Grenade Training"] = "", -- Basic_Training_-_Grenade
+      ["Grenade Training"] = "Entrainement à la grenade", -- Basic_Training_-_Grenade
 --      ["Grenadiers"] = "", -- Basic_Training_-_Grenade
       ["Guys, do you think there's more of them?"] = "Les gars, vous pensez qu'il y en a encore plus ?",
 --      ["HAHA!"] = "",
 --      ["Haha!"] = "",
 --      ["Hahahaha!"] = "",
       ["Haha, now THAT would be something!"] = "Haha, maintenant ÇA, ça va être quelquechose !",
---      ["Hammer"] = "", -- Construction_Mode, Continental_supplies
+      ["Hammer"] = "Marteau", -- Construction_Mode, Continental_supplies
       ["Hannibal"] = "Hannibal",
 --      ["Hapless Hogs"] = "",
 --      [" Hapless Hogs left!"] = "",
---      [" HAS MUTATED"] = "", -- Mutant
+      [" HAS MUTATED"] = " a muté", -- Mutant
 --      ["Hatless Jerry"] = "",
       ["Have no illusions, your tribe is dead, indifferent of your choice."] = "N'aies pas d'illusion, ta tribue est morte, quel que soit ton choix",
       ["Have we ever attacked you first?"] = "Avons-nous jamais attaqué en premier ? ",
---      ["Healing Station"] = "", -- Construction_Mode
---      ["Health Crate Placement Mode"] = "", -- Construction_Mode
+      ["Healing Station"] = "Station de soignement", -- Construction_Mode
+      ["Health Crate Placement Mode"] = "Mode de placement de caisse de soin", -- Construction_Mode
       ["Health crates extend your time."] = "Les caisses de vie augmentent votre temps.",
---      ["Heavy"] = "",
+      ["Heavy"] = "Lourd",
 --      ["Heavy Çannfantry"] = "",
 --      ["Hedge-cogs"] = "",
 --      ["Hedgehog projectile: [Fire your hog like a Sticky Bomb]"] = "", -- Continental_supplies
@@ -373,7 +373,7 @@
 --      ["Hedgewars-Knockball"] = "",
 --      ["Hedgibal Lecter"] = "",
       ["Heh, it's not that bad."] = "Hé, c'est pas si mal.",
---      ["Hellish Handgrenade"] = "", -- Construction_Mode
+      ["Hellish Handgrenade"] = "Grenade de la mort", -- Construction_Mode
       ["Hello again, "] = "Re-bonjour,",
       ["Help me, Leaks!"] = "Aide moi, Fuite !",
       ["Help me, please!!!"] = "Aide moi, s'il te plaît !!!",
@@ -382,11 +382,11 @@
       ["He must be in the village already."] = "Il doit déjà être au village",
       ["Here, let me help you!"] = "Laissez-moi vous aider !",
       ["Here, let me help you save her!"] = "Laissez-moi vous aider à la sauver !",
-      ["Here...pick your weapon!"] = "Ici...choisis ton arme !",
---      ["Hero Team"] = "", -- User_Mission_-_The_Great_Escape
+      ["Here...pick your weapon!"] = "Ici...prend ton arme !",
+      ["Hero Team"] = "Equipe de héros", -- User_Mission_-_The_Great_Escape
 	  ["He's so brave..."] = "Il est si courageux",
       ["He won't be selling us out anymore!"] = "Il ne nous vendra plus !",
---      ["Hey, guys!"] = "",
+      ["Hey, guys!"] = "Salut les gars",
       ["Hey guys!"] = "Salut les gars !",
       ["Hey! This is cheating!"] = "Hé ! C'est de la triche !",
 --      ["HIGHLANDER"] = "", -- Highlander
@@ -399,13 +399,13 @@
 --      ["Hit Combo!"] = "",
 --      ["Hmmm..."] = "",
       ["Hmmm...actually...I didn't either."] = "Humm... en fait...je ne savais pas non plus.",
---      ["Hmmm, I'll have to find some way of moving him off this anti-portal surface..."] = "", -- portal
+      ["Hmmm, I'll have to find some way of moving him off this anti-portal surface..."] = "Hmmm, je vais devoir trouver un moyen de le faire partir de la plateforme anti-portail", -- portal
       ["Hmmm...it's a draw. How unfortunate!"] = "Hmmm... C'est un ex-aequo. Pas de chance !",
 	  ["Hmmm...perhaps a little more time will help."] = "Humm...Peut être qu'un peu plus de temps aiderait",
 --      ["Hogminator"] = "",
---      ["Hogs in sight!"] = "", -- Continental_supplies
---      ["HOLY SHYTE!"] = "", -- Mutant
---      ["Homing Bee"] = "", -- Construction_Mode
+      ["Hogs in sight!"] = "Hogs en vue !", -- Continental_supplies
+      ["HOLY SHYTE!"] = "Mère de dieu !", -- Mutant
+      ["Homing Bee"] = "Abeille téléguidée", -- Construction_Mode
 --      ["Honest Lee"] = "",
       ["Hooray!"] = "Hourra ! ",
       ["Hostage Situation"] = "Situation d'otage",
@@ -426,7 +426,7 @@
       ["I could just teleport myself there..."] = "Je pourrais juste me téléporter là-bas...",
       ["I'd better get going myself."] = "Je ferais mieux de rentrer.",
       ["I didn't until about a month ago."] = "Je ne savais pas jusqu'à il y a un mois",
---      ["I don't know how you did that.. But good work! |The next one should be easy as cake for you!"] = "", -- Basic_Training_-_Rope
+      ["I don't know how you did that.. But good work! |The next one should be easy as cake for you!"] = "Je ne sais pas comment tu as fait ca... Mais bravo ! Le prochain devrai être facile!", -- Basic_Training_-_Rope
       ["I feel something...a place! They will arrive near the circles!"] = "Je sens quelque chose... une localisation ! Ils vont arriver près des cercles !",
       ["If only I had a way..."] = "Si seulement j'avais un moyen...",
       ["If only I were given a chance to explain my being here..."] = "Si seulement vous me laissiez une chance d'expliquer ce que je fais ici...",
@@ -444,9 +444,9 @@
       ["I have no idea where that mole disappeared...Çan you see it?"] = "Je n'ai aucune idée où cette taupe a bien pu aller... Peux-tu la voir ?",
       ["I have to follow that alien."] = "Je dois suivre cet extraterrestre",
       ["I have to get back to the village!"] = "Je dois retourner au village !",
-	  ["I hope you are prepared for a small challenge, young one."] = "J'espere que tu es préparé pour un petit défi, petit scarabée",
-      ["I just don't want to sink to your level."] = "Je ne veux pas m'abaisser à votre niveau.",
-      ["I just found out that they have captured your princess!"] = "Je viens de m'apercevoir qu'ils ont capturé votre princesse !",
+	  ["I hope you are prepared for a small challenge, young one."] = "J'espère que tu es préparé pour un petit défi, petit scarabée",
+      ["I just don't want to sink to your level."] = "Je ne veux pas m'abaisser à ton niveau.",
+      ["I just found out that they have captured your princess!"] = "Je viens de m'apercevoir qu'ils ont capturé ta princesse !",
       ["I just wonder where Ramon and Spiky disappeared..."] = "Je me demande seulement où Ramon et Spiky ont disparu",
       ["I'll hold them off while you return to the village!"] = "Je vais les retenir pendant que tu retournes au village",
 	  ["Imagine those targets are the wolves that killed your parents! Take your anger out on them!"] = "Imagines que ces cibles sont les loups qui ont tués tes parents ! Défoule ta colère sur eux !",
@@ -461,7 +461,7 @@
       ["I'm not sure about that!"] = "Je n'en suis pas si sûr !",
 	  ["Impressive...you are still dry as the corpse of a hawk after a week in the desert..."] = "Impressionnant...tu es aussi sec que le cadavre d'un faucon après une semaine dans le désert...",
       ["I'm so scared!"] = "J'ai tellement peur !",
---      ["Increase"] = "", -- Continental_supplies
+      ["Increase"] = "Augmente", -- Continental_supplies
       ["Incredible..."] = "Incroyable...",
       ["I need to find the others!"] = "Je dois trouver les autres !",
       ["I need to get to the other side of this island, fast!"] = "Je dois aller sur l'autre côté de cette île, rapidemment !",
@@ -470,7 +470,7 @@
       ["I need to warn the others."] = "Je dois avertir les autres.",
       ["In fact, you are the only one that's been acting strangely."] = "En fait, tu es le seul qui ait agi étrangement.",
       ["In order to get to the other side, you need to collect the crates first.|"] = "Dans le but d'atteindre l'autre coté, tu dois d'abord collecter les caisses ",
---      ["INSANITY"] = "", -- Mutant
+      ["INSANITY"] = "FOLIE", -- Mutant
       ["Instructor"] = "Instructeur", -- 01#Boot_Çamp, User_Mission_-_Dangerous_Ducklings
       ["Interesting idea, haha!"] = "Idee intéressante, haha !",
       ["Interesting! Last time you said you killed a cannibal!"] = "Intéressant ! La dernière fois tu as dit que tu avais tué un cannibale !",
@@ -521,18 +521,18 @@
       ["Just wait till I get my hands on that trauma! ARGH!"] = "Attends un peu que je mette la main sur ce traumatisme !  ARGH !",
 --      ["Kamikaze"] = "", -- Construction_Mode
 --      ["Kamikaze Expert!"] = "",
---      ["Keep it up!"] = "",
+      ["Keep it up!"] = "Continue !",
 --      ["Kerguelen"] = "", -- Continental_supplies
       ["Killing spree!"] = "Massacre",
       ["KILL IT!"] = "TUE LE !",
       ["KILLS"] = "Meurtres",
---      ["Kill the aliens!"] = "",
+      ["Kill the aliens!"] = "Tue les aliens !",
       ["Kill the cannibal!"] = "Tue le cannibale !",
       ["Kill the traitor...or spare his life!|Kill him or press [Precise]!"] = "Tue le traître... ou épargne sa vie ! |Tue le ou appuie sur [Precise] !",
 --      ["Land Sprayer"] = "", -- Construction_Mode
---      ["Laser Sight"] = "", -- Construction_Mode
+      ["Laser Sight"] = "Visée laser", -- Construction_Mode
       ["Last Target!"] = "Dernière cible !",
---      ["Leader"] = "",
+      ["Leader"] = "Chef",
 --      ["Leaderbot"] = "",
 --      ["Leaks A Lot"] = "",
       ["Leaks A Lot, depressed for killing his loved one, failed to save the village..."] = "Grosse Fuite, déprimé d'avoir tué l'élue de son coeur, échoua à sauver le village...",
@@ -557,18 +557,18 @@
 --      ["Lively Lifeguard"] = "",
 
 --      ["Lonely Cries: [Rise the water if no hog is in the circle and deal 7 damage to all enemy hogs]"] = "", -- Continental_supplies
---      ["Lonely Hog"] = "", -- ClimbHome
+      ["Lonely Hog"] = "Hog tout seul", -- ClimbHome
       ["Look, I had no choice!"] = "Écoute, je n'avais pas le choix !",
       ["Look out! There's more of them!"] = "Regarde, il y en a encore plus !",
       ["Look out! We're surrounded by cannibals!"] = "Regarde ! Nous sommes entourés par les cannibales !",
       ["Looks like the whole world is falling apart!"] = "On dirait que le monde entier tombe en morceaux !",
---      ["Low Gravity"] = "", -- Construction_Mode, Frenzy
+      ["Low Gravity"] = "Peu de gravité", -- Construction_Mode, Frenzy
       ["Luckily, I've managed to snatch some of them."] = "Heureusement, j'ai réussi à en avoir quelques unes",
 --      ["LUDICROUS KILL"] = "", -- Mutant
---      ["Made it!"] = "", -- ClimbHome
---      ["- Massive weapon bonus on first turn"] = "", -- Continental_supplies
+      ["Made it!"] = "Je l'ai fait !", -- ClimbHome
+      ["- Massive weapon bonus on first turn"] = "- Gros bonus d'arme au premier tour !", -- Continental_supplies
       ["May the spirits aid you in all your quests!"] = "Puissent les esprits t'aider dans tes quêtes !",
---      ["Medicine: [Fire some exploding medicine that will heal all hogs effected by the explosion]"] = "", -- Continental_supplies
+      ["Medicine: [Fire some exploding medicine that will heal all hogs effected by the explosion]"] = "Soin: [Tire un kit de survie explosif qui soigne tous les hogs dans le rayon de l'explosion]", -- Continental_supplies
 --      ["MEGA KILL"] = "", -- Mutant
 --      ["Meiwes"] = "",
 --      ["Mindy"] = "",
--- a/share/hedgewars/Data/Scripts/Multiplayer/Racer.lua	Tue Feb 09 21:11:16 2016 +0300
+++ b/share/hedgewars/Data/Scripts/Multiplayer/Racer.lua	Mon Mar 14 22:08:27 2016 +0300
@@ -94,7 +94,7 @@
 local fastY = {}
 local fastCount = 0
 local fastIndex = 0
-local fastColour
+local fastColour = 0xffffffff
 
 local currX = {}
 local currY = {}
@@ -540,7 +540,7 @@
             wpY[wpCount] = y
             wpCol[wpCount] = 0xffffffff
             wpCirc[wpCount] = AddVisualGear(wpX[wpCount],wpY[wpCount],vgtCircle,0,true)
-                                                                                                                                            
+
             SetVisualGearValues(wpCirc[wpCount], wpX[wpCount], wpY[wpCount], 20, 100, 1, 10, 0, wpRad, 5, wpCol[wpCount])
 
             wpCount = wpCount + 1
@@ -551,9 +551,18 @@
 end
 
 function onSpecialPoint(x,y,flag)
-    specialPointsX[specialPointsCount] = x
-    specialPointsY[specialPointsCount] = y
-    specialPointsCount = specialPointsCount + 1
+    if flag == 99 then
+        fastX[fastCount] = x
+        fastY[fastCount] = y
+        fastCount = fastCount + 1
+    else
+        addHashData(x)
+        addHashData(y)
+        addHashData(flag)
+        specialPointsX[specialPointsCount] = x
+        specialPointsY[specialPointsCount] = y
+        specialPointsCount = specialPointsCount + 1
+    end
 end
 
 function onNewTurn()
@@ -743,17 +752,18 @@
 
 function onAttack()
     at = GetCurAmmoType()
-    
+
     usedWeapons[at] = 0
 end
 
 function onAchievementsDeclaration()
     usedWeapons[amSkip] = nil
-    
+    usedWeapons[amExtraTime] = nil
+
     usedRope = usedWeapons[amRope] ~= nil
     usedPortal = usedWeapons[amPortalGun] ~= nil
     usedSaucer = usedWeapons[amJetpack] ~= nil
-    
+
     usedWeapons[amNothing] = nil
     usedWeapons[amRope] = nil
     usedWeapons[amPortalGun] = nil
@@ -775,11 +785,19 @@
         raceType = "mixed race"
     end
 
-    map = detectMap()
-    
+    map = detectMapWithDigest()
+
     for i = 0, (numTeams-1) do
         if teamScore[i] < 100000 then
             DeclareAchievement(raceType, teamNameArr[i], map, teamScore[i])
         end
     end
+
+    if map ~= nil and fastCount > 0 then
+        StartGhostPoints(fastCount)
+
+        for i = 0, (fastCount - 1) do
+            DumpPoint(fastX[i], fastY[i])
+        end
+    end
 end
--- a/share/hedgewars/Data/Scripts/Multiplayer/TechRacer.lua	Tue Feb 09 21:11:16 2016 +0300
+++ b/share/hedgewars/Data/Scripts/Multiplayer/TechRacer.lua	Mon Mar 14 22:08:27 2016 +0300
@@ -173,7 +173,7 @@
 local fastY = {}
 local fastCount = 0
 local fastIndex = 0
-local fastColour
+local fastColour = 0xffffffff
 
 local currX = {}
 local currY = {}
@@ -246,7 +246,7 @@
                 teamNameArr[i] = " " -- = i
                 teamSize[i] = 0
                 teamIndex[i] = 0
-                teamScore[i] = 100000
+                teamScore[i] = 1000000
         end
         numTeams = 0
 
@@ -350,7 +350,7 @@
 function AdjustScores()
 
         if bestTime == nil then
-                bestTime = 100000
+                bestTime = 1000000
                 bestClan = 10
                 bestTimeComment = "N/A"
         end
@@ -380,7 +380,7 @@
                 end
         end
 
-        if bestTime ~= 100000 then
+        if bestTime ~= 1000000 then
                 bestTimeComment = (bestTime/1000) ..loc("s")
         end
 
@@ -690,10 +690,11 @@
 end
 
 function onGameInit()
+    if mapID == nil then
+        mapID = 2 + GetRandom(7)
+    end
 
-		if mapID == nil then
-			mapID = 2 + GetRandom(7)
-		end
+    addHashData(mapID)
 
 		Theme = "Cave"
 
@@ -724,10 +725,22 @@
 end
 
 function onSpecialPoint(x,y,flag)
-    specialPointsX[specialPointsCount] = x
-    specialPointsY[specialPointsCount] = y
-	specialPointsFlag[specialPointsCount] = flag
-    specialPointsCount = specialPointsCount + 1
+    if flag == 99 then
+        fastX[fastCount] = x
+        fastY[fastCount] = y
+        fastCount = fastCount + 1
+    elseif flag == 0 then
+        techX[techCount], techY[techCount] = x, y
+        techCount = techCount + 1
+    else
+        addHashData(x)
+        addHashData(y)
+        addHashData(flag)
+        specialPointsX[specialPointsCount] = x
+        specialPointsY[specialPointsCount] = y
+        specialPointsFlag[specialPointsCount] = flag
+        specialPointsCount = specialPointsCount + 1
+    end
 end
 
 function InterpretPoints()
@@ -1245,6 +1258,7 @@
 
 function onAchievementsDeclaration()
     usedWeapons[amSkip] = nil
+    usedWeapons[amExtraTime] = nil
 
     usedRope = usedWeapons[amRope] ~= nil
     usedPortal = usedWeapons[amPortalGun] ~= nil
@@ -1270,13 +1284,22 @@
         raceType = "mixed race"
     end
 
-    map = detectMap()
+    map = detectMapWithDigest()
 
     for i = 0, (numTeams-1) do
-        if teamScore[i] < 100000 then
+        if teamScore[i] < 1000000 then
             DeclareAchievement(raceType, teamNameArr[i], map, teamScore[i])
         end
     end
+
+    if map ~= nil and fastCount > 0 then
+        StartGhostPoints(fastCount)
+
+        for i = 0, (fastCount - 1) do
+            DumpPoint(fastX[i], fastY[i])
+        end
+    end
+
 end
 
 function onAmmoStoreInit()
--- a/share/hedgewars/Data/Scripts/OfficialChallenges.lua	Tue Feb 09 21:11:16 2016 +0300
+++ b/share/hedgewars/Data/Scripts/OfficialChallenges.lua	Mon Mar 14 22:08:27 2016 +0300
@@ -1,47 +1,62 @@
-function detectMap()
+local maps = {
+    ["Border,60526986531,M838018718Scripts/Multiplayer/Racer.lua"] = "Racer Challenge #1"
+    , ["Border,71022545335,M-490229244Scripts/Multiplayer/Racer.lua"] = "Racer Challenge #2"
+    , ["Border,40469748943,M806689586Scripts/Multiplayer/Racer.lua"] = "Racer Challenge #3"
+    , ["85940488650,M-134869715Scripts/Multiplayer/Racer.lua"] = "Racer Challenge #4"
+    , ["62080348735,M-661895109Scripts/Multiplayer/Racer.lua"] = "Racer Challenge #5"
+    , ["56818170733,M479034891Scripts/Multiplayer/Racer.lua"] = "Racer Challenge #6"
+    , ["Border,25372705797,M1770509913Scripts/Multiplayer/Racer.lua"] = "Racer Challenge #7"
+    , ["Border,10917540013,M1902370941Scripts/Multiplayer/Racer.lua"] = "Racer Challenge #8"
+    , ["Border,43890274319,M185940363Scripts/Multiplayer/Racer.lua"] = "Racer Challenge #9"
+    , ["Border,27870148394,M751885839Scripts/Multiplayer/Racer.lua"] = "Racer Challenge #10"
+    , ["Border,22647869226,M178845011Scripts/Multiplayer/Racer.lua"] = "Racer Challenge #11"
+    , ["Border,46954401793,M706743197Scripts/Multiplayer/Racer.lua"] = "Racer Challenge #12"
+    , ["Border,60760377667,M157242054Scripts/Multiplayer/Racer.lua"] = "Racer Challenge #13"
+    , ["Border,51825989393,M-1585582638Scripts/Multiplayer/Racer.lua"] = "Racer Challenge #14"
+    , ["81841189250,M256715557Scripts/Multiplayer/Racer.lua"] = "Racer Challenge #15"
+    , ["Border,44246064625,M-528106034Scripts/Multiplayer/Racer.lua"] = "Racer Challenge #16"
+    , ["60906776802,M-1389184823Scripts/Multiplayer/Racer.lua"] = "Racer Challenge #17"
+    , ["Border,70774747774,M-534640804Scripts/Multiplayer/Racer.lua"] = "Racer Challenge #18"
+    , ["Border,50512019610,M-1839546856Scripts/Multiplayer/Racer.lua"] = "Racer Challenge #19"
+-- tech racer
+    , ["Border,19661006772,M-975391975Scripts/Multiplayer/TechRacer.lua"] = "Tech Racer #1"
+    , ["Border,19661306766,M-975391975Scripts/Multiplayer/TechRacer.lua"] = "Tech Racer #2"
+    , ["Border,19661606760,M-975391975Scripts/Multiplayer/TechRacer.lua"] = "Tech Racer #3"
+    , ["Border,19661906754,M-975391975Scripts/Multiplayer/TechRacer.lua"] = "Tech Racer #4"
+    , ["Border,19662206748,M-975391975Scripts/Multiplayer/TechRacer.lua"] = "Tech Racer #5"
+    , ["Border,19662506742,M-975391975Scripts/Multiplayer/TechRacer.lua"] = "Tech Racer #6"
+    , ["Border,19662806736,M-975391975Scripts/Multiplayer/TechRacer.lua"] = "Tech Racer #7"
+    , ["Border,19663106730,M-975391975Scripts/Multiplayer/TechRacer.lua"] = "Tech Racer #8"
+    }
+
+-- modified Adler hash
+local hashA = 0
+local hashB = 0
+local hashModule = 299993
+
+function resetHash()
+    hashA = 0
+    hashB = 0
+end
+
+function addHashData(i)
+    hashA = (hashA + i + 65536) % hashModule
+    hashB = (hashB + hashA) % hashModule
+end
+
+function hashDigest()
+    return(hashB * hashModule + hashA)
+end
+
+function detectMapWithDigest()
     if RopePercent == 100 and MinesNum == 0 then
--- challenges with border
+        mapString = hashDigest() .. "," .. LandDigest
+
         if band(GameFlags, gfBorder) ~= 0 then
-            if LandDigest == "M838018718Scripts/Multiplayer/Racer.lua" then
-                return("Racer Challenge #1")
-            elseif LandDigest == "M-490229244Scripts/Multiplayer/Racer.lua" then
-                return("Racer Challenge #2")
-            elseif LandDigest == "M806689586Scripts/Multiplayer/Racer.lua" then
-                return("Racer Challenge #3")
-            elseif LandDigest == "M1770509913Scripts/Multiplayer/Racer.lua" then
-                return("Racer Challenge #7")
-            elseif LandDigest == "M1902370941Scripts/Multiplayer/Racer.lua" then
-                return("Racer Challenge #8")
-            elseif LandDigest == "M185940363Scripts/Multiplayer/Racer.lua" then
-                return("Racer Challenge #9")
-            elseif LandDigest == "M751885839Scripts/Multiplayer/Racer.lua" then
-                return("Racer Challenge #10")
-            elseif LandDigest == "M178845011Scripts/Multiplayer/Racer.lua" then
-                return("Racer Challenge #11")
-            elseif LandDigest == "M706743197Scripts/Multiplayer/Racer.lua" then
-                return("Racer Challenge #12")
-            elseif LandDigest == "M157242054Scripts/Multiplayer/Racer.lua" then
-                return("Racer Challenge #13")
-            elseif LandDigest == "M-1585582638Scripts/Multiplayer/Racer.lua" then
-                return("Racer Challenge #14")
-            elseif LandDigest == "M-528106034Scripts/Multiplayer/Racer.lua" then
-                return("Racer Challenge #16")
-            elseif LandDigest == "M-534640804Scripts/Multiplayer/Racer.lua" then
-                return("Racer Challenge #18")
-            elseif LandDigest == "M-1839546856Scripts/Multiplayer/Racer.lua" then
-                return("Racer Challenge #19")
-            end
--- challenges without border
-        elseif LandDigest == "M-134869715Scripts/Multiplayer/Racer.lua" then
-            return("Racer Challenge #4")
-        elseif LandDigest == "M-661895109Scripts/Multiplayer/Racer.lua" then
-            return("Racer Challenge #5")
-        elseif LandDigest == "M479034891Scripts/Multiplayer/Racer.lua" then
-            return("Racer Challenge #6")
-        elseif LandDigest == "M256715557Scripts/Multiplayer/Racer.lua" then
-            return("Racer Challenge #15")
-        elseif LandDigest == "M-1389184823Scripts/Multiplayer/Racer.lua" then
-            return("Racer Challenge #17")
+            mapString = "Border," .. mapString
         end
+
+        --WriteLnToConsole(mapString)
+        return(maps[mapString])
     end
 end
--- /dev/null	Thu Jan 01 00:00:00 1970 +0000
+++ b/tools/dmg_pkg_install.sh	Mon Mar 14 22:08:27 2016 +0300
@@ -0,0 +1,39 @@
+#!/bin/bash
+
+# Downloads and install a .dmg from a URL
+#
+# Usage
+# $ dmg_pkg_install [url]
+#
+# Adopted from https://gist.github.com/afgomez/4172338
+
+
+if [[ $# -lt 1 ]]; then
+  echo "Usage: dmg_pkg_install [url]"
+  exit 1
+fi
+
+url=$*
+
+# Generate a random file name
+tmp_file=/tmp/`openssl rand -base64 10 | tr -dc '[:alnum:]'`.dmg
+
+# Download file
+echo "Downloading $url..."
+curl -# -L -o $tmp_file $url
+
+echo "Mounting image..."
+volume=`hdiutil mount $tmp_file | tail -n1 | perl -nle '/(\/Volumes\/[^ ]+)/; print $1'`
+
+# Locate .pkg
+app_pkg=`find $volume/. -name *.pkg -maxdepth 1 -print0`
+echo "Install pkg..."
+installer -pkg $app_pkg -target /
+
+# Unmount volume, delete temporal file
+echo "Cleaning up..."
+hdiutil unmount $volume -quiet
+rm $tmp_file
+
+echo "Done!"
+exit 0
\ No newline at end of file
--- /dev/null	Thu Jan 01 00:00:00 1970 +0000
+++ b/tools/fix_fpc_ios_build_patch.diff	Mon Mar 14 22:08:27 2016 +0300
@@ -0,0 +1,57 @@
+diff --git a/project_files/HedgewarsMobile/Hedgewars.xcodeproj/project.pbxproj b/project_files/HedgewarsMobile/Hedgewars.xcodeproj/project.pbxproj
+--- a/project_files/HedgewarsMobile/Hedgewars.xcodeproj/project.pbxproj
++++ b/project_files/HedgewarsMobile/Hedgewars.xcodeproj/project.pbxproj
+@@ -1830,7 +1830,7 @@
+ 			);
+ 			runOnlyForDeploymentPostprocessing = 0;
+ 			shellPath = /bin/sh;
+-			shellScript = "# Build libfpc.a\n# 9 July 2006 (Jonas Maebe)\n#   * original version\n# 15 September 2006 (Erling Johansen)\n#   * simplified\n# 26 April 2007 (Jonas Maebe)\n#  * added support for ppc64/x86_64 (future proofing)\n# 4 August 2007 (Jonas Maebe)\n#  * call ranlib after ar so the toc of the library is up-to-date\n# 3 January 2009 (Jonas Maebe)\n#  * support for ARM\n# 24 October 2009 (Jonas Maebe)\n#  * don't hardcode version 2.3.1 anymore under certain circumstances\n#  * use the FPC_RTL_UNITS_BASE setting\n# 13 December 2009 (Jonas Maebe)\n#  * use new FPC_COMPILER_BINARY_DIR setting to make it easier to change the used FPC version\n\nrm -f \"$TARGET_TEMP_DIR\"/*.a\nnarch=\n\n#temparchs=`echo $ARCHS|sed -e 's/arm[^\\w]*/arm\\\n#/'|sort -u`\ntemparchs=`echo $ARCHS|sort -u`\necho $temparchs\nfor arch in $temparchs\ndo\n\ttargetos=darwin;\n\tcase $arch in\n        arm64) fpc_arch=rossa64; fpc_rtl=aarch64 ;;\n        armv7) fpc_arch=rossarm; fpc_rtl=arm ;;\n        x86_64) fpc_arch=x64; fpc_rtl=x86_64; targetos=iphonesim ;;\n#       ppc) fpc_arch=ppc; fpc_rtl=powerpc ;;\n#\t\ti386) fpc_arch=386; fpc_rtl=i386; targetos=iphonesim ;;\n#\t\tppc64) fpc_arch=ppc64; fpc_rtl=powerpc64 ;;\n#\t\tx86_64) fpc_arch=x64; fpc_rtl=x86_64 ;;\n#\t\tarm*) fpc_arch=arm; fpc_rtl=arm ;;\n\t\t*) continue\n\tesac\n\tif test -e \"${FPC_COMPILER_BINARY_DIR}\"/ppc${fpc_arch}\n\tthen\n\t\tupath=\"$FPC_RTL_UNITS_BASE\"/`\"${FPC_COMPILER_BINARY_DIR}\"/ppc${fpc_arch} -iV`/units/${fpc_rtl}-${targetos}\n\t\tar -q \"$TARGET_TEMP_DIR\"/libfpc${narch}.a `ls \"$upath\"/*/*.o | grep -v 'darwin/fv/'`\n\t\tranlib \"$TARGET_TEMP_DIR\"/libfpc${narch}.a\n\t\tnarch=${narch}x\n\telse\n\t\techo error: can\\'t build libfpc.a for $arch \\(${FPC_COMPILER_BINARY_DIR}/ppc${fpc_arch} not found, derived from FPC_COMPILER_BINARY_DIR project setting\\)\n\tfi\ndone\n           \nif test ${#narch} -gt 1\nthen\n\tlipo -create \"$TARGET_TEMP_DIR\"/libfpc*.a -output \"$TARGET_BUILD_DIR\"/libfpc.a\n\trm -f \"$TARGET_TEMP_DIR\"/*.a\nelse\n\tmv \"$TARGET_TEMP_DIR\"/libfpc.a \"$TARGET_BUILD_DIR\"\nfi\n";
++			shellScript = "# Build libfpc.a\n# 9 July 2006 (Jonas Maebe)\n#   * original version\n# 15 September 2006 (Erling Johansen)\n#   * simplified\n# 26 April 2007 (Jonas Maebe)\n#  * added support for ppc64/x86_64 (future proofing)\n# 4 August 2007 (Jonas Maebe)\n#  * call ranlib after ar so the toc of the library is up-to-date\n# 3 January 2009 (Jonas Maebe)\n#  * support for ARM\n# 24 October 2009 (Jonas Maebe)\n#  * don't hardcode version 2.3.1 anymore under certain circumstances\n#  * use the FPC_RTL_UNITS_BASE setting\n# 13 December 2009 (Jonas Maebe)\n#  * use new FPC_COMPILER_BINARY_DIR setting to make it easier to change the used FPC version\n\nrm -f \"$TARGET_TEMP_DIR\"/*.a\nnarch=\n\n#temparchs=`echo $ARCHS|sed -e 's/arm[^\\w]*/arm\\\n#/'|sort -u`\ntemparchs=`echo $ARCHS|sort -u`\necho $temparchs\nfor arch in $temparchs\ndo\n\ttargetos=darwin;\n\tcase $arch in\n        arm64) fpc_arch=a64; fpc_rtl=aarch64 ;;\n        armv7) fpc_arch=arm; fpc_rtl=arm ;;\n        x86_64) fpc_arch=x64; fpc_rtl=x86_64; targetos=iphonesim ;;\n#       ppc) fpc_arch=ppc; fpc_rtl=powerpc ;;\n#\t\ti386) fpc_arch=386; fpc_rtl=i386; targetos=iphonesim ;;\n#\t\tppc64) fpc_arch=ppc64; fpc_rtl=powerpc64 ;;\n#\t\tx86_64) fpc_arch=x64; fpc_rtl=x86_64 ;;\n#\t\tarm*) fpc_arch=arm; fpc_rtl=arm ;;\n\t\t*) continue\n\tesac\n\tif test -e \"${FPC_COMPILER_BINARY_DIR}\"/ppc${fpc_arch}\n\tthen\n\t\tupath=\"$FPC_RTL_UNITS_BASE\"/`\"${FPC_COMPILER_BINARY_DIR}\"/ppc${fpc_arch} -iV`/units/${fpc_rtl}-${targetos}\n\t\tar -q \"$TARGET_TEMP_DIR\"/libfpc${narch}.a `ls \"$upath\"/*/*.o | grep -v 'darwin/fv/'`\n\t\tranlib \"$TARGET_TEMP_DIR\"/libfpc${narch}.a\n\t\tnarch=${narch}x\n\telse\n\t\techo error: can\\'t build libfpc.a for $arch \\(${FPC_COMPILER_BINARY_DIR}/ppc${fpc_arch} not found, derived from FPC_COMPILER_BINARY_DIR project setting\\)\n\tfi\ndone\n           \nif test ${#narch} -gt 1\nthen\n\tlipo -create \"$TARGET_TEMP_DIR\"/libfpc*.a -output \"$TARGET_BUILD_DIR\"/libfpc.a\n\trm -f \"$TARGET_TEMP_DIR\"/*.a\nelse\n\tmv \"$TARGET_TEMP_DIR\"/libfpc.a \"$TARGET_BUILD_DIR\"\nfi\n";
+ 		};
+ 		928301560F10E04C00CC5A3C /* Compile Pascal Sources */ = {
+ 			isa = PBXShellScriptBuildPhase;
+@@ -1845,7 +1845,7 @@
+ 			);
+ 			runOnlyForDeploymentPostprocessing = 0;
+ 			shellPath = /bin/sh;
+-			shellScript = "# Compile Pascal Sources\n# 15sep06,ejo  written.\n# 26 April 2007 - Jonas Maebe\n#  * support for ppc64 and x86_64\n#  * don't run when cleaning (in case running scripts when cleaning is ever fixed by Apple) (removed)\n#  * split the options in FPC_COMMON_FLAGS (common to all configurations) and FPC_CFG_SPECIFIC_FLAGS (per configuration)\n# 4 January 2009 - Jonas Maebe\n#  * support for ARM\n# 24 October 2009 - Jonas Maebe\n#  * don't hardcode 2.3.1 in some cases anymore\n# 13 December 2009 (Jonas Maebe)\n#  * use new FPC_COMPILER_BINARY_DIR setting to make it easier to change the used FPC version\n\nif test ! -e \"$FPC_MAIN_FILE\"\nthen\n\techo error: FPC_MAIN_FILE not found \\($FPC_MAIN_FILE\\)\n\texit 2\nfi\n\nfor variant in $BUILD_VARIANTS\ndo\n\tfor arch in $ARCHS\n\tdo\n\t\ttargetos=darwin;\n\t\tcase $arch in\n            arm64) fpc_arch=rossa64; fpc_rtl=aarch64 ;;\n            armv7) fpc_arch=rossarm; fpc_rtl=arm ;;\n            x86_64) fpc_arch=x64; fpc_rtl=x86_64; targetos=iphonesim ;;\n#\t\t\tppc) fpc_arch=ppc; fpc_rtl=powerpc ;;\n#\t\t\ti386) fpc_arch=386; fpc_rtl=i386; targetos=iphonesim ;;\n#\t\t\tppc64) fpc_arch=ppc64; fpc_rtl=powerpc64 ;;\n#\t\t\tx86_64) fpc_arch=x64; fpc_rtl=x86_64 ;;\n#\t\t\tarm*) fpc_arch=arm; fpc_rtl=arm ;;\n\t\t\t*) continue\n\t\tesac\n\n\t\tapp_target_temp_dir=$CONFIGURATION_TEMP_DIR/`basename \"$PROJECT_TEMP_DIR\"`\n\t\tout_dir=$app_target_temp_dir/`basename \"$DERIVED_SOURCES_DIR\"`-$variant/$arch\n\t\tfpccompiler=\"${FPC_COMPILER_BINARY_DIR}/ppc${fpc_arch}\"\n\t\tif test -e \"$fpccompiler\"\n\t\tthen\n\t\t\tfpcversion=`\"$fpccompiler\" -iV`\n\t\t\tmainunitdir=\"$FPC_RTL_UNITS_BASE/$fpcversion/units/${fpc_rtl}-${targetos}/\"\n\t\t\tmkdir -p \"$out_dir\"\n\t\t\tcd \"$out_dir\"\n\t\t\techo \"Compiling to $out_dir\"\n\t\t\trm -f compilefailed\n\t\n\t\t\t# delete any ppu files for which the \".s\" file was somehow deleted (Xcode does that sometimes in case of errors),\n\t\t\t# so that FPC will recompile the unit\n\t\t\tfor file in *.ppu\n\t\t\tdo\n\t\t\t\tasmname=`basename \"$file\" ppu`s\n\t\t\t\tif [ ! -f \"$asmname\" ]; then\n\t\t\t\t\t# can fail in case there are no .ppu files, since then it will try to erase the file with name '*.ppu'\n\t\t\t\t\t# -> use -f so it won't give an error message\n\t\t\t\t\trm -f \"$file\"\n\t\t\t\tfi\n\t\t\tdone\n\n\t\t\techo $fpccompiler -n -l -viwn -a -s -vbr -FE. $FPC_COMMON_OPTIONS $FPC_SPECIFIC_OPTIONS '\\' >ppccmd.sh\n\t\t\techo -Fi\\\"`dirname \"$FPC_MAIN_FILE\"`\\\" '\\' >>ppccmd.sh\n\t\t\techo -Fu\"$mainunitdir/*\" -Fu\"$mainunitdir/rtl\" '\\' >>ppccmd.sh\n\t\t\t# allow FPC_UNIT_PATHS to override default search directory\n\t\t\techo $FPC_UNIT_PATHS '\\' >>ppccmd.sh\n\t\t\techo \\\"$FPC_MAIN_FILE\\\" >>ppccmd.sh\n\t\t\t# cat ppccmd.sh\n\n\t\t\t/bin/sh ppccmd.sh\n\t\t\tif [ $? != 0 ]; then\n\t\t\t\ttouch \"$out_dir\"/compilefailed\n\t\t\t\texit 1\n\t\t\tfi\n\t\telse\n\t\t\ttouch \"$out_dir\"/compilefailed\n\t\t\techo $FPC_MAIN_FILE:1: error: 1: can\\'t compile for $arch \\(ppc${fpc_arch} not found\\)\n\t\t\texit 2\n\t\tfi\n\tdone\ndone\n";
++			shellScript = "# Compile Pascal Sources\n# 15sep06,ejo  written.\n# 26 April 2007 - Jonas Maebe\n#  * support for ppc64 and x86_64\n#  * don't run when cleaning (in case running scripts when cleaning is ever fixed by Apple) (removed)\n#  * split the options in FPC_COMMON_FLAGS (common to all configurations) and FPC_CFG_SPECIFIC_FLAGS (per configuration)\n# 4 January 2009 - Jonas Maebe\n#  * support for ARM\n# 24 October 2009 - Jonas Maebe\n#  * don't hardcode 2.3.1 in some cases anymore\n# 13 December 2009 (Jonas Maebe)\n#  * use new FPC_COMPILER_BINARY_DIR setting to make it easier to change the used FPC version\n\nif test ! -e \"$FPC_MAIN_FILE\"\nthen\n\techo error: FPC_MAIN_FILE not found \\($FPC_MAIN_FILE\\)\n\texit 2\nfi\n\nfor variant in $BUILD_VARIANTS\ndo\n\tfor arch in $ARCHS\n\tdo\n\t\ttargetos=darwin;\n\t\tcase $arch in\n            arm64) fpc_arch=a64; fpc_rtl=aarch64 ;;\n            armv7) fpc_arch=arm; fpc_rtl=arm ;;\n            x86_64) fpc_arch=x64; fpc_rtl=x86_64; targetos=iphonesim ;;\n#\t\t\tppc) fpc_arch=ppc; fpc_rtl=powerpc ;;\n#\t\t\ti386) fpc_arch=386; fpc_rtl=i386; targetos=iphonesim ;;\n#\t\t\tppc64) fpc_arch=ppc64; fpc_rtl=powerpc64 ;;\n#\t\t\tx86_64) fpc_arch=x64; fpc_rtl=x86_64 ;;\n#\t\t\tarm*) fpc_arch=arm; fpc_rtl=arm ;;\n\t\t\t*) continue\n\t\tesac\n\n\t\tapp_target_temp_dir=$CONFIGURATION_TEMP_DIR/`basename \"$PROJECT_TEMP_DIR\"`\n\t\tout_dir=$app_target_temp_dir/`basename \"$DERIVED_SOURCES_DIR\"`-$variant/$arch\n\t\tfpccompiler=\"${FPC_COMPILER_BINARY_DIR}/ppc${fpc_arch}\"\n\t\tif test -e \"$fpccompiler\"\n\t\tthen\n\t\t\tfpcversion=`\"$fpccompiler\" -iV`\n\t\t\tmainunitdir=\"$FPC_RTL_UNITS_BASE/$fpcversion/units/${fpc_rtl}-${targetos}/\"\n\t\t\tmkdir -p \"$out_dir\"\n\t\t\tcd \"$out_dir\"\n\t\t\techo \"Compiling to $out_dir\"\n\t\t\trm -f compilefailed\n\t\n\t\t\t# delete any ppu files for which the \".s\" file was somehow deleted (Xcode does that sometimes in case of errors),\n\t\t\t# so that FPC will recompile the unit\n\t\t\tfor file in *.ppu\n\t\t\tdo\n\t\t\t\tasmname=`basename \"$file\" ppu`s\n\t\t\t\tif [ ! -f \"$asmname\" ]; then\n\t\t\t\t\t# can fail in case there are no .ppu files, since then it will try to erase the file with name '*.ppu'\n\t\t\t\t\t# -> use -f so it won't give an error message\n\t\t\t\t\trm -f \"$file\"\n\t\t\t\tfi\n\t\t\tdone\n\n\t\t\techo $fpccompiler -n -l -viwn -a -s -vbr -FE. $FPC_COMMON_OPTIONS $FPC_SPECIFIC_OPTIONS '\\' >ppccmd.sh\n\t\t\techo -Fi\\\"`dirname \"$FPC_MAIN_FILE\"`\\\" '\\' >>ppccmd.sh\n\t\t\techo -Fu\"$mainunitdir/*\" -Fu\"$mainunitdir/rtl\" '\\' >>ppccmd.sh\n\t\t\t# allow FPC_UNIT_PATHS to override default search directory\n\t\t\techo $FPC_UNIT_PATHS '\\' >>ppccmd.sh\n\t\t\techo \\\"$FPC_MAIN_FILE\\\" >>ppccmd.sh\n\t\t\t# cat ppccmd.sh\n\n\t\t\t/bin/sh ppccmd.sh\n\t\t\tif [ $? != 0 ]; then\n\t\t\t\ttouch \"$out_dir\"/compilefailed\n\t\t\t\texit 1\n\t\t\tfi\n\t\telse\n\t\t\ttouch \"$out_dir\"/compilefailed\n\t\t\techo $FPC_MAIN_FILE:1: error: 1: can\\'t compile for $arch \\(ppc${fpc_arch} not found\\)\n\t\t\texit 2\n\t\tfi\n\tdone\ndone\n";
+ 		};
+ /* End PBXShellScriptBuildPhase section */
+ 
+@@ -2141,7 +2141,7 @@
+ 				ENABLE_BITCODE = NO;
+ 				ENABLE_STRICT_OBJC_MSGSEND = YES;
+ 				FPC_COMMON_OPTIONS = "-l- -dIPHONEOS -Cs2000000 -B  -vwi -Sgix -Fi${PROJECT_DIR}";
+-				FPC_COMPILER_BINARY_DIR = /usr/local/lib/fpc/3.1.1;
++				FPC_COMPILER_BINARY_DIR = /usr/local/lib/fpc/3.0.1;
+ 				FPC_MAIN_FILE = "$(PROJECT_DIR)/../../hedgewars/hwLibrary.pas";
+ 				FPC_RTL_UNITS_BASE = /usr/local/lib/fpc;
+ 				FPC_SPECIFIC_OPTIONS = "-Ci- -Cr- -Co- -O2 -Xs -dNOCONSOLE";
+@@ -2258,7 +2258,7 @@
+ 				ENABLE_BITCODE = NO;
+ 				ENABLE_STRICT_OBJC_MSGSEND = YES;
+ 				FPC_COMMON_OPTIONS = "-l- -dIPHONEOS -Cs2000000 -B  -vwi -Sgix -Fi${PROJECT_DIR}";
+-				FPC_COMPILER_BINARY_DIR = /usr/local/lib/fpc/3.1.1;
++				FPC_COMPILER_BINARY_DIR = /usr/local/lib/fpc/3.0.1;
+ 				FPC_MAIN_FILE = "$(PROJECT_DIR)/../../hedgewars/hwLibrary.pas";
+ 				FPC_RTL_UNITS_BASE = /usr/local/lib/fpc;
+ 				FPC_SPECIFIC_OPTIONS = "-dDEBUGFILE -O- -g -gl -gw2 -gt -ghttt -Xs-";
+@@ -2423,7 +2423,7 @@
+ 				ENABLE_STRICT_OBJC_MSGSEND = YES;
+ 				ENABLE_TESTABILITY = YES;
+ 				FPC_COMMON_OPTIONS = "-l- -dIPHONEOS -Cs2000000 -B  -vwi -Sgix -Fi${PROJECT_DIR}";
+-				FPC_COMPILER_BINARY_DIR = /usr/local/lib/fpc/3.1.1;
++				FPC_COMPILER_BINARY_DIR = /usr/local/lib/fpc/3.0.1;
+ 				FPC_MAIN_FILE = "$(PROJECT_DIR)/../../hedgewars/hwLibrary.pas";
+ 				FPC_RTL_UNITS_BASE = /usr/local/lib/fpc;
+ 				FPC_SPECIFIC_OPTIONS = "-Tiphonesim -dDEBUGFILE -O- -g -gl -gw2 -gt -ghttt -Xs-";
+@@ -2503,7 +2503,7 @@
+ 				ENABLE_BITCODE = NO;
+ 				ENABLE_STRICT_OBJC_MSGSEND = YES;
+ 				FPC_COMMON_OPTIONS = "-l- -dIPHONEOS -Cs2000000 -B  -vwi -Sgix -Fi${PROJECT_DIR}";
+-				FPC_COMPILER_BINARY_DIR = /usr/local/lib/fpc/3.1.1;
++				FPC_COMPILER_BINARY_DIR = /usr/local/lib/fpc/3.0.1;
+ 				FPC_MAIN_FILE = "$(PROJECT_DIR)/../../hedgewars/hwLibrary.pas";
+ 				FPC_RTL_UNITS_BASE = /usr/local/lib/fpc;
+ 				FPC_SPECIFIC_OPTIONS = "-Ci- -Cr- -Co- -O2 -Xs -dDEBUGFILE";