{-# LANGUAGE OverloadedStrings #-} module Main where import qualified Data.ByteString.Char8 as C import Network.PayPal.ButtonManager import Data.Ratio import Data.Time.Calendar import Data.Time.LocalTime import Control.Monad import Network.HTTP.Conduit me = Credentials { crUsername = "your_username_here", crPassword = "your_password_here", crSecurity = Signature "your_signature_here", crVersion = "56.0" } main :: IO () main = do putStrLn "creating a new non-hosted button..." let cb :: CreateButton (NONHOSTED CLEARTEXT) CART cb = CreateButton { cbVariables = Variables_CART { cartItem = Item { itAmount = 250 % 100, itItemName = Just "small button image", itBusiness = Nothing, itItemNumber = Just "SML001", itQuantity = Nothing, itShipping = Just (45 % 100), itShipping2 = Nothing, itTax = Nothing, itTaxRate = Just 0.15, itUndefinedQuantity = (), itWeight = Just (0.5, Kg) }, cartPayment = Payment { payAddressOverride = Nothing, payCurrencyCode = Just "NZD", payCustom = Nothing, payHandling = Nothing, payInvoice = Just "000002", payTaxCart = Nothing, payWeight = Nothing }, cartCart = ShoppingCart { caAction = Add, caHandlingCart = Nothing, caPaymentAction = Sale, caShoppingURL = Just "http://hip-to-be-square.com/" } }, cbButtonSubtype = Nothing, cbOptions = Options $ Just ( Option "Size" [Select "Small" (Just (200 % 100)), Select "Medium" (Just (250 % 100)), Select "Large" (Just (300 % 100))], [Option "Colour" [Select "Red" (), Select "Green" (), Select "Blue" ()]] ), cbButtonImage = Just (Left SML), cbButtonText = (), cbCountry = Just "BE", cbLanguage = Just "fr", cbExtras = [] } --print cb --print (toVariables cb) reply <- submit sandbox me cb case reply of Right (Success (CreateButton_NonHosted_Response _ html)) -> do C.writeFile "test.html" html err -> putStrLn $ "FAILED: "++show err putStrLn "fetching list of buttons currently hosted at paypal..." let bs = ButtonSearch { bsStartDate = LocalTime (fromGregorian 2011 1 1) midnight, bsEndDate = Nothing } --print (toVariables bs) searchRes <- submit sandbox me bs --print searchRes case searchRes of Right (Success (ButtonSearch_Response items)) -> forM_ items $ \item -> do print item det <- submit sandbox me (GetButtonDetails (biButtonID item)) print det err -> putStrLn $ "FAILED: "++show err