-- | Types for common servics

module Blockfrost.Types.Common
  ( URLVersion (..)
  , Healthy (..)
  , ServerTime (..)
  , Metric (..)
  ) where

import Blockfrost.Types.Shared
import Data.Aeson
import Data.Text (Text)
import Deriving.Aeson
import Servant.Docs (ToSample (..), samples, singleSample)
import Test.QuickCheck.Arbitrary (Arbitrary (..))
import Test.QuickCheck.Instances ()
import Test.QuickCheck.Modifiers

-- | Root endpoint reply
data URLVersion = URLVersion
  { URLVersion -> Text
_urlVersionUrl     :: Text
  , URLVersion -> Text
_urlVersionVersion :: Text
  }
  deriving stock (Int -> URLVersion -> ShowS
[URLVersion] -> ShowS
URLVersion -> String
(Int -> URLVersion -> ShowS)
-> (URLVersion -> String)
-> ([URLVersion] -> ShowS)
-> Show URLVersion
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [URLVersion] -> ShowS
$cshowList :: [URLVersion] -> ShowS
show :: URLVersion -> String
$cshow :: URLVersion -> String
showsPrec :: Int -> URLVersion -> ShowS
$cshowsPrec :: Int -> URLVersion -> ShowS
Show, URLVersion -> URLVersion -> Bool
(URLVersion -> URLVersion -> Bool)
-> (URLVersion -> URLVersion -> Bool) -> Eq URLVersion
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: URLVersion -> URLVersion -> Bool
$c/= :: URLVersion -> URLVersion -> Bool
== :: URLVersion -> URLVersion -> Bool
$c== :: URLVersion -> URLVersion -> Bool
Eq, (forall x. URLVersion -> Rep URLVersion x)
-> (forall x. Rep URLVersion x -> URLVersion) -> Generic URLVersion
forall x. Rep URLVersion x -> URLVersion
forall x. URLVersion -> Rep URLVersion x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep URLVersion x -> URLVersion
$cfrom :: forall x. URLVersion -> Rep URLVersion x
Generic)
  deriving (Value -> Parser [URLVersion]
Value -> Parser URLVersion
(Value -> Parser URLVersion)
-> (Value -> Parser [URLVersion]) -> FromJSON URLVersion
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [URLVersion]
$cparseJSONList :: Value -> Parser [URLVersion]
parseJSON :: Value -> Parser URLVersion
$cparseJSON :: Value -> Parser URLVersion
FromJSON, [URLVersion] -> Encoding
[URLVersion] -> Value
URLVersion -> Encoding
URLVersion -> Value
(URLVersion -> Value)
-> (URLVersion -> Encoding)
-> ([URLVersion] -> Value)
-> ([URLVersion] -> Encoding)
-> ToJSON URLVersion
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [URLVersion] -> Encoding
$ctoEncodingList :: [URLVersion] -> Encoding
toJSONList :: [URLVersion] -> Value
$ctoJSONList :: [URLVersion] -> Value
toEncoding :: URLVersion -> Encoding
$ctoEncoding :: URLVersion -> Encoding
toJSON :: URLVersion -> Value
$ctoJSON :: URLVersion -> Value
ToJSON)
  via CustomJSON '[FieldLabelModifier '[StripPrefix "_urlVersion", CamelToSnake]] URLVersion

instance ToSample URLVersion where
  toSamples :: Proxy URLVersion -> [(Text, URLVersion)]
toSamples = [(Text, URLVersion)] -> Proxy URLVersion -> [(Text, URLVersion)]
forall (f :: * -> *) a. Applicative f => a -> f a
pure ([(Text, URLVersion)] -> Proxy URLVersion -> [(Text, URLVersion)])
-> [(Text, URLVersion)] -> Proxy URLVersion -> [(Text, URLVersion)]
forall a b. (a -> b) -> a -> b
$ URLVersion -> [(Text, URLVersion)]
forall a. a -> [(Text, a)]
singleSample (URLVersion -> [(Text, URLVersion)])
-> URLVersion -> [(Text, URLVersion)]
forall a b. (a -> b) -> a -> b
$
    Text -> Text -> URLVersion
URLVersion Text
"http://blockfrost.io" Text
"0.0.0"

