{-# LANGUAGE BangPatterns #-} -- | Extra date functions. module Data.Time.Extra where import Control.Monad.Trans import Data.List import Data.Text (Text,pack) import Data.Time import System.Locale import Text.Printf -- | Get the current year. getYear :: FormatTime t => t -> Integer getYear = read . formatTime defaultTimeLocale "%Y" -- | Get the current month. getMonth :: FormatTime t => t -> Integer getMonth = read . formatTime defaultTimeLocale "%m" -- | Get the current day. getDay :: FormatTime t => t -> Integer getDay = read . formatTime defaultTimeLocale "%d" -- | Display a time span as one time relative to another. relative :: UTCTime -- ^ The later time span. -> UTCTime -- ^ The earlier time span. -> Bool -- ^ Display 'in/ago'? -> Text -- ^ Example: '3 seconds ago', 'in three days'. relative t1 t2 fix = pack $ maybe "unknown" format $ find (\(s,_,_) -> abs span'>=s) $ reverse ranges where minute = 60; hour = minute * 60; day = hour * 24; week = day * 7; month = day * 30; year = month * 12 format range = (if fix && span'>0 then "in " else "") ++ case range of (_,str,0) -> str (_,str,base) -> printf str (abs $ round (span' / base) :: Integer) ++ (if fix && span'<0 then " ago" else "") span' = t1 `diffUTCTime` t2 ranges = [(0,"%d seconds",1) ,(minute,"a minute",0) ,(minute*2,"%d minutes",minute) ,(minute*30,"half an hour",0) ,(minute*31,"%d minutes",minute) ,(hour,"an hour",0) ,(hour*2,"%d hours",hour) ,(hour*3,"a few hours",0) ,(hour*4,"%d hours",hour) ,(day,"a day",0) ,(day*2,"%d days",day) ,(week,"a week",0) ,(week*2,"%d weeks",week) ,(month,"a month",0) ,(month*2,"%d months",month) ,(year,"a year",0) ,(year*2,"%d years",year) ] -- | Run a stop-watch at the start and end of a computation. stopwatch :: MonadIO m => m a -> m (a,NominalDiffTime) stopwatch computation = do start <- liftIO $ getCurrentTime !a <- computation end <- liftIO $ getCurrentTime return (a,end `diffUTCTime` start) -- | Trivial benchmark for some monadic action. bench :: MonadIO m => Integer -> m a -> m (a,NominalDiffTime) bench i computation = go i (Nothing,0) where go n (Nothing,_) = do (a,time) <- stopwatch computation go (n-1) (Just a,time) go 0 (Just x,avg) = do return (x, avg) go n (Just _,avg) = do (a,new) <- stopwatch computation go (n-1) (Just a,(new + avg*cnt) / (cnt+1)) where cnt = fromIntegral (i-n)