{-# LANGUAGE StrictData #-}
module GitHub.Types.Base.DateTime where
import Control.Applicative ((<|>))
import Data.Aeson (FromJSON (..), ToJSON (..))
import Data.Text (Text)
import Data.Text.Arbitrary ()
import Test.QuickCheck.Arbitrary (Arbitrary (..))
import qualified Test.QuickCheck.Gen as Gen
data DateTime
= DateTimeStamp Int
| DateTimeText Text
deriving (DateTime -> DateTime -> Bool
(DateTime -> DateTime -> Bool)
-> (DateTime -> DateTime -> Bool) -> Eq DateTime
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DateTime -> DateTime -> Bool
$c/= :: DateTime -> DateTime -> Bool
== :: DateTime -> DateTime -> Bool
$c== :: DateTime -> DateTime -> Bool
Eq, Int -> DateTime -> ShowS
[DateTime] -> ShowS
DateTime -> String
(Int -> DateTime -> ShowS)
-> (DateTime -> String) -> ([DateTime] -> ShowS) -> Show DateTime
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DateTime] -> ShowS
$cshowList :: [DateTime] -> ShowS
show :: DateTime -> String
$cshow :: DateTime -> String
showsPrec :: Int -> DateTime -> ShowS
$cshowsPrec :: Int -> DateTime -> ShowS
Show, ReadPrec [DateTime]
ReadPrec DateTime
Int -> ReadS DateTime
ReadS [DateTime]
(Int -> ReadS DateTime)
-> ReadS [DateTime]
-> ReadPrec DateTime
-> ReadPrec [DateTime]
-> Read DateTime
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DateTime]
$creadListPrec :: ReadPrec [DateTime]
readPrec :: ReadPrec DateTime
$creadPrec :: ReadPrec DateTime
readList :: ReadS [DateTime]
$creadList :: ReadS [DateTime]
readsPrec :: Int -> ReadS DateTime
$creadsPrec :: Int -> ReadS DateTime
Read)
instance FromJSON DateTime where
parseJSON :: Value -> Parser DateTime
parseJSON Value
x =
Int -> DateTime
DateTimeStamp (Int -> DateTime) -> Parser Int -> Parser DateTime
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Value -> Parser Int
forall a. FromJSON a => Value -> Parser a
parseJSON Value
x
Parser DateTime -> Parser DateTime -> Parser DateTime
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Text -> DateTime
DateTimeText (Text -> DateTime) -> Parser Text -> Parser DateTime
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Value -> Parser Text
forall a. FromJSON a => Value -> Parser a
parseJSON Value
x
instance ToJSON DateTime where
toJSON :: DateTime -> Value
toJSON (DateTimeStamp Int
x) = Int -> Value
forall a. ToJSON a => a -> Value
toJSON Int
x
toJSON (DateTimeText Text
x) = Text -> Value
forall a. ToJSON a => a -> Value
toJSON Text
x
instance Arbitrary DateTime where
arbitrary :: Gen DateTime
arbitrary = [Gen DateTime] -> Gen DateTime
forall a. [Gen a] -> Gen a
Gen.oneof
[ Int -> DateTime
DateTimeStamp (Int -> DateTime) -> Gen Int -> Gen DateTime
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Gen Int
forall a. Arbitrary a => Gen a
arbitrary
, Text -> DateTime
DateTimeText (Text -> DateTime) -> Gen Text -> Gen DateTime
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Gen Text
forall a. Arbitrary a => Gen a
arbitrary
]