-- | Health endpoint reply
newtype Healthy = Healthy
  { Healthy -> Bool
isHealthy :: Bool
  }
  deriving stock (Int -> Healthy -> ShowS
[Healthy] -> ShowS
Healthy -> String
(Int -> Healthy -> ShowS)
-> (Healthy -> String) -> ([Healthy] -> ShowS) -> Show Healthy
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Healthy] -> ShowS
$cshowList :: [Healthy] -> ShowS
show :: Healthy -> String
$cshow :: Healthy -> String
showsPrec :: Int -> Healthy -> ShowS
$cshowsPrec :: Int -> Healthy -> ShowS
Show, Healthy -> Healthy -> Bool
(Healthy -> Healthy -> Bool)
-> (Healthy -> Healthy -> Bool) -> Eq Healthy
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Healthy -> Healthy -> Bool
$c/= :: Healthy -> Healthy -> Bool
== :: Healthy -> Healthy -> Bool
$c== :: Healthy -> Healthy -> Bool
Eq, (forall x. Healthy -> Rep Healthy x)
-> (forall x. Rep Healthy x -> Healthy) -> Generic Healthy
forall x. Rep Healthy x -> Healthy
forall x. Healthy -> Rep Healthy x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Healthy x -> Healthy
$cfrom :: forall x. Healthy -> Rep Healthy x
Generic)
  deriving (Value -> Parser [Healthy]
Value -> Parser Healthy
(Value -> Parser Healthy)
-> (Value -> Parser [Healthy]) -> FromJSON Healthy
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [Healthy]
$cparseJSONList :: Value -> Parser [Healthy]
parseJSON :: Value -> Parser Healthy
$cparseJSON :: Value -> Parser Healthy
FromJSON, [Healthy] -> Encoding
[Healthy] -> Value
Healthy -> Encoding
Healthy -> Value
(Healthy -> Value)
-> (Healthy -> Encoding)
-> ([Healthy] -> Value)
-> ([Healthy] -> Encoding)
-> ToJSON Healthy
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [Healthy] -> Encoding
$ctoEncodingList :: [Healthy] -> Encoding
toJSONList :: [Healthy] -> Value
$ctoJSONList :: [Healthy] -> Value
toEncoding :: Healthy -> Encoding
$ctoEncoding :: Healthy -> Encoding
toJSON :: Healthy -> Value
$ctoJSON :: Healthy -> Value
ToJSON)
  via CustomJSON '[FieldLabelModifier '[CamelToSnake]] Healthy

instance ToSample Healthy where
  toSamples :: Proxy Healthy -> [(Text, Healthy)]
toSamples = [(Text, Healthy)] -> Proxy Healthy -> [(Text, Healthy)]
forall (f :: * -> *) a. Applicative f => a -> f a
pure ([(Text, Healthy)] -> Proxy Healthy -> [(Text, Healthy)])
-> [(Text, Healthy)] -> Proxy Healthy -> [(Text, Healthy)]
forall a b. (a -> b) -> a -> b
$ Healthy -> [(Text, Healthy)]
forall a. a -> [(Text, a)]
singleSample (Healthy -> [(Text, Healthy)]) -> Healthy -> [(Text, Healthy)]
forall a b. (a -> b) -> a -> b
$ Bool -> Healthy
Healthy Bool
False

-- | Health clock endpoint reply
newtype ServerTime = ServerTime
  { ServerTime -> POSIXTime
serverTime :: POSIXTime
  }
  deriving stock (Int -> ServerTime -> ShowS
[ServerTime] -> ShowS
ServerTime -> String
(Int -> ServerTime -> ShowS)
-> (ServerTime -> String)
-> ([ServerTime] -> ShowS)
-> Show ServerTime
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ServerTime] -> ShowS
$cshowList :: [ServerTime] -> ShowS
show :: ServerTime -> String
$cshow :: ServerTime -> String
showsPrec :: Int -> ServerTime -> ShowS
$cshowsPrec :: Int -> ServerTime -> ShowS
Show, ServerTime -> ServerTime -> Bool
(ServerTime -> ServerTime -> Bool)
-> (ServerTime -> ServerTime -> Bool) -> Eq ServerTime
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ServerTime -> ServerTime -> Bool
$c/= :: ServerTime -> ServerTime -> Bool
== :: ServerTime -> ServerTime -> Bool
$c== :: ServerTime -> ServerTime -> Bool
Eq, (forall x. ServerTime -> Rep ServerTime x)
-> (forall x. Rep ServerTime x -> ServerTime) -> Generic ServerTime
forall x. Rep ServerTime x -> ServerTime
forall x. ServerTime -> Rep ServerTime x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ServerTime x -> ServerTime
$cfrom :: forall x. ServerTime -> Rep ServerTime x
Generic)

