solana-staking-csvs-0.1.2.0: Generate CSV Exports of your Solana Staking Rewards.
Safe HaskellNone
LanguageHaskell2010

Console.SolanaStaking.Api

Description

Solana Beach API requests & responses.

TODO: Extract into a solana-beach-api package.

Synopsis

Configuration

data Config Source #

Solana Beach API Configuration

Constructors

Config 

Fields

Instances

Instances details
Eq Config Source # 
Instance details

Defined in Console.SolanaStaking.Api

Methods

(==) :: Config -> Config -> Bool #

(/=) :: Config -> Config -> Bool #

Read Config Source # 
Instance details

Defined in Console.SolanaStaking.Api

Show Config Source # 
Instance details

Defined in Console.SolanaStaking.Api

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.

Instances

Instances details
Eq a => Eq (APIResponse a) Source # 
Instance details

Defined in Console.SolanaStaking.Api

Read a => Read (APIResponse a) Source # 
Instance details

Defined in Console.SolanaStaking.Api

Show a => Show (APIResponse a) Source # 
Instance details

Defined in Console.SolanaStaking.Api

FromJSON a => FromJSON (APIResponse a) Source #

Attempts to parse a processing response, then an error response, & finally the inner a response.

Instance details

Defined in Console.SolanaStaking.Api

data APIError Source #

Potential error responses from the Solana Beach API.

Constructors

APIError Text

Generic API error with message.

RetriesExceeded Text

Exceeded maximum number of ProcessingResponse retries.

Instances

Instances details
Eq APIError Source # 
Instance details

Defined in Console.SolanaStaking.Api

Read APIError Source # 
Instance details

Defined in Console.SolanaStaking.Api

Show APIError Source # 
Instance details

Defined in Console.SolanaStaking.Api

Generic APIError Source # 
Instance details

Defined in Console.SolanaStaking.Api

Associated Types

type Rep APIError :: Type -> Type #

Methods

from :: APIError -> Rep APIError x #

to :: Rep APIError x -> APIError #

type Rep APIError Source # 
Instance details

Defined in Console.SolanaStaking.Api

type Rep APIError = D1 ('MetaData "APIError" "Console.SolanaStaking.Api" "solana-staking-csvs-0.1.2.0-GjzxhebdJNpIblK1KhLIgs" '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)))

runApi :: Monad m => APIResponse a -> m (Either APIError a) Source #

