Skip to content

Commit

Permalink
Backend/enh/changes-for-detailed-fulfillment-in-payout-webhook
Browse files Browse the repository at this point in the history
  • Loading branch information
prashant601 committed Sep 9, 2024
1 parent 879aa6b commit ab68cce
Show file tree
Hide file tree
Showing 4 changed files with 28 additions and 7 deletions.
2 changes: 1 addition & 1 deletion lib/mobility-core/src/Kernel/External/Payout/Interface.hs
Original file line number Diff line number Diff line change
Expand Up @@ -41,4 +41,4 @@ payoutOrderStatus ::
PayoutOrderStatusReq ->
m PayoutOrderStatusResp
payoutOrderStatus serviceConfig req = case serviceConfig of
JuspayConfig cfg -> Juspay.payoutOrderStatus cfg req.orderId
JuspayConfig cfg -> Juspay.payoutOrderStatus cfg req.orderId req.mbExpand
Original file line number Diff line number Diff line change
Expand Up @@ -103,12 +103,13 @@ payoutOrderStatus ::
) =>
JuspayConfig ->
Text ->
Maybe Expand ->
m PayoutOrderStatusResp
payoutOrderStatus config orderId' = do
payoutOrderStatus config orderId' mbExpand = do
let url = config.url
merchantId = config.merchantId
apiKey <- decrypt config.apiKey
mkPayoutOrderStatusResp <$> Juspay.payoutOrderStatus url apiKey merchantId orderId'
mkPayoutOrderStatusResp <$> Juspay.payoutOrderStatus url apiKey merchantId orderId' mbExpand
where
mkPayoutOrderStatusResp Payout.PayoutOrderResp {..} = do
CreatePayoutOrderResp
Expand Down
21 changes: 19 additions & 2 deletions lib/mobility-core/src/Kernel/External/Payout/Interface/Types.hs
Original file line number Diff line number Diff line change
Expand Up @@ -13,6 +13,7 @@
General Public License along with this program. If not, see <https://www.gnu.org/licenses/>.
-}
{-# LANGUAGE OverloadedLists #-}
{-# LANGUAGE TemplateHaskell #-}
{-# OPTIONS_GHC -Wwarn=incomplete-record-updates #-}

module Kernel.External.Payout.Interface.Types
Expand All @@ -21,10 +22,13 @@ module Kernel.External.Payout.Interface.Types
)
where

import Kernel.Beam.Lib.UtilsTH (mkBeamInstancesForEnum)
import qualified Kernel.External.Payout.Juspay.Config as Juspay
import Kernel.External.Payout.Juspay.Types as Reexport (Fulfillment (..), PayoutOrderStatus (..))
import Kernel.Prelude
import Kernel.Storage.Esqueleto (derivePersistField)
import Kernel.Types.Common hiding (Currency)
import Servant.API (ToHttpApiData (..))

data PayoutServiceConfig = JuspayConfig Juspay.JuspayConfig
deriving (Show, Eq, Generic, ToJSON, FromJSON)
Expand Down Expand Up @@ -75,8 +79,21 @@ data CreatePayoutOrderResp = CreatePayoutOrderResp
deriving (Show, Generic)
deriving anyclass (FromJSON, ToJSON, ToSchema)

newtype PayoutOrderStatusReq = PayoutOrderStatusReq
{ orderId :: Text
data Expand = ExpandFulfillment | ExpandPayment | ExpandRefund
deriving (Show, Eq, Generic, FromJSON, ToJSON, ToSchema, Ord, Read)

$(mkBeamInstancesForEnum ''Expand)

derivePersistField "Expand"

instance ToHttpApiData Expand where
toUrlPiece ExpandFulfillment = "fulfillment"
toUrlPiece ExpandPayment = "payment"
toUrlPiece ExpandRefund = "refund"

data PayoutOrderStatusReq = PayoutOrderStatusReq
{ orderId :: Text,
mbExpand :: Maybe Expand
}
deriving (Show, Generic)
deriving anyclass (FromJSON, ToJSON)
Expand Down
7 changes: 5 additions & 2 deletions lib/mobility-core/src/Kernel/External/Payout/Juspay/Flow.hs
Original file line number Diff line number Diff line change
Expand Up @@ -16,6 +16,7 @@ module Kernel.External.Payout.Juspay.Flow where

import qualified Data.Text.Encoding as DT
import EulerHS.Types as Euler
import qualified Kernel.External.Payout.Interface.Types as Payout
import Kernel.External.Payout.Juspay.Types
import Kernel.Prelude
import Kernel.Tools.Metrics.CoreMetrics as Metrics
Expand Down Expand Up @@ -55,6 +56,7 @@ type PayoutOrderStatusAPI =
"payout" :> "merchant" :> "v1" :> "orders"
:> Capture "orderId" Text
:> BasicAuth "username-password" BasicAuthData
:> QueryParam "expand" Payout.Expand
:> Header "x-merchantid" Text
:> Get '[JSON] PayoutOrderStatusResp

Expand All @@ -64,9 +66,10 @@ payoutOrderStatus ::
Text ->
Text ->
Text ->
Maybe Payout.Expand ->
m PayoutOrderStatusResp
payoutOrderStatus url apiKey merchantId orderId = do
payoutOrderStatus url apiKey merchantId orderId mbExpand = do
let proxy = Proxy @PayoutOrderStatusAPI
eulerClient = Euler.client proxy orderId (mkBasicAuthData apiKey) (Just merchantId)
eulerClient = Euler.client proxy orderId (mkBasicAuthData apiKey) mbExpand (Just merchantId)
callAPI url eulerClient "payout-order-status" proxy
>>= fromEitherM (\err -> InternalError $ "Failed to call payout order status API: " <> show err)

0 comments on commit ab68cce

Please sign in to comment.