-- | Types for Nut.link servics

module Blockfrost.Types.NutLink
  ( NutlinkAddress (..)
  , NutlinkAddressTicker (..)
  , NutlinkTicker (..)
  ) where

import Blockfrost.Types.Shared
import Data.Aeson
import Data.Text (Text)
import Deriving.Aeson
import Servant.Docs (ToSample (..), samples, singleSample)

-- | Specific address metadata
data NutlinkAddress = NutlinkAddress
  { NutlinkAddress -> Address
_nutlinkAddressAddress      :: Address -- ^ Bech32 encoded address
  , NutlinkAddress -> Text
_nutlinkAddressMetadataUrl  :: Text -- ^ URL of the specific metadata file
  , NutlinkAddress -> Text
_nutlinkAddressMetadataHash :: Text -- ^ Hash of the metadata file
  , NutlinkAddress -> Maybe Value
_nutlinkAddressMetadata     :: Maybe Value -- ^ The cached metadata of the metadata_url file.
  }
  deriving stock (Int -> NutlinkAddress -> ShowS
[NutlinkAddress] -> ShowS
NutlinkAddress -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [NutlinkAddress] -> ShowS
$cshowList :: [NutlinkAddress] -> ShowS
show :: NutlinkAddress -> String
$cshow :: NutlinkAddress -> String
showsPrec :: Int -> NutlinkAddress -> ShowS
$cshowsPrec :: Int -> NutlinkAddress -> ShowS
Show, NutlinkAddress -> NutlinkAddress -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: NutlinkAddress -> NutlinkAddress -> Bool
$c/= :: NutlinkAddress -> NutlinkAddress -> Bool
== :: NutlinkAddress -> NutlinkAddress -> Bool
$c== :: NutlinkAddress -> NutlinkAddress -> Bool
Eq, forall x. Rep NutlinkAddress x -> NutlinkAddress
forall x. NutlinkAddress -> Rep NutlinkAddress x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep NutlinkAddress x -> NutlinkAddress
$cfrom :: forall x. NutlinkAddress -> Rep NutlinkAddress x
Generic)
  deriving (Value -> Parser [NutlinkAddress]
Value -> Parser NutlinkAddress
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [NutlinkAddress]
$cparseJSONList :: Value -> Parser [NutlinkAddress]
parseJSON :: Value -> Parser NutlinkAddress
$cparseJSON :: Value -> Parser NutlinkAddress
FromJSON, [NutlinkAddress] -> Encoding
[NutlinkAddress] -> Value
NutlinkAddress -> Encoding
NutlinkAddress -> Value
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [NutlinkAddress] -> Encoding
$ctoEncodingList :: [NutlinkAddress] -> Encoding
toJSONList :: [NutlinkAddress] -> Value
$ctoJSONList :: [NutlinkAddress] -> Value
toEncoding :: NutlinkAddress -> Encoding
$ctoEncoding :: NutlinkAddress -> Encoding
toJSON :: NutlinkAddress -> Value
$ctoJSON :: NutlinkAddress -> Value
ToJSON)
  via CustomJSON '[FieldLabelModifier '[StripPrefix "_nutlinkAddress", CamelToSnake]] NutlinkAddress

instance ToSample NutlinkAddress where
  toSamples :: Proxy NutlinkAddress -> [(Text, NutlinkAddress)]
toSamples = forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ forall a. a -> [(Text, a)]
singleSample forall a b. (a -> b) -> a -> b
$
    NutlinkAddress
      { _nutlinkAddressAddress :: Address
_nutlinkAddressAddress = Address
"addr1qxqs59lphg8g6qndelq8xwqn60ag3aeyfcp33c2kdp46a09re5df3pzwwmyq946axfcejy5n4x0y99wqpgtp2gd0k09qsgy6pz"
      , _nutlinkAddressMetadataUrl :: Text
_nutlinkAddressMetadataUrl = Text
"https://nut.link/metadata.json"
      , _nutlinkAddressMetadataHash :: Text
_nutlinkAddressMetadataHash = Text
"6bf124f217d0e5a0a8adb1dbd8540e1334280d49ab861127868339f43b3948af"
      , _nutlinkAddressMetadata :: Maybe Value
_nutlinkAddressMetadata = forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ [Pair] -> Value
object []
      }

