{-# LANGUAGE TemplateHaskell #-}
module Data.Time.Clock.Duration.QQ
(
t
, s
, ms
, µs
, ns
, ps
) where
import Control.Applicative ((<|>), liftA2)
import Data.Bool (bool)
import Data.Char (isAlpha, toLower, toUpper)
import Data.Fixed (E0, E3, E6, E9, E12)
import Data.Proxy (Proxy (Proxy))
import Data.Time.Clock.Duration.Types
import Language.Haskell.TH (Exp (AppE, ConE, SigE, VarE), Name, Q, Type (AppT, ConT))
import Language.Haskell.TH.Quote (QuasiQuoter (QuasiQuoter, quoteExp))
import Text.Parsec (char, choice, digit, eof, many1, option, optional, runParser, spaces, try)
import Text.Parsec.String (Parser)
t :: QuasiQuoter
t = QuasiQuoter { quoteExp = buildExp Nothing }
s :: QuasiQuoter
s = QuasiQuoter { quoteExp = buildExp (Just (Second, ''E0)) }
ms :: QuasiQuoter
ms = QuasiQuoter { quoteExp = buildExp (Just (Millisec, ''E3)) }
µs :: QuasiQuoter
µs = QuasiQuoter { quoteExp = buildExp (Just (Microsec, ''E6)) }
ns :: QuasiQuoter
ns = QuasiQuoter { quoteExp = buildExp (Just (Nanosec, ''E9)) }
ps :: QuasiQuoter
ps = QuasiQuoter { quoteExp = buildExp (Just (Picosec, ''E12)) }
buildExp :: Maybe ((Rational -> Time), Name) -> String -> Q Exp
buildExp munit str =
let duration = runParser durationP () "" str `catch` (error . show) in
case (munit, duration) of
(Just (_, name), WithUnit time) -> do
timeE <- [|time|]
pure $ AppE (AppE (VarE 'toRelativeDuration) (SigE (ConE 'Proxy) (AppT (ConT ''Proxy) (ConT name)))) timeE
(Just (constructor, _), WithoutUnit time) ->
let time' = constructor time
in [|toAbsoluteDuration time'|]
(Nothing, WithUnit time) -> [|toAbsoluteDuration time|]
(Nothing, WithoutUnit _) -> error "not defined"
where
catch (Left err) f = f err
catch (Right x) _ = x
digits :: Int -> Maybe Int
digits n
| n > 0 = Just . length . show $ n
| otherwise = Nothing
decimalP :: Parser Rational
decimalP = do
isNegative <- option False $ const True <$> char '-'
int <- read <$> option "0" (many1 digit)
frac <- option 0 $ do
_ <- char '.'
n <- many1 digit
pure $ read n
let int' = fromIntegral int
frac' = fromIntegral frac
pure . bool id negate isNegative $ case digits frac of
Nothing -> int'
Just n -> int' + (frac' / 10^n)
withSuffix :: String -> Parser Rational
withSuffix suffix = do
optional spaces
decimal <- decimalP
optional spaces
_ <- stringCI suffix
optional spaces
eof
pure decimal
withSuffixes :: [String] -> Parser Rational
withSuffixes = choice . map (try . withSuffix)
stringCI :: String -> Parser String
stringCI = foldr (liftA2 (:) . charCI) $ pure ""
where
charCI :: Char -> Parser Char
charCI c
| isAlpha c = char (toUpper c) <|> char (toLower c)
| otherwise = char c
relativeP :: Parser Rational
relativeP = withSuffix ""
millisecondsP, secondsP, minutesP, hoursP, daysP, weeksP, yearsP :: Parser Time
millisecondsP = Millisec <$> withSuffixes ["ms", "msec", "msecs", "millisecond", "milliseconds"]
secondsP = Second <$> withSuffixes ["s", "sec", "secs", "second", "seconds"]
minutesP = Minute <$> withSuffixes ["m", "min", "mins", "minute", "minutes"]
hoursP = Hour <$> withSuffixes ["h", "hr", "hrs", "hour", "hours"]
daysP = Day <$> withSuffixes ["d", "day", "days"]
weeksP = Week <$> withSuffixes ["w", "week", "weeks"]
yearsP = Year <$> withSuffixes ["y", "yr", "yrs", "year", "years"]
absoluteP :: Parser Time
absoluteP = choice $ map try parsers
where
parsers =
[ millisecondsP
, secondsP
, minutesP
, hoursP
, daysP
, weeksP
, yearsP
]
data Duration
= WithoutUnit Rational
| WithUnit Time
durationP :: Parser Duration
durationP = (WithUnit <$> absoluteP) <|> (WithoutUnit <$> relativeP)