module Game.LambdaHack.Common.Save
( ChanSave, saveToChan, wrapInSaves, restoreGame, saveNameCli, saveNameSer
, compatibleVersion
#ifdef EXPOSE_INTERNAL
, loopSave, delayPrint
#endif
) where
import Prelude ()
import Game.LambdaHack.Core.Prelude
import Control.Concurrent
import Control.Concurrent.Async
import qualified Control.Exception as Ex
import Data.Binary
import Data.Text (Text)
import qualified Data.Text as T
import qualified Data.Text.IO as T
import Data.Version
import System.FilePath
import System.IO (hFlush, stdout)
import qualified System.Random as R
import Game.LambdaHack.Common.File
import Game.LambdaHack.Common.Kind
import Game.LambdaHack.Common.Misc
import Game.LambdaHack.Common.Types
import Game.LambdaHack.Content.RuleKind
type ChanSave a = MVar (Maybe a)
saveToChan :: ChanSave a -> a -> IO ()
saveToChan toSave s = do
void $ tryTakeMVar toSave
putMVar toSave $ Just s
loopSave :: Binary a => COps -> (a -> FilePath) -> ChanSave a -> IO ()
loopSave cops stateToFileName toSave =
loop
where
loop = do
ms <- takeMVar toSave
case ms of
Just s -> do
dataDir <- appDataDir
tryCreateDir (dataDir </> "saves")
let fileName = stateToFileName s
yield
encodeEOF (dataDir </> "saves" </> fileName)
(rexeVersion $ corule cops)
s
loop
Nothing -> return ()
wrapInSaves :: Binary a
=> COps -> (a -> FilePath) -> (ChanSave a -> IO ()) -> IO ()
{-# INLINE wrapInSaves #-}
wrapInSaves cops stateToFileName exe = do
toSave <- newEmptyMVar
a <- async $ loopSave cops stateToFileName toSave
link a
let fin = do
putMVar toSave Nothing
threadDelay 500000
wait a
exe toSave `Ex.finally` fin
restoreGame :: Binary a => COps -> FilePath -> IO (Maybe a)
restoreGame cops fileName = do
dataDir <- appDataDir
tryCreateDir dataDir
let path bkp = dataDir </> "saves" </> bkp <> fileName
saveExists <- doesFileExist (path "")
res <- Ex.try $
if saveExists then do
let vExe1 = rexeVersion $ corule cops
(vExe2, s) <- strictDecodeEOF (path "")
if compatibleVersion vExe1 vExe2
then return $ Just s
else do
let msg = "Savefile" <+> T.pack (path "")
<+> "from an incompatible version"
<+> T.pack (showVersion vExe2)
<+> "detected while trying to restore"
<+> T.pack (showVersion vExe1)
<+> "game."
fail $ T.unpack msg
else return Nothing
let handler :: Ex.SomeException -> IO (Maybe a)
handler e = do
let msg = "Restore failed. The old file moved aside. The error message is:"
<+> (T.unwords . T.lines) (tshow e)
delayPrint msg
renameFile (path "") (path "bkp.")
return Nothing
either handler return res
compatibleVersion :: Version -> Version -> Bool
compatibleVersion v1 v2 = take 3 (versionBranch v1) == take 3 (versionBranch v2)
delayPrint :: Text -> IO ()
delayPrint t = do
delay <- R.randomRIO (0, 1000000)
threadDelay delay
T.hPutStrLn stdout t
hFlush stdout
saveNameCli :: COps -> FactionId -> String
saveNameCli COps{corule} side =
let gameShortName =
case T.words $ rtitle corule of
w : _ -> T.unpack w
_ -> "Game"
n = fromEnum side
in gameShortName
++ (if n > 0
then ".human_" ++ show n
else ".computer_" ++ show (-n))
++ ".sav"
saveNameSer :: COps -> String
saveNameSer COps{corule} =
let gameShortName =
case T.words $ rtitle corule of
w : _ -> T.unpack w
_ -> "Game"
in gameShortName ++ ".server.sav"