| Safe Haskell | Safe-Inferred |
|---|---|
| Language | Haskell2010 |
Console.SolanaStaking.Api
Description
Solana Beach API requests & responses.
TODO: Extract into a solana-beach-api package.
Synopsis
- data Config = Config {
- cApiKey :: Text
- cAccountPubKey :: Text
- mkConfig :: String -> String -> Config
- data APIResponse a
- data APIError
- runApi :: Monad m => APIResponse a -> m (Either APIError a)
- raiseAPIError :: MonadError APIError m => APIResponse a -> m a
- getAccountStakes :: (MonadReader Config m, MonadCatch m, MonadIO m) => m (APIResponse StakingAccounts)
- data StakingAccounts = StakingAccounts {}
- data StakingAccount = StakingAccount {}
- getAllStakeRewards :: (MonadReader Config m, MonadCatch m, MonadIO m) => StakingPubKey -> m ([APIError], [StakeReward])
- getYearsStakeRewards :: (MonadReader Config m, MonadCatch m, MonadIO m) => StakingPubKey -> Integer -> m ([APIError], [StakeReward])
- getStakeRewards :: (MonadReader Config m, MonadCatch m, MonadIO m) => StakingPubKey -> Maybe Integer -> m (APIResponse [StakeReward])
- data StakeReward = StakeReward {}
- getBlock :: (MonadReader Config m, MonadCatch m, MonadIO m) => Integer -> m (APIResponse Block)
- data Block = Block {}
- newtype Lamports = Lamports {}
- renderLamports :: Lamports -> Text
- scientificLamports :: Lamports -> Scientific
- newtype StakingPubKey = StakingPubKey {}
Configuration
Solana Beach API Configuration
Constructors
| Config | |
Fields
| |
mkConfig :: String -> String -> Config Source #
Create a program config from the API key & the target account's pubkey.
Requests / Responses
data APIResponse a Source #
Wrapper around error & processing responses from the API.
Constructors
| SuccessfulReponse a | |
| ProcessingResponse | |
| RateLimitResponse Int | |
| ErrorResponse APIError |
Instances
| FromJSON a => FromJSON (APIResponse a) Source # | Attempts to parse a processing response, then an error response,
& finally the inner |
Defined in Console.SolanaStaking.Api Methods parseJSON :: Value -> Parser (APIResponse a) # parseJSONList :: Value -> Parser [APIResponse a] # omittedField :: Maybe (APIResponse a) # | |
| Read a => Read (APIResponse a) Source # | |
Defined in Console.SolanaStaking.Api Methods readsPrec :: Int -> ReadS (APIResponse a) # readList :: ReadS [APIResponse a] # readPrec :: ReadPrec (APIResponse a) # readListPrec :: ReadPrec [APIResponse a] # | |
| Show a => Show (APIResponse a) Source # | |
Defined in Console.SolanaStaking.Api Methods showsPrec :: Int -> APIResponse a -> ShowS # show :: APIResponse a -> String # showList :: [APIResponse a] -> ShowS # | |
| Eq a => Eq (APIResponse a) Source # | |
Defined in Console.SolanaStaking.Api Methods (==) :: APIResponse a -> APIResponse a -> Bool # (/=) :: APIResponse a -> APIResponse a -> Bool # | |
Potential error responses from the Solana Beach API.
Constructors
| APIError Text | Generic API error with message. |
| RetriesExceeded Text | Exceeded maximum number of |
| RateLimitError Int | Rate limiting 429 error. |
Instances
| Generic APIError Source # | |
| Read APIError Source # | |
| Show APIError Source # | |
| Eq APIError Source # | |
| type Rep APIError Source # | |
Defined in Console.SolanaStaking.Api type Rep APIError = D1 ('MetaData "APIError" "Console.SolanaStaking.Api" "solana-staking-csvs-0.1.3.0-E9Qk519OQkrEnmFIJzRHLJ" 'False) (C1 ('MetaCons "APIError" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)) :+: (C1 ('MetaCons "RetriesExceeded" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)) :+: C1 ('MetaCons "RateLimitError" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int)))) | |
raiseAPIError :: MonadError APIError m => APIResponse a -> m a Source #
Pull the inner value out of an APIResponse or throw the respective
APIError.
Get Stake Accounts
getAccountStakes :: (MonadReader Config m, MonadCatch m, MonadIO m) => m (APIResponse StakingAccounts) Source #
Get the staking accounts for the cAccountPubKey.
data StakingAccounts Source #
Single Result Page of Staking Accounts Query.
Constructors
| StakingAccounts | |
Fields
| |
Instances
data StakingAccount Source #
A single Staking Account.
Constructors
| StakingAccount | |
Fields
| |
Instances
Get Staking Rewards
getAllStakeRewards :: (MonadReader Config m, MonadCatch m, MonadIO m) => StakingPubKey -> m ([APIError], [StakeReward]) Source #
Get all the staking rewards for the given account.
The API's stake-rewards route only returns a maximum of 5 rewards, so
we have to use the earliest epoch as the cursor in an additional
request to see if there are any more rewards.
getYearsStakeRewards :: (MonadReader Config m, MonadCatch m, MonadIO m) => StakingPubKey -> Integer -> m ([APIError], [StakeReward]) Source #
Get the year's worth of staking rewards for the given account.
getStakeRewards :: (MonadReader Config m, MonadCatch m, MonadIO m) => StakingPubKey -> Maybe Integer -> m (APIResponse [StakeReward]) Source #
Get the staking rewards with a staking account's pubkey.
data StakeReward Source #
A Staking Reward Payment.
Constructors
| StakeReward | |
Instances
Get Block
getBlock :: (MonadReader Config m, MonadCatch m, MonadIO m) => Integer -> m (APIResponse Block) Source #
Get information about a specific block number.
A single block on the Solana blockchain.
Constructors
| Block | |
Fields
| |
Instances
| FromJSON Block Source # | |
Defined in Console.SolanaStaking.Api | |
| Generic Block Source # | |
| Read Block Source # | |
| Show Block Source # | |
| Eq Block Source # | |
| type Rep Block Source # | |
Defined in Console.SolanaStaking.Api type Rep Block = D1 ('MetaData "Block" "Console.SolanaStaking.Api" "solana-staking-csvs-0.1.3.0-E9Qk519OQkrEnmFIJzRHLJ" 'False) (C1 ('MetaCons "Block" 'PrefixI 'True) (S1 ('MetaSel ('Just "bNumber") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Integer) :*: S1 ('MetaSel ('Just "bBlockTime") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 POSIXTime))) | |
General API Types
An amount of Lamports, each of which represent 0.000000001 SOL.
Constructors
| Lamports | |
Fields | |
renderLamports :: Lamports -> Text Source #
Render an amount of Lamports as text, converting it to SOL.
scientificLamports :: Lamports -> Scientific Source #
Convert Lamports into Scientific representation of SOL.
newtype StakingPubKey Source #
A PubKey for a Staking Account.
Constructors
| StakingPubKey | |
Fields | |