module Web.Stripe.Coupon
( Coupon(..)
, CpnId(..)
, CpnDuration(..)
, CpnPercentOff(..)
, CpnMaxRedeems(..)
, CpnRedeemBy(..)
, applyCoupon
, createCoupon
, getCoupon
, getCoupons
, delCoupon
, delCouponById
, Count(..)
, Offset(..)
, StripeConfig(..)
, StripeT(StripeT)
, runStripeT
) where
import Control.Applicative ((<$>))
import Control.Monad (liftM, mzero)
import Control.Monad.Error (MonadIO, strMsg, throwError)
import Data.Aeson (FromJSON (..), Value (..), parseJSON,
(.:), (.:?))
import qualified Data.ByteString as B
import Data.Char (toLower)
import qualified Data.Text as T
import Network.HTTP.Types (StdMethod (..))
import Web.Stripe.Client (StripeConfig (..), StripeRequest (..),
StripeT (..), baseSReq, query, queryData,
query_, runStripeT)
import Web.Stripe.Utils (Count (..), Offset (..), optionalArgs,
showByteString, textToByteString)
import Web.Stripe.Plan (Plan, amount)
data Coupon = Coupon
{ cpnId :: Maybe CpnId
, cpnDuration :: CpnDuration
, cpnPercentOff :: CpnPercentOff
} deriving Show
newtype CpnId = CpnId { unCpnId :: T.Text } deriving (Show, Eq)
data CpnDuration
= Once
| Repeating Int
| Forever
| UnknownDuration T.Text
deriving (Show, Eq)
newtype CpnPercentOff = CpnPercentOff { unCpnPercentOff :: Int } deriving (Show, Eq)
newtype CpnMaxRedeems = CpnMaxRedeems { unCpnMaxRedeems :: Int } deriving (Show, Eq)
newtype CpnRedeemBy = CpnRedeemBy { unCpnRedeemBy :: Int } deriving (Show, Eq)
applyCoupon :: Maybe Coupon -> Plan -> Int
applyCoupon mCoupon plan =
(100 couponOff mCoupon) * amount plan `div` 100
where
couponOff :: Maybe Coupon -> Int
couponOff = maybe 0 (unCpnPercentOff . cpnPercentOff)
createCoupon
:: MonadIO m
=> Coupon
-> Maybe CpnMaxRedeems
-> Maybe CpnRedeemBy
-> StripeT m ()
createCoupon c mmr mrb = query_ (cpnRq []) { sMethod = POST, sData = fdata }
where
fdata = poff:cpnDurationKV (cpnDuration c) ++ optionalArgs odata
poff = ("percent_off", showByteString . unCpnPercentOff . cpnPercentOff $ c)
odata = [ ("id", (textToByteString . unCpnId) <$> cpnId c)
, ("max_redemptions", showByteString . unCpnMaxRedeems <$> mmr)
, ("redeem_by", showByteString . unCpnRedeemBy <$> mrb)
]
getCoupon :: MonadIO m => CpnId -> StripeT m Coupon
getCoupon (CpnId cid) = return . snd =<< query (cpnRq [cid])
getCoupons :: MonadIO m => Maybe Count -> Maybe Offset -> StripeT m [Coupon]
getCoupons mc mo = liftM snd $ queryData (cpnRq []) { sQString = qs }
where
qs = optionalArgs [ ("count", show . unCount <$> mc)
, ("offset", show . unOffset <$> mo)
]
delCoupon :: MonadIO m => Coupon -> StripeT m Bool
delCoupon = handleCpnId . cpnId
where
handleCpnId Nothing = throwError $ strMsg "No coupon ID provided."
handleCpnId (Just cid) = delCouponById cid
delCouponById :: MonadIO m => CpnId -> StripeT m Bool
delCouponById (CpnId cid) = liftM snd $ queryData (cpnRq [cid]) { sMethod = DELETE }
cpnRq :: [T.Text] -> StripeRequest
cpnRq pcs = baseSReq { sDestination = "coupons":pcs }
cpnDurationKV :: CpnDuration -> [ (B.ByteString, B.ByteString) ]
cpnDurationKV d@(Repeating m) = [ ("duration", textToByteString $ fromCpnDuration d)
, ("duration_in_months", showByteString m)
]
cpnDurationKV d = [ ("duration", textToByteString $ fromCpnDuration d) ]
fromCpnDuration :: CpnDuration -> T.Text
fromCpnDuration Once = "once"
fromCpnDuration (Repeating _) = "repeating"
fromCpnDuration Forever = "forever"
fromCpnDuration (UnknownDuration d) = d
toCpnDuration :: T.Text -> Maybe Int -> CpnDuration
toCpnDuration d Nothing = case T.map toLower d of
"once" -> Once
"forever" -> Forever
_ -> UnknownDuration d
toCpnDuration d (Just ms) = case T.map toLower d of
"repeating" -> Repeating ms
_ -> UnknownDuration d
instance FromJSON Coupon where
parseJSON (Object c) = do
drn <- c .: "duration"
drns <- c .: "duration_in_months"
cId <- c .:? "id"
pctOff <- c .: "percent_off"
return $ Coupon (CpnId <$> cId) (toCpnDuration drn drns) (CpnPercentOff pctOff)
parseJSON _ = mzero