| Safe Haskell | None |
|---|---|
| Language | Haskell98 |
Twilio.APIKeys
Contents
- data APIKeys = APIKeys {
- pagingInformation :: !PagingInformation
- list :: ![APIKey]
- get :: MonadThrow m => TwilioT m APIKeys
Resource
Constructors
| APIKeys | |
Fields
| |
get :: MonadThrow m => TwilioT m APIKeys Source #
Get APIKeys.
For example, you can fetch the APIKeys resource in the IO monad as follows:
module Main where
import Control.Monad.IO.Class (liftIO)
import System.Environment (getEnv)
import Twilio.APIKeys as APIKeys
import Twilio.Types
-- | Print API Keys.
main :: IO ()
main = runTwilio' (getEnv "ACCOUNT_SID")
(getEnv "AUTH_TOKEN")
$ APIKeys.get >>= liftIO . print