module Blockfrost.Types.Shared.DatumHash
  ( DatumHash (..)
  ) where
import Data.Aeson (FromJSON (..), ToJSON (..))
import Data.String (IsString (..))
import Data.Text (Text)
import qualified Data.Text
import GHC.Generics
import Servant.API (Capture, FromHttpApiData (..), ToHttpApiData (..))
import Servant.Docs (DocCapture (..), ToCapture (..), ToSample (..), samples)
newtype DatumHash = DatumHash { DatumHash -> Text
unDatumHash :: Text }
  deriving stock (Int -> DatumHash -> ShowS
[DatumHash] -> ShowS
DatumHash -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DatumHash] -> ShowS
$cshowList :: [DatumHash] -> ShowS
show :: DatumHash -> String
$cshow :: DatumHash -> String
showsPrec :: Int -> DatumHash -> ShowS
$cshowsPrec :: Int -> DatumHash -> ShowS
Show, DatumHash -> DatumHash -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DatumHash -> DatumHash -> Bool
$c/= :: DatumHash -> DatumHash -> Bool
== :: DatumHash -> DatumHash -> Bool
$c== :: DatumHash -> DatumHash -> Bool
Eq, forall x. Rep DatumHash x -> DatumHash
forall x. DatumHash -> Rep DatumHash x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DatumHash x -> DatumHash
$cfrom :: forall x. DatumHash -> Rep DatumHash x
Generic)
  deriving newtype (ByteString -> Either Text DatumHash
Text -> Either Text DatumHash
forall a.
(Text -> Either Text a)
-> (ByteString -> Either Text a)
-> (Text -> Either Text a)
-> FromHttpApiData a
parseQueryParam :: Text -> Either Text DatumHash
$cparseQueryParam :: Text -> Either Text DatumHash
parseHeader :: ByteString -> Either Text DatumHash
$cparseHeader :: ByteString -> Either Text DatumHash
parseUrlPiece :: Text -> Either Text DatumHash
$cparseUrlPiece :: Text -> Either Text DatumHash
FromHttpApiData, DatumHash -> ByteString
DatumHash -> Builder
DatumHash -> Text
forall a.
(a -> Text)
-> (a -> Builder)
-> (a -> ByteString)
-> (a -> Text)
-> ToHttpApiData a
toQueryParam :: DatumHash -> Text
$ctoQueryParam :: DatumHash -> Text
toHeader :: DatumHash -> ByteString
$ctoHeader :: DatumHash -> ByteString
toEncodedUrlPiece :: DatumHash -> Builder
$ctoEncodedUrlPiece :: DatumHash -> Builder
toUrlPiece :: DatumHash -> Text
$ctoUrlPiece :: DatumHash -> Text
ToHttpApiData)
instance IsString DatumHash where
  fromString :: String -> DatumHash
fromString = Text -> DatumHash
DatumHash forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Text
Data.Text.pack
instance ToJSON DatumHash where
  toJSON :: DatumHash -> Value
toJSON = forall a. ToJSON a => a -> Value
toJSON forall b c a. (b -> c) -> (a -> b) -> a -> c
. DatumHash -> Text
unDatumHash
  toEncoding :: DatumHash -> Encoding
toEncoding = forall a. ToJSON a => a -> Encoding
toEncoding forall b c a. (b -> c) -> (a -> b) -> a -> c
. DatumHash -> Text
unDatumHash
instance FromJSON DatumHash where
  parseJSON :: Value -> Parser DatumHash
parseJSON = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Text -> DatumHash
DatumHash forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a. FromJSON a => Value -> Parser a
parseJSON
instance ToSample DatumHash where
    toSamples :: Proxy DatumHash -> [(Text, DatumHash)]
toSamples Proxy DatumHash
_ = forall a. [a] -> [(Text, a)]
samples forall a b. (a -> b) -> a -> b
$ forall a b. (a -> b) -> [a] -> [b]
map Text -> DatumHash
DatumHash
      [ Text
"5a595ce795815e81d22a1a522cf3987d546dc5bb016de61b002edd63a5413ec4"
      , Text
"923918e403bf43c34b4ef6b48eb2ee04babed17320d8d1b9ff9ad086e86f44ec"
      ]
instance ToCapture (Capture "datum_hash" DatumHash) where
  toCapture :: Proxy (Capture "datum_hash" DatumHash) -> DocCapture
toCapture Proxy (Capture "datum_hash" DatumHash)
_ = String -> String -> DocCapture
DocCapture String
"datum_hash" String
"Datum hash."