| Safe Haskell | None | 
|---|---|
| Language | Haskell98 | 
Twilio.Accounts
Contents
- data Accounts = Accounts {- pagingInformation :: !PagingInformation
- list :: ![Account]
 
- get :: MonadThrow m => TwilioT m Accounts
- post :: MonadThrow m => Maybe Text -> TwilioT m Account
- createSubAccount :: MonadThrow m => Maybe Text -> TwilioT m Account
Resource
Constructors
| Accounts | |
| Fields 
 | |
get :: MonadThrow m => TwilioT m Accounts Source #
Get Accounts.
For example, you can fetch the Accounts resource in the IO monad as follows:
module Main where
import Control.Monad.IO.Class (liftIO)
import System.Environment (getEnv)
import Twilio.Accounts as Accounts
import Twilio.Types
-- | Print accounts.
main :: IO ()
main = runTwilio' (getEnv "ACCOUNT_SID")
                  (getEnv "AUTH_TOKEN")
     $ Accounts.get >>= liftIO . printArguments
| :: MonadThrow m | |
| => Maybe Text | A human readable description of the new subaccount, up to 64 characters. Defaults to "SubAccount Created at {YYYY-MM-DD HH:MM meridian}". | 
| -> TwilioT m Account | 
Create a new Account instance resource as a subaccount of the one used
to make the request.
For example, you can create a subaccount, "foo", as follows:
module Main where
import Control.Monad.IO.Class (liftIO)
import System.Environment (getEnv)
import Twilio.Accounts (createSubAccount)
import Twilio.Types
-- | Create and print a subaccount, "foo".
main :: IO ()
main = runTwilio' (getEnv "ACCOUNT_SID")
                  (getEnv "AUTH_TOKEN")
     $ createSubAccount (Just "foo") >>= liftIO . print