Safe Haskell | None |
---|---|
Language | Haskell2010 |
- class AsDay p f s where
- dayParse :: String -> Either String Day
- boundFromWrapped :: (Rewrapped s s, Rewrapped e e, Unwrapped s ~ Day, Unwrapped e ~ Day, Rewrapped hs hs, Rewrapped he he, Unwrapped hs ~ Natural, Unwrapped he ~ Natural) => s -> e -> hs -> he -> (LowerTimeBound, UpperTimeBound)
- wrappedRange :: (Rewrapped a a, Rewrapped b b, Rewrapped c c, Unwrapped a ~ t, Unwrapped b ~ t, Unwrapped c ~ t, Ord t) => (t -> c) -> (t -> t) -> a -> b -> NonEmpty c
- strToHourNatural :: String -> Either String Natural
- utcRangeHours :: (Rewrapped start start, Rewrapped end end, Unwrapped start ~ UTCTime, Unwrapped end ~ UTCTime) => start -> end -> NonEmpty UTCTime
- datesInRange :: (Rewrapped a a, Rewrapped b b, Unwrapped a ~ Day, Unwrapped b ~ Day) => a -> b -> NonEmpty DayInRange
- buildRanges :: StartDate -> Maybe EndDate -> StartHour -> EndHour -> Ranges
Documentation
class AsDay p f s where Source #
(Choice p, Applicative f) => AsDay p f String Source # |
|
(Choice p, Applicative f) => AsDay p f (Integer, Int, Int) Source # |
|
>>>
import Control.Lens
>>>
import Data.Time
>>>
import Prelude (succ)
>>>
:set -XFlexibleContexts
>>>
let d = fromGregorian (2017 :: Integer) (2 :: Int) (25 :: Int)
>>>
let startD = _Wrapped # (fromGregorian (2017 :: Integer) (2 :: Int) (25 :: Int)) :: StartDate
>>>
let endD = _Wrapped # (fromGregorian (2017 :: Integer) (2 :: Int) (27 :: Int)) :: EndDate
>>>
let startH = (_Wrapped # (3 :: Natural)) :: StartHour
>>>
let endH = (_Wrapped # (5 :: Natural)) :: EndHour
dayParse :: String -> Either String Day Source #
Parse some common date formats to a Day
Examples:
>>>
dayParse "2017-01-09"
Right 2017-01-09>>>
dayParse "09/01/2017"
Right 2017-01-09>>>
dayParse "30/02/2017"
Left "Unable to parse Date Accepts [yyyy-mm-dd, yyyymmdd, mm/dd/yy, dd/mm/yyyy]: 30/02/2017">>>
dayParse "20170109"
Right 2017-01-09>>>
dayParse "010917"
Left "Unable to parse Date Accepts [yyyy-mm-dd, yyyymmdd, mm/dd/yy, dd/mm/yyyy]: 010917">>>
dayParse "02/13/17"
Right 2017-02-13>>>
dayParse "2017-01-09"
Right 2017-01-09
boundFromWrapped :: (Rewrapped s s, Rewrapped e e, Unwrapped s ~ Day, Unwrapped e ~ Day, Rewrapped hs hs, Rewrapped he he, Unwrapped hs ~ Natural, Unwrapped he ~ Natural) => s -> e -> hs -> he -> (LowerTimeBound, UpperTimeBound) Source #
Given a wrapped start and end Day
, as well as a chosen Hour
, create a pair of wrapped UTCTime
values that represent their upper and lower values. Used internally.
>>>
boundFromWrapped startD endD startH endH
(LowerBound 2017-02-25 03:00:00 UTC,UpperBound 2017-02-27 05:00:00 UTC)
wrappedRange :: (Rewrapped a a, Rewrapped b b, Rewrapped c c, Unwrapped a ~ t, Unwrapped b ~ t, Unwrapped c ~ t, Ord t) => (t -> c) -> (t -> t) -> a -> b -> NonEmpty c Source #
Provide a range builder for any wrapped types that have
an Ord
instance.
>>>
wrappedRange (_Wrapped #) succ startH endH :: NonEmpty StartHour
StartHour 3 :| [StartHour 4,StartHour 5]>>>
wrappedRange (_Wrapped #) succ endH startH :: NonEmpty StartHour
StartHour 5 :| []
strToHourNatural :: String -> Either String Natural Source #
Try to read a String
value into a Natural
representing a whole hour,
in 24 hour time. "1" .. "23" or "00"
>>>
strToHourNatural "1"
Right 1>>>
strToHourNatural "10"
Right 10>>>
strToHourNatural "0"
Left "Unable to parse 0 into acceptable hour value. Expected '1'-'23' or '00'">>>
strToHourNatural "00"
Right 0
utcRangeHours :: (Rewrapped start start, Rewrapped end end, Unwrapped start ~ UTCTime, Unwrapped end ~ UTCTime) => start -> end -> NonEmpty UTCTime Source #
Convenience function for wrappedRange
that provides a list of UTCTime
at hourly intervals between the given start and end times.
datesInRange :: (Rewrapped a a, Rewrapped b b, Unwrapped a ~ Day, Unwrapped b ~ Day) => a -> b -> NonEmpty DayInRange Source #
Given two wrapped Day
values, provide a NonEmpty
list of all the days
in between.
>>>
datesInRange startD endD
DayInRange 2017-02-25 :| [DayInRange 2017-02-26,DayInRange 2017-02-27]>>>
datesInRange endD startD
DayInRange 2017-02-27 :| []