Skip to content

Commit

Permalink
Merge #2094
Browse files Browse the repository at this point in the history
2094: Return descriptive 503 when listing stake pools with uncomplete sync r=KtorZ a=hasufell

Wrt #1971

Co-authored-by: Julian Ospald <julian.ospald@iohk.io>
  • Loading branch information
iohk-bors[bot] and hasufell committed Sep 3, 2020
2 parents f9a52ab + 282e86b commit 6160334
Show file tree
Hide file tree
Showing 3 changed files with 53 additions and 14 deletions.
8 changes: 8 additions & 0 deletions lib/core/src/Cardano/Wallet.hs
Original file line number Diff line number Diff line change
Expand Up @@ -173,6 +173,9 @@ module Cardano.Wallet

-- * Logging
, WalletLog (..)

-- * Stake pool listing
, ErrListPools (..)
) where

import Prelude hiding
Expand Down Expand Up @@ -2364,6 +2367,11 @@ data ErrWithdrawalNotWorth
= ErrWithdrawalNotWorth
deriving (Generic, Eq, Show)

-- | Errors that can occur when trying to list stake pool.
data ErrListPools
= ErrListPoolsNetworkError ErrNetworkUnavailable
| ErrListPoolsPastHorizonException PastHorizonException
deriving (Show)
{-------------------------------------------------------------------------------
Utils
-------------------------------------------------------------------------------}
Expand Down
21 changes: 16 additions & 5 deletions lib/core/src/Cardano/Wallet/Api/Server.hs
Original file line number Diff line number Diff line change
Expand Up @@ -109,6 +109,7 @@ import Cardano.Wallet
, ErrImportAddress (..)
, ErrImportRandomAddress (..)
, ErrJoinStakePool (..)
, ErrListPools (..)
, ErrListTransactions (..)
, ErrListUTxOStatistics (..)
, ErrMkTx (..)
Expand Down Expand Up @@ -315,7 +316,7 @@ import Control.Concurrent
import Control.Concurrent.Async
( race_ )
import Control.Exception
( IOException, bracket, throwIO, tryJust )
( IOException, bracket, throwIO, try, tryJust )
import Control.Monad
( forM, forever, void, when, (>=>) )
import Control.Monad.Catch
Expand Down Expand Up @@ -423,6 +424,7 @@ import qualified Cardano.Wallet.Api.Types as Api
import qualified Cardano.Wallet.Network as NW
import qualified Cardano.Wallet.Primitive.AddressDerivation.Byron as Byron
import qualified Cardano.Wallet.Primitive.AddressDerivation.Icarus as Icarus
import qualified Cardano.Wallet.Primitive.Slotting as S
import qualified Cardano.Wallet.Primitive.Types as W
import qualified Cardano.Wallet.Registry as Registry
import qualified Data.Aeson as Aeson
Expand Down Expand Up @@ -1588,17 +1590,20 @@ assignMigrationAddresses addrs selections =
Network
-------------------------------------------------------------------------------}

data ErrCurrentEpoch = ErrUnableToDetermineCurrentEpoch
data ErrCurrentEpoch
= ErrUnableToDetermineCurrentEpoch
| ErrCurrentEpochPastHorizonException PastHorizonException

getCurrentEpoch
:: forall ctx s t k . (ctx ~ ApiLayer s t k)
=> ctx
-> Handler W.EpochNo
getCurrentEpoch ctx = do
res <- liftIO $ currentEpoch ti
res <- liftIO $ try $ currentEpoch ti
case res of
Nothing -> liftE ErrUnableToDetermineCurrentEpoch
Just x -> pure x
Right Nothing -> liftE ErrUnableToDetermineCurrentEpoch
Right (Just x) -> pure x
Left e@(S.PastHorizon{}) -> liftE (ErrCurrentEpochPastHorizonException e)
where
ti :: TimeInterpreter IO
ti = timeInterpreter (ctx ^. networkLayer @t)
Expand Down Expand Up @@ -2020,6 +2025,7 @@ instance LiftHandler ErrCurrentEpoch where
[ "I'm unable to determine the current epoch. "
, "Please wait a while for the node to sync and try again."
]
ErrCurrentEpochPastHorizonException e -> handler e

instance LiftHandler ErrUnexpectedPoolIdPlaceholder where
handler = \case
Expand Down Expand Up @@ -2495,6 +2501,11 @@ instance LiftHandler ErrWithdrawalNotWorth where
, "request."
]

instance LiftHandler ErrListPools where
handler = \case
ErrListPoolsNetworkError e -> handler e
ErrListPoolsPastHorizonException e -> handler e

