predicate-typed-0.7.3.0: Predicates, Refinement types and Dsl

Safe HaskellNone
LanguageHaskell2010

Predicate.Data.DateTime

Contents

Description

promoted date time functions

Synopsis

format

data FormatTimeP p q Source #

type level expression representing a formatted time similar to formatTime using a type level Symbol to get the formatting string

>>> pz @(FormatTimeP "%F %T" Id) (readNote @LocalTime "invalid localtime" "2019-05-24 05:19:59")
PresentT "2019-05-24 05:19:59"
>>> pz @(FormatTimeP (Fst Id) (Snd Id)) ("the date is %d/%m/%Y", readNote @Day "invalid day" "2019-05-24")
PresentT "the date is 24/05/2019"
>>> pl @(FormatTimeP "%Y-%m-%d" Id) (readNote @Day "invalid day" "2019-08-17")
Present "2019-08-17" (FormatTimeP (%Y-%m-%d) 2019-08-17 | 2019-08-17)
PresentT "2019-08-17"
Instances
(PP p x ~ String, FormatTime (PP q x), P p x, Show (PP q x), P q x) => P (FormatTimeP p q :: Type) x Source # 
Instance details

Defined in Predicate.Data.DateTime

Associated Types

type PP (FormatTimeP p q) x :: Type Source #

Methods

eval :: MonadEval m => proxy (FormatTimeP p q) -> POpts -> x -> m (TT (PP (FormatTimeP p q) x)) Source #

type PP (FormatTimeP p q :: Type) x Source # 
Instance details

Defined in Predicate.Data.DateTime

type PP (FormatTimeP p q :: Type) x = String

constructors

data ParseTimeP (t :: Type) p q Source #

similar to parseTimeM

>>> pl @(ParseTimeP TimeOfDay "%H:%M%S" Id) "14:04:61"
Error ParseTimeP TimeOfDay (%H:%M%S) failed to parse
FailT "ParseTimeP TimeOfDay (%H:%M%S) failed to parse"
>>> pl @(ParseTimeP UTCTime "%F %T" Id) "1999-01-01 12:12:12"
Present 1999-01-01 12:12:12 UTC (ParseTimeP UTCTime (%F %T) 1999-01-01 12:12:12 UTC | fmt=%F %T | "1999-01-01 12:12:12")
PresentT 1999-01-01 12:12:12 UTC
Instances
P (ParseTimePT t p q) x => P (ParseTimeP t p q :: Type) x Source # 
Instance details

Defined in Predicate.Data.DateTime

Associated Types

type PP (ParseTimeP t p q) x :: Type Source #

Methods

eval :: MonadEval m => proxy (ParseTimeP t p q) -> POpts -> x -> m (TT (PP (ParseTimeP t p q) x)) Source #

type PP (ParseTimeP t p q :: Type) x Source # 
Instance details

Defined in Predicate.Data.DateTime

type PP (ParseTimeP t p q :: Type) x

data ParseTimeP' t p q Source #

similar to parseTimeM where 't' is the ParseTime type, 'p' is the datetime format and 'q' points to the content to parse

>>> pz @(ParseTimeP LocalTime "%F %T" Id) "2019-05-24 05:19:59"
PresentT 2019-05-24 05:19:59
>>> pz @(ParseTimeP LocalTime "%F %T" "2019-05-24 05:19:59") (Right "never used")
PresentT 2019-05-24 05:19:59

keeping 'q' as we might want to extract from a tuple

Instances
(ParseTime (PP t a), Typeable (PP t a), Show (PP t a), P p a, P q a, PP p a ~ String, PP q a ~ String) => P (ParseTimeP' t p q :: Type) a Source # 
Instance details

Defined in Predicate.Data.DateTime

Associated Types

type PP (ParseTimeP' t p q) a :: Type Source #

Methods

eval :: MonadEval m => proxy (ParseTimeP' t p q) -> POpts -> a -> m (TT (PP (ParseTimeP' t p q) a)) Source #

