module Codeforces.Types.RatingChange where
import           Codeforces.Types.Common
import           Data.Aeson
import           Data.Text                      ( Text )
import           Data.Time
import           Data.Time.Clock.POSIX          ( posixSecondsToUTCTime )
data RatingChange = RatingChange
    { RatingChange -> ContestId
rcContestId        :: ContestId
    , RatingChange -> Text
rcContestName      :: Text
    , RatingChange -> Handle
rcHandle           :: Handle
    , RatingChange -> Int
rcRank             :: Int
    , RatingChange -> UTCTime
rcRatingUpdateDate :: UTCTime
    , RatingChange -> Int
rcOldRating        :: Rating
    , RatingChange -> Int
rcNewRating        :: Rating
    }
    deriving Int -> RatingChange -> ShowS
[RatingChange] -> ShowS
RatingChange -> String
(Int -> RatingChange -> ShowS)
-> (RatingChange -> String)
-> ([RatingChange] -> ShowS)
-> Show RatingChange
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [RatingChange] -> ShowS
$cshowList :: [RatingChange] -> ShowS
show :: RatingChange -> String
$cshow :: RatingChange -> String
showsPrec :: Int -> RatingChange -> ShowS
$cshowsPrec :: Int -> RatingChange -> ShowS
Show
instance FromJSON RatingChange where
    parseJSON :: Value -> Parser RatingChange
parseJSON = String
-> (Object -> Parser RatingChange) -> Value -> Parser RatingChange
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"RatingChange" ((Object -> Parser RatingChange) -> Value -> Parser RatingChange)
-> (Object -> Parser RatingChange) -> Value -> Parser RatingChange
forall a b. (a -> b) -> a -> b
$ \Object
v ->
        ContestId
-> Text -> Handle -> Int -> UTCTime -> Int -> Int -> RatingChange
RatingChange
            (ContestId
 -> Text -> Handle -> Int -> UTCTime -> Int -> Int -> RatingChange)
-> Parser ContestId
-> Parser
     (Text -> Handle -> Int -> UTCTime -> Int -> Int -> RatingChange)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Object
v Object -> Text -> Parser ContestId
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"contestId")
            Parser
  (Text -> Handle -> Int -> UTCTime -> Int -> Int -> RatingChange)
-> Parser Text
-> Parser (Handle -> Int -> UTCTime -> Int -> Int -> RatingChange)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (Object
v Object -> Text -> Parser Text
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"contestName")
            Parser (Handle -> Int -> UTCTime -> Int -> Int -> RatingChange)
-> Parser Handle
-> Parser (Int -> UTCTime -> Int -> Int -> RatingChange)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (Object
v Object -> Text -> Parser Handle
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"handle")
            Parser (Int -> UTCTime -> Int -> Int -> RatingChange)
-> Parser Int -> Parser (UTCTime -> Int -> Int -> RatingChange)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (Object
v Object -> Text -> Parser Int
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"rank")
            Parser (UTCTime -> Int -> Int -> RatingChange)
-> Parser UTCTime -> Parser (Int -> Int -> RatingChange)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (POSIXTime -> UTCTime
posixSecondsToUTCTime (POSIXTime -> UTCTime) -> Parser POSIXTime -> Parser UTCTime
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Object
v Object -> Text -> Parser POSIXTime
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"ratingUpdateTimeSeconds"))
            Parser (Int -> Int -> RatingChange)
-> Parser Int -> Parser (Int -> RatingChange)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (Object
v Object -> Text -> Parser Int
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"oldRating")
            Parser (Int -> RatingChange) -> Parser Int -> Parser RatingChange
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (Object
v Object -> Text -> Parser Int
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"newRating")