{-# LANGUAGE OverloadedStrings, GeneralizedNewtypeDeriving #-}
module Clay.Time
(
Time
, sec
, ms
)
where
import Data.Text (pack)
import Clay.Common
import Clay.Property
newtype Time = Time Value
deriving (Time -> Value
(Time -> Value) -> Val Time
forall a. (a -> Value) -> Val a
value :: Time -> Value
$cvalue :: Time -> Value
Val, Time
Time -> Auto Time
forall a. a -> Auto a
auto :: Time
$cauto :: Time
Auto, Time
Time -> Normal Time
forall a. a -> Normal a
normal :: Time
$cnormal :: Time
Normal, Time
Time -> Inherit Time
forall a. a -> Inherit a
inherit :: Time
$cinherit :: Time
Inherit, Time
Time -> None Time
forall a. a -> None a
none :: Time
$cnone :: Time
None, Value -> Time
(Value -> Time) -> Other Time
forall a. (Value -> a) -> Other a
other :: Value -> Time
$cother :: Value -> Time
Other)
sec :: Double -> Time
sec :: Double -> Time
sec Double
i = Value -> Time
Time (Text -> Value
forall a. Val a => a -> Value
value (String -> Text
pack (Double -> String
forall a. Show a => a -> String
show Double
i) Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"s"))
ms :: Double -> Time
ms :: Double -> Time
ms Double
i = Value -> Time
Time (Text -> Value
forall a. Val a => a -> Value
value (String -> Text
pack (Double -> String
forall a. Show a => a -> String
show Double
i) Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"ms"))
instance Num Time where
fromInteger :: Integer -> Time
fromInteger = Double -> Time
sec (Double -> Time) -> (Integer -> Double) -> Integer -> Time
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Integer -> Double
forall a. Num a => Integer -> a
fromInteger
+ :: Time -> Time -> Time
(+) = String -> Time -> Time -> Time
forall a. HasCallStack => String -> a
error String
"plus not implemented for Time"
* :: Time -> Time -> Time
(*) = String -> Time -> Time -> Time
forall a. HasCallStack => String -> a
error String
"times not implemented for Time"
abs :: Time -> Time
abs = String -> Time -> Time
forall a. HasCallStack => String -> a
error String
"abs not implemented for Time"
signum :: Time -> Time
signum = String -> Time -> Time
forall a. HasCallStack => String -> a
error String
"signum not implemented for Time"
negate :: Time -> Time
negate = String -> Time -> Time
forall a. HasCallStack => String -> a
error String
"negate not implemented for Time"
instance Fractional Time where
fromRational :: Rational -> Time
fromRational = Double -> Time
sec (Double -> Time) -> (Rational -> Double) -> Rational -> Time
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Rational -> Double
forall a. Fractional a => Rational -> a
fromRational
recip :: Time -> Time
recip = String -> Time -> Time
forall a. HasCallStack => String -> a
error String
"recip not implemented for Time"