gameServer/OfficialServer/GameReplayStore.hs
changeset 11246 09a2d3988569
parent 11046 47a8c19ecb60
child 11320 556eafd1443a
equal deleted inserted replaced
11243:d9622394ec9c 11246:09a2d3988569
    14  * You should have received a copy of the GNU General Public License
    14  * You should have received a copy of the GNU General Public License
    15  * along with this program; if not, write to the Free Software
    15  * along with this program; if not, write to the Free Software
    16  * Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301 USA.
    16  * Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301 USA.
    17  \-}
    17  \-}
    18 
    18 
    19 {-# LANGUAGE ScopedTypeVariables #-}
    19 {-# LANGUAGE ScopedTypeVariables, OverloadedStrings #-}
    20 module OfficialServer.GameReplayStore where
    20 module OfficialServer.GameReplayStore where
    21 
    21 
    22 import Data.Time
    22 import Data.Time
    23 import Control.Exception as E
    23 import Control.Exception as E
    24 import qualified Data.Map as Map
    24 import qualified Data.Map as Map
    68         else
    68         else
    69         return (Nothing, [])
    69         return (Nothing, [])
    70     where
    70     where
    71         loadFile :: String -> IO (Maybe CheckInfo, [B.ByteString])
    71         loadFile :: String -> IO (Maybe CheckInfo, [B.ByteString])
    72         loadFile fileName = E.handle (\(e :: SomeException) ->
    72         loadFile fileName = E.handle (\(e :: SomeException) ->
    73                     warningM "REPLAYS" ("Problems reading " ++ fileName ++ ": " ++ show e) >> return (Just $ CheckInfo fileName [], [])) $ do
    73                     warningM "REPLAYS" ("Problems reading " ++ fileName ++ ": " ++ show e) >> return (Just $ CheckInfo fileName [] "", [])) $ do
    74             (teams, params1, params2, roundMsgs) <- liftM read $ readFile fileName
    74             (teams, params1, params2, roundMsgs) <- liftM read $ readFile fileName
    75             return $ (
    75             let d = replayToDemo teams (Map.fromList params1) (Map.fromList params2) (reverse roundMsgs)
    76                 Just (CheckInfo fileName teams)
    76             d `deepseq` return $ (
    77                 , let d = replayToDemo teams (Map.fromList params1) (Map.fromList params2) (reverse roundMsgs) in d `deepseq` d
    77                 Just (CheckInfo fileName teams (head $ fst d))
       
    78                 , snd d
    78                 )
    79                 )
    79 
    80 
    80 moveFailedRecord :: String -> IO ()
    81 moveFailedRecord :: String -> IO ()
    81 moveFailedRecord fn = E.handle (\(e :: SomeException) -> warningM "REPLAYS" $ show e) $
    82 moveFailedRecord fn = E.handle (\(e :: SomeException) -> warningM "REPLAYS" $ show e) $
    82     renameFile fn ("failed/" ++ drop 8 fn)
    83     renameFile fn ("failed/" ++ drop 8 fn)