Haskell is not an easy language. It takes a lot of mind wrapping to understand monads, but once you do, you lose all capability to explain it. I shall not even try to explain monads. I prefer to show by example how haskell should be written.
You can, simplistically, say a monad is data with a context. Just like with physical units, like 2m or 2Kg. Two metres are different from two kilogrammes. One pertains to length, another to mass. In monadic speak, it would be "Metre 2" or "Kilogramme 4", since monads are prefixed. You could add metres with metres, but not metres with kilogrammes. And thus type safety comes into being actually useful.
The following code is here. It has been edited in Literate Haskell and transformed with Pandoc to HTML. The original HTML file, as it came out of Pandoc, can be found here.
A Date/Time Period
- DESCRIPTION: A period that contains dates or times.
- AUTHOR: Francisco Miguel Colaço <>
- DATE: 2013-12-23
Summary
The Period
class describes a possibly infinite period of dates and times. It has functions that assess if a date or a moment in time belongs in a given periods. It has also fuctions that create new intervals with reference to the current moment (under the IO Monad).
Implementation
Declarations
This package uses several Haskell language extensions. These extensions are not deprecated, nor considered harmful.
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE StandaloneDeriving #-}
module Data.Period where
import Control.Monad
import Data.Data
import Data.List
import Data.Maybe
import Data.Time
import Data.Time.Calendar
import Data.Time.Calendar.WeekDate
The Period Data Type
A period can extend From
a start date or time, Until
an end time, with no beginning, Between
two times (or dates), or a bottom value of Infinite
, that is, from the start to the end of times. To be precise, one could make periods out of integers or numbers. The only requisite is that the type variable is orderable and showable. All numbers are. Of course, one could restrict the period type variable to dates and times only by having them belong to the Data.Time.Format.FormatTime
class. We opted not to.
Using GADTs, the type constraints of the type variable are made right at the constructors, and thus reflect themselves through all the functions that use the Period data type.
-- | An interval of orderable and showable values. The period can be `From` a
-- determined time with no end; `Until` a given time and with no start;
-- `Between` two times; or `Infinite`, meaning without start or end.
data Period a where
From :: (Ord a, Show a) => a -> Period a
Until :: (Ord a, Show a) => a -> Period a
Between :: (Ord a, Show a) => a -> a -> Period a
Infinite :: Period a
instance Show (Period a) where
show (From start) = "From " ++ show start
show (Until end) = "Until " ++ show end
show (Between start end) = "Between " ++ show start ++ " and " ++ show end
show Infinite = "All times"
deriving instance Typeable1 Period
deriving instance (Data a, Ord a, Show a) => Data (Period a)
A DatePeriod is a period of dates (days). A TimePeriod is a period of UTC times. Both values are defined in Data.Time
.
Periods can also be set in terms of any orderable and showable types, like enumerations or numbers. The library is to be used with dates and times.
Date and Time Periods
type DatePeriod = Period Day
type TimePeriod = Period UTCTime
Conversions between the two period types are possible.
-- | Converts from a time period to a date period. Truncates the period to the
-- dates, disregarding the day fractions.
toDatePeriod :: TimePeriod -> DatePeriod
toDatePeriod (From start) = From (utctDay start)
toDatePeriod (Until end) = Until (utctDay end)
toDatePeriod (Between start end) = Between (utctDay start) (utctDay end)
toDatePeriod Infinite = Infinite
-- | Converts from a date period to a time period. The period is counted from
-- the start of the first day to the end of the last.
toTimePeriod :: DatePeriod -> TimePeriod
toTimePeriod (From start) = From (UTCTime start 0.0)
toTimePeriod (Until end) = Until (UTCTime end 86399.999999)
toTimePeriod (Between start end) = Between (UTCTime start 0.0) (UTCTime end 86399.999999)
toTimePeriod Infinite = Infinite
Period Limit Tests
A period is closed when it has no upper end. That is, only Infinite
and From
periods are open. All others are closed.
isClosed Infinite
False
isClosed $ Until $ fromGregorian 2013 1 1
True
fromNow >>= return . isClosed
IO False
-- | Tells if the period has an end.
isClosed :: Period a -> Bool
isClosed Infinite = False
isClosed (From _) = False
isClosed _ = True
Any period may or may not have have a start or an end. As it may have not, the enquiry can fail. So, the answer is wrapped in the Maybe monad.
From
periods have a start, but not an end. Until
periods have only an end. Between
periods have both. Infinite
has neither.
-- | Returns the start of the period (in the Maybe Monad), if it has one.
periodStart :: Period a -> Maybe a
periodStart (From start) = Just start
periodStart (Between start _) = Just start
periodStart _ = Nothing
-- | Returns the end of the period (in the Maybe Monad), if it has one.
periodEnd :: Period a -> Maybe a
periodEnd (Until end) = Just end
periodEnd (Between _ end) = Just end
periodEnd _ = Nothing
Value Containment
contains
is meant to be used infix. Tells if a given period contains the given date. A period has inclusive bounds. A date exactly equal to one of the bounds is still contained in it.
contains :: Period a -> a -> Bool
contains Infinite _ = True
contains (From start) now = now >= start
contains (Until end) now = now <= end
contains (Between start end) now = (now >= start) && (now <= end)
belongs
is contains
with the arguments splitted. One date belongs to a period when such period contains the date.
From (fromGregorian 2013 1 1) `contains` (fromGregorian 2013 1 1)
True
(liftM2 contains) thisYear (return $ fromGregorian 2012 1 1)
IO False
(liftM2 contains) fromNow getCurrentTime
IO True
(liftM2 belongs) getCurrentTime fromNow
IO True
belongs :: a -> Period a -> Bool
n `belongs` p = p `contains` n
Constructors Reported to the Current Date
Constructors are provided that extend from or until the current day and time. The constructors are computed under the IO Monad, since they have to compute the current date.
-- | Returns a time period that extends from the present time.
fromNow :: IO TimePeriod
fromNow = liftM From getCurrentTime
-- | Returns a time period that extends until the present time.
untilNow :: IO TimePeriod
untilNow = liftM Until getCurrentTime
-- | Returns a day period that extends from the present day.
fromToday :: IO DatePeriod
fromToday = liftM (From . utctDay) getCurrentTime
-- | Returns a day period that extends until the present day.
untilToday :: IO DatePeriod
untilToday = liftM (Until . utctDay) getCurrentTime
Common Date Periods
Date periods for the current year, the current month and the current week are often requested. These have to be computed under the IO Monad, since they determine the current time.
-- | Returns a date period that spans throughout the current year.
thisYear :: IO DatePeriod
thisYear = do
(yr, _, _) <- (liftM $ toGregorian . utctDay) getCurrentTime
return $ Between (fromGregorian yr 1 1) (fromGregorian yr 12 31)
-- | Returns a date period that spans throughout the current month.
thisMonth :: IO DatePeriod
thisMonth = do
(yr, mo, _) <- (liftM $ toGregorian . utctDay) getCurrentTime
return $ Between (fromGregorian yr mo 1) (fromGregorian yr mo $ gregorianMonthLength yr mo)
-- | Returns a date period that spans throughout the week.
thisWeek :: IO DatePeriod
thisWeek = do
(yr, wk, d) <- (liftM $ toWeekDate . utctDay) getCurrentTime
return $ Between (fromWeekDate yr wk 1) (fromWeekDate yr wk 7)
A time period is quite requested: the one that comprises the current day. This period has to be computed under the IO Monad. The implementation has two flaws: do not account for end days and fall short one microssecond from the real end of the day.
-- | Returns a time period that comprises the current day.
thisDay :: IO TimePeriod
thisDay = do
today <- liftM utctDay getCurrentTime
return $ toTimePeriod $ Between today today
A very frequent query is to know if a given period contains the current day or time. These queries have to be made inside the IO Monad.
containsNow Infinite
IO True
fromToday >>= containsToday
IO True
thisYear >>= containsToday
IO True
fromNow >>= containsNow
IO True
Containment of the Current Date
-- | Tells if a date period contains the current day.
containsToday :: DatePeriod -> IO Bool
containsToday period = do
now <- getCurrentTime
return $ period `contains` utctDay now
-- | Tells if a time period contains the current time.
containsNow :: TimePeriod -> IO Bool
containsNow period = do
now <- getCurrentTime
return $ period `contains` now
Sem comentários:
Enviar um comentário