instance FromJSON ServerTime where
  parseJSON :: Value -> Parser ServerTime
parseJSON = String
-> (Object -> Parser ServerTime) -> Value -> Parser ServerTime
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"ServerTime"
    ((Object -> Parser ServerTime) -> Value -> Parser ServerTime)
-> (Object -> Parser ServerTime) -> Value -> Parser ServerTime
forall a b. (a -> b) -> a -> b
$ \Object
v -> Object
v Object -> Text -> Parser Value
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"server_time"
    Parser Value -> (Value -> Parser ServerTime) -> Parser ServerTime
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \Value
t -> POSIXTime -> ServerTime
ServerTime (POSIXTime -> ServerTime)
-> (Integer -> POSIXTime) -> Integer -> ServerTime
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Integer -> POSIXTime
millisecondsToPosix (Integer -> ServerTime) -> Parser Integer -> Parser ServerTime
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Value -> Parser Integer
forall a. FromJSON a => Value -> Parser a
parseJSON @Integer Value
t

instance ToJSON ServerTime where
  toJSON :: ServerTime -> Value
toJSON (ServerTime POSIXTime
t) =
    [Pair] -> Value
object [
      Text
"server_time" Text -> Integer -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= POSIXTime -> Integer
posixToMilliseconds POSIXTime
t
    ]

instance ToSample ServerTime where
    toSamples :: Proxy ServerTime -> [(Text, ServerTime)]
toSamples Proxy ServerTime
_ = ServerTime -> [(Text, ServerTime)]
forall a. a -> [(Text, a)]
singleSample (ServerTime -> [(Text, ServerTime)])
-> ServerTime -> [(Text, ServerTime)]
forall a b. (a -> b) -> a -> b
$ POSIXTime -> ServerTime
ServerTime (POSIXTime -> ServerTime) -> POSIXTime -> ServerTime
forall a b. (a -> b) -> a -> b
$ Integer -> POSIXTime
millisecondsToPosix Integer
1603400958947

instance Arbitrary ServerTime where
  arbitrary :: Gen ServerTime
arbitrary = do
    Positive (Integer
n :: Integer) <- Gen (Positive Integer)
forall a. Arbitrary a => Gen a
arbitrary
    ServerTime -> Gen ServerTime
forall (f :: * -> *) a. Applicative f => a -> f a
pure (ServerTime -> Gen ServerTime) -> ServerTime -> Gen ServerTime
forall a b. (a -> b) -> a -> b
$ POSIXTime -> ServerTime
ServerTime (Integer -> POSIXTime
forall a. Num a => Integer -> a
fromInteger Integer
n POSIXTime -> POSIXTime -> POSIXTime
forall a. Fractional a => a -> a -> a
/ POSIXTime
1000)

-- | Metrics response
data Metric = Metric {
    Metric -> POSIXTime
_metricTime  :: POSIXTime
  , Metric -> Integer
_metricCalls :: Integer
  }
  deriving stock (Int -> Metric -> ShowS
[Metric] -> ShowS
Metric -> String
(Int -> Metric -> ShowS)
-> (Metric -> String) -> ([Metric] -> ShowS) -> Show Metric
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Metric] -> ShowS
$cshowList :: [Metric] -> ShowS
show :: Metric -> String
$cshow :: Metric -> String
showsPrec :: Int -> Metric -> ShowS
$cshowsPrec :: Int -> Metric -> ShowS
Show, Metric -> Metric -> Bool
(Metric -> Metric -> Bool)
-> (Metric -> Metric -> Bool) -> Eq Metric
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Metric -> Metric -> Bool
$c/= :: Metric -> Metric -> Bool
== :: Metric -> Metric -> Bool
$c== :: Metric -> Metric -> Bool
Eq, (forall x. Metric -> Rep Metric x)
-> (forall x. Rep Metric x -> Metric) -> Generic Metric
forall x. Rep Metric x -> Metric
forall x. Metric -> Rep Metric x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Metric x -> Metric
$cfrom :: forall x. Metric -> Rep Metric x
Generic)
  deriving (Value -> Parser [Metric]
Value -> Parser Metric
(Value -> Parser Metric)
-> (Value -> Parser [Metric]) -> FromJSON Metric
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [Metric]
$cparseJSONList :: Value -> Parser [Metric]
parseJSON :: Value -> Parser Metric
$cparseJSON :: Value -> Parser Metric
FromJSON, [Metric] -> Encoding
[Metric] -> Value
Metric -> Encoding
Metric -> Value
(Metric -> Value)
-> (Metric -> Encoding)
-> ([Metric] -> Value)
-> ([Metric] -> Encoding)
-> ToJSON Metric
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [Metric] -> Encoding
$ctoEncodingList :: [Metric] -> Encoding
toJSONList :: [Metric] -> Value
$ctoJSONList :: [Metric] -> Value
toEncoding :: Metric -> Encoding
$ctoEncoding :: Metric -> Encoding
toJSON :: Metric -> Value
$ctoJSON :: Metric -> Value
ToJSON)
  via CustomJSON '[FieldLabelModifier '[StripPrefix "_metric", CamelToSnake]] Metric

