module Data.Gettext.GmoFile
(
GmoFile (..),
parseGmo
) where
import Control.Monad
import Data.Binary
import Data.Binary.Get
import qualified Data.ByteString.Lazy as L
import Text.Printf
data GmoFile = GmoFile {
fMagic :: Word32
, fRevision :: Word32
, fSize :: Word32
, fOriginalOffset :: Word32
, fTranslationOffset :: Word32
, fHashtableSize :: Word32
, fHashtableOffset :: Word32
, fOriginals :: [(Word32, Word32)]
, fTranslations :: [(Word32, Word32)]
, fData :: L.ByteString
}
deriving (Eq)
instance Show GmoFile where
show f = printf "<GetText file size=%d>" (fSize f)
parseGmo :: Get GmoFile
parseGmo = do
magic <- getWord32host
getWord32 <- case magic of
0x950412de -> return getWord32le
0xde120495 -> return getWord32be
_ -> fail "Invalid magic number"
let getPair :: Get (Word32, Word32)
getPair = do
x <- getWord32
y <- getWord32
return (x,y)
revision <- getWord32
size <- getWord32
origOffs <- getWord32
transOffs <- getWord32
hashSz <- getWord32
hashOffs <- getWord32
origs <- replicateM (fromIntegral size) getPair
trans <- replicateM (fromIntegral size) getPair
return $ GmoFile {
fMagic = magic,
fRevision = revision,
fSize = size,
fOriginalOffset = origOffs,
fTranslationOffset = transOffs,
fHashtableSize = hashSz,
fHashtableOffset = hashOffs,
fOriginals = origs,
fTranslations = trans,
fData = undefined }
withGmoFile :: FilePath -> (GmoFile -> IO a) -> IO a
withGmoFile path go = do
content <- L.readFile path
let gmo = (runGet parseGmo content) {fData = content}
result <- go gmo
return result