module Blockfrost.Types.Shared.DRepId
where
import Data.Aeson (FromJSON (..), ToJSON (..), withText)
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 DRepIdBech32 = DRepIdBech32 Text
deriving stock (DRepIdBech32 -> DRepIdBech32 -> Bool
(DRepIdBech32 -> DRepIdBech32 -> Bool)
-> (DRepIdBech32 -> DRepIdBech32 -> Bool) -> Eq DRepIdBech32
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: DRepIdBech32 -> DRepIdBech32 -> Bool
== :: DRepIdBech32 -> DRepIdBech32 -> Bool
$c/= :: DRepIdBech32 -> DRepIdBech32 -> Bool
/= :: DRepIdBech32 -> DRepIdBech32 -> Bool
Eq, Int -> DRepIdBech32 -> ShowS
[DRepIdBech32] -> ShowS
DRepIdBech32 -> String
(Int -> DRepIdBech32 -> ShowS)
-> (DRepIdBech32 -> String)
-> ([DRepIdBech32] -> ShowS)
-> Show DRepIdBech32
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> DRepIdBech32 -> ShowS
showsPrec :: Int -> DRepIdBech32 -> ShowS
$cshow :: DRepIdBech32 -> String
show :: DRepIdBech32 -> String
$cshowList :: [DRepIdBech32] -> ShowS
showList :: [DRepIdBech32] -> ShowS
Show, (forall x. DRepIdBech32 -> Rep DRepIdBech32 x)
-> (forall x. Rep DRepIdBech32 x -> DRepIdBech32)
-> Generic DRepIdBech32
forall x. Rep DRepIdBech32 x -> DRepIdBech32
forall x. DRepIdBech32 -> Rep DRepIdBech32 x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. DRepIdBech32 -> Rep DRepIdBech32 x
from :: forall x. DRepIdBech32 -> Rep DRepIdBech32 x
$cto :: forall x. Rep DRepIdBech32 x -> DRepIdBech32
to :: forall x. Rep DRepIdBech32 x -> DRepIdBech32
Generic)
deriving newtype (Text -> Either Text DRepIdBech32
ByteString -> Either Text DRepIdBech32
(Text -> Either Text DRepIdBech32)
-> (ByteString -> Either Text DRepIdBech32)
-> (Text -> Either Text DRepIdBech32)
-> FromHttpApiData DRepIdBech32
forall a.
(Text -> Either Text a)
-> (ByteString -> Either Text a)
-> (Text -> Either Text a)
-> FromHttpApiData a
$cparseUrlPiece :: Text -> Either Text DRepIdBech32
parseUrlPiece :: Text -> Either Text DRepIdBech32
$cparseHeader :: ByteString -> Either Text DRepIdBech32
parseHeader :: ByteString -> Either Text DRepIdBech32
$cparseQueryParam :: Text -> Either Text DRepIdBech32
parseQueryParam :: Text -> Either Text DRepIdBech32
FromHttpApiData, DRepIdBech32 -> Text
DRepIdBech32 -> ByteString
DRepIdBech32 -> Builder
(DRepIdBech32 -> Text)
-> (DRepIdBech32 -> Builder)
-> (DRepIdBech32 -> ByteString)
-> (DRepIdBech32 -> Text)
-> (DRepIdBech32 -> Builder)
-> ToHttpApiData DRepIdBech32
forall a.
(a -> Text)
-> (a -> Builder)
-> (a -> ByteString)
-> (a -> Text)
-> (a -> Builder)
-> ToHttpApiData a
$ctoUrlPiece :: DRepIdBech32 -> Text
toUrlPiece :: DRepIdBech32 -> Text
$ctoEncodedUrlPiece :: DRepIdBech32 -> Builder
toEncodedUrlPiece :: DRepIdBech32 -> Builder
$ctoHeader :: DRepIdBech32 -> ByteString
toHeader :: DRepIdBech32 -> ByteString
$ctoQueryParam :: DRepIdBech32 -> Text
toQueryParam :: DRepIdBech32 -> Text
$ctoEncodedQueryParam :: DRepIdBech32 -> Builder
toEncodedQueryParam :: DRepIdBech32 -> Builder
ToHttpApiData, Maybe DRepIdBech32
Value -> Parser [DRepIdBech32]
Value -> Parser DRepIdBech32
(Value -> Parser DRepIdBech32)
-> (Value -> Parser [DRepIdBech32])
-> Maybe DRepIdBech32
-> FromJSON DRepIdBech32
forall a.
(Value -> Parser a)
-> (Value -> Parser [a]) -> Maybe a -> FromJSON a
$cparseJSON :: Value -> Parser DRepIdBech32
parseJSON :: Value -> Parser DRepIdBech32
$cparseJSONList :: Value -> Parser [DRepIdBech32]
parseJSONList :: Value -> Parser [DRepIdBech32]
$comittedField :: Maybe DRepIdBech32
omittedField :: Maybe DRepIdBech32
FromJSON, [DRepIdBech32] -> Value
[DRepIdBech32] -> Encoding
DRepIdBech32 -> Bool
DRepIdBech32 -> Value
DRepIdBech32 -> Encoding
(DRepIdBech32 -> Value)
-> (DRepIdBech32 -> Encoding)
-> ([DRepIdBech32] -> Value)
-> ([DRepIdBech32] -> Encoding)
-> (DRepIdBech32 -> Bool)
-> ToJSON DRepIdBech32
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> (a -> Bool)
-> ToJSON a
$ctoJSON :: DRepIdBech32 -> Value
toJSON :: DRepIdBech32 -> Value
$ctoEncoding :: DRepIdBech32 -> Encoding
toEncoding :: DRepIdBech32 -> Encoding
$ctoJSONList :: [DRepIdBech32] -> Value
toJSONList :: [DRepIdBech32] -> Value
$ctoEncodingList :: [DRepIdBech32] -> Encoding
toEncodingList :: [DRepIdBech32] -> Encoding
$comitField :: DRepIdBech32 -> Bool
omitField :: DRepIdBech32 -> Bool
ToJSON)
mkDRepIdBech32 :: Text -> DRepIdBech32
mkDRepIdBech32 :: Text -> DRepIdBech32
mkDRepIdBech32 = Text -> DRepIdBech32
DRepIdBech32
unDRepIdBech32 :: DRepIdBech32 -> Text
unDRepIdBech32 :: DRepIdBech32 -> Text
unDRepIdBech32 (DRepIdBech32 Text
a) = Text
a
instance IsString DRepIdBech32 where
fromString :: String -> DRepIdBech32
fromString = Text -> DRepIdBech32
mkDRepIdBech32 (Text -> DRepIdBech32)
-> (String -> Text) -> String -> DRepIdBech32
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Text
Data.Text.pack
instance ToSample DRepIdBech32 where
toSamples :: Proxy DRepIdBech32 -> [(Text, DRepIdBech32)]
toSamples = [(Text, DRepIdBech32)]
-> Proxy DRepIdBech32 -> [(Text, DRepIdBech32)]
forall a. a -> Proxy DRepIdBech32 -> a
forall (f :: * -> *) a. Applicative f => a -> f a
pure ([(Text, DRepIdBech32)]
-> Proxy DRepIdBech32 -> [(Text, DRepIdBech32)])
-> [(Text, DRepIdBech32)]
-> Proxy DRepIdBech32
-> [(Text, DRepIdBech32)]
forall a b. (a -> b) -> a -> b
$ [DRepIdBech32] -> [(Text, DRepIdBech32)]
forall a. [a] -> [(Text, a)]
samples
[ DRepIdBech32
"drep1mvdu8slennngja7w4un6knwezufra70887zuxpprd64jxfveahn"
, DRepIdBech32
"drep1cxayn4fgy27yaucvhamsvqj3v6835mh3tjjx6x8hdnr4"
]
newtype DRepIdHex = DRepIdHex Text
deriving stock (DRepIdHex -> DRepIdHex -> Bool
(DRepIdHex -> DRepIdHex -> Bool)
-> (DRepIdHex -> DRepIdHex -> Bool) -> Eq DRepIdHex
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: DRepIdHex -> DRepIdHex -> Bool
== :: DRepIdHex -> DRepIdHex -> Bool
$c/= :: DRepIdHex -> DRepIdHex -> Bool
/= :: DRepIdHex -> DRepIdHex -> Bool
Eq, Int -> DRepIdHex -> ShowS
[DRepIdHex] -> ShowS
DRepIdHex -> String
(Int -> DRepIdHex -> ShowS)
-> (DRepIdHex -> String)
-> ([DRepIdHex] -> ShowS)
-> Show DRepIdHex
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> DRepIdHex -> ShowS
showsPrec :: Int -> DRepIdHex -> ShowS
$cshow :: DRepIdHex -> String
show :: DRepIdHex -> String
$cshowList :: [DRepIdHex] -> ShowS
showList :: [DRepIdHex] -> ShowS
Show, (forall x. DRepIdHex -> Rep DRepIdHex x)
-> (forall x. Rep DRepIdHex x -> DRepIdHex) -> Generic DRepIdHex
forall x. Rep DRepIdHex x -> DRepIdHex
forall x. DRepIdHex -> Rep DRepIdHex x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. DRepIdHex -> Rep DRepIdHex x
from :: forall x. DRepIdHex -> Rep DRepIdHex x
$cto :: forall x. Rep DRepIdHex x -> DRepIdHex
to :: forall x. Rep DRepIdHex x -> DRepIdHex
Generic)
deriving newtype (Text -> Either Text DRepIdHex
ByteString -> Either Text DRepIdHex
(Text -> Either Text DRepIdHex)
-> (ByteString -> Either Text DRepIdHex)
-> (Text -> Either Text DRepIdHex)
-> FromHttpApiData DRepIdHex
forall a.
(Text -> Either Text a)
-> (ByteString -> Either Text a)
-> (Text -> Either Text a)
-> FromHttpApiData a
$cparseUrlPiece :: Text -> Either Text DRepIdHex
parseUrlPiece :: Text -> Either Text DRepIdHex
$cparseHeader :: ByteString -> Either Text DRepIdHex
parseHeader :: ByteString -> Either Text DRepIdHex
$cparseQueryParam :: Text -> Either Text DRepIdHex
parseQueryParam :: Text -> Either Text DRepIdHex
FromHttpApiData, DRepIdHex -> Text
DRepIdHex -> ByteString
DRepIdHex -> Builder
(DRepIdHex -> Text)
-> (DRepIdHex -> Builder)
-> (DRepIdHex -> ByteString)
-> (DRepIdHex -> Text)
-> (DRepIdHex -> Builder)
-> ToHttpApiData DRepIdHex
forall a.
(a -> Text)
-> (a -> Builder)
-> (a -> ByteString)
-> (a -> Text)
-> (a -> Builder)
-> ToHttpApiData a
$ctoUrlPiece :: DRepIdHex -> Text
toUrlPiece :: DRepIdHex -> Text
$ctoEncodedUrlPiece :: DRepIdHex -> Builder
toEncodedUrlPiece :: DRepIdHex -> Builder
$ctoHeader :: DRepIdHex -> ByteString
toHeader :: DRepIdHex -> ByteString
$ctoQueryParam :: DRepIdHex -> Text
toQueryParam :: DRepIdHex -> Text
$ctoEncodedQueryParam :: DRepIdHex -> Builder
toEncodedQueryParam :: DRepIdHex -> Builder
ToHttpApiData, Maybe DRepIdHex
Value -> Parser [DRepIdHex]
Value -> Parser DRepIdHex
(Value -> Parser DRepIdHex)
-> (Value -> Parser [DRepIdHex])
-> Maybe DRepIdHex
-> FromJSON DRepIdHex
forall a.
(Value -> Parser a)
-> (Value -> Parser [a]) -> Maybe a -> FromJSON a
$cparseJSON :: Value -> Parser DRepIdHex
parseJSON :: Value -> Parser DRepIdHex
$cparseJSONList :: Value -> Parser [DRepIdHex]
parseJSONList :: Value -> Parser [DRepIdHex]
$comittedField :: Maybe DRepIdHex
omittedField :: Maybe DRepIdHex
FromJSON, [DRepIdHex] -> Value
[DRepIdHex] -> Encoding
DRepIdHex -> Bool
DRepIdHex -> Value
DRepIdHex -> Encoding
(DRepIdHex -> Value)
-> (DRepIdHex -> Encoding)
-> ([DRepIdHex] -> Value)
-> ([DRepIdHex] -> Encoding)
-> (DRepIdHex -> Bool)
-> ToJSON DRepIdHex
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> (a -> Bool)
-> ToJSON a
$ctoJSON :: DRepIdHex -> Value
toJSON :: DRepIdHex -> Value
$ctoEncoding :: DRepIdHex -> Encoding
toEncoding :: DRepIdHex -> Encoding
$ctoJSONList :: [DRepIdHex] -> Value
toJSONList :: [DRepIdHex] -> Value
$ctoEncodingList :: [DRepIdHex] -> Encoding
toEncodingList :: [DRepIdHex] -> Encoding
$comitField :: DRepIdHex -> Bool
omitField :: DRepIdHex -> Bool
ToJSON)
mkDRepIdHex :: Text -> DRepIdHex
mkDRepIdHex :: Text -> DRepIdHex
mkDRepIdHex = Text -> DRepIdHex
DRepIdHex
unDRepIdHex :: DRepIdHex -> Text
unDRepIdHex :: DRepIdHex -> Text
unDRepIdHex (DRepIdHex Text
a) = Text
a
instance IsString DRepIdHex where
fromString :: String -> DRepIdHex
fromString = Text -> DRepIdHex
mkDRepIdHex (Text -> DRepIdHex) -> (String -> Text) -> String -> DRepIdHex
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Text
Data.Text.pack
instance ToSample DRepIdHex where
toSamples :: Proxy DRepIdHex -> [(Text, DRepIdHex)]
toSamples = [(Text, DRepIdHex)] -> Proxy DRepIdHex -> [(Text, DRepIdHex)]
forall a. a -> Proxy DRepIdHex -> a
forall (f :: * -> *) a. Applicative f => a -> f a
pure ([(Text, DRepIdHex)] -> Proxy DRepIdHex -> [(Text, DRepIdHex)])
-> [(Text, DRepIdHex)] -> Proxy DRepIdHex -> [(Text, DRepIdHex)]
forall a b. (a -> b) -> a -> b
$ [DRepIdHex] -> [(Text, DRepIdHex)]
forall a. [a] -> [(Text, a)]
samples
[ DRepIdHex
"db1bc3c3f99ce68977ceaf27ab4dd917123ef9e73f85c304236eab23"
, DRepIdHex
"c1ba49d52822bc4ef30cbf77060251668f1a6ef15ca46d18f76cc758"
]
data DRepId
= DRepId_Bech32 DRepIdBech32
| DRepId_Hex DRepIdHex
deriving stock (DRepId -> DRepId -> Bool
(DRepId -> DRepId -> Bool)
-> (DRepId -> DRepId -> Bool) -> Eq DRepId
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: DRepId -> DRepId -> Bool
== :: DRepId -> DRepId -> Bool
$c/= :: DRepId -> DRepId -> Bool
/= :: DRepId -> DRepId -> Bool
Eq, Int -> DRepId -> ShowS
[DRepId] -> ShowS
DRepId -> String
(Int -> DRepId -> ShowS)
-> (DRepId -> String) -> ([DRepId] -> ShowS) -> Show DRepId
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> DRepId -> ShowS
showsPrec :: Int -> DRepId -> ShowS
$cshow :: DRepId -> String
show :: DRepId -> String
$cshowList :: [DRepId] -> ShowS
showList :: [DRepId] -> ShowS
Show, (forall x. DRepId -> Rep DRepId x)
-> (forall x. Rep DRepId x -> DRepId) -> Generic DRepId
forall x. Rep DRepId x -> DRepId
forall x. DRepId -> Rep DRepId x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. DRepId -> Rep DRepId x
from :: forall x. DRepId -> Rep DRepId x
$cto :: forall x. Rep DRepId x -> DRepId
to :: forall x. Rep DRepId x -> DRepId
Generic)
instance ToJSON DRepId where
toJSON :: DRepId -> Value
toJSON (DRepId_Bech32 DRepIdBech32
dRepIdBech32) = DRepIdBech32 -> Value
forall a. ToJSON a => a -> Value
toJSON DRepIdBech32
dRepIdBech32
toJSON (DRepId_Hex DRepIdHex
dRepIdHex) = DRepIdHex -> Value
forall a. ToJSON a => a -> Value
toJSON DRepIdHex
dRepIdHex
toEncoding :: DRepId -> Encoding
toEncoding (DRepId_Bech32 DRepIdBech32
dRepIdBech32) = DRepIdBech32 -> Encoding
forall a. ToJSON a => a -> Encoding
toEncoding DRepIdBech32
dRepIdBech32
toEncoding (DRepId_Hex DRepIdHex
dRepIdHex) = DRepIdHex -> Encoding
forall a. ToJSON a => a -> Encoding
toEncoding DRepIdHex
dRepIdHex
instance FromJSON DRepId where
parseJSON :: Value -> Parser DRepId
parseJSON = String -> (Text -> Parser DRepId) -> Value -> Parser DRepId
forall a. String -> (Text -> Parser a) -> Value -> Parser a
withText String
"dRepId" ((Text -> Parser DRepId) -> Value -> Parser DRepId)
-> (Text -> Parser DRepId) -> Value -> Parser DRepId
forall a b. (a -> b) -> a -> b
$ \case
Text
x | Text
"drep" Text -> Text -> Bool
`Data.Text.isPrefixOf` Text
x -> DRepId -> Parser DRepId
forall a. a -> Parser a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (DRepId -> Parser DRepId) -> DRepId -> Parser DRepId
forall a b. (a -> b) -> a -> b
$ DRepIdBech32 -> DRepId
DRepId_Bech32 (DRepIdBech32 -> DRepId) -> DRepIdBech32 -> DRepId
forall a b. (a -> b) -> a -> b
$ Text -> DRepIdBech32
DRepIdBech32 Text
x
Text
x | Bool
otherwise -> DRepId -> Parser DRepId
forall a. a -> Parser a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (DRepId -> Parser DRepId) -> DRepId -> Parser DRepId
forall a b. (a -> b) -> a -> b
$ DRepIdHex -> DRepId
DRepId_Hex (DRepIdHex -> DRepId) -> DRepIdHex -> DRepId
forall a b. (a -> b) -> a -> b
$ Text -> DRepIdHex
DRepIdHex Text
x
instance ToHttpApiData DRepId where
toUrlPiece :: DRepId -> Text
toUrlPiece (DRepId_Bech32 DRepIdBech32
x) = DRepIdBech32 -> Text
forall a. ToHttpApiData a => a -> Text
toUrlPiece DRepIdBech32
x
toUrlPiece (DRepId_Hex DRepIdHex
x) = DRepIdHex -> Text
forall a. ToHttpApiData a => a -> Text
toUrlPiece DRepIdHex
x
instance FromHttpApiData DRepId where
parseUrlPiece :: Text -> Either Text DRepId
parseUrlPiece Text
x | Text
"drep" Text -> Text -> Bool
`Data.Text.isPrefixOf` Text
x = DRepId -> Either Text DRepId
forall a b. b -> Either a b
Right (DRepId -> Either Text DRepId) -> DRepId -> Either Text DRepId
forall a b. (a -> b) -> a -> b
$ DRepIdBech32 -> DRepId
DRepId_Bech32 (Text -> DRepIdBech32
DRepIdBech32 Text
x)
parseUrlPiece Text
x | Bool
otherwise = DRepId -> Either Text DRepId
forall a b. b -> Either a b
Right (DRepId -> Either Text DRepId) -> DRepId -> Either Text DRepId
forall a b. (a -> b) -> a -> b
$ DRepIdHex -> DRepId
DRepId_Hex (Text -> DRepIdHex
DRepIdHex Text
x)
instance ToSample DRepId where
toSamples :: Proxy DRepId -> [(Text, DRepId)]
toSamples = [(Text, DRepId)] -> Proxy DRepId -> [(Text, DRepId)]
forall a. a -> Proxy DRepId -> a
forall (f :: * -> *) a. Applicative f => a -> f a
pure ([(Text, DRepId)] -> Proxy DRepId -> [(Text, DRepId)])
-> [(Text, DRepId)] -> Proxy DRepId -> [(Text, DRepId)]
forall a b. (a -> b) -> a -> b
$ [DRepId] -> [(Text, DRepId)]
forall a. [a] -> [(Text, a)]
samples
[ DRepIdBech32 -> DRepId
DRepId_Bech32 DRepIdBech32
"drep1mvdu8slennngja7w4un6knwezufra70887zuxpprd64jxfveahn"
, DRepIdBech32 -> DRepId
DRepId_Bech32 DRepIdBech32
"drep1cxayn4fgy27yaucvhamsvqj3v6835mh3tjjx6x8hdnr4"
, DRepIdHex -> DRepId
DRepId_Hex DRepIdHex
"db1bc3c3f99ce68977ceaf27ab4dd917123ef9e73f85c304236eab23"
, DRepIdHex -> DRepId
DRepId_Hex DRepIdHex
"c1ba49d52822bc4ef30cbf77060251668f1a6ef15ca46d18f76cc758"
]
instance ToCapture (Capture "drep_id" DRepId) where
toCapture :: Proxy (Capture "drep_id" DRepId) -> DocCapture
toCapture Proxy (Capture "drep_id" DRepId)
_ = String -> String -> DocCapture
DocCapture String
"drep_id" String
"Bech32 or hexadecimal DRep ID."