gameServer/EngineInteraction.hs
author unc0rr
Tue, 12 Nov 2013 15:38:45 +0400
changeset 9690 6a1748b71df2
parent 9401 2af7bea32e5e
child 10017 de822cd3df3a
child 10027 403b86a1d05f
permissions -rw-r--r--
Handle absence of "SCRIPT" in replay
Ignore whitespace changes - Everywhere: Within whitespace: At end of lines:
8480
42d2565b5700 Converter from game parameters to engine commands, not finished yet
unc0rr
parents: 8479
diff changeset
     1
{-# LANGUAGE OverloadedStrings #-}
42d2565b5700 Converter from game parameters to engine commands, not finished yet
unc0rr
parents: 8479
diff changeset
     2
6068
e18713ecf1e0 Introduce EngineInteraction module
unc0rr
parents:
diff changeset
     3
module EngineInteraction where
e18713ecf1e0 Introduce EngineInteraction module
unc0rr
parents:
diff changeset
     4
e18713ecf1e0 Introduce EngineInteraction module
unc0rr
parents:
diff changeset
     5
import qualified Data.Set as Set
e18713ecf1e0 Introduce EngineInteraction module
unc0rr
parents:
diff changeset
     6
import Control.Monad
e18713ecf1e0 Introduce EngineInteraction module
unc0rr
parents:
diff changeset
     7
import qualified Codec.Binary.Base64 as Base64
e18713ecf1e0 Introduce EngineInteraction module
unc0rr
parents:
diff changeset
     8
import qualified Data.ByteString.Char8 as B
e18713ecf1e0 Introduce EngineInteraction module
unc0rr
parents:
diff changeset
     9
import qualified Data.ByteString as BW
8479
8d71109b04d2 Some work on loading replay and interaction with checker
unc0rr
parents: 7766
diff changeset
    10
import qualified Data.Map as Map
8484
99c14f14f788 New checker of engine messages which is aware of glued together messages
unc0rr
parents: 8483
diff changeset
    11
import qualified Data.List as L
8480
42d2565b5700 Converter from game parameters to engine commands, not finished yet
unc0rr
parents: 8479
diff changeset
    12
import Data.Word
42d2565b5700 Converter from game parameters to engine commands, not finished yet
unc0rr
parents: 8479
diff changeset
    13
import Data.Bits
8481
692ff6468b63 - Handle mapgen-specific parameters
unc0rr
parents: 8480
diff changeset
    14
import Control.Arrow
9690
6a1748b71df2 Handle absence of "SCRIPT" in replay
unc0rr
parents: 9401
diff changeset
    15
import Data.Maybe
6069
d59745e525ec GameInfo needs room params copy
unc0rr
parents: 6068
diff changeset
    16
-------------
d59745e525ec GameInfo needs room params copy
unc0rr
parents: 6068
diff changeset
    17
import CoreTypes
8480
42d2565b5700 Converter from game parameters to engine commands, not finished yet
unc0rr
parents: 8479
diff changeset
    18
import Utils
6068
e18713ecf1e0 Introduce EngineInteraction module
unc0rr
parents:
diff changeset
    19
e18713ecf1e0 Introduce EngineInteraction module
unc0rr
parents:
diff changeset
    20
e18713ecf1e0 Introduce EngineInteraction module
unc0rr
parents:
diff changeset
    21
toEngineMsg :: B.ByteString -> B.ByteString
e18713ecf1e0 Introduce EngineInteraction module
unc0rr
parents:
diff changeset
    22
toEngineMsg msg = B.pack $ Base64.encode (fromIntegral (BW.length msg) : BW.unpack msg)
e18713ecf1e0 Introduce EngineInteraction module
unc0rr
parents:
diff changeset
    23
e18713ecf1e0 Introduce EngineInteraction module
unc0rr
parents:
diff changeset
    24
e18713ecf1e0 Introduce EngineInteraction module
unc0rr
parents:
diff changeset
    25
fromEngineMsg :: B.ByteString -> Maybe B.ByteString
e18713ecf1e0 Introduce EngineInteraction module
unc0rr
parents:
diff changeset
    26
fromEngineMsg msg = liftM BW.pack (Base64.decode (B.unpack msg) >>= removeLength)
e18713ecf1e0 Introduce EngineInteraction module
unc0rr
parents:
diff changeset
    27
    where
e18713ecf1e0 Introduce EngineInteraction module
unc0rr
parents:
diff changeset
    28
        removeLength (x:xs) = if length xs == fromIntegral x then Just xs else Nothing
e18713ecf1e0 Introduce EngineInteraction module
unc0rr
parents:
diff changeset
    29
        removeLength _ = Nothing
e18713ecf1e0 Introduce EngineInteraction module
unc0rr
parents:
diff changeset
    30
e18713ecf1e0 Introduce EngineInteraction module
unc0rr
parents:
diff changeset
    31
8484
99c14f14f788 New checker of engine messages which is aware of glued together messages
unc0rr
parents: 8483
diff changeset
    32
splitMessages :: B.ByteString -> [B.ByteString]
99c14f14f788 New checker of engine messages which is aware of glued together messages
unc0rr
parents: 8483
diff changeset
    33
splitMessages = L.unfoldr (\b -> if B.null b then Nothing else Just $ B.splitAt (1 + fromIntegral (BW.head b)) b)
99c14f14f788 New checker of engine messages which is aware of glued together messages
unc0rr
parents: 8483
diff changeset
    34
99c14f14f788 New checker of engine messages which is aware of glued together messages
unc0rr
parents: 8483
diff changeset
    35
9304
3f4c3fc146c2 Fix spectator desync in rare conditions (there was team which left during its turn, and last command with timestamp from it was '+')
unc0rr
parents: 8541
diff changeset
    36
checkNetCmd :: B.ByteString -> (B.ByteString, B.ByteString, Maybe (Maybe B.ByteString))
6068
e18713ecf1e0 Introduce EngineInteraction module
unc0rr
parents:
diff changeset
    37
checkNetCmd msg = check decoded
e18713ecf1e0 Introduce EngineInteraction module
unc0rr
parents:
diff changeset
    38
    where
8485
7cae79214537 Fix the checker after some testing
unc0rr
parents: 8484
diff changeset
    39
        decoded = liftM (splitMessages . BW.pack) $ Base64.decode $ B.unpack msg
9304
3f4c3fc146c2 Fix spectator desync in rare conditions (there was team which left during its turn, and last command with timestamp from it was '+')
unc0rr
parents: 8541
diff changeset
    40
        check Nothing = (B.empty, B.empty, Nothing)
3f4c3fc146c2 Fix spectator desync in rare conditions (there was team which left during its turn, and last command with timestamp from it was '+')
unc0rr
parents: 8541
diff changeset
    41
        check (Just msgs) = let (a, b) = (filter isLegal msgs, filter isNonEmpty a) in (encode a, encode b, lft a)
8484
99c14f14f788 New checker of engine messages which is aware of glued together messages
unc0rr
parents: 8483
diff changeset
    42
        encode = B.pack . Base64.encode . BW.unpack . B.concat
8485
7cae79214537 Fix the checker after some testing
unc0rr
parents: 8484
diff changeset
    43
        isLegal m = (B.length m > 1) && (flip Set.member legalMessages . B.head . B.tail $ m)
9304
3f4c3fc146c2 Fix spectator desync in rare conditions (there was team which left during its turn, and last command with timestamp from it was '+')
unc0rr
parents: 8541
diff changeset
    44
        lft = foldr l Nothing
3f4c3fc146c2 Fix spectator desync in rare conditions (there was team which left during its turn, and last command with timestamp from it was '+')
unc0rr
parents: 8541
diff changeset
    45
        l m n = let m' = B.head $ B.tail m; tst = flip Set.member in 
3f4c3fc146c2 Fix spectator desync in rare conditions (there was team which left during its turn, and last command with timestamp from it was '+')
unc0rr
parents: 8541
diff changeset
    46
                      if not $ tst timedMessages m' then n
9401
2af7bea32e5e - Some fixes to official server build
unc0rr
parents: 9304
diff changeset
    47
                        else if '+' /= m' then Just Nothing else Just . Just . B.pack . Base64.encode . BW.unpack $ m
8506
3889dab021b8 - Fix check for void message
unc0rr
parents: 8503
diff changeset
    48
        isNonEmpty = (/=) '+' . B.head . B.tail
6206
75e0d8169ba2 As sheepluva pointed out, allowing this message to be legal allows naughtiness. The server usage of this message does not seem to use this check.
nemo
parents: 6070
diff changeset
    49
        legalMessages = Set.fromList $ "M#+LlRrUuDdZzAaSjJ,sNpPwtghbc12345" ++ slotMessages
6068
e18713ecf1e0 Introduce EngineInteraction module
unc0rr
parents:
diff changeset
    50
        slotMessages = "\128\129\130\131\132\133\134\135\136\137\138"
9304
3f4c3fc146c2 Fix spectator desync in rare conditions (there was team which left during its turn, and last command with timestamp from it was '+')
unc0rr
parents: 8541
diff changeset
    51
        timedMessages = Set.fromList $ "+LlRrUuDdZzAaSjJ,NpPwtgc12345" ++ slotMessages
6068
e18713ecf1e0 Introduce EngineInteraction module
unc0rr
parents:
diff changeset
    52
7766
98edc0724a28 Fix most of server warnings
unc0rr
parents: 6206
diff changeset
    53
8479
8d71109b04d2 Some work on loading replay and interaction with checker
unc0rr
parents: 7766
diff changeset
    54
replayToDemo :: [TeamInfo]
8d71109b04d2 Some work on loading replay and interaction with checker
unc0rr
parents: 7766
diff changeset
    55
        -> Map.Map B.ByteString B.ByteString
8d71109b04d2 Some work on loading replay and interaction with checker
unc0rr
parents: 7766
diff changeset
    56
        -> Map.Map B.ByteString [B.ByteString]
8d71109b04d2 Some work on loading replay and interaction with checker
unc0rr
parents: 7766
diff changeset
    57
        -> [B.ByteString]
8d71109b04d2 Some work on loading replay and interaction with checker
unc0rr
parents: 7766
diff changeset
    58
        -> [B.ByteString]
9304
3f4c3fc146c2 Fix spectator desync in rare conditions (there was team which left during its turn, and last command with timestamp from it was '+')
unc0rr
parents: 8541
diff changeset
    59
replayToDemo ti mParams prms msgs = concat [
8480
42d2565b5700 Converter from game parameters to engine commands, not finished yet
unc0rr
parents: 8479
diff changeset
    60
        [em "TD"]
42d2565b5700 Converter from game parameters to engine commands, not finished yet
unc0rr
parents: 8479
diff changeset
    61
        , maybeScript
42d2565b5700 Converter from game parameters to engine commands, not finished yet
unc0rr
parents: 8479
diff changeset
    62
        , maybeMap
9304
3f4c3fc146c2 Fix spectator desync in rare conditions (there was team which left during its turn, and last command with timestamp from it was '+')
unc0rr
parents: 8541
diff changeset
    63
        , [eml ["etheme ", head $ prms Map.! "THEME"]]
3f4c3fc146c2 Fix spectator desync in rare conditions (there was team which left during its turn, and last command with timestamp from it was '+')
unc0rr
parents: 8541
diff changeset
    64
        , [eml ["eseed ", mParams Map.! "SEED"]]
8480
42d2565b5700 Converter from game parameters to engine commands, not finished yet
unc0rr
parents: 8479
diff changeset
    65
        , [eml ["e$gmflags ", showB gameFlags]]
42d2565b5700 Converter from game parameters to engine commands, not finished yet
unc0rr
parents: 8479
diff changeset
    66
        , schemeFlags
9304
3f4c3fc146c2 Fix spectator desync in rare conditions (there was team which left during its turn, and last command with timestamp from it was '+')
unc0rr
parents: 8541
diff changeset
    67
        , [eml ["e$template_filter ", mParams Map.! "TEMPLATE"]]
8481
692ff6468b63 - Handle mapgen-specific parameters
unc0rr
parents: 8480
diff changeset
    68
        , [eml ["e$mapgen ", mapgen]]
692ff6468b63 - Handle mapgen-specific parameters
unc0rr
parents: 8480
diff changeset
    69
        , mapgenSpecific
9304
3f4c3fc146c2 Fix spectator desync in rare conditions (there was team which left during its turn, and last command with timestamp from it was '+')
unc0rr
parents: 8541
diff changeset
    70
        , concatMap teamSetup ti
8480
42d2565b5700 Converter from game parameters to engine commands, not finished yet
unc0rr
parents: 8479
diff changeset
    71
        , msgs
8483
d5fd4d7a0bcc Also convert teams to complete game config.
unc0rr
parents: 8481
diff changeset
    72
        , [em "!"]
8480
42d2565b5700 Converter from game parameters to engine commands, not finished yet
unc0rr
parents: 8479
diff changeset
    73
        ]
42d2565b5700 Converter from game parameters to engine commands, not finished yet
unc0rr
parents: 8479
diff changeset
    74
    where
42d2565b5700 Converter from game parameters to engine commands, not finished yet
unc0rr
parents: 8479
diff changeset
    75
        em = toEngineMsg
42d2565b5700 Converter from game parameters to engine commands, not finished yet
unc0rr
parents: 8479
diff changeset
    76
        eml = em . B.concat
42d2565b5700 Converter from game parameters to engine commands, not finished yet
unc0rr
parents: 8479
diff changeset
    77
        mapGenTypes = ["+rnd+", "+maze+", "+drawn+"]
9690
6a1748b71df2 Handle absence of "SCRIPT" in replay
unc0rr
parents: 9401
diff changeset
    78
        maybeScript = let s = head . fromMaybe ["Normal"] $ Map.lookup "SCRIPT" prms in if s == "Normal" then [] else [eml ["escript Scripts/Multiplayer/", s, ".lua"]]
9304
3f4c3fc146c2 Fix spectator desync in rare conditions (there was team which left during its turn, and last command with timestamp from it was '+')
unc0rr
parents: 8541
diff changeset
    79
        maybeMap = let m = mParams Map.! "MAP" in if m `elem` mapGenTypes then [] else [eml ["emap ", m]]
3f4c3fc146c2 Fix spectator desync in rare conditions (there was team which left during its turn, and last command with timestamp from it was '+')
unc0rr
parents: 8541
diff changeset
    80
        scheme = tail $ prms Map.! "SCHEME"
3f4c3fc146c2 Fix spectator desync in rare conditions (there was team which left during its turn, and last command with timestamp from it was '+')
unc0rr
parents: 8541
diff changeset
    81
        mapgen = mParams Map.! "MAPGEN"
8481
692ff6468b63 - Handle mapgen-specific parameters
unc0rr
parents: 8480
diff changeset
    82
        mapgenSpecific = case mapgen of
9304
3f4c3fc146c2 Fix spectator desync in rare conditions (there was team which left during its turn, and last command with timestamp from it was '+')
unc0rr
parents: 8541
diff changeset
    83
            "+maze+" -> [eml ["e$maze_size ", head $ prms Map.! "MAZE_SIZE"]]
3f4c3fc146c2 Fix spectator desync in rare conditions (there was team which left during its turn, and last command with timestamp from it was '+')
unc0rr
parents: 8541
diff changeset
    84
            "+drawn" -> drawnMapData . head $ prms Map.! "DRAWNMAP"
8481
692ff6468b63 - Handle mapgen-specific parameters
unc0rr
parents: 8480
diff changeset
    85
            _ -> []
8480
42d2565b5700 Converter from game parameters to engine commands, not finished yet
unc0rr
parents: 8479
diff changeset
    86
        gameFlags :: Word32
42d2565b5700 Converter from game parameters to engine commands, not finished yet
unc0rr
parents: 8479
diff changeset
    87
        gameFlags = foldl (\r (b, f) -> if b == "false" then r else r .|. f) 0 $ zip scheme gameFlagConsts
42d2565b5700 Converter from game parameters to engine commands, not finished yet
unc0rr
parents: 8479
diff changeset
    88
        schemeFlags = map (\(v, (n, m)) -> eml [n, " ", showB $ (readInt_ v) * m])
42d2565b5700 Converter from game parameters to engine commands, not finished yet
unc0rr
parents: 8479
diff changeset
    89
            $ filter (\(_, (n, _)) -> not $ B.null n)
42d2565b5700 Converter from game parameters to engine commands, not finished yet
unc0rr
parents: 8479
diff changeset
    90
            $ zip (drop (length gameFlagConsts) scheme) schemeParams
8481
692ff6468b63 - Handle mapgen-specific parameters
unc0rr
parents: 8480
diff changeset
    91
        ammoStr :: B.ByteString
9304
3f4c3fc146c2 Fix spectator desync in rare conditions (there was team which left during its turn, and last command with timestamp from it was '+')
unc0rr
parents: 8541
diff changeset
    92
        ammoStr = head . tail $ prms Map.! "AMMO"
8481
692ff6468b63 - Handle mapgen-specific parameters
unc0rr
parents: 8480
diff changeset
    93
        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
8483
d5fd4d7a0bcc Also convert teams to complete game config.
unc0rr
parents: 8481
diff changeset
    94
                   (map (\(x, y) -> eml [x, " ", y]) $ zip ["eammloadt", "eammprob", "eammdelay", "eammreinf"] [a, b, c, d])
d5fd4d7a0bcc Also convert teams to complete game config.
unc0rr
parents: 8481
diff changeset
    95
                   ++ [em "eammstore" | scheme !! 14 == "true" || scheme !! 20 == "false"]
d5fd4d7a0bcc Also convert teams to complete game config.
unc0rr
parents: 8481
diff changeset
    96
        initHealth = scheme !! 27
8481
692ff6468b63 - Handle mapgen-specific parameters
unc0rr
parents: 8480
diff changeset
    97
        teamSetup :: TeamInfo -> [B.ByteString]
8499
da5394a3eb0e - Add forgotten ammo definitions
unc0rr
parents: 8496
diff changeset
    98
        teamSetup t = (++) ammo $
8541
0cd63b963330 Try to prevent hedgehogs number in team desync
unc0rr
parents: 8527
diff changeset
    99
                eml ["eaddteam <hash> ", showB $ (1 + (readInt_ $ teamcolor t) :: Int) * 2113696, " ", teamname t]
8483
d5fd4d7a0bcc Also convert teams to complete game config.
unc0rr
parents: 8481
diff changeset
   100
                : em "erdriven"
d5fd4d7a0bcc Also convert teams to complete game config.
unc0rr
parents: 8481
diff changeset
   101
                : eml ["efort ", teamfort t]
8527
bf671ddf467c Fix stupid mistake which made checker desync almost always
unc0rr
parents: 8506
diff changeset
   102
                : take (2 * hhnum t) (
8503
e60c84b42f4d Pass hogs names and hats
unc0rr
parents: 8499
diff changeset
   103
                    concatMap (\(HedgehogInfo hname hhat) -> [
e60c84b42f4d Pass hogs names and hats
unc0rr
parents: 8499
diff changeset
   104
                            eml ["eaddhh ", showB $ difficulty t, " ", initHealth, " ", hname]
e60c84b42f4d Pass hogs names and hats
unc0rr
parents: 8499
diff changeset
   105
                            , eml ["ehat ", hhat]
e60c84b42f4d Pass hogs names and hats
unc0rr
parents: 8499
diff changeset
   106
                            ])
e60c84b42f4d Pass hogs names and hats
unc0rr
parents: 8499
diff changeset
   107
                        $ hedgehogs t
e60c84b42f4d Pass hogs names and hats
unc0rr
parents: 8499
diff changeset
   108
                        )
8480
42d2565b5700 Converter from game parameters to engine commands, not finished yet
unc0rr
parents: 8479
diff changeset
   109
8481
692ff6468b63 - Handle mapgen-specific parameters
unc0rr
parents: 8480
diff changeset
   110
drawnMapData :: B.ByteString -> [B.ByteString]
8483
d5fd4d7a0bcc Also convert teams to complete game config.
unc0rr
parents: 8481
diff changeset
   111
drawnMapData = error "drawnMapData"
8480
42d2565b5700 Converter from game parameters to engine commands, not finished yet
unc0rr
parents: 8479
diff changeset
   112
42d2565b5700 Converter from game parameters to engine commands, not finished yet
unc0rr
parents: 8479
diff changeset
   113
schemeParams :: [(B.ByteString, Int)]
42d2565b5700 Converter from game parameters to engine commands, not finished yet
unc0rr
parents: 8479
diff changeset
   114
schemeParams = [
42d2565b5700 Converter from game parameters to engine commands, not finished yet
unc0rr
parents: 8479
diff changeset
   115
      ("e$damagepct", 1)
42d2565b5700 Converter from game parameters to engine commands, not finished yet
unc0rr
parents: 8479
diff changeset
   116
    , ("e$turntime", 1000)
42d2565b5700 Converter from game parameters to engine commands, not finished yet
unc0rr
parents: 8479
diff changeset
   117
    , ("", 0)
42d2565b5700 Converter from game parameters to engine commands, not finished yet
unc0rr
parents: 8479
diff changeset
   118
    , ("e$sd_turns", 1)
42d2565b5700 Converter from game parameters to engine commands, not finished yet
unc0rr
parents: 8479
diff changeset
   119
    , ("e$casefreq", 1)
42d2565b5700 Converter from game parameters to engine commands, not finished yet
unc0rr
parents: 8479
diff changeset
   120
    , ("e$minestime", 1000)
42d2565b5700 Converter from game parameters to engine commands, not finished yet
unc0rr
parents: 8479
diff changeset
   121
    , ("e$minesnum", 1)
42d2565b5700 Converter from game parameters to engine commands, not finished yet
unc0rr
parents: 8479
diff changeset
   122
    , ("e$minedudpct", 1)
42d2565b5700 Converter from game parameters to engine commands, not finished yet
unc0rr
parents: 8479
diff changeset
   123
    , ("e$explosives", 1)
42d2565b5700 Converter from game parameters to engine commands, not finished yet
unc0rr
parents: 8479
diff changeset
   124
    , ("e$healthprob", 1)
42d2565b5700 Converter from game parameters to engine commands, not finished yet
unc0rr
parents: 8479
diff changeset
   125
    , ("e$hcaseamount", 1)
42d2565b5700 Converter from game parameters to engine commands, not finished yet
unc0rr
parents: 8479
diff changeset
   126
    , ("e$waterrise", 1)
42d2565b5700 Converter from game parameters to engine commands, not finished yet
unc0rr
parents: 8479
diff changeset
   127
    , ("e$healthdec", 1)
42d2565b5700 Converter from game parameters to engine commands, not finished yet
unc0rr
parents: 8479
diff changeset
   128
    , ("e$ropepct", 1)
42d2565b5700 Converter from game parameters to engine commands, not finished yet
unc0rr
parents: 8479
diff changeset
   129
    , ("e$getawaytime", 1)
42d2565b5700 Converter from game parameters to engine commands, not finished yet
unc0rr
parents: 8479
diff changeset
   130
    ]
42d2565b5700 Converter from game parameters to engine commands, not finished yet
unc0rr
parents: 8479
diff changeset
   131
42d2565b5700 Converter from game parameters to engine commands, not finished yet
unc0rr
parents: 8479
diff changeset
   132
42d2565b5700 Converter from game parameters to engine commands, not finished yet
unc0rr
parents: 8479
diff changeset
   133
gameFlagConsts :: [Word32]
42d2565b5700 Converter from game parameters to engine commands, not finished yet
unc0rr
parents: 8479
diff changeset
   134
gameFlagConsts = [
42d2565b5700 Converter from game parameters to engine commands, not finished yet
unc0rr
parents: 8479
diff changeset
   135
          0x00001000
42d2565b5700 Converter from game parameters to engine commands, not finished yet
unc0rr
parents: 8479
diff changeset
   136
        , 0x00000010
42d2565b5700 Converter from game parameters to engine commands, not finished yet
unc0rr
parents: 8479
diff changeset
   137
        , 0x00000004
42d2565b5700 Converter from game parameters to engine commands, not finished yet
unc0rr
parents: 8479
diff changeset
   138
        , 0x00000008
42d2565b5700 Converter from game parameters to engine commands, not finished yet
unc0rr
parents: 8479
diff changeset
   139
        , 0x00000020
42d2565b5700 Converter from game parameters to engine commands, not finished yet
unc0rr
parents: 8479
diff changeset
   140
        , 0x00000040
42d2565b5700 Converter from game parameters to engine commands, not finished yet
unc0rr
parents: 8479
diff changeset
   141
        , 0x00000080
42d2565b5700 Converter from game parameters to engine commands, not finished yet
unc0rr
parents: 8479
diff changeset
   142
        , 0x00000100
42d2565b5700 Converter from game parameters to engine commands, not finished yet
unc0rr
parents: 8479
diff changeset
   143
        , 0x00000200
42d2565b5700 Converter from game parameters to engine commands, not finished yet
unc0rr
parents: 8479
diff changeset
   144
        , 0x00000400
42d2565b5700 Converter from game parameters to engine commands, not finished yet
unc0rr
parents: 8479
diff changeset
   145
        , 0x00000800
42d2565b5700 Converter from game parameters to engine commands, not finished yet
unc0rr
parents: 8479
diff changeset
   146
        , 0x00002000
42d2565b5700 Converter from game parameters to engine commands, not finished yet
unc0rr
parents: 8479
diff changeset
   147
        , 0x00004000
42d2565b5700 Converter from game parameters to engine commands, not finished yet
unc0rr
parents: 8479
diff changeset
   148
        , 0x00008000
42d2565b5700 Converter from game parameters to engine commands, not finished yet
unc0rr
parents: 8479
diff changeset
   149
        , 0x00010000
42d2565b5700 Converter from game parameters to engine commands, not finished yet
unc0rr
parents: 8479
diff changeset
   150
        , 0x00020000
42d2565b5700 Converter from game parameters to engine commands, not finished yet
unc0rr
parents: 8479
diff changeset
   151
        , 0x00040000
42d2565b5700 Converter from game parameters to engine commands, not finished yet
unc0rr
parents: 8479
diff changeset
   152
        , 0x00080000
42d2565b5700 Converter from game parameters to engine commands, not finished yet
unc0rr
parents: 8479
diff changeset
   153
        , 0x00100000
42d2565b5700 Converter from game parameters to engine commands, not finished yet
unc0rr
parents: 8479
diff changeset
   154
        , 0x00200000
42d2565b5700 Converter from game parameters to engine commands, not finished yet
unc0rr
parents: 8479
diff changeset
   155
        , 0x00400000
42d2565b5700 Converter from game parameters to engine commands, not finished yet
unc0rr
parents: 8479
diff changeset
   156
        , 0x00800000
42d2565b5700 Converter from game parameters to engine commands, not finished yet
unc0rr
parents: 8479
diff changeset
   157
        , 0x01000000
42d2565b5700 Converter from game parameters to engine commands, not finished yet
unc0rr
parents: 8479
diff changeset
   158
        , 0x02000000
42d2565b5700 Converter from game parameters to engine commands, not finished yet
unc0rr
parents: 8479
diff changeset
   159
        , 0x04000000
42d2565b5700 Converter from game parameters to engine commands, not finished yet
unc0rr
parents: 8479
diff changeset
   160
        ]
8479
8d71109b04d2 Some work on loading replay and interaction with checker
unc0rr
parents: 7766
diff changeset
   161
8d71109b04d2 Some work on loading replay and interaction with checker
unc0rr
parents: 7766
diff changeset
   162
8d71109b04d2 Some work on loading replay and interaction with checker
unc0rr
parents: 7766
diff changeset
   163