module Blockfrost.Types.Shared.BlockIndex
where
import qualified Data.Text
import GHC.Generics
import Servant.API (FromHttpApiData (..), QueryParam, ToHttpApiData (..))
import Servant.Docs
( DocQueryParam (..)
, ParamKind (..)
, ToParam (..)
, ToSample (..)
, samples
)
data BlockIndex = BlockIndex {
BlockIndex -> Integer
blockIndexHeight :: Integer
, BlockIndex -> Maybe Integer
blockIndexIndex :: Maybe Integer
}
deriving stock (BlockIndex -> BlockIndex -> Bool
(BlockIndex -> BlockIndex -> Bool)
-> (BlockIndex -> BlockIndex -> Bool) -> Eq BlockIndex
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: BlockIndex -> BlockIndex -> Bool
== :: BlockIndex -> BlockIndex -> Bool
$c/= :: BlockIndex -> BlockIndex -> Bool
/= :: BlockIndex -> BlockIndex -> Bool
Eq, Int -> BlockIndex -> ShowS
[BlockIndex] -> ShowS
BlockIndex -> String
(Int -> BlockIndex -> ShowS)
-> (BlockIndex -> String)
-> ([BlockIndex] -> ShowS)
-> Show BlockIndex
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> BlockIndex -> ShowS
showsPrec :: Int -> BlockIndex -> ShowS
$cshow :: BlockIndex -> String
show :: BlockIndex -> String
$cshowList :: [BlockIndex] -> ShowS
showList :: [BlockIndex] -> ShowS
Show, (forall x. BlockIndex -> Rep BlockIndex x)
-> (forall x. Rep BlockIndex x -> BlockIndex) -> Generic BlockIndex
forall x. Rep BlockIndex x -> BlockIndex
forall x. BlockIndex -> Rep BlockIndex x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. BlockIndex -> Rep BlockIndex x
from :: forall x. BlockIndex -> Rep BlockIndex x
$cto :: forall x. Rep BlockIndex x -> BlockIndex
to :: forall x. Rep BlockIndex x -> BlockIndex
Generic)
instance ToHttpApiData BlockIndex where
toUrlPiece :: BlockIndex -> Text
toUrlPiece BlockIndex
bi = String -> Text
Data.Text.pack (String -> Text) -> String -> Text
forall a b. (a -> b) -> a -> b
$
Integer -> String
forall a. Show a => a -> String
show (BlockIndex -> Integer
blockIndexHeight BlockIndex
bi)
String -> ShowS
forall a. Semigroup a => a -> a -> a
<> String -> (Integer -> String) -> Maybe Integer -> String
forall b a. b -> (a -> b) -> Maybe a -> b
maybe String
forall a. Monoid a => a
mempty ((Char
':'Char -> ShowS
forall a. a -> [a] -> [a]
:) ShowS -> (Integer -> String) -> Integer -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
.Integer -> String
forall a. Show a => a -> String
show) (BlockIndex -> Maybe Integer
blockIndexIndex BlockIndex
bi)
instance FromHttpApiData BlockIndex where
parseUrlPiece :: Text -> Either Text BlockIndex
parseUrlPiece Text
x = case HasCallStack => Text -> Text -> [Text]
Text -> Text -> [Text]
Data.Text.splitOn Text
":" Text
x of
[Text
""] -> Text -> Either Text BlockIndex
forall a b. a -> Either a b
Left Text
"Empty block index"
[Text
bh] -> (Integer -> Maybe Integer -> BlockIndex
`BlockIndex` Maybe Integer
forall a. Maybe a
Nothing) (Integer -> BlockIndex)
-> Either Text Integer -> Either Text BlockIndex
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Text -> Either Text Integer
forall a. FromHttpApiData a => Text -> Either Text a
parseUrlPiece Text
bh
[Text
bh, Text
idx] -> Integer -> Maybe Integer -> BlockIndex
BlockIndex (Integer -> Maybe Integer -> BlockIndex)
-> Either Text Integer -> Either Text (Maybe Integer -> BlockIndex)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Text -> Either Text Integer
forall a. FromHttpApiData a => Text -> Either Text a
parseUrlPiece Text
bh Either Text (Maybe Integer -> BlockIndex)
-> Either Text (Maybe Integer) -> Either Text BlockIndex
forall a b. Either Text (a -> b) -> Either Text a -> Either Text b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (Integer -> Maybe Integer
forall a. a -> Maybe a
Just (Integer -> Maybe Integer)
-> Either Text Integer -> Either Text (Maybe Integer)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Text -> Either Text Integer
forall a. FromHttpApiData a => Text -> Either Text a
parseUrlPiece Text
idx)
[Text]
_ -> Text -> Either Text BlockIndex
forall a b. a -> Either a b
Left Text
"Invalid block index"
instance ToParam (QueryParam "from" BlockIndex) where
toParam :: Proxy (QueryParam "from" BlockIndex) -> DocQueryParam
toParam Proxy (QueryParam "from" BlockIndex)
_ =
String -> [String] -> String -> ParamKind -> DocQueryParam
DocQueryParam
String
"blockIndex"
[]
String
"The block number and optionally also index from which (inclusive)\
\ to start search for results, concatenated using colon.\
\ Has to be lower than or equal to `to` parameter."
ParamKind
Normal
instance ToParam (QueryParam "to" BlockIndex) where
toParam :: Proxy (QueryParam "to" BlockIndex) -> DocQueryParam
toParam Proxy (QueryParam "to" BlockIndex)
_ =
String -> [String] -> String -> ParamKind -> DocQueryParam
DocQueryParam
String
"blockIndex"
[]
String
"The block number and optionally also index from which (inclusive)\
\ to end the search for results, concatenated using colon.\
\ Has to be higher than or equal to `from` parameter."
ParamKind
Normal
instance ToSample BlockIndex where
toSamples :: Proxy BlockIndex -> [(Text, BlockIndex)]
toSamples = [(Text, BlockIndex)] -> Proxy BlockIndex -> [(Text, BlockIndex)]
forall a. a -> Proxy BlockIndex -> a
forall (f :: * -> *) a. Applicative f => a -> f a
pure ([(Text, BlockIndex)] -> Proxy BlockIndex -> [(Text, BlockIndex)])
-> [(Text, BlockIndex)] -> Proxy BlockIndex -> [(Text, BlockIndex)]
forall a b. (a -> b) -> a -> b
$ [BlockIndex] -> [(Text, BlockIndex)]
forall a. [a] -> [(Text, a)]
samples [
Integer -> Maybe Integer -> BlockIndex
BlockIndex Integer
892961 Maybe Integer
forall a. Maybe a
Nothing
, Integer -> Maybe Integer -> BlockIndex
BlockIndex Integer
9999269 (Integer -> Maybe Integer
forall a. a -> Maybe a
Just Integer
10)
]