module Data.Time.LocalTime.TimeZone
(
TimeZone(..),timeZoneOffsetString,minutesToTimeZone,hoursToTimeZone,utc,
getTimeZone,getCurrentTimeZone
) where
import Data.Time.Calendar.Private
import Data.Time.Clock
import Data.Time.Clock.POSIX
import Foreign
import Foreign.C
data TimeZone = TimeZone {
timeZoneMinutes :: Int,
timeZoneSummerOnly :: Bool,
timeZoneName :: String
} deriving (Eq,Ord)
minutesToTimeZone :: Int -> TimeZone
minutesToTimeZone m = TimeZone m False ""
hoursToTimeZone :: Int -> TimeZone
hoursToTimeZone i = minutesToTimeZone (60 * i)
showT :: Int -> String
showT t = (show2 (div t 60)) ++ (show2 (mod t 60))
timeZoneOffsetString :: TimeZone -> String
timeZoneOffsetString (TimeZone t _ _) | t < 0 = '-':(showT (negate t))
timeZoneOffsetString (TimeZone t _ _) = '+':(showT t)
instance Show TimeZone where
show zone@(TimeZone _ _ "") = timeZoneOffsetString zone
show (TimeZone _ _ name) = name
utc :: TimeZone
utc = TimeZone 0 False "UTC"
foreign import ccall unsafe "HsTime.h get_current_timezone_seconds" get_current_timezone_seconds :: CTime -> Ptr CInt -> Ptr CString -> IO CLong
posixToCTime :: POSIXTime -> CTime
posixToCTime = fromInteger . floor
getTimeZone :: UTCTime -> IO TimeZone
getTimeZone time = with 0 (\pdst -> with nullPtr (\pcname -> do
secs <- get_current_timezone_seconds (posixToCTime (utcTimeToPOSIXSeconds time)) pdst pcname
case secs of
0x80000000 -> fail "localtime_r failed"
_ -> do
dst <- peek pdst
cname <- peek pcname
name <- peekCString cname
return (TimeZone (div (fromIntegral secs) 60) (dst == 1) name)
))
getCurrentTimeZone :: IO TimeZone
getCurrentTimeZone = getCurrentTime >>= getTimeZone