module Data.Time.Zones.Read (
loadTZFromFile,
loadSystemTZ,
loadLocalTZ,
loadTZFromDB,
olsonGet,
) where
import Control.Applicative
import Control.Monad (unless)
import Data.Binary
import Data.Binary.Get
import qualified Data.ByteString.Char8 as BS
import qualified Data.ByteString.Lazy.Char8 as BL
import Data.Maybe
import Data.Vector.Generic (stream, unstream)
import qualified Data.Vector.Unboxed as VU
import qualified Data.Vector as VB
import Data.Int
import Data.Time.Zones.Types
import System.Environment
import System.IO.Error
import Paths_tz hiding (version)
loadTZFromFile :: FilePath -> IO TZ
loadTZFromFile fname = runGet olsonGet <$> BL.readFile fname
loadSystemTZ :: String -> IO TZ
loadSystemTZ tzName = do
dir <- fromMaybe "/usr/share/zoneinfo" <$> getEnvMaybe "TZDIR"
loadTZFromFile $ dir ++ "/" ++ tzName
loadLocalTZ :: IO TZ
loadLocalTZ = do
tzEnv <- getEnvMaybe "TZ"
case tzEnv of
Nothing -> loadTZFromFile "/etc/localtime"
Just "" -> loadSystemTZ "UTC"
Just z -> loadSystemTZ z
getEnvMaybe :: String -> IO (Maybe String)
getEnvMaybe var =
fmap Just (getEnv var) `catchIOError`
(\e -> if isDoesNotExistError e then return Nothing else ioError e)
loadTZFromDB :: String -> IO TZ
loadTZFromDB tzName = do
fn <- getDataFileName $ tzName ++ ".zone"
loadTZFromFile fn
olsonGet :: Get TZ
olsonGet = do
version <- olsonHeader
case () of
() | version == '\0' -> olsonGetWith 4 getTime32
() | version `elem` ['2', '3'] -> do
skipOlson0
_ <- olsonHeader
olsonGetWith 8 getTime64
_ -> fail $ "olsonGet: invalid version character: " ++ show version
olsonHeader :: Get Char
olsonHeader = do
magic <- getByteString 4
unless (magic == "TZif") $ fail "olsonHeader: bad magic"
version <- toEnum <$> getInt8
skip 15
return version
skipOlson0 :: Get ()
skipOlson0 = do
tzh_ttisgmtcnt <- getInt32
tzh_ttisstdcnt <- getInt32
tzh_leapcnt <- getInt32
tzh_timecnt <- getInt32
tzh_typecnt <- getInt32
tzh_charcnt <- getInt32
skip $ (4 * tzh_timecnt) + tzh_timecnt + (6 * tzh_typecnt) + tzh_charcnt +
(8 * tzh_leapcnt) + tzh_ttisstdcnt + tzh_ttisgmtcnt
olsonGetWith :: Int -> Get Int64 -> Get TZ
olsonGetWith szTime getTime = do
tzh_ttisgmtcnt <- getInt32
tzh_ttisstdcnt <- getInt32
tzh_leapcnt <- getInt32
tzh_timecnt <- getInt32
tzh_typecnt <- getInt32
tzh_charcnt <- getInt32
transitions <- VU.replicateM tzh_timecnt getTime
indices <- VU.replicateM tzh_timecnt getInt8
infos <- VU.replicateM tzh_typecnt getTTInfo
abbrs <- getByteString tzh_charcnt
skip $ tzh_leapcnt * (szTime + 4)
skip tzh_ttisstdcnt
skip tzh_ttisgmtcnt
let isDst (_,x,_) = x
gmtOff (x,_,_) = x
isDstName (_,d,ni) = (d, abbrForInd ni abbrs)
lInfos = VU.toList infos
first = head $ filter (not . isDst) lInfos ++ lInfos
vtrans = VU.cons minBound transitions
eInfos = VU.cons first $ VU.map (infos VU.!) indices
vdiffs = VU.map gmtOff eInfos
vinfos = VB.map isDstName $ unstream $ stream eInfos
return $ TZ vtrans vdiffs vinfos
abbrForInd :: Int -> BS.ByteString -> String
abbrForInd i = BS.unpack . BS.takeWhile (/= '\0') . BS.drop i
getTTInfo :: Get (Int, Bool, Int)
getTTInfo = (,,) <$> getInt32 <*> get <*> getInt8
getInt8 :: Get Int
getInt8 = fromIntegral <$> getWord8
getInt32 :: Get Int
getInt32 = (fromIntegral :: Int32 -> Int) . fromIntegral <$> getWord32be
getTime32 :: Get Int64
getTime32 = fromIntegral <$> getInt32
getTime64 :: Get Int64
getTime64 = fromIntegral <$> getWord64be