module Web.Stripe.Plan
( Plan(..)
, amount
, PlanInterval(..)
, PlanId(..)
, PlanTrialDays(..)
, createPlan
, getPlan
, getPlans
, delPlan
, delPlanById
, Amount(..)
, Count(..)
, Currency(..)
, Offset(..)
, StripeConfig(..)
, StripeT(StripeT)
, runStripeT
) where
import Control.Applicative ((<$>), (<*>))
import Control.Monad (liftM, mzero)
import Control.Monad.Error (MonadIO)
import Data.Aeson (FromJSON (..), Value (..), (.:), (.:?))
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 (Amount (..), Count (..), Currency (..),
Offset (..), optionalArgs, showByteString,
textToByteString)
data Plan = Plan
{ planId :: PlanId
, planAmount :: Amount
, planInterval :: PlanInterval
, planName :: T.Text
, planCurrency :: Currency
, planTrialDays :: Maybe PlanTrialDays
} deriving Show
data PlanInterval = Monthly | Yearly | UnknownPlan T.Text deriving (Show, Eq)
newtype PlanId = PlanId { unPlanId :: T.Text } deriving (Show, Eq)
newtype PlanTrialDays = PlanTrialDays { unPlanTrialDays :: Int } deriving (Show, Eq)
amount :: Plan -> Int
amount plan = unAmount $ planAmount plan
createPlan :: MonadIO m => Plan -> StripeT m ()
createPlan p = query_ (planRq []) { sMethod = POST, sData = fdata }
where
fdata = pdata ++ optionalArgs odata
pdata = [ ("id", textToByteString . unPlanId $ planId p)
, ("amount", showByteString $ amount p)
, ("interval", textToByteString . fromPlanInterval $ planInterval p)
, ("name", textToByteString $ planName p)
, ("currency", textToByteString . unCurrency $ planCurrency p)
]
odata = [ ( "trial_period_days"
, showByteString . unPlanTrialDays <$> planTrialDays p
)
]
getPlan :: MonadIO m => PlanId -> StripeT m Plan
getPlan (PlanId pid) = liftM snd $ query (planRq [pid])
getPlans :: MonadIO m => Maybe Count -> Maybe Offset -> StripeT m [Plan]
getPlans mc mo = liftM snd $ queryData (planRq []) { sQString = qs }
where
qs = optionalArgs [ ("count", show . unCount <$> mc)
, ("offset", show . unOffset <$> mo)
]
delPlan :: MonadIO m => Plan -> StripeT m Bool
delPlan = delPlanById . planId
delPlanById :: MonadIO m => PlanId -> StripeT m Bool
delPlanById (PlanId pid) = liftM snd $ queryData (planRq [pid]) { sMethod = DELETE }
planRq :: [T.Text] -> StripeRequest
planRq pcs = baseSReq { sDestination = "plans":pcs }
fromPlanInterval :: PlanInterval -> T.Text
fromPlanInterval Monthly = "month"
fromPlanInterval Yearly = "year"
fromPlanInterval (UnknownPlan p) = p
toPlanInterval :: T.Text -> PlanInterval
toPlanInterval p = case T.map toLower p of
"month" -> Monthly
"year" -> Yearly
_ -> UnknownPlan p
instance FromJSON Plan where
parseJSON (Object o) = Plan
<$> (PlanId <$> o .: "id")
<*> (Amount <$> o .: "amount")
<*> (toPlanInterval <$> o .: "interval")
<*> o .: "name"
<*> (Currency <$> o .: "currency")
<*> (fmap PlanTrialDays <$> o .:? "trial_period_days")
parseJSON _ = mzero