-- | Ticker for specific metadata oracle
data NutlinkAddressTicker = NutlinkAddressTicker
  { NutlinkAddressTicker -> Text
_nutlinkAddressTickerName        :: Text -- ^ Name of the ticker
  , NutlinkAddressTicker -> Integer
_nutlinkAddressTickerCount       :: Integer -- ^ Number of ticker records
  , NutlinkAddressTicker -> Integer
_nutlinkAddressTickerLatestBlock :: Integer -- ^ Block height of the latest record
  }
  deriving stock (Int -> NutlinkAddressTicker -> ShowS
[NutlinkAddressTicker] -> ShowS
NutlinkAddressTicker -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [NutlinkAddressTicker] -> ShowS
$cshowList :: [NutlinkAddressTicker] -> ShowS
show :: NutlinkAddressTicker -> String
$cshow :: NutlinkAddressTicker -> String
showsPrec :: Int -> NutlinkAddressTicker -> ShowS
$cshowsPrec :: Int -> NutlinkAddressTicker -> ShowS
Show, NutlinkAddressTicker -> NutlinkAddressTicker -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: NutlinkAddressTicker -> NutlinkAddressTicker -> Bool
$c/= :: NutlinkAddressTicker -> NutlinkAddressTicker -> Bool
== :: NutlinkAddressTicker -> NutlinkAddressTicker -> Bool
$c== :: NutlinkAddressTicker -> NutlinkAddressTicker -> Bool
Eq, forall x. Rep NutlinkAddressTicker x -> NutlinkAddressTicker
forall x. NutlinkAddressTicker -> Rep NutlinkAddressTicker x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep NutlinkAddressTicker x -> NutlinkAddressTicker
$cfrom :: forall x. NutlinkAddressTicker -> Rep NutlinkAddressTicker x
Generic)
  deriving (Value -> Parser [NutlinkAddressTicker]
Value -> Parser NutlinkAddressTicker
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [NutlinkAddressTicker]
$cparseJSONList :: Value -> Parser [NutlinkAddressTicker]
parseJSON :: Value -> Parser NutlinkAddressTicker
$cparseJSON :: Value -> Parser NutlinkAddressTicker
FromJSON, [NutlinkAddressTicker] -> Encoding
[NutlinkAddressTicker] -> Value
NutlinkAddressTicker -> Encoding
NutlinkAddressTicker -> Value
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [NutlinkAddressTicker] -> Encoding
$ctoEncodingList :: [NutlinkAddressTicker] -> Encoding
toJSONList :: [NutlinkAddressTicker] -> Value
$ctoJSONList :: [NutlinkAddressTicker] -> Value
toEncoding :: NutlinkAddressTicker -> Encoding
$ctoEncoding :: NutlinkAddressTicker -> Encoding
toJSON :: NutlinkAddressTicker -> Value
$ctoJSON :: NutlinkAddressTicker -> Value
ToJSON)
  via CustomJSON '[FieldLabelModifier '[StripPrefix "_nutlinkAddressTicker", CamelToSnake]] NutlinkAddressTicker

instance ToSample NutlinkAddressTicker where
  toSamples :: Proxy NutlinkAddressTicker -> [(Text, NutlinkAddressTicker)]
toSamples = forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ forall a. [a] -> [(Text, a)]
samples forall a b. (a -> b) -> a -> b
$
    [ NutlinkAddressTicker
        { _nutlinkAddressTickerName :: Text
_nutlinkAddressTickerName = Text
"ADAUSD"
        , _nutlinkAddressTickerCount :: Integer
_nutlinkAddressTickerCount = Integer
1980038
        , _nutlinkAddressTickerLatestBlock :: Integer
_nutlinkAddressTickerLatestBlock = Integer
2657092
        }
    , NutlinkAddressTicker
        { _nutlinkAddressTickerName :: Text
_nutlinkAddressTickerName = Text
"ADAEUR"
        , _nutlinkAddressTickerCount :: Integer
_nutlinkAddressTickerCount = Integer
1980038
        , _nutlinkAddressTickerLatestBlock :: Integer
_nutlinkAddressTickerLatestBlock = Integer
2657092
        }
    , NutlinkAddressTicker
        { _nutlinkAddressTickerName :: Text
_nutlinkAddressTickerName = Text
"ADABTC"
        , _nutlinkAddressTickerCount :: Integer
_nutlinkAddressTickerCount = Integer
1980038
        , _nutlinkAddressTickerLatestBlock :: Integer
_nutlinkAddressTickerLatestBlock = Integer
2657092
        }
    ]

