Skip to content

Commit 3dbc4ff

Browse files
committed
Change info endpoint type to Value
1 parent d8d104e commit 3dbc4ff

File tree

2 files changed

+11
-7
lines changed

2 files changed

+11
-7
lines changed

encoins-relay-apps/src/Encoins/Relay/Apps/Delegation/Client.hs

Lines changed: 2 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -12,6 +12,7 @@ import Cardano.Server.Client.Handle (HasServantClientEnv)
1212
import Cardano.Server.Config (decodeOrErrorFromFile)
1313
import Cardano.Server.Internal (mkServantClientEnv)
1414
import Control.Exception (Exception)
15+
import Data.Aeson (ToJSON (toJSON))
1516
import Data.Bifunctor (Bifunctor (..))
1617
import qualified Data.ByteString.Lazy as BS
1718
import Data.Either.Extra (eitherToMaybe)
@@ -54,7 +55,7 @@ serverDelegatesClient :: HasServantClientEnv => Text -> IO (Either DelegationCli
5455
serverDelegatesClient ip = runDelegationClient $ client (Proxy @GetServerDelegators) ip
5556

5657
delegationInfoClient :: HasServantClientEnv => Text -> IO (Either DelegationClientError (Text, Integer))
57-
delegationInfoClient = runDelegationClient . client (Proxy @GetDelegationInfo) . fromMaybe (error "unparsable address.") . bech32ToAddress
58+
delegationInfoClient = runDelegationClient . client (Proxy @GetDelegationInfo) . toJSON . fromMaybe (error "unparsable address.") . bech32ToAddress
5859

5960
runDelegationClient :: HasServantClientEnv => ClientM a -> IO (Either DelegationClientError a)
6061
runDelegationClient c = (c `runClientM` ?servantClientEnv) <&> first fromClientError

encoins-relay-apps/src/Encoins/Relay/Apps/Delegation/Server.hs

Lines changed: 9 additions & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -14,7 +14,7 @@
1414

1515
module Encoins.Relay.Apps.Delegation.Server where
1616

17-
import Cardano.Api (writeFileJSON, NetworkId (Mainnet))
17+
import Cardano.Api (NetworkId (Mainnet), writeFileJSON)
1818
import Cardano.Server.Config (HasCreds, decodeOrErrorFromFile)
1919
import Cardano.Server.Main (runCardanoServer)
2020
import Cardano.Server.Utils.Logger (logMsg, logSmth, logger, (.<))
@@ -27,6 +27,7 @@ import Control.Monad (forM, forever, void, wh
2727
import Control.Monad.Catch (Exception, MonadCatch (catch), MonadThrow (..), SomeException, handle)
2828
import Control.Monad.IO.Class (MonadIO (..))
2929
import Control.Monad.Reader (MonadReader (ask, local), ReaderT (..))
30+
import Data.Aeson.Types (FromJSON (parseJSON), Value, parseEither)
3031
import Data.ByteString (ByteString)
3132
import Data.FileEmbed (embedFileIfExists)
3233
import Data.Fixed (Pico)
@@ -48,7 +49,7 @@ import Encoins.Relay.Apps.Delegation.Internal (DelegConfig (..), Deleg
4849
getBalances, removeDuplicates, runDelegationM, setProgress,
4950
setTokenBalance)
5051
import Encoins.Relay.Apps.Internal (formatTime, janitorFiles, loadMostRecentFile, newProgressBar)
51-
import Ledger (PubKeyHash, Address)
52+
import Ledger (PubKeyHash)
5253
import qualified PlutusAppsExtra.IO.Blockfrost as Bf
5354
import PlutusAppsExtra.Utils.Address (addressToBech32, getStakeKey)
5455
import Servant (Get, JSON, ReqBody, err404, err500, throwError, type (:<|>) ((:<|>)),
@@ -131,7 +132,7 @@ type DelegApi
131132
delegApi :: DelegationM (Map Text Integer)
132133
:<|> DelegationM [Text]
133134
:<|> (Text -> DelegationM (Map Text Integer))
134-
:<|> (Address -> DelegationM (Text, Integer))
135+
:<|> (Value -> DelegationM (Text, Integer))
135136
delegApi
136137
= getServersHandler
137138
:<|> getCurrentServersHandler
@@ -188,11 +189,13 @@ getServerDelegatesHandler ip = delegationErrorH $ do
188189

189190
------------------------------------------- Get specific delegation info by address endpoint -------------------------------------------
190191

191-
type GetDelegationInfo = "info" :> ReqBody '[JSON] Address :> Get '[JSON] (Text, Integer)
192+
type GetDelegationInfo = "info" :> ReqBody '[JSON] Value :> Get '[JSON] (Text, Integer)
192193

193194
-- Get ip of delegated server and number of tokens by address endpoint
194-
getDelegationInfoHandler :: Address -> DelegationM (Text, Integer)
195-
getDelegationInfoHandler addr = delegationErrorH $ do
195+
getDelegationInfoHandler :: Value -> DelegationM (Text, Integer)
196+
getDelegationInfoHandler addrVal = delegationErrorH $ do
197+
logSmth addrVal
198+
let addr = either error id $ parseEither id $ parseJSON addrVal
196199
let pkh = fromMaybe (throw err404) $ getStakeKey addr
197200
mbIp <- fmap delegIp . find ((== pkh) . delegStakeKey) . pDelgations <$> askProgress True
198201
mbBalance <- Map.lookup pkh <$> askTokenBalance

0 commit comments

Comments
 (0)