{-# LANGUAGE ViewPatterns #-}
module Hasura.RQL.Types.Numeric
( NonNegative,
getNonNegative,
mkNonNegative,
unsafeNonNegative,
NonNegativeInt,
getNonNegativeInt,
mkNonNegativeInt,
unsafeNonNegativeInt,
PositiveInt,
getPositiveInt,
mkPositiveInt,
unsafePositiveInt,
NonNegativeDiffTime,
unNonNegativeDiffTime,
unsafeNonNegativeDiffTime,
mkNonNegativeDiffTime,
)
where
import Data.Aeson (FromJSON, ToJSON)
import Data.Aeson qualified as Aeson
import Data.Scientific qualified as Scientific
import Hasura.Incremental (Cacheable)
import Hasura.Prelude
newtype NonNegative a = NonNegative {NonNegative a -> a
getNonNegative :: a}
deriving stock (a -> NonNegative b -> NonNegative a
(a -> b) -> NonNegative a -> NonNegative b
(forall a b. (a -> b) -> NonNegative a -> NonNegative b)
-> (forall a b. a -> NonNegative b -> NonNegative a)
-> Functor NonNegative
forall a b. a -> NonNegative b -> NonNegative a
forall a b. (a -> b) -> NonNegative a -> NonNegative b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
<$ :: a -> NonNegative b -> NonNegative a
$c<$ :: forall a b. a -> NonNegative b -> NonNegative a
fmap :: (a -> b) -> NonNegative a -> NonNegative b
$cfmap :: forall a b. (a -> b) -> NonNegative a -> NonNegative b
Functor)
deriving newtype (Int -> NonNegative a -> ShowS
[NonNegative a] -> ShowS
NonNegative a -> String
(Int -> NonNegative a -> ShowS)
-> (NonNegative a -> String)
-> ([NonNegative a] -> ShowS)
-> Show (NonNegative a)
forall a. Show a => Int -> NonNegative a -> ShowS
forall a. Show a => [NonNegative a] -> ShowS
forall a. Show a => NonNegative a -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [NonNegative a] -> ShowS
$cshowList :: forall a. Show a => [NonNegative a] -> ShowS
show :: NonNegative a -> String
$cshow :: forall a. Show a => NonNegative a -> String
showsPrec :: Int -> NonNegative a -> ShowS
$cshowsPrec :: forall a. Show a => Int -> NonNegative a -> ShowS
Show, NonNegative a -> NonNegative a -> Bool
(NonNegative a -> NonNegative a -> Bool)
-> (NonNegative a -> NonNegative a -> Bool) -> Eq (NonNegative a)
forall a. Eq a => NonNegative a -> NonNegative a -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: NonNegative a -> NonNegative a -> Bool
$c/= :: forall a. Eq a => NonNegative a -> NonNegative a -> Bool
== :: NonNegative a -> NonNegative a -> Bool
$c== :: forall a. Eq a => NonNegative a -> NonNegative a -> Bool
Eq, Eq (NonNegative a)
Eq (NonNegative a)
-> (NonNegative a -> NonNegative a -> Ordering)
-> (NonNegative a -> NonNegative a -> Bool)
-> (NonNegative a -> NonNegative a -> Bool)
-> (NonNegative a -> NonNegative a -> Bool)
-> (NonNegative a -> NonNegative a -> Bool)
-> (NonNegative a -> NonNegative a -> NonNegative a)
-> (NonNegative a -> NonNegative a -> NonNegative a)
-> Ord (NonNegative a)
NonNegative a -> NonNegative a -> Bool
NonNegative a -> NonNegative a -> Ordering
NonNegative a -> NonNegative a -> NonNegative a
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
forall a. Ord a => Eq (NonNegative a)
forall a. Ord a => NonNegative a -> NonNegative a -> Bool
forall a. Ord a => NonNegative a -> NonNegative a -> Ordering
forall a. Ord a => NonNegative a -> NonNegative a -> NonNegative a
min :: NonNegative a -> NonNegative a -> NonNegative a
$cmin :: forall a. Ord a => NonNegative a -> NonNegative a -> NonNegative a
max :: NonNegative a -> NonNegative a -> NonNegative a
$cmax :: forall a. Ord a => NonNegative a -> NonNegative a -> NonNegative a
>= :: NonNegative a -> NonNegative a -> Bool
$c>= :: forall a. Ord a => NonNegative a -> NonNegative a -> Bool
> :: NonNegative a -> NonNegative a -> Bool
$c> :: forall a. Ord a => NonNegative a -> NonNegative a -> Bool
<= :: NonNegative a -> NonNegative a -> Bool
$c<= :: forall a. Ord a => NonNegative a -> NonNegative a -> Bool
< :: NonNegative a -> NonNegative a -> Bool
$c< :: forall a. Ord a => NonNegative a -> NonNegative a -> Bool
compare :: NonNegative a -> NonNegative a -> Ordering
$ccompare :: forall a. Ord a => NonNegative a -> NonNegative a -> Ordering
$cp1Ord :: forall a. Ord a => Eq (NonNegative a)
Ord, [NonNegative a] -> Value
[NonNegative a] -> Encoding
NonNegative a -> Value
NonNegative a -> Encoding
(NonNegative a -> Value)
-> (NonNegative a -> Encoding)
-> ([NonNegative a] -> Value)
-> ([NonNegative a] -> Encoding)
-> ToJSON (NonNegative a)
forall a. ToJSON a => [NonNegative a] -> Value
forall a. ToJSON a => [NonNegative a] -> Encoding
forall a. ToJSON a => NonNegative a -> Value
forall a. ToJSON a => NonNegative a -> Encoding
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [NonNegative a] -> Encoding
$ctoEncodingList :: forall a. ToJSON a => [NonNegative a] -> Encoding
toJSONList :: [NonNegative a] -> Value
$ctoJSONList :: forall a. ToJSON a => [NonNegative a] -> Value
toEncoding :: NonNegative a -> Encoding
$ctoEncoding :: forall a. ToJSON a => NonNegative a -> Encoding
toJSON :: NonNegative a -> Value
$ctoJSON :: forall a. ToJSON a => NonNegative a -> Value
ToJSON, Rep (NonNegative a) x -> NonNegative a
NonNegative a -> Rep (NonNegative a) x
(forall x. NonNegative a -> Rep (NonNegative a) x)
-> (forall x. Rep (NonNegative a) x -> NonNegative a)
-> Generic (NonNegative a)
forall a x. Generic a => Rep (NonNegative a) x -> NonNegative a
forall a x. Generic a => NonNegative a -> Rep (NonNegative a) x
forall x. Rep (NonNegative a) x -> NonNegative a
forall x. NonNegative a -> Rep (NonNegative a) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
to :: Rep (NonNegative a) x -> NonNegative a
$cto :: forall a x. Generic a => Rep (NonNegative a) x -> NonNegative a
from :: NonNegative a -> Rep (NonNegative a) x
$cfrom :: forall a x. Generic a => NonNegative a -> Rep (NonNegative a) x
Generic, NonNegative a -> ()
(NonNegative a -> ()) -> NFData (NonNegative a)
forall a. NFData a => NonNegative a -> ()
forall a. (a -> ()) -> NFData a
rnf :: NonNegative a -> ()
$crnf :: forall a. NFData a => NonNegative a -> ()
NFData, Eq (NonNegative a)
Eq (NonNegative a)
-> (Accesses -> NonNegative a -> NonNegative a -> Bool)
-> Cacheable (NonNegative a)
Accesses -> NonNegative a -> NonNegative a -> Bool
forall a. Eq a -> (Accesses -> a -> a -> Bool) -> Cacheable a
forall a. Cacheable a => Eq (NonNegative a)
forall a.
Cacheable a =>
Accesses -> NonNegative a -> NonNegative a -> Bool
unchanged :: Accesses -> NonNegative a -> NonNegative a -> Bool
$cunchanged :: forall a.
Cacheable a =>
Accesses -> NonNegative a -> NonNegative a -> Bool
$cp1Cacheable :: forall a. Cacheable a => Eq (NonNegative a)
Cacheable, Int -> NonNegative a -> Int
NonNegative a -> Int
(Int -> NonNegative a -> Int)
-> (NonNegative a -> Int) -> Hashable (NonNegative a)
forall a. Hashable a => Int -> NonNegative a -> Int
forall a. Hashable a => NonNegative a -> Int
forall a. (Int -> a -> Int) -> (a -> Int) -> Hashable a
hash :: NonNegative a -> Int
$chash :: forall a. Hashable a => NonNegative a -> Int
hashWithSalt :: Int -> NonNegative a -> Int
$chashWithSalt :: forall a. Hashable a => Int -> NonNegative a -> Int
Hashable)
mkNonNegative :: (Ord a, Num a) => a -> Maybe (NonNegative a)
mkNonNegative :: a -> Maybe (NonNegative a)
mkNonNegative a
x = case a
x a -> a -> Bool
forall a. Ord a => a -> a -> Bool
>= a
0 of
Bool
True -> NonNegative a -> Maybe (NonNegative a)
forall a. a -> Maybe a
Just (NonNegative a -> Maybe (NonNegative a))
-> NonNegative a -> Maybe (NonNegative a)
forall a b. (a -> b) -> a -> b
$ a -> NonNegative a
forall a. a -> NonNegative a
NonNegative a
x
Bool
False -> Maybe (NonNegative a)
forall a. Maybe a
Nothing
unsafeNonNegative :: a -> NonNegative a
unsafeNonNegative :: a -> NonNegative a
unsafeNonNegative = a -> NonNegative a
forall a. a -> NonNegative a
NonNegative
instance (Fractional a, FromJSON a) => FromJSON (NonNegative a) where
parseJSON :: Value -> Parser (NonNegative a)
parseJSON = String
-> (Scientific -> Parser (NonNegative a))
-> Value
-> Parser (NonNegative a)
forall a. String -> (Scientific -> Parser a) -> Value -> Parser a
Aeson.withScientific String
"NonNegative" ((Scientific -> Parser (NonNegative a))
-> Value -> Parser (NonNegative a))
-> (Scientific -> Parser (NonNegative a))
-> Value
-> Parser (NonNegative a)
forall a b. (a -> b) -> a -> b
$ \Scientific
t -> do
case Scientific
t Scientific -> Scientific -> Bool
forall a. Ord a => a -> a -> Bool
>= Scientific
0 of
Bool
True -> NonNegative a -> Parser (NonNegative a)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (NonNegative a -> Parser (NonNegative a))
-> NonNegative a -> Parser (NonNegative a)
forall a b. (a -> b) -> a -> b
$ a -> NonNegative a
forall a. a -> NonNegative a
NonNegative (a -> NonNegative a)
-> (Scientific -> a) -> Scientific -> NonNegative a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Scientific -> a
forall a b. (Real a, Fractional b) => a -> b
realToFrac (Scientific -> NonNegative a) -> Scientific -> NonNegative a
forall a b. (a -> b) -> a -> b
$ Scientific
t
Bool
False -> String -> Parser (NonNegative a)
forall (m :: * -> *) a. MonadFail m => String -> m a
fail String
"negative value not allowed"
newtype NonNegativeInt = NonNegativeInt {NonNegativeInt -> Int
getNonNegativeInt :: Int}
deriving (Int -> NonNegativeInt -> ShowS
[NonNegativeInt] -> ShowS
NonNegativeInt -> String
(Int -> NonNegativeInt -> ShowS)
-> (NonNegativeInt -> String)
-> ([NonNegativeInt] -> ShowS)
-> Show NonNegativeInt
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [NonNegativeInt] -> ShowS
$cshowList :: [NonNegativeInt] -> ShowS
show :: NonNegativeInt -> String
$cshow :: NonNegativeInt -> String
showsPrec :: Int -> NonNegativeInt -> ShowS
$cshowsPrec :: Int -> NonNegativeInt -> ShowS
Show, NonNegativeInt -> NonNegativeInt -> Bool
(NonNegativeInt -> NonNegativeInt -> Bool)
-> (NonNegativeInt -> NonNegativeInt -> Bool) -> Eq NonNegativeInt
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: NonNegativeInt -> NonNegativeInt -> Bool
$c/= :: NonNegativeInt -> NonNegativeInt -> Bool
== :: NonNegativeInt -> NonNegativeInt -> Bool
$c== :: NonNegativeInt -> NonNegativeInt -> Bool
Eq, [NonNegativeInt] -> Value
[NonNegativeInt] -> Encoding
NonNegativeInt -> Value
NonNegativeInt -> Encoding
(NonNegativeInt -> Value)
-> (NonNegativeInt -> Encoding)
-> ([NonNegativeInt] -> Value)
-> ([NonNegativeInt] -> Encoding)
-> ToJSON NonNegativeInt
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [NonNegativeInt] -> Encoding
$ctoEncodingList :: [NonNegativeInt] -> Encoding
toJSONList :: [NonNegativeInt] -> Value
$ctoJSONList :: [NonNegativeInt] -> Value
toEncoding :: NonNegativeInt -> Encoding
$ctoEncoding :: NonNegativeInt -> Encoding
toJSON :: NonNegativeInt -> Value
$ctoJSON :: NonNegativeInt -> Value
ToJSON, (forall x. NonNegativeInt -> Rep NonNegativeInt x)
-> (forall x. Rep NonNegativeInt x -> NonNegativeInt)
-> Generic NonNegativeInt
forall x. Rep NonNegativeInt x -> NonNegativeInt
forall x. NonNegativeInt -> Rep NonNegativeInt x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep NonNegativeInt x -> NonNegativeInt
$cfrom :: forall x. NonNegativeInt -> Rep NonNegativeInt x
Generic, NonNegativeInt -> ()
(NonNegativeInt -> ()) -> NFData NonNegativeInt
forall a. (a -> ()) -> NFData a
rnf :: NonNegativeInt -> ()
$crnf :: NonNegativeInt -> ()
NFData, Eq NonNegativeInt
Eq NonNegativeInt
-> (Accesses -> NonNegativeInt -> NonNegativeInt -> Bool)
-> Cacheable NonNegativeInt
Accesses -> NonNegativeInt -> NonNegativeInt -> Bool
forall a. Eq a -> (Accesses -> a -> a -> Bool) -> Cacheable a
unchanged :: Accesses -> NonNegativeInt -> NonNegativeInt -> Bool
$cunchanged :: Accesses -> NonNegativeInt -> NonNegativeInt -> Bool
$cp1Cacheable :: Eq NonNegativeInt
Cacheable, Int -> NonNegativeInt -> Int
NonNegativeInt -> Int
(Int -> NonNegativeInt -> Int)
-> (NonNegativeInt -> Int) -> Hashable NonNegativeInt
forall a. (Int -> a -> Int) -> (a -> Int) -> Hashable a
hash :: NonNegativeInt -> Int
$chash :: NonNegativeInt -> Int
hashWithSalt :: Int -> NonNegativeInt -> Int
$chashWithSalt :: Int -> NonNegativeInt -> Int
Hashable)
mkNonNegativeInt :: Int -> Maybe NonNegativeInt
mkNonNegativeInt :: Int -> Maybe NonNegativeInt
mkNonNegativeInt Int
x = case Int
x Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= Int
0 of
Bool
True -> NonNegativeInt -> Maybe NonNegativeInt
forall a. a -> Maybe a
Just (NonNegativeInt -> Maybe NonNegativeInt)
-> NonNegativeInt -> Maybe NonNegativeInt
forall a b. (a -> b) -> a -> b
$ Int -> NonNegativeInt
NonNegativeInt Int
x
Bool
False -> Maybe NonNegativeInt
forall a. Maybe a
Nothing
unsafeNonNegativeInt :: Int -> NonNegativeInt
unsafeNonNegativeInt :: Int -> NonNegativeInt
unsafeNonNegativeInt = Int -> NonNegativeInt
NonNegativeInt
instance FromJSON NonNegativeInt where
parseJSON :: Value -> Parser NonNegativeInt
parseJSON = String
-> (Scientific -> Parser NonNegativeInt)
-> Value
-> Parser NonNegativeInt
forall a. String -> (Scientific -> Parser a) -> Value -> Parser a
Aeson.withScientific String
"NonNegativeInt" ((Scientific -> Parser NonNegativeInt)
-> Value -> Parser NonNegativeInt)
-> (Scientific -> Parser NonNegativeInt)
-> Value
-> Parser NonNegativeInt
forall a b. (a -> b) -> a -> b
$ \Scientific
t -> do
case Scientific
t Scientific -> Scientific -> Bool
forall a. Ord a => a -> a -> Bool
>= Scientific
0 of
Bool
True -> Parser NonNegativeInt
-> (Int -> Parser NonNegativeInt)
-> Maybe Int
-> Parser NonNegativeInt
forall b a. b -> (a -> b) -> Maybe a -> b
maybe (String -> Parser NonNegativeInt
forall (m :: * -> *) a. MonadFail m => String -> m a
fail String
"integer passed is out of bounds") (NonNegativeInt -> Parser NonNegativeInt
forall (f :: * -> *) a. Applicative f => a -> f a
pure (NonNegativeInt -> Parser NonNegativeInt)
-> (Int -> NonNegativeInt) -> Int -> Parser NonNegativeInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> NonNegativeInt
NonNegativeInt) (Maybe Int -> Parser NonNegativeInt)
-> Maybe Int -> Parser NonNegativeInt
forall a b. (a -> b) -> a -> b
$ Scientific -> Maybe Int
forall i. (Integral i, Bounded i) => Scientific -> Maybe i
Scientific.toBoundedInteger Scientific
t
Bool
False -> String -> Parser NonNegativeInt
forall (m :: * -> *) a. MonadFail m => String -> m a
fail String
"negative value not allowed"
newtype PositiveInt = PositiveInt {PositiveInt -> Int
getPositiveInt :: Int}
deriving (Int -> PositiveInt -> ShowS
[PositiveInt] -> ShowS
PositiveInt -> String
(Int -> PositiveInt -> ShowS)
-> (PositiveInt -> String)
-> ([PositiveInt] -> ShowS)
-> Show PositiveInt
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PositiveInt] -> ShowS
$cshowList :: [PositiveInt] -> ShowS
show :: PositiveInt -> String
$cshow :: PositiveInt -> String
showsPrec :: Int -> PositiveInt -> ShowS
$cshowsPrec :: Int -> PositiveInt -> ShowS
Show, PositiveInt -> PositiveInt -> Bool
(PositiveInt -> PositiveInt -> Bool)
-> (PositiveInt -> PositiveInt -> Bool) -> Eq PositiveInt
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PositiveInt -> PositiveInt -> Bool
$c/= :: PositiveInt -> PositiveInt -> Bool
== :: PositiveInt -> PositiveInt -> Bool
$c== :: PositiveInt -> PositiveInt -> Bool
Eq, [PositiveInt] -> Value
[PositiveInt] -> Encoding
PositiveInt -> Value
PositiveInt -> Encoding
(PositiveInt -> Value)
-> (PositiveInt -> Encoding)
-> ([PositiveInt] -> Value)
-> ([PositiveInt] -> Encoding)
-> ToJSON PositiveInt
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [PositiveInt] -> Encoding
$ctoEncodingList :: [PositiveInt] -> Encoding
toJSONList :: [PositiveInt] -> Value
$ctoJSONList :: [PositiveInt] -> Value
toEncoding :: PositiveInt -> Encoding
$ctoEncoding :: PositiveInt -> Encoding
toJSON :: PositiveInt -> Value
$ctoJSON :: PositiveInt -> Value
ToJSON, (forall x. PositiveInt -> Rep PositiveInt x)
-> (forall x. Rep PositiveInt x -> PositiveInt)
-> Generic PositiveInt
forall x. Rep PositiveInt x -> PositiveInt
forall x. PositiveInt -> Rep PositiveInt x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep PositiveInt x -> PositiveInt
$cfrom :: forall x. PositiveInt -> Rep PositiveInt x
Generic, PositiveInt -> ()
(PositiveInt -> ()) -> NFData PositiveInt
forall a. (a -> ()) -> NFData a
rnf :: PositiveInt -> ()
$crnf :: PositiveInt -> ()
NFData, Eq PositiveInt
Eq PositiveInt
-> (Accesses -> PositiveInt -> PositiveInt -> Bool)
-> Cacheable PositiveInt
Accesses -> PositiveInt -> PositiveInt -> Bool
forall a. Eq a -> (Accesses -> a -> a -> Bool) -> Cacheable a
unchanged :: Accesses -> PositiveInt -> PositiveInt -> Bool
$cunchanged :: Accesses -> PositiveInt -> PositiveInt -> Bool
$cp1Cacheable :: Eq PositiveInt
Cacheable, Int -> PositiveInt -> Int
PositiveInt -> Int
(Int -> PositiveInt -> Int)
-> (PositiveInt -> Int) -> Hashable PositiveInt
forall a. (Int -> a -> Int) -> (a -> Int) -> Hashable a
hash :: PositiveInt -> Int
$chash :: PositiveInt -> Int
hashWithSalt :: Int -> PositiveInt -> Int
$chashWithSalt :: Int -> PositiveInt -> Int
Hashable)
mkPositiveInt :: Int -> Maybe PositiveInt
mkPositiveInt :: Int -> Maybe PositiveInt
mkPositiveInt Int
x = case Int
x Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
0 of
Bool
True -> PositiveInt -> Maybe PositiveInt
forall a. a -> Maybe a
Just (PositiveInt -> Maybe PositiveInt)
-> PositiveInt -> Maybe PositiveInt
forall a b. (a -> b) -> a -> b
$ Int -> PositiveInt
PositiveInt Int
x
Bool
False -> Maybe PositiveInt
forall a. Maybe a
Nothing
unsafePositiveInt :: Int -> PositiveInt
unsafePositiveInt :: Int -> PositiveInt
unsafePositiveInt = Int -> PositiveInt
PositiveInt
instance FromJSON PositiveInt where
parseJSON :: Value -> Parser PositiveInt
parseJSON = String
-> (Scientific -> Parser PositiveInt)
-> Value
-> Parser PositiveInt
forall a. String -> (Scientific -> Parser a) -> Value -> Parser a
Aeson.withScientific String
"NonNegativeInt" ((Scientific -> Parser PositiveInt) -> Value -> Parser PositiveInt)
-> (Scientific -> Parser PositiveInt)
-> Value
-> Parser PositiveInt
forall a b. (a -> b) -> a -> b
$ \Scientific
t -> do
case Scientific
t Scientific -> Scientific -> Bool
forall a. Ord a => a -> a -> Bool
> Scientific
0 of
Bool
True -> Parser PositiveInt
-> (Int -> Parser PositiveInt) -> Maybe Int -> Parser PositiveInt
forall b a. b -> (a -> b) -> Maybe a -> b
maybe (String -> Parser PositiveInt
forall (m :: * -> *) a. MonadFail m => String -> m a
fail String
"integer passed is out of bounds") (PositiveInt -> Parser PositiveInt
forall (f :: * -> *) a. Applicative f => a -> f a
pure (PositiveInt -> Parser PositiveInt)
-> (Int -> PositiveInt) -> Int -> Parser PositiveInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> PositiveInt
PositiveInt) (Maybe Int -> Parser PositiveInt)
-> Maybe Int -> Parser PositiveInt
forall a b. (a -> b) -> a -> b
$ Scientific -> Maybe Int
forall i. (Integral i, Bounded i) => Scientific -> Maybe i
Scientific.toBoundedInteger Scientific
t
Bool
False -> String -> Parser PositiveInt
forall (m :: * -> *) a. MonadFail m => String -> m a
fail String
"integer passed is out of bounds"
newtype NonNegativeDiffTime = NonNegativeDiffTime {NonNegativeDiffTime -> DiffTime
unNonNegativeDiffTime :: DiffTime}
deriving (Int -> NonNegativeDiffTime -> ShowS
[NonNegativeDiffTime] -> ShowS
NonNegativeDiffTime -> String
(Int -> NonNegativeDiffTime -> ShowS)
-> (NonNegativeDiffTime -> String)
-> ([NonNegativeDiffTime] -> ShowS)
-> Show NonNegativeDiffTime
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [NonNegativeDiffTime] -> ShowS
$cshowList :: [NonNegativeDiffTime] -> ShowS
show :: NonNegativeDiffTime -> String
$cshow :: NonNegativeDiffTime -> String
showsPrec :: Int -> NonNegativeDiffTime -> ShowS
$cshowsPrec :: Int -> NonNegativeDiffTime -> ShowS
Show, NonNegativeDiffTime -> NonNegativeDiffTime -> Bool
(NonNegativeDiffTime -> NonNegativeDiffTime -> Bool)
-> (NonNegativeDiffTime -> NonNegativeDiffTime -> Bool)
-> Eq NonNegativeDiffTime
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: NonNegativeDiffTime -> NonNegativeDiffTime -> Bool
$c/= :: NonNegativeDiffTime -> NonNegativeDiffTime -> Bool
== :: NonNegativeDiffTime -> NonNegativeDiffTime -> Bool
$c== :: NonNegativeDiffTime -> NonNegativeDiffTime -> Bool
Eq, [NonNegativeDiffTime] -> Value
[NonNegativeDiffTime] -> Encoding
NonNegativeDiffTime -> Value
NonNegativeDiffTime -> Encoding
(NonNegativeDiffTime -> Value)
-> (NonNegativeDiffTime -> Encoding)
-> ([NonNegativeDiffTime] -> Value)
-> ([NonNegativeDiffTime] -> Encoding)
-> ToJSON NonNegativeDiffTime
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [NonNegativeDiffTime] -> Encoding
$ctoEncodingList :: [NonNegativeDiffTime] -> Encoding
toJSONList :: [NonNegativeDiffTime] -> Value
$ctoJSONList :: [NonNegativeDiffTime] -> Value
toEncoding :: NonNegativeDiffTime -> Encoding
$ctoEncoding :: NonNegativeDiffTime -> Encoding
toJSON :: NonNegativeDiffTime -> Value
$ctoJSON :: NonNegativeDiffTime -> Value
ToJSON, (forall x. NonNegativeDiffTime -> Rep NonNegativeDiffTime x)
-> (forall x. Rep NonNegativeDiffTime x -> NonNegativeDiffTime)
-> Generic NonNegativeDiffTime
forall x. Rep NonNegativeDiffTime x -> NonNegativeDiffTime
forall x. NonNegativeDiffTime -> Rep NonNegativeDiffTime x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep NonNegativeDiffTime x -> NonNegativeDiffTime
$cfrom :: forall x. NonNegativeDiffTime -> Rep NonNegativeDiffTime x
Generic, NonNegativeDiffTime -> ()
(NonNegativeDiffTime -> ()) -> NFData NonNegativeDiffTime
forall a. (a -> ()) -> NFData a
rnf :: NonNegativeDiffTime -> ()
$crnf :: NonNegativeDiffTime -> ()
NFData, Eq NonNegativeDiffTime
Eq NonNegativeDiffTime
-> (Accesses -> NonNegativeDiffTime -> NonNegativeDiffTime -> Bool)
-> Cacheable NonNegativeDiffTime
Accesses -> NonNegativeDiffTime -> NonNegativeDiffTime -> Bool
forall a. Eq a -> (Accesses -> a -> a -> Bool) -> Cacheable a
unchanged :: Accesses -> NonNegativeDiffTime -> NonNegativeDiffTime -> Bool
$cunchanged :: Accesses -> NonNegativeDiffTime -> NonNegativeDiffTime -> Bool
$cp1Cacheable :: Eq NonNegativeDiffTime
Cacheable, Integer -> NonNegativeDiffTime
NonNegativeDiffTime -> NonNegativeDiffTime
NonNegativeDiffTime -> NonNegativeDiffTime -> NonNegativeDiffTime
(NonNegativeDiffTime -> NonNegativeDiffTime -> NonNegativeDiffTime)
-> (NonNegativeDiffTime
-> NonNegativeDiffTime -> NonNegativeDiffTime)
-> (NonNegativeDiffTime
-> NonNegativeDiffTime -> NonNegativeDiffTime)
-> (NonNegativeDiffTime -> NonNegativeDiffTime)
-> (NonNegativeDiffTime -> NonNegativeDiffTime)
-> (NonNegativeDiffTime -> NonNegativeDiffTime)
-> (Integer -> NonNegativeDiffTime)
-> Num NonNegativeDiffTime
forall a.
(a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (Integer -> a)
-> Num a
fromInteger :: Integer -> NonNegativeDiffTime
$cfromInteger :: Integer -> NonNegativeDiffTime
signum :: NonNegativeDiffTime -> NonNegativeDiffTime
$csignum :: NonNegativeDiffTime -> NonNegativeDiffTime
abs :: NonNegativeDiffTime -> NonNegativeDiffTime
$cabs :: NonNegativeDiffTime -> NonNegativeDiffTime
negate :: NonNegativeDiffTime -> NonNegativeDiffTime
$cnegate :: NonNegativeDiffTime -> NonNegativeDiffTime
* :: NonNegativeDiffTime -> NonNegativeDiffTime -> NonNegativeDiffTime
$c* :: NonNegativeDiffTime -> NonNegativeDiffTime -> NonNegativeDiffTime
- :: NonNegativeDiffTime -> NonNegativeDiffTime -> NonNegativeDiffTime
$c- :: NonNegativeDiffTime -> NonNegativeDiffTime -> NonNegativeDiffTime
+ :: NonNegativeDiffTime -> NonNegativeDiffTime -> NonNegativeDiffTime
$c+ :: NonNegativeDiffTime -> NonNegativeDiffTime -> NonNegativeDiffTime
Num)
unsafeNonNegativeDiffTime :: DiffTime -> NonNegativeDiffTime
unsafeNonNegativeDiffTime :: DiffTime -> NonNegativeDiffTime
unsafeNonNegativeDiffTime = DiffTime -> NonNegativeDiffTime
NonNegativeDiffTime
mkNonNegativeDiffTime :: DiffTime -> Maybe NonNegativeDiffTime
mkNonNegativeDiffTime :: DiffTime -> Maybe NonNegativeDiffTime
mkNonNegativeDiffTime DiffTime
x = case DiffTime
x DiffTime -> DiffTime -> Bool
forall a. Ord a => a -> a -> Bool
>= DiffTime
0 of
Bool
True -> NonNegativeDiffTime -> Maybe NonNegativeDiffTime
forall a. a -> Maybe a
Just (NonNegativeDiffTime -> Maybe NonNegativeDiffTime)
-> NonNegativeDiffTime -> Maybe NonNegativeDiffTime
forall a b. (a -> b) -> a -> b
$ DiffTime -> NonNegativeDiffTime
NonNegativeDiffTime DiffTime
x
Bool
False -> Maybe NonNegativeDiffTime
forall a. Maybe a
Nothing
instance FromJSON NonNegativeDiffTime where
parseJSON :: Value -> Parser NonNegativeDiffTime
parseJSON = String
-> (Scientific -> Parser NonNegativeDiffTime)
-> Value
-> Parser NonNegativeDiffTime
forall a. String -> (Scientific -> Parser a) -> Value -> Parser a
Aeson.withScientific String
"NonNegativeDiffTime" ((Scientific -> Parser NonNegativeDiffTime)
-> Value -> Parser NonNegativeDiffTime)
-> (Scientific -> Parser NonNegativeDiffTime)
-> Value
-> Parser NonNegativeDiffTime
forall a b. (a -> b) -> a -> b
$ \Scientific
t -> do
case Scientific
t Scientific -> Scientific -> Bool
forall a. Ord a => a -> a -> Bool
>= Scientific
0 of
Bool
True -> NonNegativeDiffTime -> Parser NonNegativeDiffTime
forall (m :: * -> *) a. Monad m => a -> m a
return (NonNegativeDiffTime -> Parser NonNegativeDiffTime)
-> NonNegativeDiffTime -> Parser NonNegativeDiffTime
forall a b. (a -> b) -> a -> b
$ DiffTime -> NonNegativeDiffTime
NonNegativeDiffTime (DiffTime -> NonNegativeDiffTime)
-> (Scientific -> DiffTime) -> Scientific -> NonNegativeDiffTime
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Scientific -> DiffTime
forall a b. (Real a, Fractional b) => a -> b
realToFrac (Scientific -> NonNegativeDiffTime)
-> Scientific -> NonNegativeDiffTime
forall a b. (a -> b) -> a -> b
$ Scientific
t
Bool
False -> String -> Parser NonNegativeDiffTime
forall (m :: * -> *) a. MonadFail m => String -> m a
fail String
"negative value not allowed"