-- | Script Hash newtype

module Blockfrost.Types.Shared.ScriptHash
  ( ScriptHash (..)
  ) where

import Data.Aeson (FromJSON (..), ToJSON (..), Value(..), (.=), (.:))
import Data.String (IsString (..))
import Data.Text (Text)
import qualified Data.Text
import qualified Data.Vector
import GHC.Generics
import Servant.API (Capture, FromHttpApiData (..), ToHttpApiData (..))
import Servant.Docs (DocCapture (..), ToCapture (..), ToSample (..), samples)

-- | Script Hash newtype
newtype ScriptHash = ScriptHash { ScriptHash -> Text
unScriptHash :: Text }
  deriving stock (Int -> ScriptHash -> ShowS
[ScriptHash] -> ShowS
ScriptHash -> String
(Int -> ScriptHash -> ShowS)
-> (ScriptHash -> String)
-> ([ScriptHash] -> ShowS)
-> Show ScriptHash
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ScriptHash] -> ShowS
$cshowList :: [ScriptHash] -> ShowS
show :: ScriptHash -> String
$cshow :: ScriptHash -> String
showsPrec :: Int -> ScriptHash -> ShowS
$cshowsPrec :: Int -> ScriptHash -> ShowS
Show, ScriptHash -> ScriptHash -> Bool
(ScriptHash -> ScriptHash -> Bool)
-> (ScriptHash -> ScriptHash -> Bool) -> Eq ScriptHash
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ScriptHash -> ScriptHash -> Bool
$c/= :: ScriptHash -> ScriptHash -> Bool
== :: ScriptHash -> ScriptHash -> Bool
$c== :: ScriptHash -> ScriptHash -> Bool
Eq, (forall x. ScriptHash -> Rep ScriptHash x)
-> (forall x. Rep ScriptHash x -> ScriptHash) -> Generic ScriptHash
forall x. Rep ScriptHash x -> ScriptHash
forall x. ScriptHash -> Rep ScriptHash x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ScriptHash x -> ScriptHash
$cfrom :: forall x. ScriptHash -> Rep ScriptHash x
Generic)
  deriving newtype (ByteString -> Either Text ScriptHash
Text -> Either Text ScriptHash
(Text -> Either Text ScriptHash)
-> (ByteString -> Either Text ScriptHash)
-> (Text -> Either Text ScriptHash)
-> FromHttpApiData ScriptHash
forall a.
(Text -> Either Text a)
-> (ByteString -> Either Text a)
-> (Text -> Either Text a)
-> FromHttpApiData a
parseQueryParam :: Text -> Either Text ScriptHash
$cparseQueryParam :: Text -> Either Text ScriptHash
parseHeader :: ByteString -> Either Text ScriptHash
$cparseHeader :: ByteString -> Either Text ScriptHash
parseUrlPiece :: Text -> Either Text ScriptHash
$cparseUrlPiece :: Text -> Either Text ScriptHash
FromHttpApiData, ScriptHash -> ByteString
ScriptHash -> Builder
ScriptHash -> Text
(ScriptHash -> Text)
-> (ScriptHash -> Builder)
-> (ScriptHash -> ByteString)
-> (ScriptHash -> Text)
-> ToHttpApiData ScriptHash
forall a.
(a -> Text)
-> (a -> Builder)
-> (a -> ByteString)
-> (a -> Text)
-> ToHttpApiData a
toQueryParam :: ScriptHash -> Text
$ctoQueryParam :: ScriptHash -> Text
toHeader :: ScriptHash -> ByteString
$ctoHeader :: ScriptHash -> ByteString
toEncodedUrlPiece :: ScriptHash -> Builder
$ctoEncodedUrlPiece :: ScriptHash -> Builder
toUrlPiece :: ScriptHash -> Text
$ctoUrlPiece :: ScriptHash -> Text
ToHttpApiData)

instance IsString ScriptHash where
  fromString :: String -> ScriptHash
fromString = Text -> ScriptHash
ScriptHash (Text -> ScriptHash) -> (String -> Text) -> String -> ScriptHash
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Text
Data.Text.pack

instance ToJSON ScriptHash where
  toJSON :: ScriptHash -> Value