Evaluate an API response.

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 :: (MonadIO m, MonadReader Config 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

Instances details
Eq StakingAccounts Source # 
Instance details

Defined in Console.SolanaStaking.Api

Read StakingAccounts Source # 
Instance details

Defined in Console.SolanaStaking.Api

Show StakingAccounts Source # 
Instance details

Defined in Console.SolanaStaking.Api

Generic StakingAccounts Source # 
Instance details

Defined in Console.SolanaStaking.Api

Associated Types

type Rep StakingAccounts :: Type -> Type #

FromJSON StakingAccounts Source # 
Instance details

Defined in Console.SolanaStaking.Api

type Rep StakingAccounts Source # 
Instance details

Defined in Console.SolanaStaking.Api

type Rep StakingAccounts = D1 ('MetaData "StakingAccounts" "Console.SolanaStaking.Api" "solana-staking-csvs-0.1.2.0-GjzxhebdJNpIblK1KhLIgs" 'False) (C1 ('MetaCons "StakingAccounts" 'PrefixI 'True) (S1 ('MetaSel ('Just "saResults") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [StakingAccount]) :*: S1 ('MetaSel ('Just "saTotalPages") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Integer)))

data StakingAccount Source #

A single Staking Account.

Constructors

StakingAccount 

Fields

Instances

Instances details
Eq StakingAccount Source # 
Instance details

Defined in Console.SolanaStaking.Api

Read StakingAccount Source # 
Instance details

Defined in Console.SolanaStaking.Api

Show StakingAccount Source # 
Instance details

Defined in Console.SolanaStaking.Api

Generic StakingAccount Source # 
Instance details

Defined in Console.SolanaStaking.Api

Associated Types

type Rep StakingAccount :: Type -> Type #

FromJSON StakingAccount Source # 
Instance details

Defined in Console.SolanaStaking.Api

type Rep StakingAccount Source # 
Instance details

Defined in Console.SolanaStaking.Api

type Rep StakingAccount = D1 ('MetaData "StakingAccount" "Console.SolanaStaking.Api" "solana-staking-csvs-0.1.2.0-GjzxhebdJNpIblK1KhLIgs" 'False) (C1 ('MetaCons "StakingAccount" 'PrefixI 'True) (S1 ('MetaSel ('Just "saPubKey") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 StakingPubKey) :*: (S1 ('MetaSel ('Just "saLamports") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Lamports) :*: S1 ('MetaSel ('Just "saValidatorName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text))))

Get Staking Rewards

getAllStakeRewards :: (MonadIO m, MonadReader Config 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 :: (MonadIO m, MonadReader Config m) => StakingPubKey -> Integer -> m ([APIError], [StakeReward]) Source #

Get the year's worth of staking rewards for the given account.

getStakeRewards :: (MonadIO m, MonadReader Config 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 

Fields

Instances

Instances details
Eq StakeReward Source # 
Instance details

Defined in Console.SolanaStaking.Api

Read StakeReward Source # 
Instance details

Defined in Console.SolanaStaking.Api

Show StakeReward Source # 
Instance details

Defined in Console.SolanaStaking.Api

Generic StakeReward Source # 
Instance details

Defined in Console.SolanaStaking.Api

Associated Types

type Rep StakeReward :: Type -> Type #

FromJSON StakeReward Source # 
Instance details

Defined in Console.SolanaStaking.Api

type Rep StakeReward Source # 
Instance details

Defined in Console.SolanaStaking.Api

type Rep StakeReward = D1 ('MetaData "StakeReward" "Console.SolanaStaking.Api" "solana-staking-csvs-0.1.2.0-GjzxhebdJNpIblK1KhLIgs" 'False) (C1 ('MetaCons "StakeReward" 'PrefixI 'True) ((S1 ('MetaSel ('Just "srEpoch") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Integer) :*: S1 ('MetaSel ('Just "srSlot") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Integer)) :*: (S1 ('MetaSel ('Just "srAmount") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Lamports) :*: S1 ('MetaSel ('Just "srTimestamp") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 POSIXTime))))

Get Block

getBlock :: (MonadIO m, MonadReader Config m) => Integer -> m (APIResponse Block) Source #

Get information about a specific block number.

data Block Source #

A single block on the Solana blockchain.

Constructors

Block 

Fields

Instances

Instances details
Eq Block Source # 
Instance details

Defined in Console.SolanaStaking.Api

Methods

(==) :: Block -> Block -> Bool #

(/=) :: Block -> Block -> Bool #

Read Block Source # 
Instance details

Defined in Console.SolanaStaking.Api

Show Block Source # 
Instance details

Defined in Console.SolanaStaking.Api

Methods

showsPrec :: Int -> Block -> ShowS #

show :: Block -> String #

showList :: [Block] -> ShowS #

Generic Block Source # 
Instance details

Defined in Console.SolanaStaking.Api

Associated Types

type Rep Block :: Type -> Type #

Methods

from :: Block -> Rep Block x #

to :: Rep Block x -> Block #

FromJSON Block Source # 
Instance details

Defined in Console.SolanaStaking.Api

type Rep Block Source # 
Instance details

Defined in Console.SolanaStaking.Api

type Rep Block = D1 ('MetaData "Block" "Console.SolanaStaking.Api" "solana-staking-csvs-0.1.2.0-GjzxhebdJNpIblK1KhLIgs" '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

newtype Lamports Source #

An amount of Lamports, each of which represent 0.000000001 SOL.

Constructors

Lamports 

Instances

Instances details
Eq Lamports Source # 
Instance details

Defined in Console.SolanaStaking.Api

Read Lamports Source # 
Instance details

Defined in Console.SolanaStaking.Api

Show Lamports Source # 
Instance details

Defined in Console.SolanaStaking.Api

Generic Lamports Source # 
Instance details

Defined in Console.SolanaStaking.Api

Associated Types

type Rep Lamports :: Type -> Type #

Methods

from :: Lamports -> Rep Lamports x #

to :: Rep Lamports x -> Lamports #

FromJSON Lamports Source # 
Instance details

Defined in Console.SolanaStaking.Api

type Rep Lamports Source # 
Instance details

Defined in Console.SolanaStaking.Api

type Rep Lamports = D1 ('MetaData "Lamports" "Console.SolanaStaking.Api" "solana-staking-csvs-0.1.2.0-GjzxhebdJNpIblK1KhLIgs" 'True) (C1 ('MetaCons "Lamports" 'PrefixI 'True) (S1 ('MetaSel ('Just "fromLamports") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Integer)))

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 

Instances

Instances details
Eq StakingPubKey Source # 
Instance details

Defined in Console.SolanaStaking.Api

Read StakingPubKey Source # 
Instance details

Defined in Console.SolanaStaking.Api

Show StakingPubKey Source # 
Instance details

Defined in Console.SolanaStaking.Api

Generic StakingPubKey Source # 
Instance details

Defined in Console.SolanaStaking.Api

Associated Types

type Rep StakingPubKey :: Type -> Type #

FromJSON StakingPubKey Source # 
Instance details

Defined in Console.SolanaStaking.Api

type Rep StakingPubKey Source # 
Instance details

Defined in Console.SolanaStaking.Api

type Rep StakingPubKey = D1 ('MetaData "StakingPubKey" "Console.SolanaStaking.Api" "solana-staking-csvs-0.1.2.0-GjzxhebdJNpIblK1KhLIgs" 'True) (C1 ('MetaCons "StakingPubKey" 'PrefixI 'True) (S1 ('MetaSel ('Just "fromStakingPubKey") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)))