{-# OPTIONS -fno-warn-unused-imports #-}
{-# LANGUAGE ForeignFunctionInterface #-}
module Data.Time.LocalTime.Internal.TimeZone
(
TimeZone(..),timeZoneOffsetString,timeZoneOffsetString',timeZoneOffsetString'',minutesToTimeZone,hoursToTimeZone,utc,
getTimeZone,getCurrentTimeZone
) where
import Data.Time.Calendar.Private
import Data.Time.Clock.System
import Data.Time.Clock.POSIX
import Data.Time.Clock.Internal.UTCTime
#if __GLASGOW_HASKELL__ >= 709
import Foreign
#else
import Foreign.Safe
#endif
import Foreign.C
import Control.DeepSeq
import Data.Typeable
import Data.Data
data TimeZone = TimeZone {
TimeZone -> Int
timeZoneMinutes :: Int,
TimeZone -> Bool
timeZoneSummerOnly :: Bool,
TimeZone -> String
timeZoneName :: String
} deriving (TimeZone -> TimeZone -> Bool
(TimeZone -> TimeZone -> Bool)
-> (TimeZone -> TimeZone -> Bool) -> Eq TimeZone
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TimeZone -> TimeZone -> Bool
$c/= :: TimeZone -> TimeZone -> Bool
== :: TimeZone -> TimeZone -> Bool
$c== :: TimeZone -> TimeZone -> Bool
External instance of the constraint type Eq Char
External instance of the constraint type Eq Char
External instance of the constraint type forall a. Eq a => Eq [a]
External instance of the constraint type Eq Bool
External instance of the constraint type Eq Int
Eq,Eq TimeZone
Eq TimeZone
-> (TimeZone -> TimeZone -> Ordering)
-> (TimeZone -> TimeZone -> Bool)
-> (TimeZone -> TimeZone -> Bool)
-> (TimeZone -> TimeZone -> Bool)
-> (TimeZone -> TimeZone -> Bool)
-> (TimeZone -> TimeZone -> TimeZone)
-> (TimeZone -> TimeZone -> TimeZone)
-> Ord TimeZone
TimeZone -> TimeZone -> Bool
TimeZone -> TimeZone -> Ordering
TimeZone -> TimeZone -> TimeZone
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: TimeZone -> TimeZone -> TimeZone
$cmin :: TimeZone -> TimeZone -> TimeZone
max :: TimeZone -> TimeZone -> TimeZone
$cmax :: TimeZone -> TimeZone -> TimeZone
>= :: TimeZone -> TimeZone -> Bool
$c>= :: TimeZone -> TimeZone -> Bool
> :: TimeZone -> TimeZone -> Bool
$c> :: TimeZone -> TimeZone -> Bool
<= :: TimeZone -> TimeZone -> Bool
$c<= :: TimeZone -> TimeZone -> Bool
< :: TimeZone -> TimeZone -> Bool
$c< :: TimeZone -> TimeZone -> Bool
compare :: TimeZone -> TimeZone -> Ordering
$ccompare :: TimeZone -> TimeZone -> Ordering
External instance of the constraint type Ord Char
External instance of the constraint type Ord Char
External instance of the constraint type Ord Char
External instance of the constraint type forall a. Ord a => Ord [a]
External instance of the constraint type Ord Bool
Instance of class: Eq of the constraint type Eq TimeZone
External instance of the constraint type Ord Int
Instance of class: Ord of the constraint type Ord TimeZone
Instance of class: Eq of the constraint type Eq TimeZone
Ord,Typeable TimeZone
DataType
Constr
Typeable TimeZone
-> (forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> TimeZone -> c TimeZone)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c TimeZone)
-> (TimeZone -> Constr)
-> (TimeZone -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c TimeZone))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c TimeZone))
-> ((forall b. Data b => b -> b) -> TimeZone -> TimeZone)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> TimeZone -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> TimeZone -> r)
-> (forall u. (forall d. Data d => d -> u) -> TimeZone -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> TimeZone -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> TimeZone -> m TimeZone)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> TimeZone -> m TimeZone)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> TimeZone -> m TimeZone)
-> Data TimeZone
TimeZone -> DataType
TimeZone -> Constr
(forall b. Data b => b -> b) -> TimeZone -> TimeZone
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> TimeZone -> c TimeZone
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c TimeZone
forall a.
Typeable a
-> (forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> TimeZone -> u
forall u. (forall d. Data d => d -> u) -> TimeZone -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> TimeZone -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> TimeZone -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> TimeZone -> m TimeZone
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> TimeZone -> m TimeZone
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c TimeZone
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> TimeZone -> c TimeZone
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c TimeZone)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c TimeZone)
$cTimeZone :: Constr
$tTimeZone :: DataType
gmapMo :: (forall d. Data d => d -> m d) -> TimeZone -> m TimeZone
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> TimeZone -> m TimeZone
gmapMp :: (forall d. Data d => d -> m d) -> TimeZone -> m TimeZone
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> TimeZone -> m TimeZone
gmapM :: (forall d. Data d => d -> m d) -> TimeZone -> m TimeZone
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> TimeZone -> m TimeZone
gmapQi :: Int -> (forall d. Data d => d -> u) -> TimeZone -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> TimeZone -> u
gmapQ :: (forall d. Data d => d -> u) -> TimeZone -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> TimeZone -> [u]
gmapQr :: (r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> TimeZone -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> TimeZone -> r
gmapQl :: (r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> TimeZone -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> TimeZone -> r
gmapT :: (forall b. Data b => b -> b) -> TimeZone -> TimeZone
$cgmapT :: (forall b. Data b => b -> b) -> TimeZone -> TimeZone
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c TimeZone)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c TimeZone)
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c TimeZone)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c TimeZone)
dataTypeOf :: TimeZone -> DataType
$cdataTypeOf :: TimeZone -> DataType
toConstr :: TimeZone -> Constr
$ctoConstr :: TimeZone -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c TimeZone
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c TimeZone
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> TimeZone -> c TimeZone
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> TimeZone -> c TimeZone
External instance of the constraint type Data Char
External instance of the constraint type Data Char
External instance of the constraint type Data Int
External instance of the constraint type Data Bool
External instance of the constraint type Data Char
External instance of the constraint type forall a. Data a => Data [a]
Data, Typeable)
instance NFData TimeZone where
rnf :: TimeZone -> ()
rnf (TimeZone Int
m Bool
so String
n) = Int -> ()
forall a. NFData a => a -> ()
External instance of the constraint type NFData Int
rnf Int
m () -> () -> ()
`seq` Bool -> ()
forall a. NFData a => a -> ()
External instance of the constraint type NFData Bool
rnf Bool
so () -> () -> ()
`seq` String -> ()
forall a. NFData a => a -> ()
External instance of the constraint type forall a. NFData a => NFData [a]
External instance of the constraint type NFData Char
rnf String
n () -> () -> ()
`seq` ()
minutesToTimeZone :: Int -> TimeZone
minutesToTimeZone :: Int -> TimeZone
minutesToTimeZone Int
m = Int -> Bool -> String -> TimeZone
TimeZone Int
m Bool
False String
""
hoursToTimeZone :: Int -> TimeZone
hoursToTimeZone :: Int -> TimeZone
hoursToTimeZone Int
i = Int -> TimeZone
minutesToTimeZone (Int
60 Int -> Int -> Int
forall a. Num a => a -> a -> a
External instance of the constraint type Num Int
* Int
i)
showT :: Bool -> PadOption -> Int -> String
showT :: Bool -> PadOption -> Int -> String
showT Bool
False PadOption
opt Int
t = PadOption -> Int -> String
forall t. ShowPadded t => PadOption -> t -> String
External instance of the constraint type ShowPadded Int
showPaddedNum PadOption
opt ((Int -> Int -> Int
forall a. Integral a => a -> a -> a
External instance of the constraint type Integral Int
div Int
t Int
60) Int -> Int -> Int
forall a. Num a => a -> a -> a
External instance of the constraint type Num Int
* Int
100 Int -> Int -> Int
forall a. Num a => a -> a -> a
External instance of the constraint type Num Int
+ (Int -> Int -> Int
forall a. Integral a => a -> a -> a
External instance of the constraint type Integral Int
mod Int
t Int
60))
showT Bool
True PadOption
opt Int
t = let
opt' :: PadOption
opt' = case PadOption
opt of
PadOption
NoPad -> PadOption
NoPad
Pad Int
i Char
c -> Int -> Char -> PadOption
Pad (Int -> Int -> Int
forall a. Ord a => a -> a -> a
External instance of the constraint type Ord Int
max Int
0 (Int -> Int) -> Int -> Int
forall a b. (a -> b) -> a -> b
$ Int
i Int -> Int -> Int
forall a. Num a => a -> a -> a
External instance of the constraint type Num Int
- Int
3) Char
c
in PadOption -> Int -> String
forall t. ShowPadded t => PadOption -> t -> String
External instance of the constraint type ShowPadded Int
showPaddedNum PadOption
opt' (Int -> Int -> Int
forall a. Integral a => a -> a -> a
External instance of the constraint type Integral Int
div Int
t Int
60) String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
":" String -> String -> String
forall a. [a] -> [a] -> [a]
++ Int -> String
forall t. ShowPadded t => t -> String
External instance of the constraint type ShowPadded Int
show2 (Int -> Int -> Int
forall a. Integral a => a -> a -> a
External instance of the constraint type Integral Int
mod Int
t Int
60)
timeZoneOffsetString'' :: Bool -> PadOption -> TimeZone -> String
timeZoneOffsetString'' :: Bool -> PadOption -> TimeZone -> String
timeZoneOffsetString'' Bool
colon PadOption
opt (TimeZone Int
t Bool
_ String
_) | Int
t Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
External instance of the constraint type Ord Int
< Int
0 = Char
'-'Char -> String -> String
forall a. a -> [a] -> [a]
:(Bool -> PadOption -> Int -> String
showT Bool
colon PadOption
opt (Int -> Int
forall a. Num a => a -> a
External instance of the constraint type Num Int
negate Int
t))
timeZoneOffsetString'' Bool
colon PadOption
opt (TimeZone Int
t Bool
_ String
_) = Char
'+'Char -> String -> String
forall a. a -> [a] -> [a]
:(Bool -> PadOption -> Int -> String
showT Bool
colon PadOption
opt Int
t)
timeZoneOffsetString' :: Maybe Char -> TimeZone -> String
timeZoneOffsetString' :: Maybe Char -> TimeZone -> String
timeZoneOffsetString' Maybe Char
Nothing = Bool -> PadOption -> TimeZone -> String
timeZoneOffsetString'' Bool
False PadOption
NoPad
timeZoneOffsetString' (Just Char
c) = Bool -> PadOption -> TimeZone -> String
timeZoneOffsetString'' Bool
False (PadOption -> TimeZone -> String)
-> PadOption -> TimeZone -> String
forall a b. (a -> b) -> a -> b
$ Int -> Char -> PadOption
Pad Int
4 Char
c
timeZoneOffsetString :: TimeZone -> String
timeZoneOffsetString :: TimeZone -> String
timeZoneOffsetString = Bool -> PadOption -> TimeZone -> String
timeZoneOffsetString'' Bool
False (Int -> Char -> PadOption
Pad Int
4 Char
'0')
instance Show TimeZone where
show :: TimeZone -> String
show zone :: TimeZone
zone@(TimeZone Int
_ Bool
_ String
"") = TimeZone -> String
timeZoneOffsetString TimeZone
zone
show (TimeZone Int
_ Bool
_ String
name) = String
name
utc :: TimeZone
utc :: TimeZone
utc = Int -> Bool -> String -> TimeZone
TimeZone Int
0 Bool
False String
"UTC"
{-# CFILES cbits/HsTime.c #-}
foreign import ccall unsafe "HsTime.h get_current_timezone_seconds" get_current_timezone_seconds :: CTime -> Ptr CInt -> Ptr CString -> IO CLong
getTimeZoneCTime :: CTime -> IO TimeZone
getTimeZoneCTime :: CTime -> IO TimeZone
getTimeZoneCTime CTime
ctime = CInt -> (Ptr CInt -> IO TimeZone) -> IO TimeZone
forall a b. Storable a => a -> (Ptr a -> IO b) -> IO b
External instance of the constraint type Storable CInt
with CInt
0 (\Ptr CInt
pdst -> Ptr CChar -> (Ptr (Ptr CChar) -> IO TimeZone) -> IO TimeZone
forall a b. Storable a => a -> (Ptr a -> IO b) -> IO b
External instance of the constraint type forall a. Storable (Ptr a)
with Ptr CChar
forall a. Ptr a
nullPtr (\Ptr (Ptr CChar)
pcname -> do
CLong
secs <- CTime -> Ptr CInt -> Ptr (Ptr CChar) -> IO CLong
get_current_timezone_seconds CTime
ctime Ptr CInt
pdst Ptr (Ptr CChar)
pcname
case CLong
secs of
CLong
0x80000000 -> String -> IO TimeZone
forall (m :: * -> *) a. MonadFail m => String -> m a
External instance of the constraint type MonadFail IO
fail String
"localtime_r failed"
CLong
_ -> do
CInt
dst <- Ptr CInt -> IO CInt
forall a. Storable a => Ptr a -> IO a
External instance of the constraint type Storable CInt
peek Ptr CInt
pdst
Ptr CChar
cname <- Ptr (Ptr CChar) -> IO (Ptr CChar)
forall a. Storable a => Ptr a -> IO a
External instance of the constraint type forall a. Storable (Ptr a)
peek Ptr (Ptr CChar)
pcname
String
name <- Ptr CChar -> IO String
peekCString Ptr CChar
cname
TimeZone -> IO TimeZone
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type Monad IO
return (Int -> Bool -> String -> TimeZone
TimeZone (Int -> Int -> Int
forall a. Integral a => a -> a -> a
External instance of the constraint type Integral Int
div (CLong -> Int
forall a b. (Integral a, Num b) => a -> b
External instance of the constraint type Num Int
External instance of the constraint type Integral CLong
fromIntegral CLong
secs) Int
60) (CInt
dst CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
External instance of the constraint type Eq CInt
== CInt
1) String
name)
))
toCTime :: Int64 -> IO CTime
toCTime :: Int64 -> IO CTime
toCTime Int64
t = let
tt :: Int64
tt = Int64 -> Int64
forall a b. (Integral a, Num b) => a -> b
External instance of the constraint type Num Int64
External instance of the constraint type Integral Int64
fromIntegral Int64
t
t' :: Int64
t' = Int64 -> Int64
forall a b. (Integral a, Num b) => a -> b
External instance of the constraint type Num Int64
External instance of the constraint type Integral Int64
fromIntegral Int64
tt
in if Int64
t' Int64 -> Int64 -> Bool
forall a. Eq a => a -> a -> Bool
External instance of the constraint type Eq Int64
== Int64
t then CTime -> IO CTime
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type Monad IO
return (CTime -> IO CTime) -> CTime -> IO CTime
forall a b. (a -> b) -> a -> b
$ Int64 -> CTime
CTime Int64
tt else String -> IO CTime
forall (m :: * -> *) a. MonadFail m => String -> m a
External instance of the constraint type MonadFail IO
fail String
"Data.Time.LocalTime.Internal.TimeZone.toCTime: Overflow"
getTimeZoneSystem :: SystemTime -> IO TimeZone
getTimeZoneSystem :: SystemTime -> IO TimeZone
getTimeZoneSystem SystemTime
t = do
CTime
ctime <- Int64 -> IO CTime
toCTime (Int64 -> IO CTime) -> Int64 -> IO CTime
forall a b. (a -> b) -> a -> b
$ SystemTime -> Int64
systemSeconds SystemTime
t
CTime -> IO TimeZone
getTimeZoneCTime CTime
ctime
getTimeZone :: UTCTime -> IO TimeZone
getTimeZone :: UTCTime -> IO TimeZone
getTimeZone UTCTime
t = do
CTime
ctime <- Int64 -> IO CTime
toCTime (Int64 -> IO CTime) -> Int64 -> IO CTime
forall a b. (a -> b) -> a -> b
$ POSIXTime -> Int64
forall a b. (RealFrac a, Integral b) => a -> b
External instance of the constraint type Integral Int64
External instance of the constraint type RealFrac POSIXTime
floor (POSIXTime -> Int64) -> POSIXTime -> Int64
forall a b. (a -> b) -> a -> b
$ UTCTime -> POSIXTime
utcTimeToPOSIXSeconds UTCTime
t
CTime -> IO TimeZone
getTimeZoneCTime CTime
ctime
getCurrentTimeZone :: IO TimeZone
getCurrentTimeZone :: IO TimeZone
getCurrentTimeZone = IO SystemTime
getSystemTime IO SystemTime -> (SystemTime -> IO TimeZone) -> IO TimeZone
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
External instance of the constraint type Monad IO
>>= SystemTime -> IO TimeZone
getTimeZoneSystem