Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- data TimeObject = TimeObject {}
- data Form
- data IntervalDirection
- data TimeData = TimeData {}
- timedata' :: TimeData
- data TimeContext = TimeContext {}
- data InstantValue = InstantValue {}
- data SingleTimeValue
- data TimeValue = TimeValue SingleTimeValue [SingleTimeValue] (Maybe Text)
- type SeriesPredicate = TimeObject -> TimeContext -> ([TimeObject], [TimeObject])
- data AMPM
- data SeasonName
- data Season = Season {}
- newtype NoShow a = NoShow a
- data Predicate
- runPredicate :: Predicate -> SeriesPredicate
- emptyTimeDatePredicate :: Predicate
- mkEmptyPredicate :: Predicate
- mkSeriesPredicate :: SeriesPredicate -> Predicate
- mkSecondPredicate :: Int -> Predicate
- mkMinutePredicate :: Int -> Predicate
- mkHourPredicate :: Bool -> Int -> Predicate
- mkAMPMPredicate :: AMPM -> Predicate
- mkDayOfTheWeekPredicate :: Int -> Predicate
- mkDayOfTheMonthPredicate :: Int -> Predicate
- mkMonthPredicate :: Int -> Predicate
- mkYearPredicate :: Int -> Predicate
- mkIntersectPredicate :: Predicate -> Predicate -> Predicate
- mkReplaceIntersectPredicate :: Predicate -> Predicate -> Predicate -> Predicate
- mkTimeIntervalsPredicate :: TimeIntervalType -> Predicate -> Predicate -> Predicate
- containsTimeIntervalsPredicate :: Predicate -> Bool
- diffStartTime :: TimeObject -> TimeObject -> NominalDiffTime
- isEmptyPredicate :: Predicate -> Bool
- seasonStart :: Season -> Day
- seasonEnd :: Season -> Day
- nextSeason :: Season -> Season
- prevSeason :: Season -> Season
- seasonOf :: Day -> Season
- seasonPredicate :: Predicate
- weekdayPredicate :: Predicate
- periodicPredicate :: Grain -> Int -> TimeObject -> Predicate
- toMidnight :: Day -> UTCTime
- runSecondPredicate :: Int -> SeriesPredicate
- runMinutePredicate :: Int -> SeriesPredicate
- runHourPredicate :: Maybe AMPM -> Bool -> Int -> SeriesPredicate
- runAMPMPredicate :: AMPM -> SeriesPredicate
- runDayOfTheWeekPredicate :: Int -> SeriesPredicate
- runDayOfTheMonthPredicate :: Int -> SeriesPredicate
- runMonthPredicate :: Int -> SeriesPredicate
- runYearPredicate :: Int -> SeriesPredicate
- safeMax :: Int
- runReplaceIntersectPredicate :: Predicate -> Predicate -> Predicate -> SeriesPredicate
- runComposeWithReplacement :: SeriesPredicate -> SeriesPredicate -> SeriesPredicate -> SeriesPredicate
- runIntersectPredicate :: Predicate -> Predicate -> SeriesPredicate
- runCompose :: SeriesPredicate -> SeriesPredicate -> SeriesPredicate
- runTimeIntervalsPredicate :: TimeIntervalType -> Predicate -> Predicate -> SeriesPredicate
- safeMaxInterval :: Int
- timeSeqMap :: Bool -> (TimeObject -> TimeContext -> Maybe TimeObject) -> Predicate -> SeriesPredicate
- timeSequence :: Grain -> Int -> TimeObject -> ([TimeObject], [TimeObject])
- pad :: Int -> Int -> Text
- timezoneOffset :: TimeZone -> Text
- toRFC3339 :: ZonedTime -> Text
- instantValue :: TimeZoneSeries -> UTCTime -> Grain -> InstantValue
- timeValue :: TimeZoneSeries -> TimeObject -> SingleTimeValue
- openInterval :: TimeZoneSeries -> IntervalDirection -> TimeObject -> SingleTimeValue
- timeRound :: TimeObject -> Grain -> TimeObject
- timePlus :: TimeObject -> Grain -> Integer -> TimeObject
- timePlusEnd :: TimeObject -> Grain -> Integer -> TimeObject
- timeEnd :: TimeObject -> UTCTime
- timeStartingAtTheEndOf :: TimeObject -> TimeObject
- data TimeIntervalType
- timeInterval :: TimeIntervalType -> TimeObject -> TimeObject -> TimeObject
- timeStartsBeforeTheEndOf :: TimeObject -> TimeObject -> Bool
- timeBefore :: TimeObject -> TimeObject -> Bool
- timeIntersect :: TimeObject -> TimeObject -> Maybe TimeObject
Documentation
data TimeObject Source #
Instances
Eq TimeObject Source # | |
Defined in Duckling.Time.Types (==) :: TimeObject -> TimeObject -> Bool # (/=) :: TimeObject -> TimeObject -> Bool # | |
Show TimeObject Source # | |
Defined in Duckling.Time.Types showsPrec :: Int -> TimeObject -> ShowS # show :: TimeObject -> String # showList :: [TimeObject] -> ShowS # |
Instances
Eq Form Source # | |
Ord Form Source # | |
Show Form Source # | |
Generic Form Source # | |
Hashable Form Source # | |
Defined in Duckling.Time.Types | |
NFData Form Source # | |
Defined in Duckling.Time.Types | |
type Rep Form Source # | |
Defined in Duckling.Time.Types type Rep Form = D1 ('MetaData "Form" "Duckling.Time.Types" "duckling-0.2.0.0-4AU1pRwMU7E8YjNdB7ILfy" 'False) ((C1 ('MetaCons "DayOfWeek" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "TimeOfDay" 'PrefixI 'True) (S1 ('MetaSel ('Just "hours") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Int)) :*: S1 ('MetaSel ('Just "is12H") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool))) :+: (C1 ('MetaCons "Month" 'PrefixI 'True) (S1 ('MetaSel ('Just "month") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int)) :+: C1 ('MetaCons "PartOfDay" 'PrefixI 'False) (U1 :: Type -> Type))) |
data IntervalDirection Source #
Instances
Instances
Eq TimeData Source # | |
Ord TimeData Source # | |
Defined in Duckling.Time.Types | |
Show TimeData Source # | |
Hashable TimeData Source # | |
Defined in Duckling.Time.Types | |
NFData TimeData Source # | |
Defined in Duckling.Time.Types | |
Resolve TimeData Source # | |
Defined in Duckling.Time.Types type ResolvedValue TimeData Source # | |
type ResolvedValue TimeData Source # | |
Defined in Duckling.Time.Types |
data TimeContext Source #
data InstantValue Source #
Instances
Eq InstantValue Source # | |
Defined in Duckling.Time.Types (==) :: InstantValue -> InstantValue -> Bool # (/=) :: InstantValue -> InstantValue -> Bool # | |
Show InstantValue Source # | |
Defined in Duckling.Time.Types showsPrec :: Int -> InstantValue -> ShowS # show :: InstantValue -> String # showList :: [InstantValue] -> ShowS # | |
ToJSON InstantValue Source # | |
Defined in Duckling.Time.Types toJSON :: InstantValue -> Value # toEncoding :: InstantValue -> Encoding # toJSONList :: [InstantValue] -> Value # toEncodingList :: [InstantValue] -> Encoding # |
data SingleTimeValue Source #
SimpleValue InstantValue | |
IntervalValue (InstantValue, InstantValue) | |
OpenIntervalValue (InstantValue, IntervalDirection) |
Instances
Eq SingleTimeValue Source # | |
Defined in Duckling.Time.Types (==) :: SingleTimeValue -> SingleTimeValue -> Bool # (/=) :: SingleTimeValue -> SingleTimeValue -> Bool # | |
Show SingleTimeValue Source # | |
Defined in Duckling.Time.Types showsPrec :: Int -> SingleTimeValue -> ShowS # show :: SingleTimeValue -> String # showList :: [SingleTimeValue] -> ShowS # | |
ToJSON SingleTimeValue Source # | |
Defined in Duckling.Time.Types toJSON :: SingleTimeValue -> Value # toEncoding :: SingleTimeValue -> Encoding # toJSONList :: [SingleTimeValue] -> Value # toEncodingList :: [SingleTimeValue] -> Encoding # |
type SeriesPredicate = TimeObject -> TimeContext -> ([TimeObject], [TimeObject]) Source #
Return a tuple of (past, future) elements
data SeasonName Source #
Instances
Regular seasons of the Northern Hemisphere.
NoShow a |
mkSecondPredicate :: Int -> Predicate Source #
mkMinutePredicate :: Int -> Predicate Source #
mkAMPMPredicate :: AMPM -> Predicate Source #
mkMonthPredicate :: Int -> Predicate Source #
mkYearPredicate :: Int -> Predicate Source #
diffStartTime :: TimeObject -> TimeObject -> NominalDiffTime Source #
isEmptyPredicate :: Predicate -> Bool Source #
seasonStart :: Season -> Day Source #
nextSeason :: Season -> Season Source #
prevSeason :: Season -> Season Source #
periodicPredicate :: Grain -> Int -> TimeObject -> Predicate Source #
toMidnight :: Day -> UTCTime Source #
runHourPredicate :: Maybe AMPM -> Bool -> Int -> SeriesPredicate Source #
runComposeWithReplacement :: SeriesPredicate -> SeriesPredicate -> SeriesPredicate -> SeriesPredicate Source #
timeSeqMap :: Bool -> (TimeObject -> TimeContext -> Maybe TimeObject) -> Predicate -> SeriesPredicate Source #
Applies f
to each interval yielded by g
.
| Intervals including "now" are in the future.
timeSequence :: Grain -> Int -> TimeObject -> ([TimeObject], [TimeObject]) Source #
timezoneOffset :: TimeZone -> Text Source #
Return the timezone offset portion of the RFC3339 format, e.g. "-02:00".
toRFC3339 :: ZonedTime -> Text Source #
Return a RFC3339 formatted time, e.g. "2013-02-12T04:30:00.000-02:00". | Backward-compatible with Duckling: fraction of second is milli and padded.
instantValue :: TimeZoneSeries -> UTCTime -> Grain -> InstantValue Source #
timeValue :: TimeZoneSeries -> TimeObject -> SingleTimeValue Source #
timeRound :: TimeObject -> Grain -> TimeObject Source #
timePlus :: TimeObject -> Grain -> Integer -> TimeObject Source #
timePlusEnd :: TimeObject -> Grain -> Integer -> TimeObject Source #
Shifts the whole interval by n units of theGrain Returned interval has the same length as the input one
timeEnd :: TimeObject -> UTCTime Source #
data TimeIntervalType Source #
Closed if the interval between A and B should include B Open if the interval should end right before B
Instances
Eq TimeIntervalType Source # | |
Defined in Duckling.Time.Types (==) :: TimeIntervalType -> TimeIntervalType -> Bool # (/=) :: TimeIntervalType -> TimeIntervalType -> Bool # | |
Show TimeIntervalType Source # | |
Defined in Duckling.Time.Types showsPrec :: Int -> TimeIntervalType -> ShowS # show :: TimeIntervalType -> String # showList :: [TimeIntervalType] -> ShowS # |
timeInterval :: TimeIntervalType -> TimeObject -> TimeObject -> TimeObject Source #
timeStartsBeforeTheEndOf :: TimeObject -> TimeObject -> Bool Source #
timeBefore :: TimeObject -> TimeObject -> Bool Source #
timeIntersect :: TimeObject -> TimeObject -> Maybe TimeObject Source #
Intersection between two TimeObject
.
The resulting grain and end fields are the smallest.
Prefers intervals when the range is equal.