{-# LANGUAGE OverloadedStrings #-} module Main where import Prelude hiding (getLine, lookup, putStr, putStrLn) import Data.Default import Data.Text (Text) import Data.Text.IO import Web.PayPal.Adaptive -- You need to create a sandbox app on PayPal and enter its credentials -- below for this app to run. -- -- Also, the email associated with the sandbox app will need at least -- a dollar in its sandbox account. accountEmail, userId, password, sig :: Text accountEmail = "foo@example.com" userId = "foo_api1.example.com" password = "bar" sig = "baz" -- You must also create a sandbox user on PayPal. Enter its email here. -- This is the account we'll be sending money to and from. sandboxTestUser :: Text sandboxTestUser = "user@mail.com" main :: IO () main = do putStrLn "-- Sending money to another PayPal account." toPayPal client send >>= print putStrLn "" putStrLn "-- Creating a payment from another account to us." r <- toPayPal client create print r putStrLn "" case r of Left _ -> putStrLn "Stopping on create payment failure." Right payResp -> do let payKey = _prPayKey payResp putStrLn "-- Go here and use the other account's password to approve the payment:" putStrLn $ approvalUrl client payKey putStrLn "" putStrLn "-- Once that's done press enter ..." _ <- getLine putStrLn "-- Now looking up the payment on PayPal to make sure that succeeded." putStrLn "-- If it did _prPayExecStatus will have changed from PeCreated to PeCompleted." toPayPal client (LookupPayKey payKey) >>= print client :: PpClient client = PpClient { _clAppId = "APP-80W284485P519543T" -- Currently the ID for all sandbox apps. , _clEnv = PpSandbox , _clPassword = password , _clSig = sig , _clUserId = userId } send :: SendPayment send = def { _spReceiverList = ReceiverList { _rlAmount = USD 100 , _rlEmail = sandboxTestUser } , _spSenderEmail = accountEmail } create :: CreatePayment create = def { _cpReceiverList = ReceiverList { _rlAmount = USD 100 , _rlEmail = accountEmail } , _cpSenderEmail = sandboxTestUser }