instance LiftHandler ErrTxTooLarge where
handler = \case
ErrTxTooLarge {tooLargeCurrentSize, tooLargeMaximumSize} ->
Expand Down
38 changes: 29 additions & 9 deletions lib/shelley/src/Cardano/Wallet/Shelley/Pools.hs
Original file line number Diff line number Diff line change
Expand Up @@ -37,6 +37,8 @@ import Cardano.Pool.DB
( DBLayer (..), ErrPointAlreadyExists (..), readPoolLifeCycleStatus )
import Cardano.Pool.Metadata
( StakePoolMetadataFetchLog )
import Cardano.Wallet
( ErrListPools (..) )
import Cardano.Wallet.Api.Types
( ApiT (..) )
import Cardano.Wallet.Network
Expand All @@ -49,7 +51,13 @@ import Cardano.Wallet.Network
, follow
)
import Cardano.Wallet.Primitive.Slotting
( TimeInterpreter, epochOf, epochPred, firstSlotInEpoch, startTime )
( PastHorizonException (..)
, TimeInterpreter
, epochOf
, epochPred
, firstSlotInEpoch
, startTime
)
import Cardano.Wallet.Primitive.Types
( ActiveSlotCoefficient (..)
, BlockHeader
Expand Down Expand Up @@ -84,16 +92,20 @@ import Cardano.Wallet.Unsafe
( unsafeMkPercentage )
import Control.Concurrent
( threadDelay )
import Control.Exception
( try )
import Control.Monad
( forM, forM_, forever, unless, void, when, (<=<) )
import Control.Monad.IO.Class
( liftIO )
import Control.Monad.Trans.Except
( ExceptT (..), runExceptT, withExceptT )
( ExceptT (..), mapExceptT, runExceptT, throwE, withExceptT )
import Control.Monad.Trans.State
( State, evalState, state )
import Control.Tracer
( Tracer, contramap, traceWith )
import Data.Bifunctor
( first )
import Data.Function
( (&) )
import Data.Generics.Internal.VL.Lens
Expand Down Expand Up @@ -157,7 +169,7 @@ data StakePoolLayer = StakePoolLayer
:: EpochNo
-- Exclude all pools that retired in or before this epoch.
-> Coin
-> ExceptT ErrNetworkUnavailable IO [Api.ApiStakePool]
-> ExceptT ErrListPools IO [Api.ApiStakePool]
}

newStakePoolLayer
Expand Down Expand Up @@ -186,17 +198,18 @@ newStakePoolLayer nl db@DBLayer {..} =
:: EpochNo
-- Exclude all pools that retired in or before this epoch.
-> Coin
-> ExceptT ErrNetworkUnavailable IO [Api.ApiStakePool]
-> ExceptT ErrListPools IO [Api.ApiStakePool]
_listPools currentEpoch userStake = do
tip <- withExceptT fromErrCurrentNodeTip $ currentNodeTip nl
rawLsqData <- stakeDistribution nl tip userStake
rawLsqData <- mapExceptT (fmap (first ErrListPoolsNetworkError))
$ stakeDistribution nl tip userStake
let lsqData = combineLsqData rawLsqData
dbData <- liftIO $ readPoolDbData db
seed <- liftIO $ atomically readSystemSeed
-- TODO:
-- Use a more efficient way of filtering out retired pools.
-- See: https://jira.iohk.io/projects/ADP/issues/ADP-383
liftIO $
r <- liftIO $ try $
sortByReward seed
. filter (not . poolIsRetired)
. map snd
Expand All @@ -206,11 +219,18 @@ newStakePoolLayer nl db@DBLayer {..} =
(nOpt rawLsqData)
lsqData
dbData
case r of
Left e@(PastHorizon{}) -> throwE (ErrListPoolsPastHorizonException e)
Right r' -> pure r'

where
fromErrCurrentNodeTip :: ErrCurrentNodeTip -> ErrNetworkUnavailable

fromErrCurrentNodeTip :: ErrCurrentNodeTip -> ErrListPools
fromErrCurrentNodeTip = \case
ErrCurrentNodeTipNetworkUnreachable e -> e
ErrCurrentNodeTipNotFound -> ErrNetworkUnreachable "tip not found"
ErrCurrentNodeTipNetworkUnreachable e ->
ErrListPoolsNetworkError e
ErrCurrentNodeTipNotFound ->
ErrListPoolsNetworkError $ ErrNetworkUnreachable "tip not found"

epochIsInFuture :: EpochNo -> Bool
epochIsInFuture = (> currentEpoch)
Expand Down

0 comments on commit 6160334

Please sign in to comment.