type PP (ParseTimeP' t p q :: Type) a Source # 
Instance details

Defined in Predicate.Data.DateTime

type PP (ParseTimeP' t p q :: Type) a = PP t a

data ParseTimes (t :: Type) p q Source #

A convenience method to match against many different datetime formats to find the first match

>>> pz @(ParseTimes LocalTime '["%Y-%m-%d %H:%M:%S", "%m/%d/%y %H:%M:%S", "%B %d %Y %H:%M:%S", "%Y-%m-%dT%H:%M:%S"] "03/11/19 01:22:33") ()
PresentT 2019-03-11 01:22:33
>>> pz @(ParseTimes LocalTime (Fst Id) (Snd Id)) (["%Y-%m-%d %H:%M:%S", "%m/%d/%y %H:%M:%S", "%B %d %Y %H:%M:%S", "%Y-%m-%dT%H:%M:%S"], "03/11/19 01:22:33")
PresentT 2019-03-11 01:22:33
>>> pl @(Map (ParseTimes Day '["%Y-%m-%d", "%m/%d/%y", "%b %d %Y"] Id) Id) ["2001-01-01", "Jan 24 2009", "03/29/0x7"]
Error no match on (03/29/0x7) (Map(i=2, a="03/29/0x7") excnt=1)
FailT "no match on (03/29/0x7)"
>>> pl @(Map (ParseTimes Day '["%Y-%m-%d", "%m/%d/%y", "%b %d %Y"] Id) Id) ["2001-01-01", "Jan 24 2009", "03/29/07"]
Present [2001-01-01,2009-01-24,2007-03-29] (Map [2001-01-01,2009-01-24,2007-03-29] | ["2001-01-01","Jan 24 2009","03/29/07"])
PresentT [2001-01-01,2009-01-24,2007-03-29]
Instances
P (ParseTimesT t p q) x => P (ParseTimes t p q :: Type) x Source # 
Instance details

Defined in Predicate.Data.DateTime

Associated Types

type PP (ParseTimes t p q) x :: Type Source #

Methods

eval :: MonadEval m => proxy (ParseTimes t p q) -> POpts -> x -> m (TT (PP (ParseTimes t p q) x)) Source #

type PP (ParseTimes t p q :: Type) x Source # 
Instance details

Defined in Predicate.Data.DateTime

type PP (ParseTimes t p q :: Type) x

data ParseTimes' t p q Source #

A convenience method to match against many different datetime formats to find the first match

Instances
(ParseTime (PP t a), Typeable (PP t a), Show (PP t a), P p a, P q a, PP p a ~ [String], PP q a ~ String) => P (ParseTimes' t p q :: Type) a Source # 
Instance details

Defined in Predicate.Data.DateTime

Associated Types

type PP (ParseTimes' t p q) a :: Type Source #

Methods

eval :: MonadEval m => proxy (ParseTimes' t p q) -> POpts -> a -> m (TT (PP (ParseTimes' t p q) a)) Source #

type PP (ParseTimes' t p q :: Type) a Source # 
Instance details

Defined in Predicate.Data.DateTime

type PP (ParseTimes' t p q :: Type) a = PP t a

data MkDay p Source #

create a Day from three int values passed in as year month and day

>>> pz @(MkDay '(1,2,3) >> 'Just Id) ()
PresentT 0001-02-03
>>> pz @(Just (MkDay '(1,2,3))) 1
PresentT 0001-02-03
>>> pz @(MkDay Id) (2019,12,30)
PresentT (Just 2019-12-30)
>>> pz @(MkDay Id) (1999,3,13)
PresentT (Just 1999-03-13)
Instances
P (MkDayT p) x => P (MkDay p :: Type) x Source # 
Instance details

Defined in Predicate.Data.DateTime

Associated Types

type PP (MkDay p) x :: Type Source #

Methods

eval :: MonadEval m => proxy (MkDay p) -> POpts -> x -> m (TT (PP (MkDay p) x)) Source #

type PP (MkDay p :: Type) x Source # 
Instance details

Defined in Predicate.Data.DateTime

type PP (MkDay p :: Type) x

data MkDay' p q r Source #

create a Day from three int values passed in as year month and day

>>> pz @(MkDay' (Fst Id) (Snd Id) (Thd Id)) (2019,99,99999)
PresentT Nothing
Instances
(P p x, P q x, P r x, PP p x ~ Int, PP q x ~ Int, PP r x ~ Int) => P (MkDay' p q r :: Type) x Source # 
Instance details

Defined in Predicate.Data.DateTime

Associated Types

type PP (MkDay' p q r) x :: Type Source #

Methods

eval :: MonadEval m => proxy (MkDay' p q r) -> POpts -> x -> m (TT (PP (MkDay' p q r) x)) Source #

type PP (MkDay' p q r :: Type) x Source # 
Instance details

Defined in Predicate.Data.DateTime

type PP (MkDay' p q r :: Type) x = Maybe Day

data MkDayExtra p Source #

create a Day, week number, and the day of the week from three numbers passed in as year month and day

>>> pz @(MkDayExtra '(1,2,3) >> 'Just Id >> Fst Id) ()
PresentT 0001-02-03
>>> pz @(Fst (Just (MkDayExtra '(1,2,3)))) 1
PresentT 0001-02-03
>>> pz @(MkDayExtra Id) (2019,12,30)
PresentT (Just (2019-12-30,1,1))
>>> pz @(MkDayExtra Id) (1999,3,13)
PresentT (Just (1999-03-13,10,6))
Instances
P (MkDayExtraT p) x => P (MkDayExtra p :: Type) x Source # 
Instance details

Defined in Predicate.Data.DateTime

Associated Types

type PP (MkDayExtra p) x :: Type Source #

Methods

eval :: MonadEval m => proxy (MkDayExtra p) -> POpts -> x -> m (TT (PP (MkDayExtra p) x)) Source #

type PP (MkDayExtra p :: Type) x Source # 
Instance details

Defined in Predicate.Data.DateTime

type PP (MkDayExtra p :: Type) x

data MkDayExtra' p q r Source #

create a Day, week number, and the day of the week from three numbers passed in as year month and day

>>> pz @(MkDayExtra' (Fst Id) (Snd Id) (Thd Id)) (2019,99,99999)
PresentT Nothing
Instances
(P p x, P q x, P r x, PP p x ~ Int, PP q x ~ Int, PP r x ~ Int) => P (MkDayExtra' p q r :: Type) x Source # 
Instance details

Defined in Predicate.Data.DateTime

Associated Types

type PP (MkDayExtra' p q r) x :: Type Source #

Methods

eval :: MonadEval m => proxy (MkDayExtra' p q r) -> POpts -> x -> m (TT (PP (MkDayExtra' p q r) x)) Source #

type PP (MkDayExtra' p q r :: Type) x Source # 
Instance details

Defined in Predicate.Data.DateTime

type PP (MkDayExtra' p q r :: Type) x = Maybe (Day, Int, Int)

data MkTime p Source #

create a TimeOfDay from a three-tuple of year month and day

>>> pz @(MkTime '(1,2,3 % 12345)) ()
PresentT 01:02:00.000243013365
>>> pz @(MkTime Id) (12,13,65)
PresentT 12:13:65
>>> pz @(MkTime Id) (17,3,13)
PresentT 17:03:13
Instances
P (MkTimeT p) x => P (MkTime p :: Type) x Source # 
Instance details

Defined in Predicate.Data.DateTime

Associated Types

type PP (MkTime p) x :: Type Source #

Methods

eval :: MonadEval m => proxy (MkTime p) -> POpts -> x -> m (TT (PP (MkTime p) x)) Source #

type PP (MkTime p :: Type) x Source # 
Instance details

Defined in Predicate.Data.DateTime

type PP (MkTime p :: Type) x

data MkTime' p q r Source #

create a TimeOfDay from three int values passed in as year month and day

>>> pz @(MkTime' (Fst Id) (Snd Id) (Thd Id)) (13,99,99999)
PresentT 13:99:99999
Instances
(P p x, P q x, P r x, PP p x ~ Int, PP q x ~ Int, PP r x ~ Rational) => P (MkTime' p q r :: Type) x Source # 
Instance details

Defined in Predicate.Data.DateTime

Associated Types

type PP (MkTime' p q r) x :: Type Source #

Methods

eval :: MonadEval m => proxy (MkTime' p q r) -> POpts -> x -> m (TT (PP (MkTime' p q r) x)) Source #

type PP (MkTime' p q r :: Type) x Source # 
Instance details

Defined in Predicate.Data.DateTime

type PP (MkTime' p q r :: Type) x = TimeOfDay

data PosixToUTCTime p Source #

convert posix time (seconds since 01-01-1970) to UTCTime

>>> pl @(PosixToUTCTime Id) 1593384312
Present 2020-06-28 22:45:12 UTC (PosixToUTCTime 2020-06-28 22:45:12 UTC | 1593384312 % 1)
PresentT 2020-06-28 22:45:12 UTC
>>> pl @(PosixToUTCTime Id >> UTCTimeToPosix Id) 1593384312
Present 1593384312 % 1 ((>>) 1593384312 % 1 | {UTCTimeToPosix 1593384312 % 1 | 2020-06-28 22:45:12 UTC})
PresentT (1593384312 % 1)
>>> pl @(PosixToUTCTime (Id % 1000)) 1593384312000
Present 2020-06-28 22:45:12 UTC (PosixToUTCTime 2020-06-28 22:45:12 UTC | 1593384312 % 1)
PresentT 2020-06-28 22:45:12 UTC
>>> pl @(PosixToUTCTime Id) (3600*4+60*7+12)
Present 1970-01-01 04:07:12 UTC (PosixToUTCTime 1970-01-01 04:07:12 UTC | 14832 % 1)
PresentT 1970-01-01 04:07:12 UTC
>>> pz @(Rescan "^Date\\((\\d+)([^\\)]+)\\)" Id >> Head Id >> Snd Id >> ReadP Integer (Id !! 0) >> PosixToUTCTime (Id % 1000)) "Date(1530144000000+0530)"
PresentT 2018-06-28 00:00:00 UTC
Instances
(PP p x ~ Rational, P p x) => P (PosixToUTCTime p :: Type) x Source # 
Instance details

Defined in Predicate.Data.DateTime

Associated Types

type PP (PosixToUTCTime p) x :: Type Source #

Methods

eval :: MonadEval m => proxy (PosixToUTCTime p) -> POpts -> x -> m (TT (PP (PosixToUTCTime p) x)) Source #

type PP (PosixToUTCTime p :: Type) x Source # 
Instance details

Defined in Predicate.Data.DateTime

type PP (PosixToUTCTime p :: Type) x = UTCTime

destructors

data UnMkDay p Source #

uncreate a Day returning year month and day

>>> pz @(UnMkDay Id) (readNote "invalid day" "2019-12-30")
PresentT (2019,12,30)
Instances
(PP p x ~ Day, P p x) => P (UnMkDay p :: Type) x Source # 
Instance details

Defined in Predicate.Data.DateTime

Associated Types

type PP (UnMkDay p) x :: Type Source #

Methods

eval :: MonadEval m => proxy (UnMkDay p) -> POpts -> x -> m (TT (PP (UnMkDay p) x)) Source #

type PP (UnMkDay p :: Type) x Source # 
Instance details

Defined in Predicate.Data.DateTime

type PP (UnMkDay p :: Type) x = (Int, Int, Int)

data ToWeekDate p Source #

get the day of the week

>>> pz @(Just (MkDay '(2020,7,11)) >> '(UnMkDay Id, ToWeekYear Id,ToWeekDate Id)) ()
PresentT ((2020,7,11),28,(6,"Saturday"))
Instances
(P p x, PP p x ~ Day) => P (ToWeekDate p :: Type) x Source # 
Instance details

Defined in Predicate.Data.DateTime

Associated Types

type PP (ToWeekDate p) x :: Type Source #

Methods

eval :: MonadEval m => proxy (ToWeekDate p) -> POpts -> x -> m (TT (PP (ToWeekDate p) x)) Source #

type PP (ToWeekDate p :: Type) x Source # 
Instance details

Defined in Predicate.Data.DateTime

type PP (ToWeekDate p :: Type) x = (Int, String)

data ToWeekYear p Source #

get week number of the year

>>> pz @(Just (MkDay '(2020,7,11)) >> ToWeekYear Id) ()
PresentT 28
Instances
(P p x, PP p x ~ Day) => P (ToWeekYear p :: Type) x Source # 
Instance details

Defined in Predicate.Data.DateTime

Associated Types

type PP (ToWeekYear p) x :: Type Source #

Methods

eval :: MonadEval m => proxy (ToWeekYear p) -> POpts -> x -> m (TT (PP (ToWeekYear p) x)) Source #

type PP (ToWeekYear p :: Type) x Source # 
Instance details

Defined in Predicate.Data.DateTime

type PP (ToWeekYear p :: Type) x = Int

data ToDay p Source #

extract Day from a DateTime

>>> pz @(ReadP UTCTime Id >> ToDay Id) "2020-07-06 12:11:13Z"
PresentT 2020-07-06
Instances
(P p x, Show (PP p x), ToDayC (PP p x)) => P (ToDay p :: Type) x Source # 
Instance details

Defined in Predicate.Data.DateTime

Associated Types

type PP (ToDay p) x :: Type Source #

Methods

eval :: MonadEval m => proxy (ToDay p) -> POpts -> x -> m (TT (PP (ToDay p) x)) Source #

type PP (ToDay p :: Type) x Source # 
Instance details

Defined in Predicate.Data.DateTime

type PP (ToDay p :: Type) x = Day

data ToTime p Source #

extract TimeOfDay from DateTime

>>> pz @(ReadP UTCTime Id >> ToDay Id) "2020-07-06 12:11:13Z"
PresentT 2020-07-06
Instances
(P p x, Show (PP p x), ToTimeC (PP p x)) => P (ToTime p :: Type) x Source # 
Instance details

Defined in Predicate.Data.DateTime

Associated Types

type PP (ToTime p) x :: Type Source #

Methods

eval :: MonadEval m => proxy (ToTime p) -> POpts -> x -> m (TT (PP (ToTime p) x)) Source #

type PP (ToTime p :: Type) x Source # 
Instance details

Defined in Predicate.Data.DateTime

type PP (ToTime p :: Type) x = TimeOfDay

data UnMkTime p Source #

uncreate a TimeOfDay returning hour minute seconds picoseconds

>>> pz @(ReadP UTCTime "2019-01-01 12:13:14.1234Z" >> ToTime Id >> UnMkTime Id) ()
PresentT (12,13,70617 % 5000)
>>> pz @(ReadP UTCTime Id >> ToTime Id >> UnMkTime Id) "2020-07-22 08:01:14.127Z"
PresentT (8,1,14127 % 1000)
>>> pz @(ReadP ZonedTime Id >> '(UnMkDay (ToDay Id), UnMkTime (ToTime Id))) "2020-07-11 11:41:12.333 CET"
PresentT ((2020,7,11),(11,41,12333 % 1000))
Instances
(PP p x ~ TimeOfDay, P p x) => P (UnMkTime p :: Type) x Source # 
Instance details

Defined in Predicate.Data.DateTime

Associated Types

type PP (UnMkTime p) x :: Type Source #

Methods

eval :: MonadEval m => proxy (UnMkTime p) -> POpts -> x -> m (TT (PP (UnMkTime p) x)) Source #

type PP (UnMkTime p :: Type) x Source # 
Instance details

Defined in Predicate.Data.DateTime

type PP (UnMkTime p :: Type) x = (Int, Int, Rational)

data UTCTimeToPosix p Source #

convert UTCTime to posix time (seconds since 01-01-1970)

>>> pl @(ReadP UTCTime Id >> UTCTimeToPosix Id) "2020-06-28 22:45:12 UTC"
Present 1593384312 % 1 ((>>) 1593384312 % 1 | {UTCTimeToPosix 1593384312 % 1 | 2020-06-28 22:45:12 UTC})
PresentT (1593384312 % 1)
>>> pz @(Rescan "^Date\\((\\d+)([^\\)]+)\\)" Id >> Head Id >> Snd Id >> ((ReadP Integer (Id !! 0) >> PosixToUTCTime (Id % 1000)) &&& ReadP TimeZone (Id !! 1))) "Date(1530144000000+0530)"
PresentT (2018-06-28 00:00:00 UTC,+0530)

not so useful: instead use ParseTimeP FormatTimeP with %s %q %z etc

>>> pz @(ParseTimeP ZonedTime "%s%Q%z" Id)  "153014400.000+0530"
PresentT 1974-11-07 05:30:00 +0530
Instances
(PP p x ~ UTCTime, P p x) => P (UTCTimeToPosix p :: Type) x Source # 
Instance details

Defined in Predicate.Data.DateTime

Associated Types

type PP (UTCTimeToPosix p) x :: Type Source #

Methods

eval :: MonadEval m => proxy (UTCTimeToPosix p) -> POpts -> x -> m (TT (PP (UTCTimeToPosix p) x)) Source #

type PP (UTCTimeToPosix p :: Type) x Source # 
Instance details

Defined in Predicate.Data.DateTime

type PP (UTCTimeToPosix p :: Type) x = Rational