{-# LANGUAGE OverloadedStrings #-} module CoinbasePro.WebSocketFeed.Channel.Status ( Status (..) ) where import Data.Aeson (FromJSON, parseJSON, withObject, (.:)) import CoinbasePro.MarketData.Types (Product) import CoinbasePro.Types (Currency) data Status = Status { Status -> [Currency] currencies :: [Currency] , Status -> [Product] products :: [Product] } deriving (Status -> Status -> Bool (Status -> Status -> Bool) -> (Status -> Status -> Bool) -> Eq Status forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a /= :: Status -> Status -> Bool $c/= :: Status -> Status -> Bool == :: Status -> Status -> Bool $c== :: Status -> Status -> Bool Eq, Int -> Status -> ShowS [Status] -> ShowS Status -> String (Int -> Status -> ShowS) -> (Status -> String) -> ([Status] -> ShowS) -> Show Status forall a. (Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a showList :: [Status] -> ShowS $cshowList :: [Status] -> ShowS show :: Status -> String $cshow :: Status -> String showsPrec :: Int -> Status -> ShowS $cshowsPrec :: Int -> Status -> ShowS Show) instance FromJSON Status where parseJSON :: Value -> Parser Status parseJSON = String -> (Object -> Parser Status) -> Value -> Parser Status forall a. String -> (Object -> Parser a) -> Value -> Parser a withObject String "status" ((Object -> Parser Status) -> Value -> Parser Status) -> (Object -> Parser Status) -> Value -> Parser Status forall a b. (a -> b) -> a -> b $ \Object o -> [Currency] -> [Product] -> Status Status ([Currency] -> [Product] -> Status) -> Parser [Currency] -> Parser ([Product] -> Status) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b <$> Object o Object -> Text -> Parser [Currency] forall a. FromJSON a => Object -> Text -> Parser a .: Text "currencies" Parser ([Product] -> Status) -> Parser [Product] -> Parser Status forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b <*> Object o Object -> Text -> Parser [Product] forall a. FromJSON a => Object -> Text -> Parser a .: Text "products"