Skip to content
Snippets Groups Projects
Commit 4794d63b authored by Jean-Paul Calderone's avatar Jean-Paul Calderone
Browse files

hlint suggested improvements

parent 79abc9ea
No related branches found
No related tags found
1 merge request!2Stripe webhook
...@@ -7,10 +7,6 @@ ...@@ -7,10 +7,6 @@
module SpecPersistence where module SpecPersistence where
import Test.QuickCheck
( Property
, (==>)
)
import Control.Monad.IO.Class import Control.Monad.IO.Class
( liftIO ( liftIO
) )
...@@ -23,7 +19,9 @@ import Test.Hspec.Expectations ...@@ -23,7 +19,9 @@ import Test.Hspec.Expectations
( shouldReturn ( shouldReturn
) )
import Test.QuickCheck import Test.QuickCheck
( property ( Property
, property
, (==>)
) )
import Test.QuickCheck.Monadic import Test.QuickCheck.Monadic
( monadicIO ( monadicIO
...@@ -77,8 +75,9 @@ paidVoucherMismatchFingerprint getDB = property $ \voucher fingerprint fingerpri ...@@ -77,8 +75,9 @@ paidVoucherMismatchFingerprint getDB = property $ \voucher fingerprint fingerpri
redeem fingerprint' `shouldReturn` Left AlreadyRedeemed redeem fingerprint' `shouldReturn` Left AlreadyRedeemed
makeSpec :: VoucherDatabase d => IO d -> Spec makeSpec :: VoucherDatabase d => IO d -> Spec
makeSpec getDB = do makeSpec getDB =
describe "voucher interactions" $ do describe "voucher interactions" $
do
it "denies redemption of a not-paid-for voucher" $ unpaidVoucherNotRedeemable getDB it "denies redemption of a not-paid-for voucher" $ unpaidVoucherNotRedeemable getDB
it "allows redemption of paid-for vouchers" $ paidVoucherRedeemable getDB it "allows redemption of paid-for vouchers" $ paidVoucherRedeemable getDB
it "allows multiple redemption as long as the same fingerprint is used" $ paidVoucherMultiRedeemable getDB it "allows multiple redemption as long as the same fingerprint is used" $ paidVoucherMultiRedeemable getDB
......
...@@ -77,7 +77,7 @@ stripeAPI :: Proxy StripeAPI ...@@ -77,7 +77,7 @@ stripeAPI :: Proxy StripeAPI
stripeAPI = Proxy stripeAPI = Proxy
app :: IO Application app :: IO Application
app = memory >>= return . stripeServer >>= return . serve stripeAPI app = serve stripeAPI . stripeServer <$> memory
spec_webhook :: Spec spec_webhook :: Spec
spec_webhook = with app $ do spec_webhook = with app $ do
......
...@@ -163,7 +163,7 @@ charges withVoucher = ...@@ -163,7 +163,7 @@ charges withVoucher =
if withVoucher then if withVoucher then
metaDatasWithVoucher metaDatasWithVoucher
else else
metaDatasWithVoucher metaDatasWithoutVoucher
) -- chargeMetaData :: MetaData ) -- chargeMetaData :: MetaData
<*> arbitrary -- chargeStatementDescription :: Maybe StatementDescription <*> arbitrary -- chargeStatementDescription :: Maybe StatementDescription
<*> arbitrary -- chargeReceiptEmail :: Maybe Text <*> arbitrary -- chargeReceiptEmail :: Maybe Text
...@@ -184,4 +184,4 @@ posixTimes :: Gen UTCTime ...@@ -184,4 +184,4 @@ posixTimes :: Gen UTCTime
posixTimes = (arbitrary :: Gen Integer) `suchThatMap` (Just . posixSecondsToUTCTime . fromIntegral . abs) posixTimes = (arbitrary :: Gen Integer) `suchThatMap` (Just . posixSecondsToUTCTime . fromIntegral . abs)
hasVoucher :: MetaData -> Bool hasVoucher :: MetaData -> Bool
hasVoucher (MetaData items) = any (== "Voucher") . (map fst) $ items hasVoucher (MetaData items) = elem "Voucher" . map fst $ items
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment