{-# LANGUAGE OverloadedStrings #-}
module Database.Bloodhound.Internal.Versions.Common.Types.Units
( Bytes (..),
Interval (..),
TimeInterval (..),
gigabytes,
kilobytes,
megabytes,
parseStringInterval,
)
where
import Database.Bloodhound.Internal.Utils.Imports
import Text.Read (Read (..))
import qualified Text.Read as TR
newtype Bytes
= Bytes Int
deriving newtype (Bytes -> Bytes -> Bool
(Bytes -> Bytes -> Bool) -> (Bytes -> Bytes -> Bool) -> Eq Bytes
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Bytes -> Bytes -> Bool
== :: Bytes -> Bytes -> Bool
$c/= :: Bytes -> Bytes -> Bool
/= :: Bytes -> Bytes -> Bool
Eq, Int -> Bytes -> ShowS
[Bytes] -> ShowS
Bytes -> String
(Int -> Bytes -> ShowS)
-> (Bytes -> String) -> ([Bytes] -> ShowS) -> Show Bytes
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Bytes -> ShowS
showsPrec :: Int -> Bytes -> ShowS
$cshow :: Bytes -> String
show :: Bytes -> String
$cshowList :: [Bytes] -> ShowS
showList :: [Bytes] -> ShowS
Show, Eq Bytes
Eq Bytes =>
(Bytes -> Bytes -> Ordering)
-> (Bytes -> Bytes -> Bool)
-> (Bytes -> Bytes -> Bool)
-> (Bytes -> Bytes -> Bool)
-> (Bytes -> Bytes -> Bool)
-> (Bytes -> Bytes -> Bytes)
-> (Bytes -> Bytes -> Bytes)
-> Ord Bytes
Bytes -> Bytes -> Bool
Bytes -> Bytes -> Ordering
Bytes -> Bytes -> Bytes
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: Bytes -> Bytes -> Ordering
compare :: Bytes -> Bytes -> Ordering
$c< :: Bytes -> Bytes -> Bool
< :: Bytes -> Bytes -> Bool
$c<= :: Bytes -> Bytes -> Bool
<= :: Bytes -> Bytes -> Bool
$c> :: Bytes -> Bytes -> Bool
> :: Bytes -> Bytes -> Bool
$c>= :: Bytes -> Bytes -> Bool
>= :: Bytes -> Bytes -> Bool
$cmax :: Bytes -> Bytes -> Bytes
max :: Bytes -> Bytes -> Bytes
$cmin :: Bytes -> Bytes -> Bytes
min :: Bytes -> Bytes -> Bytes
Ord, [Bytes] -> Value
[Bytes] -> Encoding
Bytes -> Bool
Bytes -> Value
Bytes -> Encoding
(Bytes -> Value)
-> (Bytes -> Encoding)
-> ([Bytes] -> Value)
-> ([Bytes] -> Encoding)
-> (Bytes -> Bool)
-> ToJSON Bytes
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> (a -> Bool)
-> ToJSON a
$ctoJSON :: Bytes -> Value
toJSON :: Bytes -> Value
$ctoEncoding :: Bytes -> Encoding
toEncoding :: Bytes -> Encoding
$ctoJSONList :: [Bytes] -> Value
toJSONList :: [Bytes] -> Value
$ctoEncodingList :: [Bytes] -> Encoding
toEncodingList :: [Bytes] -> Encoding
$comitField :: Bytes -> Bool
omitField :: Bytes -> Bool
ToJSON, Maybe Bytes
Value -> Parser [Bytes]
Value -> Parser Bytes
(Value -> Parser Bytes)
-> (Value -> Parser [Bytes]) -> Maybe Bytes -> FromJSON Bytes
forall a.
(Value -> Parser a)
-> (Value -> Parser [a]) -> Maybe a -> FromJSON a
$cparseJSON :: Value -> Parser Bytes
parseJSON :: Value -> Parser Bytes
$cparseJSONList :: Value -> Parser [Bytes]
parseJSONList :: Value -> Parser [Bytes]
$comittedField :: Maybe Bytes
omittedField :: Maybe Bytes
FromJSON)
gigabytes :: Int -> Bytes
gigabytes :: Int -> Bytes
gigabytes Int
n = Int -> Bytes
megabytes (Int
1000 Int -> Int -> Int
forall a. Num a => a -> a -> a
* Int
n)
megabytes :: Int -> Bytes
megabytes :: Int -> Bytes
megabytes Int
n = Int -> Bytes
kilobytes (Int
1000 Int -> Int -> Int
forall a. Num a => a -> a -> a
* Int
n)
kilobytes :: Int -> Bytes
kilobytes :: Int -> Bytes
kilobytes Int
n = Int -> Bytes
Bytes (Int
1000 Int -> Int -> Int
forall a. Num a => a -> a -> a
* Int
n)
data TimeInterval
= Weeks
| Days
| Hours
| Minutes
| Seconds
deriving stock (TimeInterval -> TimeInterval -> Bool
(TimeInterval -> TimeInterval -> Bool)
-> (TimeInterval -> TimeInterval -> Bool) -> Eq TimeInterval
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: TimeInterval -> TimeInterval -> Bool
== :: TimeInterval -> TimeInterval -> Bool
$c/= :: TimeInterval -> TimeInterval -> Bool
/= :: TimeInterval -> TimeInterval -> Bool
Eq)
instance Show TimeInterval where
show :: TimeInterval -> String
show TimeInterval
Weeks = String
"w"
show TimeInterval
Days = String
"d"
show TimeInterval
Hours = String
"h"
show TimeInterval
Minutes = String
"m"
show TimeInterval
Seconds = String
"s"
instance Read TimeInterval where
readPrec :: ReadPrec TimeInterval
readPrec = Char -> ReadPrec TimeInterval
forall {m :: * -> *}. MonadFail m => Char -> m TimeInterval
f (Char -> ReadPrec TimeInterval)
-> ReadPrec Char -> ReadPrec TimeInterval
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< ReadPrec Char
TR.get
where
f :: Char -> m TimeInterval
f Char
'w' = TimeInterval -> m TimeInterval
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return TimeInterval
Weeks
f Char
'd' = TimeInterval -> m TimeInterval
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return TimeInterval
Days
f Char
'h' = TimeInterval -> m TimeInterval
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return TimeInterval
Hours
f Char
'm' = TimeInterval -> m TimeInterval
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return TimeInterval
Minutes
f Char
's' = TimeInterval -> m TimeInterval
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return TimeInterval
Seconds
f Char
_ = String -> m TimeInterval
forall a. String -> m a
forall (m :: * -> *) a. MonadFail m => String -> m a
fail String
"TimeInterval expected one of w, d, h, m, s"
data Interval
= Year
| Quarter
| Month
| Week
| Day
| Hour
| Minute
| Second
deriving stock (Interval -> Interval -> Bool
(Interval -> Interval -> Bool)
-> (Interval -> Interval -> Bool) -> Eq Interval
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Interval -> Interval -> Bool
== :: Interval -> Interval -> Bool
$c/= :: Interval -> Interval -> Bool
/= :: Interval -> Interval -> Bool
Eq, Int -> Interval -> ShowS
[Interval] -> ShowS
Interval -> String
(Int -> Interval -> ShowS)
-> (Interval -> String) -> ([Interval] -> ShowS) -> Show Interval
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Interval -> ShowS
showsPrec :: Int -> Interval -> ShowS
$cshow :: Interval -> String
show :: Interval -> String
$cshowList :: [Interval] -> ShowS
showList :: [Interval] -> ShowS
Show)
instance ToJSON Interval where
toJSON :: Interval -> Value
toJSON Interval
Year = Value
"year"
toJSON Interval
Quarter = Value
"quarter"
toJSON Interval
Month = Value
"month"
toJSON Interval
Week = Value
"week"
toJSON Interval
Day = Value
"day"
toJSON Interval
Hour = Value
"hour"
toJSON Interval
Minute = Value
"minute"
toJSON Interval
Second = Value
"second"
parseStringInterval :: (Monad m, MonadFail m) => String -> m NominalDiffTime
parseStringInterval :: forall (m :: * -> *).
(Monad m, MonadFail m) =>
String -> m NominalDiffTime
parseStringInterval String
s = case (Char -> Bool) -> String -> (String, String)
forall a. (a -> Bool) -> [a] -> ([a], [a])
span Char -> Bool
isNumber String
s of
(String
"", String
_) -> String -> m NominalDiffTime
forall a. String -> m a
forall (m :: * -> *) a. MonadFail m => String -> m a
fail String
"Invalid interval"
(String
nS, String
unitS) -> case (String -> Maybe Integer
forall a. Read a => String -> Maybe a
readMay String
nS, String -> Maybe TimeInterval
forall a. Read a => String -> Maybe a
readMay String
unitS) of
(Just Integer
n, Just TimeInterval
unit) -> NominalDiffTime -> m NominalDiffTime
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Integer -> NominalDiffTime
forall a. Num a => Integer -> a
fromInteger (Integer
n Integer -> Integer -> Integer
forall a. Num a => a -> a -> a
* TimeInterval -> Integer
forall {a}. Num a => TimeInterval -> a
unitNDT TimeInterval
unit))
(Maybe Integer
Nothing, Maybe TimeInterval
_) -> String -> m NominalDiffTime
forall a. String -> m a
forall (m :: * -> *) a. MonadFail m => String -> m a
fail String
"Invalid interval number"
(Maybe Integer
_, Maybe TimeInterval
Nothing) -> String -> m NominalDiffTime
forall a. String -> m a
forall (m :: * -> *) a. MonadFail m => String -> m a
fail String
"Invalid interval unit"
where
unitNDT :: TimeInterval -> a
unitNDT TimeInterval
Seconds = a
1
unitNDT TimeInterval
Minutes = a
60
unitNDT TimeInterval
Hours = a
60 a -> a -> a
forall a. Num a => a -> a -> a
* a
60
unitNDT TimeInterval
Days = a
24 a -> a -> a
forall a. Num a => a -> a -> a
* a
60 a -> a -> a
forall a. Num a => a -> a -> a
* a
60
unitNDT TimeInterval
Weeks = a
7 a -> a -> a
forall a. Num a => a -> a -> a
* a
24 a -> a -> a
forall a. Num a => a -> a -> a
* a
60 a -> a -> a
forall a. Num a => a -> a -> a
* a
60