twilio-0.1.1.0: Twilio REST API library for Haskell

Safe HaskellNone
LanguageHaskell98

Control.Monad.Twilio

Contents

Synopsis

The Twilio monad

type Twilio = TwilioT IO Source

This monad allows you to make authenticated REST API requests to Twilio using your AccountSID and AuthToken.

runTwilio :: Credentials -> Twilio a -> IO a Source

Run zero or more REST API requests to Twilio.

runTwilio' Source

Arguments

:: IO String

Account SID

-> IO String

Authentication Token

-> Twilio a 
-> IO a 

Parse an AccountSID and AuthToken before running zero or more REST API requests to Twilio.

For example, you can fetch the Calls resource in the IO monad as follows:

module Main where

import Control.Monad.IO.Class (liftIO)
import System.Environment (getEnv)
import Twilio.Calls as Calls
import Twilio.Types

-- | Print calls.
main :: IO ()
main = runTwilio' (getEnv "ACCOUNT_SID")
                  (getEnv "AUTH_TOKEN")
     $ Calls.get >>= liftIO . print

The Twilio monad transformer

newtype TwilioT m a Source

This monad transformer allows you to make authenticated REST API requests to Twilio using your AccountSID and AuthToken.

Constructors

TwilioT (Monad m => (Credentials, AccountSID) -> RequestT m a) 

Instances

MonadTrans TwilioT 
Monad m => Monad (TwilioT m) 
Functor (TwilioT m) 
Applicative m => Applicative (TwilioT m) 
MonadThrow m => MonadThrow (TwilioT m) 
MonadIO m => MonadIO (TwilioT m) 
Monad m => MonadRequest (TwilioT m) 
(MonadThrow m, Post2 a b r) => Post (a -> b -> TwilioT m r) 
(MonadThrow m, Post1 a r) => Post (a -> TwilioT m r)

Instances of Post1 are instances of Post.

(MonadThrow m, Post0 r) => Post (TwilioT m r)

Instances of Post0 are instances of Post.

(MonadThrow m, Get1 a r) => Get (a -> TwilioT m r)

Instances of Get1 are instances of Get.

(MonadThrow m, Get0 r) => Get (TwilioT m r)

Instances of Get0 are instances of Get.

Monad m => MonadReader (Credentials, AccountSID) (TwilioT m) 

runTwilioT :: MonadIO m => Credentials -> TwilioT m a -> m a Source

Run zero or more REST API requests to Twilio, unwrapping the inner monad m.

runTwilioT' Source

Arguments

:: (Functor m, MonadThrow m, MonadIO m) 
=> m String

Account SID

-> m String

Authentication Token

-> TwilioT m a 
-> m a 

Parse an AccountSID and AuthToken before running zero or more REST API requests to Twilio, unwrapping the inner monad m.

Types

type Credentials = (AccountSID, AuthToken) Source

Your AccountSID and AuthToken are used to make authenticated REST API requests to Twilio.

data TwilioException Source

The set of Exceptions that may be thrown when attempting to make requests against Twilio's REST API.