module Data.HodaTime.Offset.Internal
(
Offset(..)
,maxOffsetHours
,maxOffsetSeconds
,minOffsetSeconds
,empty
,toStringRep
,fromSeconds
,adjustInstant
,addClamped
,minusClamped
)
where
import Data.HodaTime.Instant.Internal (Instant, add, minus)
import qualified Data.HodaTime.Duration.Internal as D (fromSeconds)
import Data.HodaTime.Constants (secondsPerHour)
import Data.HodaTime.Internal (secondsFromSeconds, clamp)
newtype Offset = Offset { Offset -> Int
offsetSeconds :: Int }
deriving (Offset -> Offset -> Bool
(Offset -> Offset -> Bool)
-> (Offset -> Offset -> Bool) -> Eq Offset
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Offset -> Offset -> Bool
== :: Offset -> Offset -> Bool
$c/= :: Offset -> Offset -> Bool
/= :: Offset -> Offset -> Bool
Eq, Eq Offset
Eq Offset =>
(Offset -> Offset -> Ordering)
-> (Offset -> Offset -> Bool)
-> (Offset -> Offset -> Bool)
-> (Offset -> Offset -> Bool)
-> (Offset -> Offset -> Bool)
-> (Offset -> Offset -> Offset)
-> (Offset -> Offset -> Offset)
-> Ord Offset
Offset -> Offset -> Bool
Offset -> Offset -> Ordering
Offset -> Offset -> Offset
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
$ccompare :: Offset -> Offset -> Ordering
compare :: Offset -> Offset -> Ordering
$c< :: Offset -> Offset -> Bool
< :: Offset -> Offset -> Bool
$c<= :: Offset -> Offset -> Bool
<= :: Offset -> Offset -> Bool
$c> :: Offset -> Offset -> Bool
> :: Offset -> Offset -> Bool
$c>= :: Offset -> Offset -> Bool
>= :: Offset -> Offset -> Bool
$cmax :: Offset -> Offset -> Offset
max :: Offset -> Offset -> Offset
$cmin :: Offset -> Offset -> Offset
min :: Offset -> Offset -> Offset
Ord, Int -> Offset -> ShowS
[Offset] -> ShowS
Offset -> String
(Int -> Offset -> ShowS)
-> (Offset -> String) -> ([Offset] -> ShowS) -> Show Offset
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Offset -> ShowS
showsPrec :: Int -> Offset -> ShowS
$cshow :: Offset -> String
show :: Offset -> String
$cshowList :: [Offset] -> ShowS
showList :: [Offset] -> ShowS
Show)
maxOffsetHours :: Num a => a
maxOffsetHours :: forall a. Num a => a
maxOffsetHours = a
18
maxOffsetSeconds :: Num a => a
maxOffsetSeconds :: forall a. Num a => a
maxOffsetSeconds = a
forall a. Num a => a
maxOffsetHours a -> a -> a
forall a. Num a => a -> a -> a
* a
forall a. Num a => a
secondsPerHour
minOffsetSeconds :: Num a => a
minOffsetSeconds :: forall a. Num a => a
minOffsetSeconds = a -> a
forall a. Num a => a -> a
negate a
forall a. Num a => a
maxOffsetSeconds
empty :: Offset
empty :: Offset
empty = Int -> Offset
Offset Int
0
toStringRep :: Offset -> String
toStringRep :: Offset -> String
toStringRep (Offset Int
secs) = String
rep
where
utc :: String
utc = String
"UTC"
rep :: String
rep = if Int
secs Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
0 then String
utc else String
utc String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
sign String -> ShowS
forall a. [a] -> [a] -> [a]
++ Int -> String
forall a. Show a => a -> String
show Int
h String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
":" String -> ShowS
forall a. [a] -> [a] -> [a]
++ Int -> String
forall a. Show a => a -> String
show Int
s
sign :: String
sign = if Int
secs Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
0 then String
"-" else String
"+"
h :: Int
h = Int
secs Int -> Int -> Int
forall a. Integral a => a -> a -> a
`div` Int
forall a. Num a => a
secondsPerHour
s :: Int
s = Int
secs Int -> Int -> Int
forall a. Num a => a -> a -> a
- (Int
hInt -> Int -> Int
forall a. Num a => a -> a -> a
*Int
forall a. Num a => a
secondsPerHour)
fromSeconds :: Integral a => a -> Offset
fromSeconds :: forall a. Integral a => a -> Offset
fromSeconds = Int -> Offset
Offset (Int -> Offset) -> (a -> Int) -> a -> Offset
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> Int
forall a b. (Integral a, Num b) => a -> b
secondsFromSeconds (a -> Int) -> (a -> a) -> a -> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> a -> a -> a
forall a. Ord a => a -> a -> a -> a
clamp a
forall a. Num a => a
minOffsetSeconds a
forall a. Num a => a
maxOffsetSeconds
addClamped :: Offset -> Offset -> Offset
addClamped :: Offset -> Offset -> Offset
addClamped (Offset Int
lsecs) (Offset Int
rsecs) = Int -> Offset
forall a. Integral a => a -> Offset
fromSeconds (Int -> Offset) -> Int -> Offset
forall a b. (a -> b) -> a -> b
$ Int
lsecs Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
rsecs
minusClamped :: Offset -> Offset -> Offset
minusClamped :: Offset -> Offset -> Offset
minusClamped (Offset Int
lsecs) (Offset Int
rsecs) = Int -> Offset
forall a. Integral a => a -> Offset
fromSeconds (Int -> Offset) -> Int -> Offset
forall a b. (a -> b) -> a -> b
$ Int
lsecs Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
rsecs
adjustInstant :: Offset -> Instant -> Instant
adjustInstant :: Offset -> Instant -> Instant
adjustInstant (Offset Int
secs) Instant
instant = Instant
instant'
where
op :: Instant -> Duration -> Instant
op = if Int
secs Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
0 then Instant -> Duration -> Instant
minus else Instant -> Duration -> Instant
add
duration :: Duration
duration = Int -> Duration
D.fromSeconds (Int -> Duration) -> (Int -> Int) -> Int -> Duration
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> Int
forall a. Num a => a -> a
abs (Int -> Duration) -> Int -> Duration
forall a b. (a -> b) -> a -> b
$ Int
secs
instant' :: Instant
instant' = Instant
instant Instant -> Duration -> Instant
`op` Duration
duration