{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE TypeSynonymInstances #-}
module Data.Hourglass.Format
(
TimeFormatElem(..)
, TimeFormatFct(..)
, TimeFormatString(..)
, TimeFormat(..)
, ISO8601_Date(..)
, ISO8601_DateAndTime(..)
, timePrint
, timeParse
, timeParseE
, localTimePrint
, localTimeParse
, localTimeParseE
) where
import Data.Hourglass.Types
import Data.Hourglass.Time
import Data.Hourglass.Calendar
import Data.Hourglass.Local
import Data.Hourglass.Utils
import Data.Char (isDigit, ord)
import Data.Int
data TimeFormatElem =
Format_Year2
| Format_Year4
| Format_Year
| Format_Month
| Format_Month2
| Format_MonthName_Short
| Format_DayYear
| Format_Day
| Format_Day2
| Format_Hour
| Format_Minute
| Format_Second
| Format_UnixSecond
| Format_MilliSecond
| Format_MicroSecond
| Format_NanoSecond
| Format_Precision Int
| Format_TimezoneName
| Format_TzHM_Colon_Z
| Format_TzHM_Colon
| Format_TzHM
| Format_Tz_Offset
| Format_Spaces
| Format_Text Char
| Format_Fct TimeFormatFct
deriving (Int -> TimeFormatElem -> ShowS
[TimeFormatElem] -> ShowS
TimeFormatElem -> String
(Int -> TimeFormatElem -> ShowS)
-> (TimeFormatElem -> String)
-> ([TimeFormatElem] -> ShowS)
-> Show TimeFormatElem
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [TimeFormatElem] -> ShowS
$cshowList :: [TimeFormatElem] -> ShowS
show :: TimeFormatElem -> String
$cshow :: TimeFormatElem -> String
showsPrec :: Int -> TimeFormatElem -> ShowS
$cshowsPrec :: Int -> TimeFormatElem -> ShowS
Show,TimeFormatElem -> TimeFormatElem -> Bool
(TimeFormatElem -> TimeFormatElem -> Bool)
-> (TimeFormatElem -> TimeFormatElem -> Bool) -> Eq TimeFormatElem
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TimeFormatElem -> TimeFormatElem -> Bool
$c/= :: TimeFormatElem -> TimeFormatElem -> Bool
== :: TimeFormatElem -> TimeFormatElem -> Bool
$c== :: TimeFormatElem -> TimeFormatElem -> Bool
Eq)
data TimeFormatFct = TimeFormatFct
{ TimeFormatFct -> String
timeFormatFctName :: String
, TimeFormatFct
-> DateTime -> String -> Either String (DateTime, String)
timeFormatParse :: DateTime -> String -> Either String (DateTime, String)
, TimeFormatFct -> DateTime -> String
timeFormatPrint :: DateTime -> String
}
instance Show TimeFormatFct where
show :: TimeFormatFct -> String
show = TimeFormatFct -> String
timeFormatFctName
instance Eq TimeFormatFct where
t1 :: TimeFormatFct
t1 == :: TimeFormatFct -> TimeFormatFct -> Bool
== t2 :: TimeFormatFct
t2 = TimeFormatFct -> String
timeFormatFctName TimeFormatFct
t1 String -> String -> Bool
forall a. Eq a => a -> a -> Bool
== TimeFormatFct -> String
timeFormatFctName TimeFormatFct
t2
newtype TimeFormatString = TimeFormatString [TimeFormatElem]
deriving (Int -> TimeFormatString -> ShowS
[TimeFormatString] -> ShowS
TimeFormatString -> String
(Int -> TimeFormatString -> ShowS)
-> (TimeFormatString -> String)
-> ([TimeFormatString] -> ShowS)
-> Show TimeFormatString
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [TimeFormatString] -> ShowS
$cshowList :: [TimeFormatString] -> ShowS
show :: TimeFormatString -> String
$cshow :: TimeFormatString -> String
showsPrec :: Int -> TimeFormatString -> ShowS
$cshowsPrec :: Int -> TimeFormatString -> ShowS
Show,TimeFormatString -> TimeFormatString -> Bool
(TimeFormatString -> TimeFormatString -> Bool)
-> (TimeFormatString -> TimeFormatString -> Bool)
-> Eq TimeFormatString
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TimeFormatString -> TimeFormatString -> Bool
$c/= :: TimeFormatString -> TimeFormatString -> Bool
== :: TimeFormatString -> TimeFormatString -> Bool
$c== :: TimeFormatString -> TimeFormatString -> Bool
Eq)
class TimeFormat format where
toFormat :: format -> TimeFormatString
data ISO8601_Date = ISO8601_Date
deriving (Int -> ISO8601_Date -> ShowS
[ISO8601_Date] -> ShowS
ISO8601_Date -> String
(Int -> ISO8601_Date -> ShowS)
-> (ISO8601_Date -> String)
-> ([ISO8601_Date] -> ShowS)
-> Show ISO8601_Date
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ISO8601_Date] -> ShowS
$cshowList :: [ISO8601_Date] -> ShowS
show :: ISO8601_Date -> String
$cshow :: ISO8601_Date -> String
showsPrec :: Int -> ISO8601_Date -> ShowS
$cshowsPrec :: Int -> ISO8601_Date -> ShowS
Show,ISO8601_Date -> ISO8601_Date -> Bool
(ISO8601_Date -> ISO8601_Date -> Bool)
-> (ISO8601_Date -> ISO8601_Date -> Bool) -> Eq ISO8601_Date
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ISO8601_Date -> ISO8601_Date -> Bool
$c/= :: ISO8601_Date -> ISO8601_Date -> Bool
== :: ISO8601_Date -> ISO8601_Date -> Bool
$c== :: ISO8601_Date -> ISO8601_Date -> Bool
Eq)
data ISO8601_DateAndTime = ISO8601_DateAndTime
deriving (Int -> ISO8601_DateAndTime -> ShowS
[ISO8601_DateAndTime] -> ShowS
ISO8601_DateAndTime -> String
(Int -> ISO8601_DateAndTime -> ShowS)
-> (ISO8601_DateAndTime -> String)
-> ([ISO8601_DateAndTime] -> ShowS)
-> Show ISO8601_DateAndTime
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ISO8601_DateAndTime] -> ShowS
$cshowList :: [ISO8601_DateAndTime] -> ShowS
show :: ISO8601_DateAndTime -> String
$cshow :: ISO8601_DateAndTime -> String
showsPrec :: Int -> ISO8601_DateAndTime -> ShowS
$cshowsPrec :: Int -> ISO8601_DateAndTime -> ShowS
Show,ISO8601_DateAndTime -> ISO8601_DateAndTime -> Bool
(ISO8601_DateAndTime -> ISO8601_DateAndTime -> Bool)
-> (ISO8601_DateAndTime -> ISO8601_DateAndTime -> Bool)
-> Eq ISO8601_DateAndTime
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ISO8601_DateAndTime -> ISO8601_DateAndTime -> Bool
$c/= :: ISO8601_DateAndTime -> ISO8601_DateAndTime -> Bool
== :: ISO8601_DateAndTime -> ISO8601_DateAndTime -> Bool
$c== :: ISO8601_DateAndTime -> ISO8601_DateAndTime -> Bool
Eq)
instance TimeFormat [TimeFormatElem] where
toFormat :: [TimeFormatElem] -> TimeFormatString
toFormat = [TimeFormatElem] -> TimeFormatString
TimeFormatString
instance TimeFormat TimeFormatString where
toFormat :: TimeFormatString -> TimeFormatString
toFormat = TimeFormatString -> TimeFormatString
forall a. a -> a
id
instance TimeFormat String where
toFormat :: String -> TimeFormatString
toFormat = [TimeFormatElem] -> TimeFormatString
TimeFormatString ([TimeFormatElem] -> TimeFormatString)
-> (String -> [TimeFormatElem]) -> String -> TimeFormatString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> [TimeFormatElem]
toFormatElem
where toFormatElem :: String -> [TimeFormatElem]
toFormatElem [] = []
toFormatElem ('Y':'Y':'Y':'Y':r :: String
r) = TimeFormatElem
Format_Year4 TimeFormatElem -> [TimeFormatElem] -> [TimeFormatElem]
forall a. a -> [a] -> [a]
: String -> [TimeFormatElem]
toFormatElem String
r
toFormatElem ('Y':'Y':r :: String
r) = TimeFormatElem
Format_Year2 TimeFormatElem -> [TimeFormatElem] -> [TimeFormatElem]
forall a. a -> [a] -> [a]
: String -> [TimeFormatElem]
toFormatElem String
r
toFormatElem ('M':'M':r :: String
r) = TimeFormatElem
Format_Month2 TimeFormatElem -> [TimeFormatElem] -> [TimeFormatElem]
forall a. a -> [a] -> [a]
: String -> [TimeFormatElem]
toFormatElem String
r
toFormatElem ('M':'o':'n':r :: String
r) = TimeFormatElem
Format_MonthName_Short TimeFormatElem -> [TimeFormatElem] -> [TimeFormatElem]
forall a. a -> [a] -> [a]
: String -> [TimeFormatElem]
toFormatElem String
r
toFormatElem ('M':'I':r :: String
r) = TimeFormatElem
Format_Minute TimeFormatElem -> [TimeFormatElem] -> [TimeFormatElem]
forall a. a -> [a] -> [a]
: String -> [TimeFormatElem]
toFormatElem String
r
toFormatElem ('M':r :: String
r) = TimeFormatElem
Format_Month TimeFormatElem -> [TimeFormatElem] -> [TimeFormatElem]
forall a. a -> [a] -> [a]
: String -> [TimeFormatElem]
toFormatElem String
r
toFormatElem ('D':'D':r :: String
r) = TimeFormatElem
Format_Day2 TimeFormatElem -> [TimeFormatElem] -> [TimeFormatElem]
forall a. a -> [a] -> [a]
: String -> [TimeFormatElem]
toFormatElem String
r
toFormatElem ('H':r :: String
r) = TimeFormatElem
Format_Hour TimeFormatElem -> [TimeFormatElem] -> [TimeFormatElem]
forall a. a -> [a] -> [a]
: String -> [TimeFormatElem]
toFormatElem String
r
toFormatElem ('S':r :: String
r) = TimeFormatElem
Format_Second TimeFormatElem -> [TimeFormatElem] -> [TimeFormatElem]
forall a. a -> [a] -> [a]
: String -> [TimeFormatElem]
toFormatElem String
r
toFormatElem ('m':'s':r :: String
r) = TimeFormatElem
Format_MilliSecond TimeFormatElem -> [TimeFormatElem] -> [TimeFormatElem]
forall a. a -> [a] -> [a]
: String -> [TimeFormatElem]
toFormatElem String
r
toFormatElem ('u':'s':r :: String
r) = TimeFormatElem
Format_MicroSecond TimeFormatElem -> [TimeFormatElem] -> [TimeFormatElem]
forall a. a -> [a] -> [a]
: String -> [TimeFormatElem]
toFormatElem String
r
toFormatElem ('μ':r :: String
r) = TimeFormatElem
Format_MicroSecond TimeFormatElem -> [TimeFormatElem] -> [TimeFormatElem]
forall a. a -> [a] -> [a]
: String -> [TimeFormatElem]
toFormatElem String
r
toFormatElem ('n':'s':r :: String
r) = TimeFormatElem
Format_NanoSecond TimeFormatElem -> [TimeFormatElem] -> [TimeFormatElem]
forall a. a -> [a] -> [a]
: String -> [TimeFormatElem]
toFormatElem String
r
toFormatElem ('p':'1':r :: String
r) = Int -> TimeFormatElem
Format_Precision 1 TimeFormatElem -> [TimeFormatElem] -> [TimeFormatElem]
forall a. a -> [a] -> [a]
: String -> [TimeFormatElem]
toFormatElem String
r
toFormatElem ('p':'2':r :: String
r) = Int -> TimeFormatElem
Format_Precision 2 TimeFormatElem -> [TimeFormatElem] -> [TimeFormatElem]
forall a. a -> [a] -> [a]
: String -> [TimeFormatElem]
toFormatElem String
r
toFormatElem ('p':'3':r :: String
r) = Int -> TimeFormatElem
Format_Precision 3 TimeFormatElem -> [TimeFormatElem] -> [TimeFormatElem]
forall a. a -> [a] -> [a]
: String -> [TimeFormatElem]
toFormatElem String
r
toFormatElem ('p':'4':r :: String
r) = Int -> TimeFormatElem
Format_Precision 4 TimeFormatElem -> [TimeFormatElem] -> [TimeFormatElem]
forall a. a -> [a] -> [a]
: String -> [TimeFormatElem]
toFormatElem String
r
toFormatElem ('p':'5':r :: String
r) = Int -> TimeFormatElem
Format_Precision 5 TimeFormatElem -> [TimeFormatElem] -> [TimeFormatElem]
forall a. a -> [a] -> [a]
: String -> [TimeFormatElem]
toFormatElem String
r
toFormatElem ('p':'6':r :: String
r) = Int -> TimeFormatElem
Format_Precision 6 TimeFormatElem -> [TimeFormatElem] -> [TimeFormatElem]
forall a. a -> [a] -> [a]
: String -> [TimeFormatElem]
toFormatElem String
r
toFormatElem ('p':'7':r :: String
r) = Int -> TimeFormatElem
Format_Precision 7 TimeFormatElem -> [TimeFormatElem] -> [TimeFormatElem]
forall a. a -> [a] -> [a]
: String -> [TimeFormatElem]
toFormatElem String
r
toFormatElem ('p':'8':r :: String
r) = Int -> TimeFormatElem
Format_Precision 8 TimeFormatElem -> [TimeFormatElem] -> [TimeFormatElem]
forall a. a -> [a] -> [a]
: String -> [TimeFormatElem]
toFormatElem String
r
toFormatElem ('p':'9':r :: String
r) = Int -> TimeFormatElem
Format_Precision 9 TimeFormatElem -> [TimeFormatElem] -> [TimeFormatElem]
forall a. a -> [a] -> [a]
: String -> [TimeFormatElem]
toFormatElem String
r
toFormatElem ('E':'P':'O':'C':'H':r :: String
r) = TimeFormatElem
Format_UnixSecond TimeFormatElem -> [TimeFormatElem] -> [TimeFormatElem]
forall a. a -> [a] -> [a]
: String -> [TimeFormatElem]
toFormatElem String
r
toFormatElem ('T':'Z':'H':'M':r :: String
r) = TimeFormatElem
Format_TzHM TimeFormatElem -> [TimeFormatElem] -> [TimeFormatElem]
forall a. a -> [a] -> [a]
: String -> [TimeFormatElem]
toFormatElem String
r
toFormatElem ('T':'Z':'H':':':'M':r :: String
r) = TimeFormatElem
Format_TzHM_Colon TimeFormatElem -> [TimeFormatElem] -> [TimeFormatElem]
forall a. a -> [a] -> [a]
: String -> [TimeFormatElem]
toFormatElem String
r
toFormatElem ('T':'Z':'O':'F':'S':r :: String
r) = TimeFormatElem
Format_Tz_Offset TimeFormatElem -> [TimeFormatElem] -> [TimeFormatElem]
forall a. a -> [a] -> [a]
: String -> [TimeFormatElem]
toFormatElem String
r
toFormatElem ('\\':c :: Char
c:r :: String
r) = Char -> TimeFormatElem
Format_Text Char
c TimeFormatElem -> [TimeFormatElem] -> [TimeFormatElem]
forall a. a -> [a] -> [a]
: String -> [TimeFormatElem]
toFormatElem String
r
toFormatElem (' ':r :: String
r) = TimeFormatElem
Format_Spaces TimeFormatElem -> [TimeFormatElem] -> [TimeFormatElem]
forall a. a -> [a] -> [a]
: String -> [TimeFormatElem]
toFormatElem String
r
toFormatElem (c :: Char
c:r :: String
r) = Char -> TimeFormatElem
Format_Text Char
c TimeFormatElem -> [TimeFormatElem] -> [TimeFormatElem]
forall a. a -> [a] -> [a]
: String -> [TimeFormatElem]
toFormatElem String
r
instance TimeFormat ISO8601_Date where
toFormat :: ISO8601_Date -> TimeFormatString
toFormat _ = [TimeFormatElem] -> TimeFormatString
TimeFormatString [TimeFormatElem
Format_Year,TimeFormatElem
dash,TimeFormatElem
Format_Month2,TimeFormatElem
dash,TimeFormatElem
Format_Day2]
where dash :: TimeFormatElem
dash = Char -> TimeFormatElem
Format_Text '-'
instance TimeFormat ISO8601_DateAndTime where
toFormat :: ISO8601_DateAndTime -> TimeFormatString
toFormat _ = [TimeFormatElem] -> TimeFormatString
TimeFormatString
[TimeFormatElem
Format_Year,TimeFormatElem
dash,TimeFormatElem
Format_Month2,TimeFormatElem
dash,TimeFormatElem
Format_Day2
,Char -> TimeFormatElem
Format_Text 'T'
,TimeFormatElem
Format_Hour,TimeFormatElem
colon,TimeFormatElem
Format_Minute,TimeFormatElem
colon,TimeFormatElem
Format_Second
,TimeFormatElem
Format_TzHM_Colon_Z
]
where dash :: TimeFormatElem
dash = Char -> TimeFormatElem
Format_Text '-'
colon :: TimeFormatElem
colon = Char -> TimeFormatElem
Format_Text ':'
monthFromShort :: String -> Either String Month
monthFromShort :: String -> Either String Month
monthFromShort str :: String
str =
case String
str of
"Jan" -> Month -> Either String Month
forall a b. b -> Either a b
Right Month
January
"Feb" -> Month -> Either String Month
forall a b. b -> Either a b
Right Month
February
"Mar" -> Month -> Either String Month
forall a b. b -> Either a b
Right Month
March
"Apr" -> Month -> Either String Month
forall a b. b -> Either a b
Right Month
April
"May" -> Month -> Either String Month
forall a b. b -> Either a b
Right Month
May
"Jun" -> Month -> Either String Month
forall a b. b -> Either a b
Right Month
June
"Jul" -> Month -> Either String Month
forall a b. b -> Either a b
Right Month
July
"Aug" -> Month -> Either String Month
forall a b. b -> Either a b
Right Month
August
"Sep" -> Month -> Either String Month
forall a b. b -> Either a b
Right Month
September
"Oct" -> Month -> Either String Month
forall a b. b -> Either a b
Right Month
October
"Nov" -> Month -> Either String Month
forall a b. b -> Either a b
Right Month
November
"Dec" -> Month -> Either String Month
forall a b. b -> Either a b
Right Month
December
_ -> String -> Either String Month
forall a b. a -> Either a b
Left (String -> Either String Month) -> String -> Either String Month
forall a b. (a -> b) -> a -> b
$ "unknown month: " String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
str
printWith :: (TimeFormat format, Timeable t)
=> format
-> TimezoneOffset
-> t
-> String
printWith :: format -> TimezoneOffset -> t -> String
printWith fmt :: format
fmt tzOfs :: TimezoneOffset
tzOfs@(TimezoneOffset tz :: Int
tz) t :: t
t = (TimeFormatElem -> String) -> [TimeFormatElem] -> String
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap TimeFormatElem -> String
fmtToString [TimeFormatElem]
fmtElems
where fmtToString :: TimeFormatElem -> String
fmtToString Format_Year = Int -> String
forall a. Show a => a -> String
show (Date -> Int
dateYear Date
date)
fmtToString Format_Year4 = Int -> String
forall a. (Show a, Ord a, Num a, Integral a) => a -> String
pad4 (Date -> Int
dateYear Date
date)
fmtToString Format_Year2 = Int -> String
forall a. (Show a, Ord a, Num a, Integral a) => a -> String
pad2 (Date -> Int
dateYear Date
dateInt -> Int -> Int
forall a. Num a => a -> a -> a
-1900)
fmtToString Format_Month2 = Int -> String
forall a. (Show a, Ord a, Num a, Integral a) => a -> String
pad2 (Month -> Int
forall a. Enum a => a -> Int
fromEnum (Date -> Month
dateMonth Date
date)Int -> Int -> Int
forall a. Num a => a -> a -> a
+1)
fmtToString Format_Month = Int -> String
forall a. Show a => a -> String
show (Month -> Int
forall a. Enum a => a -> Int
fromEnum (Date -> Month
dateMonth Date
date)Int -> Int -> Int
forall a. Num a => a -> a -> a
+1)
fmtToString Format_MonthName_Short = Int -> ShowS
forall a. Int -> [a] -> [a]
take 3 ShowS -> ShowS
forall a b. (a -> b) -> a -> b
$ Month -> String
forall a. Show a => a -> String
show (Date -> Month
dateMonth Date
date)
fmtToString Format_Day2 = Int -> String
forall a. (Show a, Ord a, Num a, Integral a) => a -> String
pad2 (Date -> Int
dateDay Date
date)
fmtToString Format_Day = Int -> String
forall a. Show a => a -> String
show (Date -> Int
dateDay Date
date)
fmtToString Format_Hour = Int -> String
forall a. (Show a, Ord a, Num a, Integral a) => a -> String
pad2 (Hours -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral (TimeOfDay -> Hours
todHour TimeOfDay
tm) :: Int)
fmtToString Format_Minute = Int -> String
forall a. (Show a, Ord a, Num a, Integral a) => a -> String
pad2 (Minutes -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral (TimeOfDay -> Minutes
todMin TimeOfDay
tm) :: Int)
fmtToString Format_Second = Int -> String
forall a. (Show a, Ord a, Num a, Integral a) => a -> String
pad2 (Seconds -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral (TimeOfDay -> Seconds
todSec TimeOfDay
tm) :: Int)
fmtToString Format_MilliSecond = Int -> Int64 -> String
forall a. (Show a, Ord a, Num a, Integral a) => Int -> a -> String
padN 3 (Int64
ns Int64 -> Int64 -> Int64
forall a. Integral a => a -> a -> a
`div` 1000000)
fmtToString Format_MicroSecond = Int -> Int64 -> String
forall a. (Show a, Ord a, Num a, Integral a) => Int -> a -> String
padN 3 ((Int64
ns Int64 -> Int64 -> Int64
forall a. Integral a => a -> a -> a
`div` 1000) Int64 -> Int64 -> Int64
forall a. Integral a => a -> a -> a
`mod` 1000)
fmtToString Format_NanoSecond = Int -> Int64 -> String
forall a. (Show a, Ord a, Num a, Integral a) => Int -> a -> String
padN 3 (Int64
ns Int64 -> Int64 -> Int64
forall a. Integral a => a -> a -> a
`mod` 1000)
fmtToString (Format_Precision n :: Int
n)
| Int
n Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= 1 Bool -> Bool -> Bool
&& Int
n Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<= 9 = Int -> Int64 -> String
forall a. (Show a, Ord a, Num a, Integral a) => Int -> a -> String
padN Int
n (Int64
ns Int64 -> Int64 -> Int64
forall a. Integral a => a -> a -> a
`div` (10 Int64 -> Int -> Int64
forall a b. (Num a, Integral b) => a -> b -> a
^ (9 Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
n)))
| Bool
otherwise = ShowS
forall a. HasCallStack => String -> a
error "invalid precision format"
fmtToString Format_UnixSecond = Int64 -> String
forall a. Show a => a -> String
show Int64
unixSecs
fmtToString Format_TimezoneName = ""
fmtToString Format_Tz_Offset = Int -> String
forall a. Show a => a -> String
show Int
tz
fmtToString Format_TzHM = TimezoneOffset -> String
forall a. Show a => a -> String
show TimezoneOffset
tzOfs
fmtToString Format_TzHM_Colon_Z
| Int
tz Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== 0 = "Z"
| Bool
otherwise = TimeFormatElem -> String
fmtToString TimeFormatElem
Format_TzHM_Colon
fmtToString Format_TzHM_Colon =
let (tzH :: Int
tzH, tzM :: Int
tzM) = Int -> Int
forall a. Num a => a -> a
abs Int
tz Int -> Int -> (Int, Int)
forall a. Integral a => a -> a -> (a, a)
`divMod` 60
sign :: String
sign = if Int
tz Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< 0 then "-" else "+"
in String
sign String -> ShowS
forall a. [a] -> [a] -> [a]
++ Int -> String
forall a. (Show a, Ord a, Num a, Integral a) => a -> String
pad2 Int
tzH String -> ShowS
forall a. [a] -> [a] -> [a]
++ ":" String -> ShowS
forall a. [a] -> [a] -> [a]
++ Int -> String
forall a. (Show a, Ord a, Num a, Integral a) => a -> String
pad2 Int
tzM
fmtToString Format_Spaces = " "
fmtToString (Format_Text c :: Char
c) = [Char
c]
fmtToString f :: TimeFormatElem
f = ShowS
forall a. HasCallStack => String -> a
error ("implemented printing format: " String -> ShowS
forall a. [a] -> [a] -> [a]
++ TimeFormatElem -> String
forall a. Show a => a -> String
show TimeFormatElem
f)
(TimeFormatString fmtElems :: [TimeFormatElem]
fmtElems) = format -> TimeFormatString
forall format. TimeFormat format => format -> TimeFormatString
toFormat format
fmt
(Elapsed (Seconds unixSecs :: Int64
unixSecs)) = t -> Elapsed
forall t. Timeable t => t -> Elapsed
timeGetElapsed t
t
(DateTime date :: Date
date tm :: TimeOfDay
tm) = t -> DateTime
forall t. Timeable t => t -> DateTime
timeGetDateTimeOfDay t
t
(NanoSeconds ns :: Int64
ns) = t -> NanoSeconds
forall t. Timeable t => t -> NanoSeconds
timeGetNanoSeconds t
t
localTimePrint :: (TimeFormat format, Timeable t)
=> format
-> LocalTime t
-> String
localTimePrint :: format -> LocalTime t -> String
localTimePrint fmt :: format
fmt lt :: LocalTime t
lt = LocalTime String -> String
forall t. LocalTime t -> t
localTimeUnwrap (LocalTime String -> String) -> LocalTime String -> String
forall a b. (a -> b) -> a -> b
$ (t -> String) -> LocalTime t -> LocalTime String
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (format -> TimezoneOffset -> t -> String
forall format t.
(TimeFormat format, Timeable t) =>
format -> TimezoneOffset -> t -> String
printWith format
fmt (LocalTime t -> TimezoneOffset
forall t. LocalTime t -> TimezoneOffset
localTimeGetTimezone LocalTime t
lt)) LocalTime t
lt
timePrint :: (TimeFormat format, Timeable t)
=> format
-> t
-> String
timePrint :: format -> t -> String
timePrint fmt :: format
fmt t :: t
t = format -> TimezoneOffset -> t -> String
forall format t.
(TimeFormat format, Timeable t) =>
format -> TimezoneOffset -> t -> String
printWith format
fmt TimezoneOffset
timezone_UTC t
t
localTimeParseE :: TimeFormat format
=> format
-> String
-> Either (TimeFormatElem, String) (LocalTime DateTime, String)
localTimeParseE :: format
-> String
-> Either (TimeFormatElem, String) (LocalTime DateTime, String)
localTimeParseE fmt :: format
fmt timeString :: String
timeString = (DateTime, TimezoneOffset)
-> [TimeFormatElem]
-> String
-> Either (TimeFormatElem, String) (LocalTime DateTime, String)
loop (DateTime, TimezoneOffset)
ini [TimeFormatElem]
fmtElems String
timeString
where (TimeFormatString fmtElems :: [TimeFormatElem]
fmtElems) = format -> TimeFormatString
forall format. TimeFormat format => format -> TimeFormatString
toFormat format
fmt
toLocal :: (t, TimezoneOffset) -> LocalTime t
toLocal (dt :: t
dt, tz :: TimezoneOffset
tz) = TimezoneOffset -> t -> LocalTime t
forall t. Time t => TimezoneOffset -> t -> LocalTime t
localTime TimezoneOffset
tz t
dt
loop :: (DateTime, TimezoneOffset)
-> [TimeFormatElem]
-> String
-> Either (TimeFormatElem, String) (LocalTime DateTime, String)
loop acc :: (DateTime, TimezoneOffset)
acc [] s :: String
s = (LocalTime DateTime, String)
-> Either (TimeFormatElem, String) (LocalTime DateTime, String)
forall a b. b -> Either a b
Right ((DateTime, TimezoneOffset) -> LocalTime DateTime
forall t. Time t => (t, TimezoneOffset) -> LocalTime t
toLocal (DateTime, TimezoneOffset)
acc, String
s)
loop _ (x :: TimeFormatElem
x:_) [] = (TimeFormatElem, String)
-> Either (TimeFormatElem, String) (LocalTime DateTime, String)
forall a b. a -> Either a b
Left (TimeFormatElem
x, "empty")
loop acc :: (DateTime, TimezoneOffset)
acc (x :: TimeFormatElem
x:xs :: [TimeFormatElem]
xs) s :: String
s =
case (DateTime, TimezoneOffset)
-> TimeFormatElem
-> String
-> Either String ((DateTime, TimezoneOffset), String)
processOne (DateTime, TimezoneOffset)
acc TimeFormatElem
x String
s of
Left err :: String
err -> (TimeFormatElem, String)
-> Either (TimeFormatElem, String) (LocalTime DateTime, String)
forall a b. a -> Either a b
Left (TimeFormatElem
x, String
err)
Right (nacc :: (DateTime, TimezoneOffset)
nacc, s' :: String
s') -> (DateTime, TimezoneOffset)
-> [TimeFormatElem]
-> String
-> Either (TimeFormatElem, String) (LocalTime DateTime, String)
loop (DateTime, TimezoneOffset)
nacc [TimeFormatElem]
xs String
s'
processOne :: (DateTime, TimezoneOffset)
-> TimeFormatElem
-> String
-> Either String ((DateTime, TimezoneOffset), String)
processOne _ _ [] = String -> Either String ((DateTime, TimezoneOffset), String)
forall a b. a -> Either a b
Left "empty"
processOne acc :: (DateTime, TimezoneOffset)
acc (Format_Text c :: Char
c) (x :: Char
x:xs :: String
xs)
| Char
c Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
x = ((DateTime, TimezoneOffset), String)
-> Either String ((DateTime, TimezoneOffset), String)
forall a b. b -> Either a b
Right ((DateTime, TimezoneOffset)
acc, String
xs)
| Bool
otherwise = String -> Either String ((DateTime, TimezoneOffset), String)
forall a b. a -> Either a b
Left ("unexpected char, got: " String -> ShowS
forall a. [a] -> [a] -> [a]
++ Char -> String
forall a. Show a => a -> String
show Char
c)
processOne acc :: (DateTime, TimezoneOffset)
acc Format_Year s :: String
s =
(Int64 -> (DateTime, TimezoneOffset))
-> Either String (Int64, String)
-> Either String ((DateTime, TimezoneOffset), String)
forall t a a b. (t -> a) -> Either a (t, b) -> Either a (a, b)
onSuccess (\y :: Int64
y -> (Date -> Date)
-> (DateTime, TimezoneOffset) -> (DateTime, TimezoneOffset)
forall b. (Date -> Date) -> (DateTime, b) -> (DateTime, b)
modDate (Int64 -> Date -> Date
setYear Int64
y) (DateTime, TimezoneOffset)
acc) (Either String (Int64, String)
-> Either String ((DateTime, TimezoneOffset), String))
-> Either String (Int64, String)
-> Either String ((DateTime, TimezoneOffset), String)
forall a b. (a -> b) -> a -> b
$ String -> Either String (Int64, String)
forall a. Num a => String -> Either String (a, String)
isNumber String
s
processOne acc :: (DateTime, TimezoneOffset)
acc Format_Year4 s :: String
s =
(Int64 -> (DateTime, TimezoneOffset))
-> Either String (Int64, String)
-> Either String ((DateTime, TimezoneOffset), String)
forall t a a b. (t -> a) -> Either a (t, b) -> Either a (a, b)
onSuccess (\y :: Int64
y -> (Date -> Date)
-> (DateTime, TimezoneOffset) -> (DateTime, TimezoneOffset)
forall b. (Date -> Date) -> (DateTime, b) -> (DateTime, b)
modDate (Int64 -> Date -> Date
setYear Int64
y) (DateTime, TimezoneOffset)
acc) (Either String (Int64, String)
-> Either String ((DateTime, TimezoneOffset), String))
-> Either String (Int64, String)
-> Either String ((DateTime, TimezoneOffset), String)
forall a b. (a -> b) -> a -> b
$ Int -> String -> Either String (Int64, String)
getNDigitNum 4 String
s
processOne acc :: (DateTime, TimezoneOffset)
acc Format_Year2 s :: String
s = (Int64 -> (DateTime, TimezoneOffset))
-> Either String (Int64, String)
-> Either String ((DateTime, TimezoneOffset), String)
forall t a a b. (t -> a) -> Either a (t, b) -> Either a (a, b)
onSuccess
(\y :: Int64
y -> let year :: Int64
year = if Int64
y Int64 -> Int64 -> Bool
forall a. Ord a => a -> a -> Bool
< 70 then Int64
y Int64 -> Int64 -> Int64
forall a. Num a => a -> a -> a
+ 2000 else Int64
y Int64 -> Int64 -> Int64
forall a. Num a => a -> a -> a
+ 1900 in (Date -> Date)
-> (DateTime, TimezoneOffset) -> (DateTime, TimezoneOffset)
forall b. (Date -> Date) -> (DateTime, b) -> (DateTime, b)
modDate (Int64 -> Date -> Date
setYear Int64
year) (DateTime, TimezoneOffset)
acc)
(Either String (Int64, String)
-> Either String ((DateTime, TimezoneOffset), String))
-> Either String (Int64, String)
-> Either String ((DateTime, TimezoneOffset), String)
forall a b. (a -> b) -> a -> b
$ Int -> String -> Either String (Int64, String)
getNDigitNum 2 String
s
processOne acc :: (DateTime, TimezoneOffset)
acc Format_Month2 s :: String
s =
(Int64 -> (DateTime, TimezoneOffset))
-> Either String (Int64, String)
-> Either String ((DateTime, TimezoneOffset), String)
forall t a a b. (t -> a) -> Either a (t, b) -> Either a (a, b)
onSuccess (\m :: Int64
m -> (Date -> Date)
-> (DateTime, TimezoneOffset) -> (DateTime, TimezoneOffset)
forall b. (Date -> Date) -> (DateTime, b) -> (DateTime, b)
modDate (Month -> Date -> Date
setMonth (Month -> Date -> Date) -> Month -> Date -> Date
forall a b. (a -> b) -> a -> b
$ Int -> Month
forall a. Enum a => Int -> a
toEnum ((Int64 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int64
m Int -> Int -> Int
forall a. Num a => a -> a -> a
- 1) Int -> Int -> Int
forall a. Integral a => a -> a -> a
`mod` 12)) (DateTime, TimezoneOffset)
acc) (Either String (Int64, String)
-> Either String ((DateTime, TimezoneOffset), String))
-> Either String (Int64, String)
-> Either String ((DateTime, TimezoneOffset), String)
forall a b. (a -> b) -> a -> b
$ Int -> String -> Either String (Int64, String)
getNDigitNum 2 String
s
processOne acc :: (DateTime, TimezoneOffset)
acc Format_MonthName_Short s :: String
s =
(Month -> (DateTime, TimezoneOffset))
-> Either String (Month, String)
-> Either String ((DateTime, TimezoneOffset), String)
forall t a a b. (t -> a) -> Either a (t, b) -> Either a (a, b)
onSuccess (\m :: Month
m -> (Date -> Date)
-> (DateTime, TimezoneOffset) -> (DateTime, TimezoneOffset)
forall b. (Date -> Date) -> (DateTime, b) -> (DateTime, b)
modDate (Month -> Date -> Date
setMonth Month
m) (DateTime, TimezoneOffset)
acc) (Either String (Month, String)
-> Either String ((DateTime, TimezoneOffset), String))
-> Either String (Month, String)
-> Either String ((DateTime, TimezoneOffset), String)
forall a b. (a -> b) -> a -> b
$ String -> Either String (Month, String)
getMonth String
s
processOne acc :: (DateTime, TimezoneOffset)
acc Format_Day2 s :: String
s =
(Int64 -> (DateTime, TimezoneOffset))
-> Either String (Int64, String)
-> Either String ((DateTime, TimezoneOffset), String)
forall t a a b. (t -> a) -> Either a (t, b) -> Either a (a, b)
onSuccess (\d :: Int64
d -> (Date -> Date)
-> (DateTime, TimezoneOffset) -> (DateTime, TimezoneOffset)
forall b. (Date -> Date) -> (DateTime, b) -> (DateTime, b)
modDate (Int64 -> Date -> Date
forall a. Integral a => a -> Date -> Date
setDay Int64
d) (DateTime, TimezoneOffset)
acc) (Either String (Int64, String)
-> Either String ((DateTime, TimezoneOffset), String))
-> Either String (Int64, String)
-> Either String ((DateTime, TimezoneOffset), String)
forall a b. (a -> b) -> a -> b
$ Int -> String -> Either String (Int64, String)
getNDigitNum 2 String
s
processOne acc :: (DateTime, TimezoneOffset)
acc Format_Hour s :: String
s =
(Int64 -> (DateTime, TimezoneOffset))
-> Either String (Int64, String)
-> Either String ((DateTime, TimezoneOffset), String)
forall t a a b. (t -> a) -> Either a (t, b) -> Either a (a, b)
onSuccess (\h :: Int64
h -> (TimeOfDay -> TimeOfDay)
-> (DateTime, TimezoneOffset) -> (DateTime, TimezoneOffset)
forall b.
(TimeOfDay -> TimeOfDay) -> (DateTime, b) -> (DateTime, b)
modTime (Int64 -> TimeOfDay -> TimeOfDay
setHour Int64
h) (DateTime, TimezoneOffset)
acc) (Either String (Int64, String)
-> Either String ((DateTime, TimezoneOffset), String))
-> Either String (Int64, String)
-> Either String ((DateTime, TimezoneOffset), String)
forall a b. (a -> b) -> a -> b
$ Int -> String -> Either String (Int64, String)
getNDigitNum 2 String
s
processOne acc :: (DateTime, TimezoneOffset)
acc Format_Minute s :: String
s =
(Int64 -> (DateTime, TimezoneOffset))
-> Either String (Int64, String)
-> Either String ((DateTime, TimezoneOffset), String)
forall t a a b. (t -> a) -> Either a (t, b) -> Either a (a, b)
onSuccess (\mi :: Int64
mi -> (TimeOfDay -> TimeOfDay)
-> (DateTime, TimezoneOffset) -> (DateTime, TimezoneOffset)
forall b.
(TimeOfDay -> TimeOfDay) -> (DateTime, b) -> (DateTime, b)
modTime (Int64 -> TimeOfDay -> TimeOfDay
setMin Int64
mi) (DateTime, TimezoneOffset)
acc) (Either String (Int64, String)
-> Either String ((DateTime, TimezoneOffset), String))
-> Either String (Int64, String)
-> Either String ((DateTime, TimezoneOffset), String)
forall a b. (a -> b) -> a -> b
$ Int -> String -> Either String (Int64, String)
getNDigitNum 2 String
s
processOne acc :: (DateTime, TimezoneOffset)
acc Format_Second s :: String
s =
(Int64 -> (DateTime, TimezoneOffset))
-> Either String (Int64, String)
-> Either String ((DateTime, TimezoneOffset), String)
forall t a a b. (t -> a) -> Either a (t, b) -> Either a (a, b)
onSuccess (\sec :: Int64
sec -> (TimeOfDay -> TimeOfDay)
-> (DateTime, TimezoneOffset) -> (DateTime, TimezoneOffset)
forall b.
(TimeOfDay -> TimeOfDay) -> (DateTime, b) -> (DateTime, b)
modTime (Int64 -> TimeOfDay -> TimeOfDay
setSec Int64
sec) (DateTime, TimezoneOffset)
acc) (Either String (Int64, String)
-> Either String ((DateTime, TimezoneOffset), String))
-> Either String (Int64, String)
-> Either String ((DateTime, TimezoneOffset), String)
forall a b. (a -> b) -> a -> b
$ Int -> String -> Either String (Int64, String)
getNDigitNum 2 String
s
processOne acc :: (DateTime, TimezoneOffset)
acc Format_MilliSecond s :: String
s =
(Int64 -> (DateTime, TimezoneOffset))
-> Either String (Int64, String)
-> Either String ((DateTime, TimezoneOffset), String)
forall t a a b. (t -> a) -> Either a (t, b) -> Either a (a, b)
onSuccess (\ms :: Int64
ms -> (TimeOfDay -> TimeOfDay)
-> (DateTime, TimezoneOffset) -> (DateTime, TimezoneOffset)
forall b.
(TimeOfDay -> TimeOfDay) -> (DateTime, b) -> (DateTime, b)
modTime ((Int, Int) -> Int64 -> TimeOfDay -> TimeOfDay
setNsMask (6,3) Int64
ms) (DateTime, TimezoneOffset)
acc) (Either String (Int64, String)
-> Either String ((DateTime, TimezoneOffset), String))
-> Either String (Int64, String)
-> Either String ((DateTime, TimezoneOffset), String)
forall a b. (a -> b) -> a -> b
$ Int -> String -> Either String (Int64, String)
getNDigitNum 3 String
s
processOne acc :: (DateTime, TimezoneOffset)
acc Format_MicroSecond s :: String
s =
(Int64 -> (DateTime, TimezoneOffset))
-> Either String (Int64, String)
-> Either String ((DateTime, TimezoneOffset), String)
forall t a a b. (t -> a) -> Either a (t, b) -> Either a (a, b)
onSuccess (\us :: Int64
us -> (TimeOfDay -> TimeOfDay)
-> (DateTime, TimezoneOffset) -> (DateTime, TimezoneOffset)
forall b.
(TimeOfDay -> TimeOfDay) -> (DateTime, b) -> (DateTime, b)
modTime ((Int, Int) -> Int64 -> TimeOfDay -> TimeOfDay
setNsMask (3,3) Int64
us) (DateTime, TimezoneOffset)
acc) (Either String (Int64, String)
-> Either String ((DateTime, TimezoneOffset), String))
-> Either String (Int64, String)
-> Either String ((DateTime, TimezoneOffset), String)
forall a b. (a -> b) -> a -> b
$ Int -> String -> Either String (Int64, String)
getNDigitNum 3 String
s
processOne acc :: (DateTime, TimezoneOffset)
acc Format_NanoSecond s :: String
s =
(Int64 -> (DateTime, TimezoneOffset))
-> Either String (Int64, String)
-> Either String ((DateTime, TimezoneOffset), String)
forall t a a b. (t -> a) -> Either a (t, b) -> Either a (a, b)
onSuccess (\ns :: Int64
ns -> (TimeOfDay -> TimeOfDay)
-> (DateTime, TimezoneOffset) -> (DateTime, TimezoneOffset)
forall b.
(TimeOfDay -> TimeOfDay) -> (DateTime, b) -> (DateTime, b)
modTime ((Int, Int) -> Int64 -> TimeOfDay -> TimeOfDay
setNsMask (0,3) Int64
ns) (DateTime, TimezoneOffset)
acc) (Either String (Int64, String)
-> Either String ((DateTime, TimezoneOffset), String))
-> Either String (Int64, String)
-> Either String ((DateTime, TimezoneOffset), String)
forall a b. (a -> b) -> a -> b
$ Int -> String -> Either String (Int64, String)
getNDigitNum 3 String
s
processOne acc :: (DateTime, TimezoneOffset)
acc (Format_Precision p :: Int
p) s :: String
s =
(Int64 -> (DateTime, TimezoneOffset))
-> Either String (Int64, String)
-> Either String ((DateTime, TimezoneOffset), String)
forall t a a b. (t -> a) -> Either a (t, b) -> Either a (a, b)
onSuccess (\num :: Int64
num -> (TimeOfDay -> TimeOfDay)
-> (DateTime, TimezoneOffset) -> (DateTime, TimezoneOffset)
forall b.
(TimeOfDay -> TimeOfDay) -> (DateTime, b) -> (DateTime, b)
modTime (Int64 -> TimeOfDay -> TimeOfDay
setNS Int64
num) (DateTime, TimezoneOffset)
acc) (Either String (Int64, String)
-> Either String ((DateTime, TimezoneOffset), String))
-> Either String (Int64, String)
-> Either String ((DateTime, TimezoneOffset), String)
forall a b. (a -> b) -> a -> b
$ Int -> String -> Either String (Int64, String)
getNDigitNum Int
p String
s
processOne acc :: (DateTime, TimezoneOffset)
acc Format_UnixSecond s :: String
s =
(Int64 -> (DateTime, TimezoneOffset))
-> Either String (Int64, String)
-> Either String ((DateTime, TimezoneOffset), String)
forall t a a b. (t -> a) -> Either a (t, b) -> Either a (a, b)
onSuccess (\sec :: Int64
sec ->
let newDate :: DateTime
newDate = ElapsedP -> DateTime
dateTimeFromUnixEpochP (ElapsedP -> DateTime) -> ElapsedP -> DateTime
forall a b. (a -> b) -> a -> b
$ (Elapsed -> NanoSeconds -> ElapsedP)
-> NanoSeconds -> Elapsed -> ElapsedP
forall a b c. (a -> b -> c) -> b -> a -> c
flip Elapsed -> NanoSeconds -> ElapsedP
ElapsedP 0 (Elapsed -> ElapsedP) -> Elapsed -> ElapsedP
forall a b. (a -> b) -> a -> b
$ Seconds -> Elapsed
Elapsed (Seconds -> Elapsed) -> Seconds -> Elapsed
forall a b. (a -> b) -> a -> b
$ Int64 -> Seconds
Seconds Int64
sec
in (DateTime -> DateTime)
-> (DateTime, TimezoneOffset) -> (DateTime, TimezoneOffset)
forall t a b. (t -> a) -> (t, b) -> (a, b)
modDT (DateTime -> DateTime -> DateTime
forall a b. a -> b -> a
const DateTime
newDate) (DateTime, TimezoneOffset)
acc) (Either String (Int64, String)
-> Either String ((DateTime, TimezoneOffset), String))
-> Either String (Int64, String)
-> Either String ((DateTime, TimezoneOffset), String)
forall a b. (a -> b) -> a -> b
$ String -> Either String (Int64, String)
forall a. Num a => String -> Either String (a, String)
isNumber String
s
processOne acc :: (DateTime, TimezoneOffset)
acc Format_TzHM_Colon_Z a :: String
a@(c :: Char
c:s :: String
s)
| Char
c Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== 'Z' = ((DateTime, TimezoneOffset), String)
-> Either String ((DateTime, TimezoneOffset), String)
forall a b. b -> Either a b
Right ((DateTime, TimezoneOffset)
acc, String
s)
| Bool
otherwise = (DateTime, TimezoneOffset)
-> TimeFormatElem
-> String
-> Either String ((DateTime, TimezoneOffset), String)
processOne (DateTime, TimezoneOffset)
acc TimeFormatElem
Format_TzHM_Colon String
a
processOne acc :: (DateTime, TimezoneOffset)
acc Format_TzHM_Colon (c :: Char
c:s :: String
s) =
Bool
-> (DateTime, TimezoneOffset)
-> Char
-> String
-> Either String ((DateTime, TimezoneOffset), String)
forall a b.
Bool
-> (a, b)
-> Char
-> String
-> Either String ((a, TimezoneOffset), String)
parseHMSign Bool
True (DateTime, TimezoneOffset)
acc Char
c String
s
processOne acc :: (DateTime, TimezoneOffset)
acc Format_TzHM (c :: Char
c:s :: String
s) =
Bool
-> (DateTime, TimezoneOffset)
-> Char
-> String
-> Either String ((DateTime, TimezoneOffset), String)
forall a b.
Bool
-> (a, b)
-> Char
-> String
-> Either String ((a, TimezoneOffset), String)
parseHMSign Bool
False (DateTime, TimezoneOffset)
acc Char
c String
s
processOne acc :: (DateTime, TimezoneOffset)
acc Format_Spaces (' ':s :: String
s) = ((DateTime, TimezoneOffset), String)
-> Either String ((DateTime, TimezoneOffset), String)
forall a b. b -> Either a b
Right ((DateTime, TimezoneOffset)
acc, String
s)
processOne _ f :: TimeFormatElem
f _ = String -> Either String ((DateTime, TimezoneOffset), String)
forall a. HasCallStack => String -> a
error ("unimplemened parsing format: " String -> ShowS
forall a. [a] -> [a] -> [a]
++ TimeFormatElem -> String
forall a. Show a => a -> String
show TimeFormatElem
f)
parseHMSign :: Bool
-> (a, b)
-> Char
-> String
-> Either String ((a, TimezoneOffset), String)
parseHMSign expectColon :: Bool
expectColon acc :: (a, b)
acc signChar :: Char
signChar afterSign :: String
afterSign =
case Char
signChar of
'+' -> Bool
-> Bool
-> String
-> (a, b)
-> Either String ((a, TimezoneOffset), String)
forall a b.
Bool
-> Bool
-> String
-> (a, b)
-> Either String ((a, TimezoneOffset), String)
parseHM Bool
False Bool
expectColon String
afterSign (a, b)
acc
'-' -> Bool
-> Bool
-> String
-> (a, b)
-> Either String ((a, TimezoneOffset), String)
forall a b.
Bool
-> Bool
-> String
-> (a, b)
-> Either String ((a, TimezoneOffset), String)
parseHM Bool
True Bool
expectColon String
afterSign (a, b)
acc
_ -> Bool
-> Bool
-> String
-> (a, b)
-> Either String ((a, TimezoneOffset), String)
forall a b.
Bool
-> Bool
-> String
-> (a, b)
-> Either String ((a, TimezoneOffset), String)
parseHM Bool
False Bool
expectColon (Char
signCharChar -> ShowS
forall a. a -> [a] -> [a]
:String
afterSign) (a, b)
acc
parseHM :: Bool
-> Bool
-> String
-> (a, b)
-> Either String ((a, TimezoneOffset), String)
parseHM isNeg :: Bool
isNeg True (h1 :: Char
h1:h2 :: Char
h2:':':m1 :: Char
m1:m2 :: Char
m2:xs :: String
xs) acc :: (a, b)
acc
| String -> Bool
allDigits [Char
h1,Char
h2,Char
m1,Char
m2] = let tz :: TimezoneOffset
tz = Bool -> Char -> Char -> Char -> Char -> TimezoneOffset
toTZ Bool
isNeg Char
h1 Char
h2 Char
m1 Char
m2
in ((a, TimezoneOffset), String)
-> Either String ((a, TimezoneOffset), String)
forall a b. b -> Either a b
Right ((b -> TimezoneOffset) -> (a, b) -> (a, TimezoneOffset)
forall t b a. (t -> b) -> (a, t) -> (a, b)
modTZ (TimezoneOffset -> b -> TimezoneOffset
forall a b. a -> b -> a
const TimezoneOffset
tz) (a, b)
acc, String
xs)
| Bool
otherwise = String -> Either String ((a, TimezoneOffset), String)
forall a b. a -> Either a b
Left ("not digits chars: " String -> ShowS
forall a. [a] -> [a] -> [a]
++ ShowS
forall a. Show a => a -> String
show [Char
h1,Char
h2,Char
m1,Char
m2])
parseHM isNeg :: Bool
isNeg False (h1 :: Char
h1:h2 :: Char
h2:m1 :: Char
m1:m2 :: Char
m2:xs :: String
xs) acc :: (a, b)
acc
| String -> Bool
allDigits [Char
h1,Char
h2,Char
m1,Char
m2] = let tz :: TimezoneOffset
tz = Bool -> Char -> Char -> Char -> Char -> TimezoneOffset
toTZ Bool
isNeg Char
h1 Char
h2 Char
m1 Char
m2
in ((a, TimezoneOffset), String)
-> Either String ((a, TimezoneOffset), String)
forall a b. b -> Either a b
Right ((b -> TimezoneOffset) -> (a, b) -> (a, TimezoneOffset)
forall t b a. (t -> b) -> (a, t) -> (a, b)
modTZ (TimezoneOffset -> b -> TimezoneOffset
forall a b. a -> b -> a
const TimezoneOffset
tz) (a, b)
acc, String
xs)
| Bool
otherwise = String -> Either String ((a, TimezoneOffset), String)
forall a b. a -> Either a b
Left ("not digits chars: " String -> ShowS
forall a. [a] -> [a] -> [a]
++ ShowS
forall a. Show a => a -> String
show [Char
h1,Char
h2,Char
m1,Char
m2])
parseHM _ _ _ _ = String -> Either String ((a, TimezoneOffset), String)
forall a b. a -> Either a b
Left "invalid timezone format"
toTZ :: Bool -> Char -> Char -> Char -> Char -> TimezoneOffset
toTZ isNeg :: Bool
isNeg h1 :: Char
h1 h2 :: Char
h2 m1 :: Char
m1 m2 :: Char
m2 = Int -> TimezoneOffset
TimezoneOffset ((if Bool
isNeg then Int -> Int
forall a. Num a => a -> a
negate else Int -> Int
forall a. a -> a
id) Int
minutes)
where minutes :: Int
minutes = (String -> Int
forall a. Num a => String -> a
toInt [Char
h1,Char
h2] Int -> Int -> Int
forall a. Num a => a -> a -> a
* 60) Int -> Int -> Int
forall a. Num a => a -> a -> a
+ String -> Int
forall a. Num a => String -> a
toInt [Char
m1,Char
m2]
onSuccess :: (t -> a) -> Either a (t, b) -> Either a (a, b)
onSuccess f :: t -> a
f (Right (v :: t
v, s' :: b
s')) = (a, b) -> Either a (a, b)
forall a b. b -> Either a b
Right (t -> a
f t
v, b
s')
onSuccess _ (Left s :: a
s) = a -> Either a (a, b)
forall a b. a -> Either a b
Left a
s
isNumber :: Num a => String -> Either String (a, String)
isNumber :: String -> Either String (a, String)
isNumber s :: String
s =
case (Char -> Bool) -> String -> (String, String)
forall a. (a -> Bool) -> [a] -> ([a], [a])
span Char -> Bool
isDigit String
s of
("",s2 :: String
s2) -> String -> Either String (a, String)
forall a b. a -> Either a b
Left ("no digits chars:" String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
s2)
(s1 :: String
s1,s2 :: String
s2) -> (a, String) -> Either String (a, String)
forall a b. b -> Either a b
Right (String -> a
forall a. Num a => String -> a
toInt String
s1, String
s2)
getNDigitNum :: Int -> String -> Either String (Int64, String)
getNDigitNum :: Int -> String -> Either String (Int64, String)
getNDigitNum n :: Int
n s :: String
s =
case Int -> String -> Either String (String, String)
getNChar Int
n String
s of
Left err :: String
err -> String -> Either String (Int64, String)
forall a b. a -> Either a b
Left String
err
Right (s1 :: String
s1, s2 :: String
s2) | Bool -> Bool
not (String -> Bool
allDigits String
s1) -> String -> Either String (Int64, String)
forall a b. a -> Either a b
Left ("not a digit chars in " String -> ShowS
forall a. [a] -> [a] -> [a]
++ ShowS
forall a. Show a => a -> String
show String
s1)
| Bool
otherwise -> (Int64, String) -> Either String (Int64, String)
forall a b. b -> Either a b
Right (String -> Int64
forall a. Num a => String -> a
toInt String
s1, String
s2)
getMonth :: String -> Either String (Month, String)
getMonth :: String -> Either String (Month, String)
getMonth s :: String
s =
Int -> String -> Either String (String, String)
getNChar 3 String
s Either String (String, String)
-> ((String, String) -> Either String (Month, String))
-> Either String (Month, String)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \(s1 :: String
s1, s2 :: String
s2) -> String -> Either String Month
monthFromShort String
s1 Either String Month
-> (Month -> Either String (Month, String))
-> Either String (Month, String)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \m :: Month
m -> (Month, String) -> Either String (Month, String)
forall a b. b -> Either a b
Right (Month
m, String
s2)
getNChar :: Int -> String -> Either String (String, String)
getNChar :: Int -> String -> Either String (String, String)
getNChar n :: Int
n s :: String
s
| String -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length String
s1 Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
n = String -> Either String (String, String)
forall a b. a -> Either a b
Left ("not enough chars: expecting " String -> ShowS
forall a. [a] -> [a] -> [a]
++ Int -> String
forall a. Show a => a -> String
show Int
n String -> ShowS
forall a. [a] -> [a] -> [a]
++ " got " String -> ShowS
forall a. [a] -> [a] -> [a]
++ ShowS
forall a. Show a => a -> String
show String
s1)
| Bool
otherwise = (String, String) -> Either String (String, String)
forall a b. b -> Either a b
Right (String
s1, String
s2)
where
(s1 :: String
s1, s2 :: String
s2) = Int -> String -> (String, String)
forall a. Int -> [a] -> ([a], [a])
splitAt Int
n String
s
toInt :: Num a => String -> a
toInt :: String -> a
toInt = (a -> Char -> a) -> a -> String -> a
forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
foldl (\acc :: a
acc w :: Char
w -> a
acc a -> a -> a
forall a. Num a => a -> a -> a
* 10 a -> a -> a
forall a. Num a => a -> a -> a
+ Int -> a
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Char -> Int
ord Char
w Int -> Int -> Int
forall a. Num a => a -> a -> a
- Char -> Int
ord '0')) 0
allDigits :: String -> Bool
allDigits = [Bool] -> Bool
forall (t :: * -> *). Foldable t => t Bool -> Bool
and ([Bool] -> Bool) -> (String -> [Bool]) -> String -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Char -> Bool) -> String -> [Bool]
forall a b. (a -> b) -> [a] -> [b]
map Char -> Bool
isDigit
ini :: (DateTime, TimezoneOffset)
ini = (Date -> TimeOfDay -> DateTime
DateTime (Int -> Month -> Int -> Date
Date 0 (Int -> Month
forall a. Enum a => Int -> a
toEnum 0) 0) (Hours -> Minutes -> Seconds -> NanoSeconds -> TimeOfDay
TimeOfDay 0 0 0 0), Int -> TimezoneOffset
TimezoneOffset 0)
modDT :: (t -> a) -> (t, b) -> (a, b)
modDT f :: t -> a
f (dt :: t
dt, tz :: b
tz) = (t -> a
f t
dt, b
tz)
modDate :: (Date -> Date) -> (DateTime, b) -> (DateTime, b)
modDate f :: Date -> Date
f (DateTime d :: Date
d tp :: TimeOfDay
tp, tz :: b
tz) = (Date -> TimeOfDay -> DateTime
DateTime (Date -> Date
f Date
d) TimeOfDay
tp, b
tz)
modTime :: (TimeOfDay -> TimeOfDay) -> (DateTime, b) -> (DateTime, b)
modTime f :: TimeOfDay -> TimeOfDay
f (DateTime d :: Date
d tp :: TimeOfDay
tp, tz :: b
tz) = (Date -> TimeOfDay -> DateTime
DateTime Date
d (TimeOfDay -> TimeOfDay
f TimeOfDay
tp), b
tz)
modTZ :: (t -> b) -> (a, t) -> (a, b)
modTZ f :: t -> b
f (dt :: a
dt, tz :: t
tz) = (a
dt, t -> b
f t
tz)
setYear :: Int64 -> Date -> Date
setYear :: Int64 -> Date -> Date
setYear y :: Int64
y (Date _ m :: Month
m d :: Int
d) = Int -> Month -> Int -> Date
Date (Int64 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int64
y) Month
m Int
d
setMonth :: Month -> Date -> Date
setMonth m :: Month
m (Date y :: Int
y _ d :: Int
d) = Int -> Month -> Int -> Date
Date Int
y Month
m Int
d
setDay :: a -> Date -> Date
setDay d :: a
d (Date y :: Int
y m :: Month
m _) = Int -> Month -> Int -> Date
Date Int
y Month
m (a -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral a
d)
setHour :: Int64 -> TimeOfDay -> TimeOfDay
setHour h :: Int64
h (TimeOfDay _ m :: Minutes
m s :: Seconds
s ns :: NanoSeconds
ns) = Hours -> Minutes -> Seconds -> NanoSeconds -> TimeOfDay
TimeOfDay (Int64 -> Hours
Hours Int64
h) Minutes
m Seconds
s NanoSeconds
ns
setMin :: Int64 -> TimeOfDay -> TimeOfDay
setMin m :: Int64
m (TimeOfDay h :: Hours
h _ s :: Seconds
s ns :: NanoSeconds
ns) = Hours -> Minutes -> Seconds -> NanoSeconds -> TimeOfDay
TimeOfDay Hours
h (Int64 -> Minutes
Minutes Int64
m) Seconds
s NanoSeconds
ns
setSec :: Int64 -> TimeOfDay -> TimeOfDay
setSec s :: Int64
s (TimeOfDay h :: Hours
h m :: Minutes
m _ ns :: NanoSeconds
ns) = Hours -> Minutes -> Seconds -> NanoSeconds -> TimeOfDay
TimeOfDay Hours
h Minutes
m (Int64 -> Seconds
Seconds Int64
s) NanoSeconds
ns
setNS :: Int64 -> TimeOfDay -> TimeOfDay
setNS v :: Int64
v (TimeOfDay h :: Hours
h m :: Minutes
m s :: Seconds
s _ ) = Hours -> Minutes -> Seconds -> NanoSeconds -> TimeOfDay
TimeOfDay Hours
h Minutes
m Seconds
s (Int64 -> NanoSeconds
NanoSeconds Int64
v)
setNsMask :: (Int, Int) -> Int64 -> TimeOfDay -> TimeOfDay
setNsMask :: (Int, Int) -> Int64 -> TimeOfDay -> TimeOfDay
setNsMask (shift :: Int
shift, mask :: Int
mask) val :: Int64
val (TimeOfDay h :: Hours
h mins :: Minutes
mins seconds :: Seconds
seconds (NanoSeconds ns :: Int64
ns)) =
let (nsD :: Int64
nsD,keepL :: Int64
keepL) = Int64
ns Int64 -> Int64 -> (Int64, Int64)
forall a. Integral a => a -> a -> (a, a)
`divMod` Int64
s
(keepH :: Int64
keepH,_) = Int64
nsD Int64 -> Int64 -> (Int64, Int64)
forall a. Integral a => a -> a -> (a, a)
`divMod` Int64
m
v :: Int64
v = ((Int64
keepH Int64 -> Int64 -> Int64
forall a. Num a => a -> a -> a
* Int64
m Int64 -> Int64 -> Int64
forall a. Num a => a -> a -> a
+ Int64 -> Int64
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int64
val) Int64 -> Int64 -> Int64
forall a. Num a => a -> a -> a
* Int64
s) Int64 -> Int64 -> Int64
forall a. Num a => a -> a -> a
+ Int64
keepL
in Hours -> Minutes -> Seconds -> NanoSeconds -> TimeOfDay
TimeOfDay Hours
h Minutes
mins Seconds
seconds (Int64 -> NanoSeconds
NanoSeconds Int64
v)
where s :: Int64
s = 10 Int64 -> Int -> Int64
forall a b. (Num a, Integral b) => a -> b -> a
^ Int
shift
m :: Int64
m = 10 Int64 -> Int -> Int64
forall a b. (Num a, Integral b) => a -> b -> a
^ Int
mask
localTimeParse :: TimeFormat format
=> format
-> String
-> Maybe (LocalTime DateTime)
localTimeParse :: format -> String -> Maybe (LocalTime DateTime)
localTimeParse fmt :: format
fmt s :: String
s = ((TimeFormatElem, String) -> Maybe (LocalTime DateTime))
-> ((LocalTime DateTime, String) -> Maybe (LocalTime DateTime))
-> Either (TimeFormatElem, String) (LocalTime DateTime, String)
-> Maybe (LocalTime DateTime)
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either (Maybe (LocalTime DateTime)
-> (TimeFormatElem, String) -> Maybe (LocalTime DateTime)
forall a b. a -> b -> a
const Maybe (LocalTime DateTime)
forall a. Maybe a
Nothing) (LocalTime DateTime -> Maybe (LocalTime DateTime)
forall a. a -> Maybe a
Just (LocalTime DateTime -> Maybe (LocalTime DateTime))
-> ((LocalTime DateTime, String) -> LocalTime DateTime)
-> (LocalTime DateTime, String)
-> Maybe (LocalTime DateTime)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (LocalTime DateTime, String) -> LocalTime DateTime
forall a b. (a, b) -> a
fst) (Either (TimeFormatElem, String) (LocalTime DateTime, String)
-> Maybe (LocalTime DateTime))
-> Either (TimeFormatElem, String) (LocalTime DateTime, String)
-> Maybe (LocalTime DateTime)
forall a b. (a -> b) -> a -> b
$ format
-> String
-> Either (TimeFormatElem, String) (LocalTime DateTime, String)
forall format.
TimeFormat format =>
format
-> String
-> Either (TimeFormatElem, String) (LocalTime DateTime, String)
localTimeParseE format
fmt String
s
timeParseE :: TimeFormat format => format -> String
-> Either (TimeFormatElem, String) (DateTime, String)
timeParseE :: format
-> String -> Either (TimeFormatElem, String) (DateTime, String)
timeParseE fmt :: format
fmt timeString :: String
timeString = ((TimeFormatElem, String)
-> Either (TimeFormatElem, String) (DateTime, String))
-> ((LocalTime DateTime, String)
-> Either (TimeFormatElem, String) (DateTime, String))
-> Either (TimeFormatElem, String) (LocalTime DateTime, String)
-> Either (TimeFormatElem, String) (DateTime, String)
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either (TimeFormatElem, String)
-> Either (TimeFormatElem, String) (DateTime, String)
forall a b. a -> Either a b
Left (\(d :: LocalTime DateTime
d,s :: String
s) -> (DateTime, String)
-> Either (TimeFormatElem, String) (DateTime, String)
forall a b. b -> Either a b
Right (LocalTime DateTime -> DateTime
forall t. Time t => LocalTime t -> t
localTimeToGlobal LocalTime DateTime
d, String
s))
(Either (TimeFormatElem, String) (LocalTime DateTime, String)
-> Either (TimeFormatElem, String) (DateTime, String))
-> Either (TimeFormatElem, String) (LocalTime DateTime, String)
-> Either (TimeFormatElem, String) (DateTime, String)
forall a b. (a -> b) -> a -> b
$ format
-> String
-> Either (TimeFormatElem, String) (LocalTime DateTime, String)
forall format.
TimeFormat format =>
format
-> String
-> Either (TimeFormatElem, String) (LocalTime DateTime, String)
localTimeParseE format
fmt String
timeString
timeParse :: TimeFormat format => format -> String -> Maybe DateTime
timeParse :: format -> String -> Maybe DateTime
timeParse fmt :: format
fmt s :: String
s = LocalTime DateTime -> DateTime
forall t. Time t => LocalTime t -> t
localTimeToGlobal (LocalTime DateTime -> DateTime)
-> Maybe (LocalTime DateTime) -> Maybe DateTime
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
`fmap` format -> String -> Maybe (LocalTime DateTime)
forall format.
TimeFormat format =>
format -> String -> Maybe (LocalTime DateTime)
localTimeParse format
fmt String
s