module Game.LambdaHack.Common.HSFile
( encodeEOF, strictDecodeEOF
, tryCreateDir, doesFileExist, tryWriteFile, readFile, renameFile
#ifdef EXPOSE_INTERNAL
, encodeData
#endif
) where
import Prelude ()
import Game.LambdaHack.Common.Prelude
import qualified Codec.Compression.Zlib as Z
import qualified Control.Exception as Ex
import Data.Binary
import qualified Data.ByteString.Lazy as LBS
import System.Directory
import System.FilePath
import System.IO (IOMode (..), hClose, openBinaryFile, readFile,
withBinaryFile, writeFile)
encodeData :: Binary a => FilePath -> a -> IO ()
encodeData path a = do
let tmpPath = path <.> "tmp"
Ex.bracketOnError
(openBinaryFile tmpPath WriteMode)
(\h -> hClose h >> removeFile tmpPath)
(\h -> do
LBS.hPut h . Z.compress . encode $ a
hClose h
renameFile tmpPath path
)
encodeEOF :: Binary a => FilePath -> a -> IO ()
encodeEOF path a = encodeData path (a, "OK" :: String)
strictDecodeEOF :: Binary a => FilePath -> IO a
strictDecodeEOF path =
withBinaryFile path ReadMode $ \h -> do
c <- LBS.hGetContents h
let (a, n) = decode $ Z.decompress c
if n == ("OK" :: String)
then return $! a
else fail $ "Fatal error: corrupted file " ++ path
tryCreateDir :: FilePath -> IO ()
tryCreateDir dir = do
dirExists <- doesDirectoryExist dir
unless dirExists $
Ex.handle (\(_ :: Ex.IOException) -> return ())
(createDirectory dir)
tryWriteFile :: FilePath -> String -> IO ()
tryWriteFile path content = do
fileExists <- doesFileExist path
unless fileExists $
Ex.handle (\(_ :: Ex.IOException) -> return ())
(writeFile path content)