expand with a fromDuration and support for mixed unit durations
This commit is contained in:
parent
af5e1d0494
commit
ca83b16415
1 changed files with 60 additions and 14 deletions
|
@ -1,26 +1,72 @@
|
||||||
{- Time for humans.
|
{- Time for humans.
|
||||||
-
|
-
|
||||||
- Copyright 2012 Joey Hess <joey@kitenet.net>
|
- Copyright 2012-2013 Joey Hess <joey@kitenet.net>
|
||||||
-
|
-
|
||||||
- Licensed under the GNU GPL version 3 or higher.
|
- Licensed under the GNU GPL version 3 or higher.
|
||||||
-}
|
-}
|
||||||
|
|
||||||
module Utility.HumanTime where
|
module Utility.HumanTime (
|
||||||
|
Duration(..),
|
||||||
|
durationToPOSIXTime,
|
||||||
|
parseDuration,
|
||||||
|
fromDuration,
|
||||||
|
) where
|
||||||
|
|
||||||
import Utility.PartialPrelude
|
import Utility.PartialPrelude
|
||||||
|
import Utility.Applicative
|
||||||
|
|
||||||
import Data.Time.Clock.POSIX (POSIXTime)
|
import Data.Time.Clock.POSIX (POSIXTime)
|
||||||
|
import Data.Char
|
||||||
|
import qualified Data.Map as M
|
||||||
|
|
||||||
{- Parses a human-input time duration, of the form "5h" or "1m". -}
|
newtype Duration = Duration { durationSeconds :: Integer }
|
||||||
parseDuration :: String -> Maybe POSIXTime
|
deriving (Eq, Ord, Read, Show)
|
||||||
parseDuration s = do
|
|
||||||
num <- readish s :: Maybe Integer
|
durationToPOSIXTime :: Duration -> POSIXTime
|
||||||
units <- findUnits =<< lastMaybe s
|
durationToPOSIXTime = fromIntegral . durationSeconds
|
||||||
return $ fromIntegral num * units
|
|
||||||
|
{- Parses a human-input time duration, of the form "5h", "1m", "5h1m", etc -}
|
||||||
|
parseDuration :: String -> Maybe Duration
|
||||||
|
parseDuration = Duration <$$> go 0
|
||||||
where
|
where
|
||||||
findUnits 's' = Just 1
|
go n [] = return n
|
||||||
findUnits 'm' = Just 60
|
go n s = do
|
||||||
findUnits 'h' = Just $ 60 * 60
|
num <- readish s :: Maybe Integer
|
||||||
findUnits 'd' = Just $ 60 * 60 * 24
|
let (c:rest) = dropWhile isDigit s
|
||||||
findUnits 'y' = Just $ 60 * 60 * 24 * 365
|
u <- M.lookup c unitmap
|
||||||
findUnits _ = Nothing
|
go (n + num * u) rest
|
||||||
|
|
||||||
|
fromDuration :: Duration -> String
|
||||||
|
fromDuration = concat . map showunit . go [] units . durationSeconds
|
||||||
|
where
|
||||||
|
showunit (u, n)
|
||||||
|
| n > 0 = show n ++ [u]
|
||||||
|
| otherwise = ""
|
||||||
|
go c [] _ = reverse c
|
||||||
|
go c ((u, n):us) d =
|
||||||
|
let (q,r) = d `quotRem` n
|
||||||
|
in go ((u, q):c) us r
|
||||||
|
|
||||||
|
units :: [(Char, Integer)]
|
||||||
|
units =
|
||||||
|
[ ('y', ysecs)
|
||||||
|
, ('d', dsecs)
|
||||||
|
, ('h', hsecs)
|
||||||
|
, ('m', msecs)
|
||||||
|
, ('s', 1)
|
||||||
|
]
|
||||||
|
|
||||||
|
unitmap :: M.Map Char Integer
|
||||||
|
unitmap = M.fromList units
|
||||||
|
|
||||||
|
ysecs :: Integer
|
||||||
|
ysecs = dsecs * 365
|
||||||
|
|
||||||
|
dsecs :: Integer
|
||||||
|
dsecs = hsecs * 24
|
||||||
|
|
||||||
|
hsecs :: Integer
|
||||||
|
hsecs = msecs * 60
|
||||||
|
|
||||||
|
msecs :: Integer
|
||||||
|
msecs = 60
|
||||||
|
|
Loading…
Add table
Add a link
Reference in a new issue