module Data.HodaTime.Pattern.ZonedDateTime
(
pat_dayz
,pat_monthz
,pat_yearz
,ZonedDateTimeInfo(..)
)
where
import Data.HodaTime.Pattern.Internal
import Data.HodaTime.CalendarDateTime.Internal (IsCalendar, Month)
import Data.HodaTime.ZonedDateTime.Internal (ZonedDateTime(..))
import qualified Data.HodaTime.ZonedDateTime.Internal as ZDT
import Control.Monad.Catch (MonadThrow, throwM)
import qualified Data.Text as T
import qualified Data.Text.Lazy.Builder as TLB
import Control.Applicative ((<|>))
import Text.Parsec (digit, count, string, choice, oneOf, (<?>))
import qualified Text.Parsec as P (char)
import Formatting (left, (%.), later)
data ZonedDateTimeInfo cal m =
ZonedDateTimeInfo
{
forall cal (m :: * -> *). ZonedDateTimeInfo cal m -> m Int
day :: m Int
,forall cal (m :: * -> *). ZonedDateTimeInfo cal m -> m (Month cal)
month :: m (Month cal)
,forall cal (m :: * -> *). ZonedDateTimeInfo cal m -> m Int
year :: m Int
,forall cal (m :: * -> *). ZonedDateTimeInfo cal m -> Int
hour :: Int
,forall cal (m :: * -> *). ZonedDateTimeInfo cal m -> Int
minute :: Int
,forall cal (m :: * -> *). ZonedDateTimeInfo cal m -> Int
second :: Int
,forall cal (m :: * -> *). ZonedDateTimeInfo cal m -> Int
nanoSecond :: Int
,forall cal (m :: * -> *). ZonedDateTimeInfo cal m -> String
zone :: String
}
pat_yearz :: (MonadThrow m, IsCalendar cal) => Int -> Pattern (ZonedDateTimeInfo cal m -> ZonedDateTimeInfo cal m) (ZonedDateTime cal -> String) String
pat_yearz :: forall (m :: * -> *) cal.
(MonadThrow m, IsCalendar cal) =>
Int
-> Pattern
(ZonedDateTimeInfo cal m -> ZonedDateTimeInfo cal m)
(ZonedDateTime cal -> String)
String
pat_yearz Int
c = Parser (ZonedDateTimeInfo cal m -> ZonedDateTimeInfo cal m) String
-> Format String (ZonedDateTime cal -> String)
-> Pattern
(ZonedDateTimeInfo cal m -> ZonedDateTimeInfo cal m)
(ZonedDateTime cal -> String)
String
forall a b r. Parser a r -> Format r b -> Pattern a b r
Pattern Parser (ZonedDateTimeInfo cal m -> ZonedDateTimeInfo cal m) String
forall {u} {cal}.
ParsecT
String
u
Identity
(ZonedDateTimeInfo cal m -> ZonedDateTimeInfo cal m)
p Format String (ZonedDateTime cal -> String)
forall {r'}. Format r' (ZonedDateTime cal -> r')
fmt
where
rep :: a -> [a]
rep = Int -> a -> [a]
forall a. Int -> a -> [a]
replicate Int
c
zeros :: String
zeros = Char -> String
forall {a}. a -> [a]
rep Char
'0'
nines :: String
nines = Char -> String
forall {a}. a -> [a]
rep Char
'9'
p :: ParsecT
String
u
Identity
(ZonedDateTimeInfo cal m -> ZonedDateTimeInfo cal m)
p = (\Int
y -> \ZonedDateTimeInfo cal m
zdti -> ZonedDateTimeInfo cal m
zdti { year = pure y}) (Int -> ZonedDateTimeInfo cal m -> ZonedDateTimeInfo cal m)
-> (String -> Int)
-> String
-> ZonedDateTimeInfo cal m
-> ZonedDateTimeInfo cal m
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Int
forall a. Read a => String -> a
read (String -> ZonedDateTimeInfo cal m -> ZonedDateTimeInfo cal m)
-> ParsecT String u Identity String
-> ParsecT
String
u
Identity
(ZonedDateTimeInfo cal m -> ZonedDateTimeInfo cal m)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Int
-> ParsecT String u Identity Char
-> ParsecT String u Identity String
forall s (m :: * -> *) t u a.
Stream s m t =>
Int -> ParsecT s u m a -> ParsecT s u m [a]
count Int
c ParsecT String u Identity Char
forall s (m :: * -> *) u. Stream s m Char => ParsecT s u m Char
digit ParsecT
String
u
Identity
(ZonedDateTimeInfo cal m -> ZonedDateTimeInfo cal m)
-> String
-> ParsecT
String
u
Identity
(ZonedDateTimeInfo cal m -> ZonedDateTimeInfo cal m)
forall s u (m :: * -> *) a.
ParsecT s u m a -> String -> ParsecT s u m a
<?> String
"year: " String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
zeros String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"-" String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
nines
fmt :: Format r' (ZonedDateTime cal -> r')
fmt = Int -> Char -> Format r' (Builder -> r')
forall a r. Buildable a => Int -> Char -> Format r (a -> r)
left Int
c Char
'0' Format r' (Builder -> r')
-> Format r' (ZonedDateTime cal -> r')
-> Format r' (ZonedDateTime cal -> r')
forall r r' a.
Format r (Builder -> r') -> Format r' a -> Format r a
%. (ZonedDateTime cal -> Int) -> Format r' (ZonedDateTime cal -> r')
forall b a r. Show b => (a -> b) -> Format r (a -> r)
f_shown ZonedDateTime cal -> Int
forall cal. IsCalendar cal => ZonedDateTime cal -> Int
ZDT.year
pat_monthz :: IsCalendar cal => Int -> Pattern (ZonedDateTime cal -> ZonedDateTime cal) (ZonedDateTime cal -> String) String
pat_monthz :: forall cal.
IsCalendar cal =>
Int
-> Pattern
(ZonedDateTime cal -> ZonedDateTime cal)
(ZonedDateTime cal -> String)
String
pat_monthz = Int
-> Pattern
(ZonedDateTime cal -> ZonedDateTime cal)
(ZonedDateTime cal -> String)
String
forall a. HasCallStack => a
undefined
pat_dayz :: (MonadThrow m, IsCalendar cal) => Pattern (ZonedDateTimeInfo cal m -> ZonedDateTimeInfo cal m) (ZonedDateTime cal -> String) String
pat_dayz :: forall (m :: * -> *) cal.
(MonadThrow m, IsCalendar cal) =>
Pattern
(ZonedDateTimeInfo cal m -> ZonedDateTimeInfo cal m)
(ZonedDateTime cal -> String)
String
pat_dayz = Parser (ZonedDateTimeInfo cal m -> ZonedDateTimeInfo cal m) String
-> Format String (ZonedDateTime cal -> String)
-> Pattern
(ZonedDateTimeInfo cal m -> ZonedDateTimeInfo cal m)
(ZonedDateTime cal -> String)
String
forall a b r. Parser a r -> Format r b -> Pattern a b r
Pattern Parser (ZonedDateTimeInfo cal m -> ZonedDateTimeInfo cal m) String
forall {u} {cal}.
ParsecT
String
u
Identity
(ZonedDateTimeInfo cal m -> ZonedDateTimeInfo cal m)
p Format String (ZonedDateTime cal -> String)
forall {r'}. Format r' (ZonedDateTime cal -> r')
fmt
where
p :: ParsecT
String
u
Identity
(ZonedDateTimeInfo cal m -> ZonedDateTimeInfo cal m)
p = (\Int
d -> \ZonedDateTimeInfo cal m
zdti -> ZonedDateTimeInfo cal m
zdti { day = pure d}) (Int -> ZonedDateTimeInfo cal m -> ZonedDateTimeInfo cal m)
-> ParsecT String u Identity Int
-> ParsecT
String
u
Identity
(ZonedDateTimeInfo cal m -> ZonedDateTimeInfo cal m)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (ParsecT String u Identity Int
forall {u}. ParsecT String u Identity Int
p_a ParsecT String u Identity Int
-> ParsecT String u Identity Int -> ParsecT String u Identity Int
forall a.
ParsecT String u Identity a
-> ParsecT String u Identity a -> ParsecT String u Identity a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> ParsecT String u Identity Int
forall {u}. ParsecT String u Identity Int
p_b) ParsecT
String
u
Identity
(ZonedDateTimeInfo cal m -> ZonedDateTimeInfo cal m)
-> String
-> ParsecT
String
u
Identity
(ZonedDateTimeInfo cal m -> ZonedDateTimeInfo cal m)
forall s u (m :: * -> *) a.
ParsecT s u m a -> String -> ParsecT s u m a
<?> String
"day: 01-31"
p_a :: ParsecT String u Identity Int
p_a = Char -> Char -> Int
forall n. (Num n, Read n) => Char -> Char -> n
digitsToInt (Char -> Char -> Int)
-> ParsecT String u Identity Char
-> ParsecT String u Identity (Char -> Int)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> ParsecT String u Identity Char
forall s (m :: * -> *) u.
Stream s m Char =>
String -> ParsecT s u m Char
oneOf [Char
'0'..Char
'2'] ParsecT String u Identity (Char -> Int)
-> ParsecT String u Identity Char -> ParsecT String u Identity Int
forall a b.
ParsecT String u Identity (a -> b)
-> ParsecT String u Identity a -> ParsecT String u Identity b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ParsecT String u Identity Char
forall s (m :: * -> *) u. Stream s m Char => ParsecT s u m Char
digit
p_b :: ParsecT String u Identity Int
p_b = Char -> Char -> Int
forall n. (Num n, Read n) => Char -> Char -> n
digitsToInt (Char -> Char -> Int)
-> ParsecT String u Identity Char
-> ParsecT String u Identity (Char -> Int)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Char -> ParsecT String u Identity Char
forall s (m :: * -> *) u.
Stream s m Char =>
Char -> ParsecT s u m Char
P.char Char
'3' ParsecT String u Identity (Char -> Int)
-> ParsecT String u Identity Char -> ParsecT String u Identity Int
forall a b.
ParsecT String u Identity (a -> b)
-> ParsecT String u Identity a -> ParsecT String u Identity b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> String -> ParsecT String u Identity Char
forall s (m :: * -> *) u.
Stream s m Char =>
String -> ParsecT s u m Char
oneOf [Char
'0', Char
'1']
fmt :: Format r' (ZonedDateTime cal -> r')
fmt = Int -> Char -> Format r' (Builder -> r')
forall a r. Buildable a => Int -> Char -> Format r (a -> r)
left Int
2 Char
'0' Format r' (Builder -> r')
-> Format r' (ZonedDateTime cal -> r')
-> Format r' (ZonedDateTime cal -> r')
forall r r' a.
Format r (Builder -> r') -> Format r' a -> Format r a
%. (ZonedDateTime cal -> Int) -> Format r' (ZonedDateTime cal -> r')
forall b a r. Show b => (a -> b) -> Format r (a -> r)
f_shown ZonedDateTime cal -> Int
forall cal. IsCalendar cal => ZonedDateTime cal -> Int
ZDT.day