toJSON = Text -> Value
forall a. ToJSON a => a -> Value
toJSON (Text -> Value) -> (ScriptHash -> Text) -> ScriptHash -> Value
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ScriptHash -> Text
unScriptHash
  toEncoding :: ScriptHash -> Encoding
toEncoding = Text -> Encoding
forall a. ToJSON a => a -> Encoding
toEncoding (Text -> Encoding)
-> (ScriptHash -> Text) -> ScriptHash -> Encoding
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ScriptHash -> Text
unScriptHash
instance FromJSON ScriptHash where
  parseJSON :: Value -> Parser ScriptHash
parseJSON = (Text -> ScriptHash) -> Parser Text -> Parser ScriptHash
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Text -> ScriptHash
ScriptHash (Parser Text -> Parser ScriptHash)
-> (Value -> Parser Text) -> Value -> Parser ScriptHash
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Value -> Parser Text
forall a. FromJSON a => Value -> Parser a
parseJSON

-- Custom instance for list used by script list endpoint
instance {-# OVERLAPS #-} ToJSON [ScriptHash] where
  toJSON :: [ScriptHash] -> Value
toJSON = Array -> Value
Array (Array -> Value)
-> ([ScriptHash] -> Array) -> [ScriptHash] -> Value
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Value] -> Array
forall a. [a] -> Vector a
Data.Vector.fromList ([Value] -> Array)
-> ([ScriptHash] -> [Value]) -> [ScriptHash] -> Array
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ScriptHash -> Value) -> [ScriptHash] -> [Value]
forall a b. (a -> b) -> [a] -> [b]
map (\ScriptHash
sh -> Object -> Value
Object (Text
"script_hash" Text -> Value -> Object
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= (Text -> Value
forall a. ToJSON a => a -> Value
toJSON (Text -> Value) -> (ScriptHash -> Text) -> ScriptHash -> Value
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ScriptHash -> Text
unScriptHash (ScriptHash -> Value) -> ScriptHash -> Value
forall a b. (a -> b) -> a -> b
$ ScriptHash
sh)))
instance {-# OVERLAPS #-} FromJSON [ScriptHash] where
  parseJSON :: Value -> Parser [ScriptHash]
parseJSON (Array Array
a) = (Value -> Parser ScriptHash) -> [Value] -> Parser [ScriptHash]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM Value -> Parser ScriptHash
forall a. FromJSON a => Value -> Parser a
parseJSON' (Array -> [Value]
forall a. Vector a -> [a]
Data.Vector.toList Array
a)
    where
      parseJSON' :: Value -> Parser a
parseJSON' (Object Object
b) = Object
b Object -> Text -> Parser a
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"script_hash"
      parseJSON' Value
_          = String -> Parser a
forall (m :: * -> *) a. MonadFail m => String -> m a
fail String
"Unexpected type for ScriptHash"
  parseJSON Value
_         = String -> Parser [ScriptHash]
forall (m :: * -> *) a. MonadFail m => String -> m a
fail String
"Expected array for [ScriptHash]"

instance ToSample ScriptHash where
    toSamples :: Proxy ScriptHash -> [(Text, ScriptHash)]
toSamples Proxy ScriptHash
_ = [ScriptHash] -> [(Text, ScriptHash)]
forall a. [a] -> [(Text, a)]
samples ([ScriptHash] -> [(Text, ScriptHash)])
-> [ScriptHash] -> [(Text, ScriptHash)]
forall a b. (a -> b) -> a -> b
$ (Text -> ScriptHash) -> [Text] -> [ScriptHash]
forall a b. (a -> b) -> [a] -> [b]
map Text -> ScriptHash
ScriptHash
      [ Text
"67f33146617a5e61936081db3b2117cbf59bd2123748f58ac9678656"
      , Text
"e1457a0c47dfb7a2f6b8fbb059bdceab163c05d34f195b87b9f2b30e"
      ]

instance ToCapture (Capture "script_hash" ScriptHash) where
  toCapture :: Proxy (Capture "script_hash" ScriptHash) -> DocCapture
toCapture Proxy (Capture "script_hash" ScriptHash)
_ = String -> String -> DocCapture
DocCapture String
"script_hash" String
"Hash of the script."