-- | Specific ticker record
data NutlinkTicker = NutlinkTicker
  { NutlinkTicker -> TxHash
_nutlinkTickerTxHash      :: TxHash -- ^ Hash of the transaction
  , NutlinkTicker -> Integer
_nutlinkTickerBlockHeight :: Integer -- ^ Block height of the record
  , NutlinkTicker -> Integer
_nutlinkTickerTxIndex     :: Integer -- ^ Transaction index within the block
  , NutlinkTicker -> Value
_nutlinkTickerPayload     :: Value -- ^ Content of the ticker
  }
  deriving stock (Int -> NutlinkTicker -> ShowS
[NutlinkTicker] -> ShowS
NutlinkTicker -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [NutlinkTicker] -> ShowS
$cshowList :: [NutlinkTicker] -> ShowS
show :: NutlinkTicker -> String
$cshow :: NutlinkTicker -> String
showsPrec :: Int -> NutlinkTicker -> ShowS
$cshowsPrec :: Int -> NutlinkTicker -> ShowS
Show, NutlinkTicker -> NutlinkTicker -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: NutlinkTicker -> NutlinkTicker -> Bool
$c/= :: NutlinkTicker -> NutlinkTicker -> Bool
== :: NutlinkTicker -> NutlinkTicker -> Bool
$c== :: NutlinkTicker -> NutlinkTicker -> Bool
Eq, forall x. Rep NutlinkTicker x -> NutlinkTicker
forall x. NutlinkTicker -> Rep NutlinkTicker x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep NutlinkTicker x -> NutlinkTicker
$cfrom :: forall x. NutlinkTicker -> Rep NutlinkTicker x
Generic)
  deriving (Value -> Parser [NutlinkTicker]
Value -> Parser NutlinkTicker
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [NutlinkTicker]
$cparseJSONList :: Value -> Parser [NutlinkTicker]
parseJSON :: Value -> Parser NutlinkTicker
$cparseJSON :: Value -> Parser NutlinkTicker
FromJSON, [NutlinkTicker] -> Encoding
[NutlinkTicker] -> Value
NutlinkTicker -> Encoding
NutlinkTicker -> Value
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [NutlinkTicker] -> Encoding
$ctoEncodingList :: [NutlinkTicker] -> Encoding
toJSONList :: [NutlinkTicker] -> Value
$ctoJSONList :: [NutlinkTicker] -> Value
toEncoding :: NutlinkTicker -> Encoding
$ctoEncoding :: NutlinkTicker -> Encoding
toJSON :: NutlinkTicker -> Value
$ctoJSON :: NutlinkTicker -> Value
ToJSON)
  via CustomJSON '[FieldLabelModifier '[StripPrefix "_nutlinkTicker", CamelToSnake]] NutlinkTicker

instance ToSample NutlinkTicker where
  toSamples :: Proxy NutlinkTicker -> [(Text, NutlinkTicker)]
toSamples = forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ forall a. a -> [(Text, a)]
singleSample forall a b. (a -> b) -> a -> b
$
    NutlinkTicker
      { _nutlinkTickerTxHash :: TxHash
_nutlinkTickerTxHash = TxHash
"e8073fd5318ff43eca18a852527166aa8008bee9ee9e891f585612b7e4ba700b"
      , _nutlinkTickerBlockHeight :: Integer
_nutlinkTickerBlockHeight = Integer
2657092
      , _nutlinkTickerTxIndex :: Integer
_nutlinkTickerTxIndex = Integer
8
      , _nutlinkTickerPayload :: Value
_nutlinkTickerPayload = [Pair] -> Value
object []
      }

-- Re-use @NutlinkTicker@ for response with address field
instance {-# OVERLAPS #-} ToJSON (Address, NutlinkTicker) where
  toJSON :: (Address, NutlinkTicker) -> Value
toJSON (Address
addr, NutlinkTicker
nt) = case forall a. ToJSON a => a -> Value
toJSON NutlinkTicker
nt of
    (Object Object
o) -> Object -> Value
Object (Object
o forall a. Semigroup a => a -> a -> a
<> (Key
"address" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= (forall a. ToJSON a => a -> Value
toJSON Address
addr)))
    Value
_          -> forall a. HasCallStack => String -> a
error String
"Absurd"

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