instance ToSample Metric where
    toSamples :: Proxy Metric -> [(Text, Metric)]
toSamples Proxy Metric
_ = [Metric] -> [(Text, Metric)]
forall a. [a] -> [(Text, a)]
samples ([Metric] -> [(Text, Metric)]) -> [Metric] -> [(Text, Metric)]
forall a b. (a -> b) -> a -> b
$
      [ POSIXTime -> Integer -> Metric
Metric POSIXTime
1612543884 Integer
42
      , POSIXTime -> Integer -> Metric
Metric POSIXTime
1614523884 Integer
6942
      ]

-- Re-use @Metric@ for response with endpoint field
instance {-# OVERLAPS #-} ToJSON (Text, Metric) where
  toJSON :: (Text, Metric) -> Value
toJSON (Text
enp, Metric
m) = case Metric -> Value
forall a. ToJSON a => a -> Value
toJSON Metric
m of
    (Object Object
o) -> Object -> Value
Object (Object
o Object -> Object -> Object
forall a. Semigroup a => a -> a -> a
<> (Text
"endpoint" Text -> Value -> Object
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= (Text -> Value
forall a. ToJSON a => a -> Value
toJSON Text
enp)))
    Value
_          -> String -> Value
forall a. HasCallStack => String -> a
error String
"Absurd"

instance {-# OVERLAPS #-} FromJSON (Text, Metric) where
  parseJSON :: Value -> Parser (Text, Metric)
parseJSON v :: Value
v@(Object Object
o) = do
    Text
enp <- Object
o Object -> Text -> Parser Text
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"endpoint"
    Metric
ticker <- Value -> Parser Metric
forall a. FromJSON a => Value -> Parser a
parseJSON Value
v
    (Text, Metric) -> Parser (Text, Metric)
forall (m :: * -> *) a. Monad m => a -> m a
return (Text
enp, Metric
ticker)
  parseJSON Value
_ = String -> Parser (Text, Metric)
forall (m :: * -> *) a. MonadFail m => String -> m a
fail String
"Unexpected type for (Text, Metric)"

instance {-# OVERLAPS #-} ToSample (Text, Metric) where
  toSamples :: Proxy (Text, Metric) -> [(Text, (Text, Metric))]
toSamples Proxy (Text, Metric)
_ = [(Text, Metric)] -> [(Text, (Text, Metric))]
forall a. [a] -> [(Text, a)]
samples ([(Text, Metric)] -> [(Text, (Text, Metric))])
-> [(Text, Metric)] -> [(Text, (Text, Metric))]
forall a b. (a -> b) -> a -> b
$
    [ (Text
"block", POSIXTime -> Integer -> Metric
Metric POSIXTime
1612543814 Integer
182)
    , (Text
"epoch", POSIXTime -> Integer -> Metric
Metric POSIXTime
1612543814 Integer
42)
    , (Text
"block", POSIXTime -> Integer -> Metric
Metric POSIXTime
1612543812 Integer
775)
    , (Text
"epoch", POSIXTime -> Integer -> Metric
Metric POSIXTime
1612523884 Integer
4)
    , (Text
"block", POSIXTime -> Integer -> Metric
Metric POSIXTime
1612553884 Integer
89794)
    ]