-- | The module containing the functions directly related to the month calculations, and exposed in the library. module Months where import Helpers -- | Computes the average of the number of days in a months by folding the list given by monthLengthList meanMonth :: Double meanMonth = let months = map realToFrac monthLengthList in mean months -- | Returns a list of Ints containing the lengths of every month in a Gregorian Cycle. -- A Gregorian cycle (or whatever it is called) is made of 400 years. -- Each year has 12 months, -- Of which: -- 7 have 31 days, -- 4 have 30 days, -- and 1 has either 28 days, or 29 days if the year is bissextile. -- In the gregorian calendar, a year is bissextile if its number is dividable by 4, -- except when it is dividable by 100, but it is bissextile when it is dividable by 400. monthLengthList :: [Int] monthLengthList = longMonths ++ shortMonths ++ febIntercalary ++ febBissextile where longMonths = [31 | x <- [1..(7 * 400)]] -- 7 31-day months a year on a 400-year cycle shortMonths = [30 | x <- [1..(4 * 400)]] -- 4 30-day months a year on the same cycle febIntercalary = [28 | x <- [1..400], not (bissextile x)] febBissextile = [29 | x <- [1..400], bissextile x] -- | Tells whether a year is bissextile bissextile :: Int -> Bool bissextile x = ((x `dividableBy` 4) && not (x `dividableBy` 100)) || (x == 400)