quickbooks-0.5.0.1: QuickBooks API binding.

Safe HaskellNone
LanguageHaskell2010

QuickBooks

Contents

Description

For more information, see:

Synopsis

Authentication and authorization

getAccessTokens :: OAuthToken -> OAuthVerifier -> IO (Either String (QuickBooksResponse OAuthToken)) Source

Exchange oauth_verifier for access tokens

getTempTokens :: CallbackURL -> IO (Either String (QuickBooksResponse OAuthToken)) Source

Get temporary tokens to request permission.

Example:

>>> :{
do eitherTempTokens <- getTempTokens "localhost"
   case eitherTempTokens of
     Left e -> putStrLn e
     Right _ -> putStrLn "I got my request tokens!"
:}
...
I got my request tokens!

cancelOAuthAuthorization :: OAuthToken -> IO (Either String (QuickBooksResponse ())) Source

Invalidate an OAuth access token and disconnect from QuickBooks.

Transaction entities

Invoices

Types

CRUD an invoice

createInvoice :: OAuthToken -> Invoice -> IO (Either String (QuickBooksResponse Invoice)) Source

Create an invoice.

Example:

>>> import Data.Maybe (fromJust)
>>> :{
do resp <- createInvoice oAuthToken testInvoice
   case resp of
     Left err -> putStrLn $ "My custom error message: " ++ err
     Right (QuickBooksInvoiceResponse invoice) -> do
       deleteInvoice oAuthToken (fromJust (invoiceId invoice)) (fromJust (invoiceSyncToken invoice))
       putStrLn "I created an invoice!"
:}
I created an invoice!

Note that we deleted the item we created using deleteInvoice.

createInvoice' :: APIConfig -> AppConfig -> OAuthToken -> Invoice -> IO (Either String (QuickBooksResponse Invoice)) Source

Like createInvoice but accepts an APIConfig rather than reading it from the environment

readInvoice :: OAuthToken -> InvoiceId -> IO (Either String (QuickBooksResponse Invoice)) Source

Retrieve the details of an invoice that has been previously created.

Example:

First, we create an invoice (see createInvoice):

>>> import Data.Maybe (fromJust)
>>> Right (QuickBooksInvoiceResponse cInvoice) <- createInvoice oAuthToken testInvoice

Then, we read the invoice and test that it is the same invoice we created:

>>> let cInvoiceId = fromJust (invoiceId cInvoice)
>>> :{
do eitherReadInvoice <- readInvoice oAuthToken cInvoiceId
   case eitherReadInvoice of
     Left _ -> return False
     Right (QuickBooksInvoiceResponse rInvoice) -> return (cInvoice == rInvoice)
:}
True

Finally, we delete the invoice we created:

>>> deleteInvoice oAuthToken cInvoiceId (fromJust (invoiceSyncToken cInvoice))

readInvoice' :: APIConfig -> AppConfig -> OAuthToken -> InvoiceId -> IO (Either String (QuickBooksResponse Invoice)) Source

Like readInvoice but accepts an APIConfig rather than reading it from the environment

updateInvoice :: OAuthToken -> Invoice -> IO (Either String (QuickBooksResponse Invoice)) Source

Update an invoice.

Example:

First, we create an invoice (see createInvoice):

>>> import Data.Maybe (fromJust)
>>> Right (QuickBooksInvoiceResponse cInvoice) <- createInvoice oAuthToken testInvoice

Then, we update the customer reference of the invoice:

>>> let nInvoice = cInvoice { invoiceCustomerRef = Reference Nothing Nothing "1" }
>>> :{
do eitherUpdateInvoice <- updateInvoice oAuthToken nInvoice
   case eitherUpdateInvoice of
     Left _ -> return False
     Right (QuickBooksInvoiceResponse uInvoice) ->
       return (invoiceCustomerRef cInvoice == invoiceCustomerRef uInvoice)
:}
False

Finally, we delete the invoice we created:

>>> deleteInvoice oAuthToken (fromJust (invoiceId cInvoice)) (fromJust (invoiceSyncToken cInvoice))

updateInvoice' :: APIConfig -> AppConfig -> OAuthToken -> Invoice -> IO (Either String (QuickBooksResponse Invoice)) Source

Like updateInvoice but accepts an APIConfig rather than reading it from the environment

deleteInvoice :: OAuthToken -> InvoiceId -> SyncToken -> IO (Either String (QuickBooksResponse DeletedInvoice)) Source

Delete an invoice.

Example:

First, we create an invoice (see createInvoice):

>>> import Data.Maybe (fromJust)
>>> Right (QuickBooksInvoiceResponse cInvoice) <- createInvoice oAuthToken testInvoice

Then, we delete it:

>>> let cInvoiceId = fromJust (invoiceId cInvoice)
>>> let cInvoiceSyncToken = fromJust (invoiceSyncToken cInvoice)
>>> :{
do eitherDeleteInvoice <- deleteInvoice oAuthToken cInvoiceId cInvoiceSyncToken
   case eitherDeleteInvoice of
     Left e -> putStrLn e
     Right _ -> putStrLn "I deleted an invoice!"
:}
I deleted an invoice!

deleteInvoice' :: APIConfig -> AppConfig -> OAuthToken -> InvoiceId -> SyncToken -> IO (Either String (QuickBooksResponse DeletedInvoice)) Source

Like deleteInvoice but accepts an APIConfig rather than reading it from the environment

Send an invoice via email

data EmailAddress :: *

Represents an email address.

emailAddress :: ByteString -> Maybe EmailAddress

Smart constructor for an email address

sendInvoice :: OAuthToken -> InvoiceId -> EmailAddress -> IO (Either String (QuickBooksResponse Invoice)) Source

Send an invoice via email.

Example:

First, we create an invoice (see createInvoice):

>>> import Data.Maybe (fromJust)
>>> Right (QuickBooksInvoiceResponse cInvoice) <- createInvoice oAuthToken testInvoice

Then, we send the invoice via email:

>>> let cInvoiceId = fromJust (invoiceId cInvoice)
>>> let testEmail = fromJust (emailAddress "test@test.com")
>>> :{
do eitherSendInvoice <- sendInvoice oAuthToken cInvoiceId testEmail
   case eitherSendInvoice of
     Left e  -> putStrLn e
     Right _ -> putStrLn "I sent an invoice!"
:}
I sent an invoice!

Finally, we delete the invoice we created:

>>> deleteInvoice oAuthToken cInvoiceId (fromJust (invoiceSyncToken cInvoice))

Read in configuration files

Name list entities

Customer

queryCustomer :: OAuthToken -> Text -> IO (Either String (QuickBooksResponse [Customer])) Source

>>> :{
  do eitherQueryCustomer <-
       queryCustomer oAuthToken "Rondonuwu Fruit and Vegi"
     case eitherQueryCustomer of
       Right (QuickBooksCustomerResponse (customer:_)) ->
         print (customerId customer)
       _ ->
         putStrLn "Nothing"
:}
Just "21"

Line

queryItem :: OAuthToken -> Text -> IO (Either String (QuickBooksResponse [Item])) Source

>>> :{
  do eitherQueryItem <- queryItem oAuthToken "Hours"
     case eitherQueryItem of
       Right (QuickBooksItemResponse (item:_)) ->
         print (itemId item)
       _ ->
         putStrLn "Nothing"
:}
Just "2"