Skip to content

Commit d386fe1

Browse files
committed
stripe format
1 parent 8602849 commit d386fe1

File tree

3 files changed

+118
-93
lines changed

3 files changed

+118
-93
lines changed
Lines changed: 20 additions & 16 deletions
Original file line numberDiff line numberDiff line change
@@ -1,25 +1,29 @@
1-
-- | Private helper functions. Note that all contents of this module are excluded from the versioning scheme.
21
{-# LANGUAGE BangPatterns #-}
2+
3+
-- | Private helper functions. Note that all contents of this module are excluded from the versioning scheme.
34
module Stripe.Client.Internal.Helpers where
45

5-
import Servant.Client
66
import Network.HTTP.Types.Status
7+
import Servant.Client
78

8-
runRequest :: Int -> Int -> IO (Either ClientError a) -> IO (Either ClientError a)
9+
runRequest ::
10+
Int -> Int -> IO (Either ClientError a) -> IO (Either ClientError a)
911
runRequest maxRetries !retryCount makeRequest =
10-
do res <- makeRequest
11-
case res of
12-
Right ok -> pure (Right ok)
13-
Left err@(ConnectionError _) -> maybeRetry err
14-
Left err@(FailureResponse _ resp)
15-
| ("stripe-should-retry", "true") `elem` responseHeaders resp -> maybeRetry err
16-
| ("stripe-should-retry", "false") `elem` responseHeaders resp -> pure (Left err)
17-
| responseStatusCode resp == conflict409 -> maybeRetry err
18-
| statusCode (responseStatusCode resp) >= 500 -> maybeRetry err
19-
| otherwise -> pure (Left err)
20-
Left err -> pure (Left err)
12+
do
13+
res <- makeRequest
14+
case res of
15+
Right ok -> pure (Right ok)
16+
Left err@(ConnectionError _) -> maybeRetry err
17+
Left err@(FailureResponse _ resp)
18+
| ("stripe-should-retry", "true") `elem` responseHeaders resp -> maybeRetry err
19+
| ("stripe-should-retry", "false") `elem` responseHeaders resp ->
20+
pure (Left err)
21+
| responseStatusCode resp == conflict409 -> maybeRetry err
22+
| statusCode (responseStatusCode resp) >= 500 -> maybeRetry err
23+
| otherwise -> pure (Left err)
24+
Left err -> pure (Left err)
2125
where
2226
maybeRetry err =
2327
if retryCount + 1 >= maxRetries
24-
then pure (Left err)
25-
else runRequest maxRetries (retryCount + 1) makeRequest
28+
then pure (Left err)
29+
else runRequest maxRetries (retryCount + 1) makeRequest
Lines changed: 33 additions & 31 deletions
Original file line numberDiff line numberDiff line change
@@ -1,55 +1,57 @@
11
module Stripe.Webhook.Verify
2-
( verifyStripeSignature
3-
, WebhookSecret, VerificationResult(..)
2+
( verifyStripeSignature,
3+
WebhookSecret,
4+
VerificationResult (..),
45
)
56
where
67

78
import Crypto.Hash.Algorithms
89
import Crypto.MAC.HMAC
910
import Data.Bifunctor
1011
import Data.ByteArray.Encoding
12+
import qualified Data.ByteString as BS
13+
import qualified Data.ByteString.Char8 as BSC
1114
import Data.Time
1215
import Data.Time.Clock.POSIX
1316
import Safe
14-
import qualified Data.ByteString as BS
15-
import qualified Data.ByteString.Char8 as BSC
1617

1718
-- | Your webhook secret, can be obtained from the Stripe dashboard. Format: @whsec_<redacted>@
1819
type WebhookSecret = BS.ByteString
1920

2021
-- | Output of the webhook signature verification
2122
data VerificationResult
22-
= VOk UTCTime
23-
-- ^ Signature verification successful, check the time against the current time and reject /too old/ requests.
24-
| VFailed
25-
-- ^ Signature verification failed. Check that your 'WebhookSecret' is correct.
26-
| VInvalidSignature
27-
-- ^ Invalid signature. Verify that you are passing the raw contents of the @stripe-signature@ header.
23+
= -- | Signature verification successful, check the time against the current time and reject /too old/ requests.
24+
VOk UTCTime
25+
| -- | Signature verification failed. Check that your 'WebhookSecret' is correct.
26+
VFailed
27+
| -- | Invalid signature. Verify that you are passing the raw contents of the @stripe-signature@ header.
28+
VInvalidSignature
2829
deriving (Show, Eq)
2930

3031
-- | Verify the @stripe-signature@ header
3132
verifyStripeSignature ::
32-
WebhookSecret
33-
-- ^ Your webhook secret
34-
-> BS.ByteString
35-
-- ^ Value of the @stripe-signature@ header
36-
-> BS.ByteString
37-
-- ^ Raw request body received from Stripe
38-
-> VerificationResult
33+
-- | Your webhook secret
34+
WebhookSecret ->
35+
-- | Value of the @stripe-signature@ header
36+
BS.ByteString ->
37+
-- | Raw request body received from Stripe
38+
BS.ByteString ->
39+
VerificationResult
3940
verifyStripeSignature secret sig rawBody =
4041
let sigMap = map (second (BS.drop 1) . BSC.break (\c -> c == '=')) . BSC.split ',' $ sig
4142
needed =
42-
do t <- lookup "t" sigMap
43-
(parsedTime :: Int) <- readMay (BSC.unpack t)
44-
v1 <- lookup "v1" sigMap
45-
pure (t, posixSecondsToUTCTime $ fromIntegral parsedTime, v1)
46-
in case needed of
47-
Nothing -> VInvalidSignature
48-
Just (rawTime, time, v1) ->
49-
let payload = rawTime <> BSC.singleton '.' <> rawBody
50-
computedSig :: HMAC SHA256
51-
computedSig = hmac secret payload
52-
hexSig = convertToBase Base16 computedSig
53-
in if hexSig == v1
54-
then VOk time
55-
else VFailed
43+
do
44+
t <- lookup "t" sigMap
45+
(parsedTime :: Int) <- readMay (BSC.unpack t)
46+
v1 <- lookup "v1" sigMap
47+
pure (t, posixSecondsToUTCTime $ fromIntegral parsedTime, v1)
48+
in case needed of
49+
Nothing -> VInvalidSignature
50+
Just (rawTime, time, v1) ->
51+
let payload = rawTime <> BSC.singleton '.' <> rawBody
52+
computedSig :: HMAC SHA256
53+
computedSig = hmac secret payload
54+
hexSig = convertToBase Base16 computedSig
55+
in if hexSig == v1
56+
then VOk time
57+
else VFailed
Lines changed: 65 additions & 46 deletions
Original file line numberDiff line numberDiff line change
@@ -1,53 +1,72 @@
11
-- | The API
2-
32
module Stripe.Api where
43

5-
import Stripe.Resources
6-
7-
import Servant.API
84
import qualified Data.Text as T
5+
import Servant.API
6+
import Stripe.Resources
97

108
type StripeAuth = BasicAuth "Stripe API" ()
119

12-
type StripeApi
13-
= "v1" :> StripeApiInternal
14-
15-
type StripeApiInternal
16-
= "customers" :> CustomerApi
17-
:<|> "products" :> ProductApi
18-
:<|> "prices" :> PriceApi
19-
:<|> "subscriptions" :> SubscriptionApi
20-
:<|> "checkout" :> "sessions" :> CheckoutApi
21-
:<|> "billing_portal" :> "sessions" :> CustomerPortalApi
22-
:<|> "events" :> EventApi
23-
24-
type CustomerApi
25-
= StripeAuth :> ReqBody '[FormUrlEncoded] CustomerCreate :> Post '[JSON] Customer
26-
:<|> StripeAuth :> Capture ":customer_id" CustomerId :> Get '[JSON] Customer
27-
:<|> StripeAuth :> Capture ":customer_id" CustomerId :> ReqBody '[FormUrlEncoded] CustomerUpdate :> Post '[JSON] Customer
28-
:<|> StripeAuth :> QueryParam "starting_after" CustomerId :> Get '[JSON] (StripeList Customer)
29-
30-
type EventApi
31-
= StripeAuth :> Capture ":event_id" EventId :> Get '[JSON] Event
32-
:<|> StripeAuth :> QueryParam "starting_after" EventId :> Get '[JSON] (StripeList Event)
33-
34-
type ProductApi
35-
= StripeAuth :> ReqBody '[FormUrlEncoded] ProductCreate :> Post '[JSON] Product
36-
:<|> StripeAuth :> Capture ":product_id" ProductId :> Get '[JSON] Product
37-
38-
type PriceApi
39-
= StripeAuth :> ReqBody '[FormUrlEncoded] PriceCreate :> Post '[JSON] Price
40-
:<|> StripeAuth :> Capture ":product_id" PriceId :> Get '[JSON] Price
41-
:<|> StripeAuth :> QueryParam "lookup_keys[]" T.Text :> Get '[JSON] (StripeList Price)
42-
43-
type SubscriptionApi
44-
= StripeAuth :> ReqBody '[FormUrlEncoded] SubscriptionCreate :> Post '[JSON] Subscription
45-
:<|> StripeAuth :> Capture ":subscription_id" SubscriptionId :> Get '[JSON] Subscription
46-
:<|> StripeAuth :> QueryParam "customer" CustomerId :> Get '[JSON] (StripeList Subscription)
47-
48-
type CheckoutApi
49-
= StripeAuth :> ReqBody '[FormUrlEncoded] CheckoutSessionCreate :> Post '[JSON] CheckoutSession
50-
:<|> StripeAuth :> Capture ":session_id" CheckoutSessionId :> Get '[JSON] CheckoutSession
51-
52-
type CustomerPortalApi
53-
= StripeAuth :> ReqBody '[FormUrlEncoded] CustomerPortalCreate :> Post '[JSON] CustomerPortal
10+
type StripeApi =
11+
"v1" :> StripeApiInternal
12+
13+
type StripeApiInternal =
14+
"customers" :> CustomerApi
15+
:<|> "products" :> ProductApi
16+
:<|> "prices" :> PriceApi
17+
:<|> "subscriptions" :> SubscriptionApi
18+
:<|> "checkout" :> "sessions" :> CheckoutApi
19+
:<|> "billing_portal" :> "sessions" :> CustomerPortalApi
20+
:<|> "events" :> EventApi
21+
22+
type CustomerApi =
23+
StripeAuth :> ReqBody '[FormUrlEncoded] CustomerCreate :> Post '[JSON] Customer
24+
:<|> StripeAuth :> Capture ":customer_id" CustomerId :> Get '[JSON] Customer
25+
:<|> StripeAuth
26+
:> Capture ":customer_id" CustomerId
27+
:> ReqBody '[FormUrlEncoded] CustomerUpdate
28+
:> Post '[JSON] Customer
29+
:<|> StripeAuth
30+
:> QueryParam "starting_after" CustomerId
31+
:> Get '[JSON] (StripeList Customer)
32+
33+
type EventApi =
34+
StripeAuth :> Capture ":event_id" EventId :> Get '[JSON] Event
35+
:<|> StripeAuth
36+
:> QueryParam "starting_after" EventId
37+
:> Get '[JSON] (StripeList Event)
38+
39+
type ProductApi =
40+
StripeAuth :> ReqBody '[FormUrlEncoded] ProductCreate :> Post '[JSON] Product
41+
:<|> StripeAuth :> Capture ":product_id" ProductId :> Get '[JSON] Product
42+
43+
type PriceApi =
44+
StripeAuth :> ReqBody '[FormUrlEncoded] PriceCreate :> Post '[JSON] Price
45+
:<|> StripeAuth :> Capture ":product_id" PriceId :> Get '[JSON] Price
46+
:<|> StripeAuth
47+
:> QueryParam "lookup_keys[]" T.Text
48+
:> Get '[JSON] (StripeList Price)
49+
50+
type SubscriptionApi =
51+
StripeAuth
52+
:> ReqBody '[FormUrlEncoded] SubscriptionCreate
53+
:> Post '[JSON] Subscription
54+
:<|> StripeAuth
55+
:> Capture ":subscription_id" SubscriptionId
56+
:> Get '[JSON] Subscription
57+
:<|> StripeAuth
58+
:> QueryParam "customer" CustomerId
59+
:> Get '[JSON] (StripeList Subscription)
60+
61+
type CheckoutApi =
62+
StripeAuth
63+
:> ReqBody '[FormUrlEncoded] CheckoutSessionCreate
64+
:> Post '[JSON] CheckoutSession
65+
:<|> StripeAuth
66+
:> Capture ":session_id" CheckoutSessionId
67+
:> Get '[JSON] CheckoutSession
68+
69+
type CustomerPortalApi =
70+
StripeAuth
71+
:> ReqBody '[FormUrlEncoded] CustomerPortalCreate
72+
:> Post '[JSON] CustomerPortal

0 commit comments

Comments
 (0)