twilio-0.2.0.1: Twilio REST API library for Haskell

Copyright(C) 2017- Mark Andrus Roberts
LicenseBSD-style (see the file LICENSE)
MaintainerMark Andrus Roberts <markandrusroberts@gmail.com>
Stabilityprovisional
Safe HaskellNone
LanguageHaskell98

Twilio.Types.SIDs

Contents

Description

This module defines all of the SIDs (string identifiers) for Twilio resources in a single place.

Synopsis

Documentation

newtype AccountSID Source #

Constructors

AccountSID 

Fields

Instances

Bounded AccountSID Source # 
Eq AccountSID Source # 
Data AccountSID Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> AccountSID -> c AccountSID #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c AccountSID #

toConstr :: AccountSID -> Constr #

dataTypeOf :: AccountSID -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c AccountSID) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c AccountSID) #

gmapT :: (forall b. Data b => b -> b) -> AccountSID -> AccountSID #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> AccountSID -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> AccountSID -> r #

gmapQ :: (forall d. Data d => d -> u) -> AccountSID -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> AccountSID -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> AccountSID -> m AccountSID #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> AccountSID -> m AccountSID #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> AccountSID -> m AccountSID #

Ord AccountSID Source # 
Read AccountSID Source # 
Show AccountSID Source # 
Ix AccountSID Source # 
IsString AccountSID Source # 
Generic AccountSID Source # 

Associated Types

type Rep AccountSID :: * -> * #

Hashable AccountSID Source # 
ToJSON AccountSID Source # 
FromJSON AccountSID Source # 
NFData AccountSID Source # 

Methods

rnf :: AccountSID -> () #

IsSID AccountSID Source # 
Get1 AccountSID Account Source # 
Monad m => MonadReader (Credentials, AccountSID) (TwilioT m) # 
type Rep AccountSID Source # 
type Rep AccountSID = D1 * (MetaData "AccountSID" "Twilio.Types.SIDs" "twilio-0.2.0.1-Cwy6vZAHYb886DlZ9eauoR" True) (C1 * (MetaCons "AccountSID" PrefixI True) (S1 * (MetaSel (Just Symbol "getAccountSID") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (SID A C))))

newtype AddressSID Source #

Constructors

AddressSID 

Fields

Instances

Bounded AddressSID Source # 
Eq AddressSID Source # 
Data AddressSID Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> AddressSID -> c AddressSID #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c AddressSID #

toConstr :: AddressSID -> Constr #

dataTypeOf :: AddressSID -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c AddressSID) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c AddressSID) #

gmapT :: (forall b. Data b => b -> b) -> AddressSID -> AddressSID #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> AddressSID -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> AddressSID -> r #

gmapQ :: (forall d. Data d => d -> u) -> AddressSID -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> AddressSID -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> AddressSID -> m AddressSID #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> AddressSID -> m AddressSID #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> AddressSID -> m AddressSID #

Ord AddressSID Source # 
Read AddressSID Source # 
Show AddressSID Source # 
Ix AddressSID Source # 
IsString AddressSID Source # 
Generic AddressSID Source # 

Associated Types

type Rep AddressSID :: * -> * #

Hashable AddressSID Source # 
ToJSON AddressSID Source # 
FromJSON AddressSID Source # 
NFData AddressSID Source # 

Methods

rnf :: AddressSID -> () #

IsSID AddressSID Source # 
Get1 AddressSID Address Source # 
type Rep AddressSID Source # 
type Rep AddressSID = D1 * (MetaData "AddressSID" "Twilio.Types.SIDs" "twilio-0.2.0.1-Cwy6vZAHYb886DlZ9eauoR" True) (C1 * (MetaCons "AddressSID" PrefixI True) (S1 * (MetaSel (Just Symbol "getAddressSID") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (SID A D))))

newtype APIKeySID Source #

Constructors

APIKeySID 

Fields

Instances

Bounded APIKeySID Source # 
Eq APIKeySID Source # 
Data APIKeySID Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> APIKeySID -> c APIKeySID #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c APIKeySID #

toConstr :: APIKeySID -> Constr #

dataTypeOf :: APIKeySID -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c APIKeySID) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c APIKeySID) #

gmapT :: (forall b. Data b => b -> b) -> APIKeySID -> APIKeySID #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> APIKeySID -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> APIKeySID -> r #

gmapQ :: (forall d. Data d => d -> u) -> APIKeySID -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> APIKeySID -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> APIKeySID -> m APIKeySID #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> APIKeySID -> m APIKeySID #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> APIKeySID -> m APIKeySID #

Ord APIKeySID Source # 
Read APIKeySID Source # 
Show APIKeySID Source # 
Ix APIKeySID Source # 
IsString APIKeySID Source # 
Generic APIKeySID Source # 

Associated Types

type Rep APIKeySID :: * -> * #

Hashable APIKeySID Source # 
ToJSON APIKeySID Source # 
FromJSON APIKeySID Source # 
NFData APIKeySID Source # 

Methods

rnf :: APIKeySID -> () #

IsSID APIKeySID Source # 
Get1 APIKeySID APIKey Source # 
type Rep APIKeySID Source # 
type Rep APIKeySID = D1 * (MetaData "APIKeySID" "Twilio.Types.SIDs" "twilio-0.2.0.1-Cwy6vZAHYb886DlZ9eauoR" True) (C1 * (MetaCons "APIKeySID" PrefixI True) (S1 * (MetaSel (Just Symbol "getAPIKeySID") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (SID S K))))

newtype ApplicationSID Source #

Constructors

ApplicationSID 

Fields

Instances

Bounded ApplicationSID Source # 
Eq ApplicationSID Source # 
Data ApplicationSID Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ApplicationSID -> c ApplicationSID #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ApplicationSID #

toConstr :: ApplicationSID -> Constr #

dataTypeOf :: ApplicationSID -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c ApplicationSID) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ApplicationSID) #

gmapT :: (forall b. Data b => b -> b) -> ApplicationSID -> ApplicationSID #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ApplicationSID -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ApplicationSID -> r #

gmapQ :: (forall d. Data d => d -> u) -> ApplicationSID -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ApplicationSID -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ApplicationSID -> m ApplicationSID #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ApplicationSID -> m ApplicationSID #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ApplicationSID -> m ApplicationSID #

Ord ApplicationSID Source # 
Read ApplicationSID Source # 
Show ApplicationSID Source # 
Ix ApplicationSID Source # 
IsString ApplicationSID Source # 
Generic ApplicationSID Source # 

Associated Types

type Rep ApplicationSID :: * -> * #

Hashable ApplicationSID Source # 
ToJSON ApplicationSID Source # 
FromJSON ApplicationSID Source # 
NFData ApplicationSID Source # 

Methods

rnf :: ApplicationSID -> () #

IsSID ApplicationSID Source # 
Get1 ApplicationSID Application Source # 
type Rep ApplicationSID Source # 
type Rep ApplicationSID = D1 * (MetaData "ApplicationSID" "Twilio.Types.SIDs" "twilio-0.2.0.1-Cwy6vZAHYb886DlZ9eauoR" True) (C1 * (MetaCons "ApplicationSID" PrefixI True) (S1 * (MetaSel (Just Symbol "getApplicationSID") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (SID A P))))

newtype CallSID Source #

Constructors

CallSID 

Fields

Instances

Bounded CallSID Source # 
Eq CallSID Source # 

Methods

(==) :: CallSID -> CallSID -> Bool #

(/=) :: CallSID -> CallSID -> Bool #

Data CallSID Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> CallSID -> c CallSID #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c CallSID #

toConstr :: CallSID -> Constr #

dataTypeOf :: CallSID -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c CallSID) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c CallSID) #

gmapT :: (forall b. Data b => b -> b) -> CallSID -> CallSID #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> CallSID -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> CallSID -> r #

gmapQ :: (forall d. Data d => d -> u) -> CallSID -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> CallSID -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> CallSID -> m CallSID #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> CallSID -> m CallSID #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> CallSID -> m CallSID #

Ord CallSID Source # 
Read CallSID Source # 
Show CallSID Source # 
Ix CallSID Source # 
IsString CallSID Source # 

Methods

fromString :: String -> CallSID #

Generic CallSID Source # 

Associated Types

type Rep CallSID :: * -> * #

Methods

from :: CallSID -> Rep CallSID x #

to :: Rep CallSID x -> CallSID #

Hashable CallSID Source # 

Methods

hashWithSalt :: Int -> CallSID -> Int #

hash :: CallSID -> Int #

ToJSON CallSID Source # 
FromJSON CallSID Source # 
NFData CallSID Source # 

Methods

rnf :: CallSID -> () #

IsSID CallSID Source # 
Get1 CallSID Feedback Source # 
Get1 CallSID Call Source # 

Methods

get1 :: MonadThrow m => CallSID -> TwilioT m Call Source #

Get2 ConferenceSID CallSID Participant Source # 
Get2 QueueSID CallSID Member Source # 
type Rep CallSID Source # 
type Rep CallSID = D1 * (MetaData "CallSID" "Twilio.Types.SIDs" "twilio-0.2.0.1-Cwy6vZAHYb886DlZ9eauoR" True) (C1 * (MetaCons "CallSID" PrefixI True) (S1 * (MetaSel (Just Symbol "getCallSID") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (SID C A))))

newtype ConferenceSID Source #

Constructors

ConferenceSID 

Fields

Instances

Bounded ConferenceSID Source # 
Eq ConferenceSID Source # 
Data ConferenceSID Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ConferenceSID -> c ConferenceSID #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ConferenceSID #

toConstr :: ConferenceSID -> Constr #

dataTypeOf :: ConferenceSID -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c ConferenceSID) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ConferenceSID) #

gmapT :: (forall b. Data b => b -> b) -> ConferenceSID -> ConferenceSID #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ConferenceSID -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ConferenceSID -> r #

gmapQ :: (forall d. Data d => d -> u) -> ConferenceSID -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ConferenceSID -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ConferenceSID -> m ConferenceSID #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ConferenceSID -> m ConferenceSID #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ConferenceSID -> m ConferenceSID #

Ord ConferenceSID Source # 
Read ConferenceSID Source # 
Show ConferenceSID Source # 
Ix ConferenceSID Source # 
IsString ConferenceSID Source # 
Generic ConferenceSID Source # 

Associated Types

type Rep ConferenceSID :: * -> * #

Hashable ConferenceSID Source # 
ToJSON ConferenceSID Source # 
FromJSON ConferenceSID Source # 
NFData ConferenceSID Source # 

Methods

rnf :: ConferenceSID -> () #

IsSID ConferenceSID Source # 
Get1 ConferenceSID Participants Source # 
Get1 ConferenceSID Conference Source # 
Get2 ConferenceSID CallSID Participant Source # 
type Rep ConferenceSID Source # 
type Rep ConferenceSID = D1 * (MetaData "ConferenceSID" "Twilio.Types.SIDs" "twilio-0.2.0.1-Cwy6vZAHYb886DlZ9eauoR" True) (C1 * (MetaCons "ConferenceSID" PrefixI True) (S1 * (MetaSel (Just Symbol "getConferenceSID") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (SID C O))))

newtype ConnectAppSID Source #

Constructors

ConnectAppSID 

Fields

Instances

Bounded ConnectAppSID Source # 
Eq ConnectAppSID Source # 
Data ConnectAppSID Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ConnectAppSID -> c ConnectAppSID #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ConnectAppSID #

toConstr :: ConnectAppSID -> Constr #

dataTypeOf :: ConnectAppSID -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c ConnectAppSID) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ConnectAppSID) #

gmapT :: (forall b. Data b => b -> b) -> ConnectAppSID -> ConnectAppSID #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ConnectAppSID -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ConnectAppSID -> r #

gmapQ :: (forall d. Data d => d -> u) -> ConnectAppSID -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ConnectAppSID -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ConnectAppSID -> m ConnectAppSID #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ConnectAppSID -> m ConnectAppSID #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ConnectAppSID -> m ConnectAppSID #

Ord ConnectAppSID Source # 
Read ConnectAppSID Source # 
Show ConnectAppSID Source # 
Ix ConnectAppSID Source # 
IsString ConnectAppSID Source # 
Generic ConnectAppSID Source # 

Associated Types

type Rep ConnectAppSID :: * -> * #

Hashable ConnectAppSID Source # 
ToJSON ConnectAppSID Source # 
FromJSON ConnectAppSID Source # 
NFData ConnectAppSID Source # 

Methods

rnf :: ConnectAppSID -> () #

IsSID ConnectAppSID Source # 
Get1 ConnectAppSID ConnectApp Source # 
Get1 ConnectAppSID AuthorizedConnectApp Source # 
type Rep ConnectAppSID Source # 
type Rep ConnectAppSID = D1 * (MetaData "ConnectAppSID" "Twilio.Types.SIDs" "twilio-0.2.0.1-Cwy6vZAHYb886DlZ9eauoR" True) (C1 * (MetaCons "ConnectAppSID" PrefixI True) (S1 * (MetaSel (Just Symbol "getConnectAppSID") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (SID C N))))

newtype CredentialSID Source #

Constructors

CredentialSID 

Fields

Instances

Bounded CredentialSID Source # 
Eq CredentialSID Source # 
Data CredentialSID Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> CredentialSID -> c CredentialSID #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c CredentialSID #

toConstr :: CredentialSID -> Constr #

dataTypeOf :: CredentialSID -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c CredentialSID) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c CredentialSID) #

gmapT :: (forall b. Data b => b -> b) -> CredentialSID -> CredentialSID #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> CredentialSID -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> CredentialSID -> r #

gmapQ :: (forall d. Data d => d -> u) -> CredentialSID -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> CredentialSID -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> CredentialSID -> m CredentialSID #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> CredentialSID -> m CredentialSID #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> CredentialSID -> m CredentialSID #

Ord CredentialSID Source # 
Read CredentialSID Source # 
Show CredentialSID Source # 
Ix CredentialSID Source # 
IsString CredentialSID Source # 
Generic CredentialSID Source # 

Associated Types

type Rep CredentialSID :: * -> * #

Hashable CredentialSID Source # 
ToJSON CredentialSID Source # 
FromJSON CredentialSID Source # 
NFData CredentialSID Source # 

Methods

rnf :: CredentialSID -> () #

IsSID CredentialSID Source # 
type Rep CredentialSID Source # 
type Rep CredentialSID = D1 * (MetaData "CredentialSID" "Twilio.Types.SIDs" "twilio-0.2.0.1-Cwy6vZAHYb886DlZ9eauoR" True) (C1 * (MetaCons "CredentialSID" PrefixI True) (S1 * (MetaSel (Just Symbol "getCredentialSID") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (SID S C))))

newtype CredentialListSID Source #

Constructors

CredentialListSID 

Instances

Bounded CredentialListSID Source # 
Eq CredentialListSID Source # 
Data CredentialListSID Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> CredentialListSID -> c CredentialListSID #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c CredentialListSID #

toConstr :: CredentialListSID -> Constr #

dataTypeOf :: CredentialListSID -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c CredentialListSID) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c CredentialListSID) #

gmapT :: (forall b. Data b => b -> b) -> CredentialListSID -> CredentialListSID #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> CredentialListSID -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> CredentialListSID -> r #

gmapQ :: (forall d. Data d => d -> u) -> CredentialListSID -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> CredentialListSID -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> CredentialListSID -> m CredentialListSID #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> CredentialListSID -> m CredentialListSID #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> CredentialListSID -> m CredentialListSID #

Ord CredentialListSID Source # 
Read CredentialListSID Source # 
Show CredentialListSID Source # 
Ix CredentialListSID Source # 
IsString CredentialListSID Source # 
Generic CredentialListSID Source # 
Hashable CredentialListSID Source # 
ToJSON CredentialListSID Source # 
FromJSON CredentialListSID Source # 
NFData CredentialListSID Source # 

Methods

rnf :: CredentialListSID -> () #

IsSID CredentialListSID Source # 
type Rep CredentialListSID Source # 
type Rep CredentialListSID = D1 * (MetaData "CredentialListSID" "Twilio.Types.SIDs" "twilio-0.2.0.1-Cwy6vZAHYb886DlZ9eauoR" True) (C1 * (MetaCons "CredentialListSID" PrefixI True) (S1 * (MetaSel (Just Symbol "getCredentialListSID") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (SID C L))))

newtype DomainSID Source #

Constructors

DomainSID 

Fields

Instances

Bounded DomainSID Source # 
Eq DomainSID Source # 
Data DomainSID Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> DomainSID -> c DomainSID #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c DomainSID #

toConstr :: DomainSID -> Constr #

dataTypeOf :: DomainSID -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c DomainSID) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c DomainSID) #

gmapT :: (forall b. Data b => b -> b) -> DomainSID -> DomainSID #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> DomainSID -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> DomainSID -> r #

gmapQ :: (forall d. Data d => d -> u) -> DomainSID -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> DomainSID -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> DomainSID -> m DomainSID #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> DomainSID -> m DomainSID #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> DomainSID -> m DomainSID #

Ord DomainSID Source # 
Read DomainSID Source # 
Show DomainSID Source # 
Ix DomainSID Source # 
IsString DomainSID Source # 
Generic DomainSID Source # 

Associated Types

type Rep DomainSID :: * -> * #

Hashable DomainSID Source # 
ToJSON DomainSID Source # 
FromJSON DomainSID Source # 
NFData DomainSID Source # 

Methods

rnf :: DomainSID -> () #

IsSID DomainSID Source # 
type Rep DomainSID Source # 
type Rep DomainSID = D1 * (MetaData "DomainSID" "Twilio.Types.SIDs" "twilio-0.2.0.1-Cwy6vZAHYb886DlZ9eauoR" True) (C1 * (MetaCons "DomainSID" PrefixI True) (S1 * (MetaSel (Just Symbol "getDomainSID") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (SID S D))))

newtype FeedbackSummarySID Source #

Constructors

FeedbackSummarySID 

Instances

Bounded FeedbackSummarySID Source # 
Eq FeedbackSummarySID Source # 
Data FeedbackSummarySID Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> FeedbackSummarySID -> c FeedbackSummarySID #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c FeedbackSummarySID #

toConstr :: FeedbackSummarySID -> Constr #

dataTypeOf :: FeedbackSummarySID -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c FeedbackSummarySID) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c FeedbackSummarySID) #

gmapT :: (forall b. Data b => b -> b) -> FeedbackSummarySID -> FeedbackSummarySID #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> FeedbackSummarySID -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> FeedbackSummarySID -> r #

gmapQ :: (forall d. Data d => d -> u) -> FeedbackSummarySID -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> FeedbackSummarySID -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> FeedbackSummarySID -> m FeedbackSummarySID #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> FeedbackSummarySID -> m FeedbackSummarySID #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> FeedbackSummarySID -> m FeedbackSummarySID #

Ord FeedbackSummarySID Source # 
Read FeedbackSummarySID Source # 
Show FeedbackSummarySID Source # 
Ix FeedbackSummarySID Source # 
IsString FeedbackSummarySID Source # 
Generic FeedbackSummarySID Source # 
Hashable FeedbackSummarySID Source # 
ToJSON FeedbackSummarySID Source # 
FromJSON FeedbackSummarySID Source # 
NFData FeedbackSummarySID Source # 

Methods

rnf :: FeedbackSummarySID -> () #

IsSID FeedbackSummarySID Source # 
type Rep FeedbackSummarySID Source # 
type Rep FeedbackSummarySID = D1 * (MetaData "FeedbackSummarySID" "Twilio.Types.SIDs" "twilio-0.2.0.1-Cwy6vZAHYb886DlZ9eauoR" True) (C1 * (MetaCons "FeedbackSummarySID" PrefixI True) (S1 * (MetaSel (Just Symbol "getFeedbackSummarySID") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (SID F S))))

newtype IPAccessControlListSID Source #

Instances

Bounded IPAccessControlListSID Source # 
Eq IPAccessControlListSID Source # 
Data IPAccessControlListSID Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> IPAccessControlListSID -> c IPAccessControlListSID #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c IPAccessControlListSID #

toConstr :: IPAccessControlListSID -> Constr #

dataTypeOf :: IPAccessControlListSID -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c IPAccessControlListSID) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c IPAccessControlListSID) #

gmapT :: (forall b. Data b => b -> b) -> IPAccessControlListSID -> IPAccessControlListSID #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> IPAccessControlListSID -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> IPAccessControlListSID -> r #

gmapQ :: (forall d. Data d => d -> u) -> IPAccessControlListSID -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> IPAccessControlListSID -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> IPAccessControlListSID -> m IPAccessControlListSID #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> IPAccessControlListSID -> m IPAccessControlListSID #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> IPAccessControlListSID -> m IPAccessControlListSID #

Ord IPAccessControlListSID Source # 
Read IPAccessControlListSID Source # 
Show IPAccessControlListSID Source # 
Ix IPAccessControlListSID Source # 
IsString IPAccessControlListSID Source # 
Generic IPAccessControlListSID Source # 
Hashable IPAccessControlListSID Source # 
ToJSON IPAccessControlListSID Source # 
FromJSON IPAccessControlListSID Source # 
NFData IPAccessControlListSID Source # 

Methods

rnf :: IPAccessControlListSID -> () #

IsSID IPAccessControlListSID Source # 
type Rep IPAccessControlListSID Source # 
type Rep IPAccessControlListSID = D1 * (MetaData "IPAccessControlListSID" "Twilio.Types.SIDs" "twilio-0.2.0.1-Cwy6vZAHYb886DlZ9eauoR" True) (C1 * (MetaCons "IPAccessControlListSID" PrefixI True) (S1 * (MetaSel (Just Symbol "getIPAccessControlListSID") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (SID A L))))

newtype IPAddressSID Source #

Constructors

IPAddressSID 

Fields

Instances

Bounded IPAddressSID Source # 
Eq IPAddressSID Source # 
Data IPAddressSID Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> IPAddressSID -> c IPAddressSID #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c IPAddressSID #

toConstr :: IPAddressSID -> Constr #

dataTypeOf :: IPAddressSID -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c IPAddressSID) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c IPAddressSID) #

gmapT :: (forall b. Data b => b -> b) -> IPAddressSID -> IPAddressSID #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> IPAddressSID -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> IPAddressSID -> r #

gmapQ :: (forall d. Data d => d -> u) -> IPAddressSID -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> IPAddressSID -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> IPAddressSID -> m IPAddressSID #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> IPAddressSID -> m IPAddressSID #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> IPAddressSID -> m IPAddressSID #

Ord IPAddressSID Source # 
Read IPAddressSID Source # 
Show IPAddressSID Source # 
Ix IPAddressSID Source # 
IsString IPAddressSID Source # 
Generic IPAddressSID Source # 

Associated Types

type Rep IPAddressSID :: * -> * #

Hashable IPAddressSID Source # 
ToJSON IPAddressSID Source # 
FromJSON IPAddressSID Source # 
NFData IPAddressSID Source # 

Methods

rnf :: IPAddressSID -> () #

IsSID IPAddressSID Source # 
type Rep IPAddressSID Source # 
type Rep IPAddressSID = D1 * (MetaData "IPAddressSID" "Twilio.Types.SIDs" "twilio-0.2.0.1-Cwy6vZAHYb886DlZ9eauoR" True) (C1 * (MetaCons "IPAddressSID" PrefixI True) (S1 * (MetaSel (Just Symbol "getIPAddressSID") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (SID I P))))

newtype MediaSID Source #

Constructors

MediaSID 

Fields

Instances

Bounded MediaSID Source # 
Eq MediaSID Source # 
Data MediaSID Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> MediaSID -> c MediaSID #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c MediaSID #

toConstr :: MediaSID -> Constr #

dataTypeOf :: MediaSID -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c MediaSID) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c MediaSID) #

gmapT :: (forall b. Data b => b -> b) -> MediaSID -> MediaSID #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> MediaSID -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> MediaSID -> r #

gmapQ :: (forall d. Data d => d -> u) -> MediaSID -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> MediaSID -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> MediaSID -> m MediaSID #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> MediaSID -> m MediaSID #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> MediaSID -> m MediaSID #

Ord MediaSID Source # 
Read MediaSID Source # 
Show MediaSID Source # 
Ix MediaSID Source # 
IsString MediaSID Source # 
Generic MediaSID Source # 

Associated Types

type Rep MediaSID :: * -> * #

Methods

from :: MediaSID -> Rep MediaSID x #

to :: Rep MediaSID x -> MediaSID #

Hashable MediaSID Source # 

Methods

hashWithSalt :: Int -> MediaSID -> Int #

hash :: MediaSID -> Int #

ToJSON MediaSID Source # 
FromJSON MediaSID Source # 
NFData MediaSID Source # 

Methods

rnf :: MediaSID -> () #

IsSID MediaSID Source # 
Get2 MessageSID MediaSID Media Source # 
type Rep MediaSID Source # 
type Rep MediaSID = D1 * (MetaData "MediaSID" "Twilio.Types.SIDs" "twilio-0.2.0.1-Cwy6vZAHYb886DlZ9eauoR" True) (C1 * (MetaCons "MediaSID" PrefixI True) (S1 * (MetaSel (Just Symbol "getMediaSID") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (SID M E))))

newtype MessageSID Source #

Instances

Eq MessageSID Source # 
Data MessageSID Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> MessageSID -> c MessageSID #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c MessageSID #

toConstr :: MessageSID -> Constr #

dataTypeOf :: MessageSID -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c MessageSID) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c MessageSID) #

gmapT :: (forall b. Data b => b -> b) -> MessageSID -> MessageSID #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> MessageSID -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> MessageSID -> r #

gmapQ :: (forall d. Data d => d -> u) -> MessageSID -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> MessageSID -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> MessageSID -> m MessageSID #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> MessageSID -> m MessageSID #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> MessageSID -> m MessageSID #

Ord MessageSID Source # 
Read MessageSID Source # 
Show MessageSID Source # 
Generic MessageSID Source # 

Associated Types

type Rep MessageSID :: * -> * #

Hashable MessageSID Source # 
ToJSON MessageSID Source # 
FromJSON MessageSID Source # 
NFData MessageSID Source # 

Methods

rnf :: MessageSID -> () #

IsSID MessageSID Source # 
Get1 MessageSID MediaList Source # 
Get1 MessageSID Message Source # 
Get2 MessageSID MediaSID Media Source # 
type Rep MessageSID Source # 
type Rep MessageSID = D1 * (MetaData "MessageSID" "Twilio.Types.SIDs" "twilio-0.2.0.1-Cwy6vZAHYb886DlZ9eauoR" True) (C1 * (MetaCons "MessageSID" PrefixI True) (S1 * (MetaSel (Just Symbol "getMessageSID") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Either SMSMessageSID MMSMessageSID))))

newtype MMSMessageSID Source #

Constructors

MMSMessageSID 

Fields

Instances

Bounded MMSMessageSID Source # 
Eq MMSMessageSID Source # 
Data MMSMessageSID Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> MMSMessageSID -> c MMSMessageSID #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c MMSMessageSID #

toConstr :: MMSMessageSID -> Constr #

dataTypeOf :: MMSMessageSID -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c MMSMessageSID) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c MMSMessageSID) #

gmapT :: (forall b. Data b => b -> b) -> MMSMessageSID -> MMSMessageSID #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> MMSMessageSID -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> MMSMessageSID -> r #

gmapQ :: (forall d. Data d => d -> u) -> MMSMessageSID -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> MMSMessageSID -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> MMSMessageSID -> m MMSMessageSID #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> MMSMessageSID -> m MMSMessageSID #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> MMSMessageSID -> m MMSMessageSID #

Ord MMSMessageSID Source # 
Read MMSMessageSID Source # 
Show MMSMessageSID Source # 
Ix MMSMessageSID Source # 
IsString MMSMessageSID Source # 
Generic MMSMessageSID Source # 

Associated Types

type Rep MMSMessageSID :: * -> * #

Hashable MMSMessageSID Source # 
ToJSON MMSMessageSID Source # 
FromJSON MMSMessageSID Source # 
NFData MMSMessageSID Source # 

Methods

rnf :: MMSMessageSID -> () #

IsSID MMSMessageSID Source # 
type Rep MMSMessageSID Source # 
type Rep MMSMessageSID = D1 * (MetaData "MMSMessageSID" "Twilio.Types.SIDs" "twilio-0.2.0.1-Cwy6vZAHYb886DlZ9eauoR" True) (C1 * (MetaCons "MMSMessageSID" PrefixI True) (S1 * (MetaSel (Just Symbol "getMMSMessageSID") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (SID M M))))

newtype PhoneNumberSID Source #

Constructors

PhoneNumberSID 

Fields

Instances

Bounded PhoneNumberSID Source # 
Eq PhoneNumberSID Source # 
Data PhoneNumberSID Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> PhoneNumberSID -> c PhoneNumberSID #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c PhoneNumberSID #

toConstr :: PhoneNumberSID -> Constr #

dataTypeOf :: PhoneNumberSID -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c PhoneNumberSID) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c PhoneNumberSID) #

gmapT :: (forall b. Data b => b -> b) -> PhoneNumberSID -> PhoneNumberSID #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> PhoneNumberSID -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> PhoneNumberSID -> r #

gmapQ :: (forall d. Data d => d -> u) -> PhoneNumberSID -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> PhoneNumberSID -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> PhoneNumberSID -> m PhoneNumberSID #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> PhoneNumberSID -> m PhoneNumberSID #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> PhoneNumberSID -> m PhoneNumberSID #

Ord PhoneNumberSID Source # 
Read PhoneNumberSID Source # 
Show PhoneNumberSID Source # 
Ix PhoneNumberSID Source # 
IsString PhoneNumberSID Source # 
Generic PhoneNumberSID Source # 

Associated Types

type Rep PhoneNumberSID :: * -> * #

Hashable PhoneNumberSID Source # 
ToJSON PhoneNumberSID Source # 
FromJSON PhoneNumberSID Source # 
NFData PhoneNumberSID Source # 

Methods

rnf :: PhoneNumberSID -> () #

IsSID PhoneNumberSID Source # 
Get1 PhoneNumberSID OutgoingCallerID Source # 
Get1 PhoneNumberSID IncomingPhoneNumber Source # 
type Rep PhoneNumberSID Source # 
type Rep PhoneNumberSID = D1 * (MetaData "PhoneNumberSID" "Twilio.Types.SIDs" "twilio-0.2.0.1-Cwy6vZAHYb886DlZ9eauoR" True) (C1 * (MetaCons "PhoneNumberSID" PrefixI True) (S1 * (MetaSel (Just Symbol "getPhoneNumberSID") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (SID P N))))

newtype QueueSID Source #

Constructors

QueueSID 

Fields

Instances

Bounded QueueSID Source # 
Eq QueueSID Source # 
Data QueueSID Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> QueueSID -> c QueueSID #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c QueueSID #

toConstr :: QueueSID -> Constr #

dataTypeOf :: QueueSID -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c QueueSID) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c QueueSID) #

gmapT :: (forall b. Data b => b -> b) -> QueueSID -> QueueSID #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> QueueSID -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> QueueSID -> r #

gmapQ :: (forall d. Data d => d -> u) -> QueueSID -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> QueueSID -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> QueueSID -> m QueueSID #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> QueueSID -> m QueueSID #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> QueueSID -> m QueueSID #

Ord QueueSID Source # 
Read QueueSID Source # 
Show QueueSID Source # 
Ix QueueSID Source # 
IsString QueueSID Source # 
Generic QueueSID Source # 

Associated Types

type Rep QueueSID :: * -> * #

Methods

from :: QueueSID -> Rep QueueSID x #

to :: Rep QueueSID x -> QueueSID #

Hashable QueueSID Source # 

Methods

hashWithSalt :: Int -> QueueSID -> Int #

hash :: QueueSID -> Int #

ToJSON QueueSID Source # 
FromJSON QueueSID Source # 
NFData QueueSID Source # 

Methods

rnf :: QueueSID -> () #

IsSID QueueSID Source # 
Get1 QueueSID Member Source # 
Get1 QueueSID Members Source # 
Get1 QueueSID Queue Source # 
Get2 QueueSID CallSID Member Source # 
type Rep QueueSID Source # 
type Rep QueueSID = D1 * (MetaData "QueueSID" "Twilio.Types.SIDs" "twilio-0.2.0.1-Cwy6vZAHYb886DlZ9eauoR" True) (C1 * (MetaCons "QueueSID" PrefixI True) (S1 * (MetaSel (Just Symbol "getQueueSID") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (SID Q U))))

newtype RecordingSID Source #

Constructors

RecordingSID 

Fields

Instances

Bounded RecordingSID Source # 
Eq RecordingSID Source # 
Data RecordingSID Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> RecordingSID -> c RecordingSID #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c RecordingSID #

toConstr :: RecordingSID -> Constr #

dataTypeOf :: RecordingSID -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c RecordingSID) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c RecordingSID) #

gmapT :: (forall b. Data b => b -> b) -> RecordingSID -> RecordingSID #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> RecordingSID -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> RecordingSID -> r #

gmapQ :: (forall d. Data d => d -> u) -> RecordingSID -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> RecordingSID -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> RecordingSID -> m RecordingSID #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> RecordingSID -> m RecordingSID #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> RecordingSID -> m RecordingSID #

Ord RecordingSID Source # 
Read RecordingSID Source # 
Show RecordingSID Source # 
Ix RecordingSID Source # 
IsString RecordingSID Source # 
Generic RecordingSID Source # 

Associated Types

type Rep RecordingSID :: * -> * #

Hashable RecordingSID Source # 
ToJSON RecordingSID Source # 
FromJSON RecordingSID Source # 
NFData RecordingSID Source # 

Methods

rnf :: RecordingSID -> () #

IsSID RecordingSID Source # 
Get1 RecordingSID Recording Source # 
type Rep RecordingSID Source # 
type Rep RecordingSID = D1 * (MetaData "RecordingSID" "Twilio.Types.SIDs" "twilio-0.2.0.1-Cwy6vZAHYb886DlZ9eauoR" True) (C1 * (MetaCons "RecordingSID" PrefixI True) (S1 * (MetaSel (Just Symbol "getRecordingSID") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (SID R E))))

newtype ShortCodeSID Source #

Constructors

ShortCodeSID 

Fields

Instances

Bounded ShortCodeSID Source # 
Eq ShortCodeSID Source # 
Data ShortCodeSID Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ShortCodeSID -> c ShortCodeSID #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ShortCodeSID #

toConstr :: ShortCodeSID -> Constr #

dataTypeOf :: ShortCodeSID -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c ShortCodeSID) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ShortCodeSID) #

gmapT :: (forall b. Data b => b -> b) -> ShortCodeSID -> ShortCodeSID #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ShortCodeSID -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ShortCodeSID -> r #

gmapQ :: (forall d. Data d => d -> u) -> ShortCodeSID -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ShortCodeSID -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ShortCodeSID -> m ShortCodeSID #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ShortCodeSID -> m ShortCodeSID #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ShortCodeSID -> m ShortCodeSID #

Ord ShortCodeSID Source # 
Read ShortCodeSID Source # 
Show ShortCodeSID Source # 
Ix ShortCodeSID Source # 
IsString ShortCodeSID Source # 
Generic ShortCodeSID Source # 

Associated Types

type Rep ShortCodeSID :: * -> * #

Hashable ShortCodeSID Source # 
ToJSON ShortCodeSID Source # 
FromJSON ShortCodeSID Source # 
NFData ShortCodeSID Source # 

Methods

rnf :: ShortCodeSID -> () #

IsSID ShortCodeSID Source # 
Get1 ShortCodeSID ShortCode Source # 
type Rep ShortCodeSID Source # 
type Rep ShortCodeSID = D1 * (MetaData "ShortCodeSID" "Twilio.Types.SIDs" "twilio-0.2.0.1-Cwy6vZAHYb886DlZ9eauoR" True) (C1 * (MetaCons "ShortCodeSID" PrefixI True) (S1 * (MetaSel (Just Symbol "getShortCodeSID") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (SID S C))))

newtype SMSMessageSID Source #

Constructors

SMSMessageSID 

Fields

Instances

Bounded SMSMessageSID Source # 
Eq SMSMessageSID Source # 
Data SMSMessageSID Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> SMSMessageSID -> c SMSMessageSID #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c SMSMessageSID #

toConstr :: SMSMessageSID -> Constr #

dataTypeOf :: SMSMessageSID -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c SMSMessageSID) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c SMSMessageSID) #

gmapT :: (forall b. Data b => b -> b) -> SMSMessageSID -> SMSMessageSID #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SMSMessageSID -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SMSMessageSID -> r #

gmapQ :: (forall d. Data d => d -> u) -> SMSMessageSID -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> SMSMessageSID -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> SMSMessageSID -> m SMSMessageSID #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> SMSMessageSID -> m SMSMessageSID #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> SMSMessageSID -> m SMSMessageSID #

Ord SMSMessageSID Source # 
Read SMSMessageSID Source # 
Show SMSMessageSID Source # 
Ix SMSMessageSID Source # 
IsString SMSMessageSID Source # 
Generic SMSMessageSID Source # 

Associated Types

type Rep SMSMessageSID :: * -> * #

Hashable SMSMessageSID Source # 
ToJSON SMSMessageSID Source # 
FromJSON SMSMessageSID Source # 
NFData SMSMessageSID Source # 

Methods

rnf :: SMSMessageSID -> () #

IsSID SMSMessageSID Source # 
type Rep SMSMessageSID Source # 
type Rep SMSMessageSID = D1 * (MetaData "SMSMessageSID" "Twilio.Types.SIDs" "twilio-0.2.0.1-Cwy6vZAHYb886DlZ9eauoR" True) (C1 * (MetaCons "SMSMessageSID" PrefixI True) (S1 * (MetaSel (Just Symbol "getSMSMessageSID") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (SID S M))))

newtype TranscriptionSID Source #

Constructors

TranscriptionSID 

Fields

Instances

Bounded TranscriptionSID Source # 
Eq TranscriptionSID Source # 
Data TranscriptionSID Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> TranscriptionSID -> c TranscriptionSID #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c TranscriptionSID #

toConstr :: TranscriptionSID -> Constr #

dataTypeOf :: TranscriptionSID -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c TranscriptionSID) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c TranscriptionSID) #

gmapT :: (forall b. Data b => b -> b) -> TranscriptionSID -> TranscriptionSID #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> TranscriptionSID -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> TranscriptionSID -> r #

gmapQ :: (forall d. Data d => d -> u) -> TranscriptionSID -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> TranscriptionSID -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> TranscriptionSID -> m TranscriptionSID #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> TranscriptionSID -> m TranscriptionSID #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> TranscriptionSID -> m TranscriptionSID #

Ord TranscriptionSID Source # 
Read TranscriptionSID Source # 
Show TranscriptionSID Source # 
Ix TranscriptionSID Source # 
IsString TranscriptionSID Source # 
Generic TranscriptionSID Source # 
Hashable TranscriptionSID Source # 
ToJSON TranscriptionSID Source # 
FromJSON TranscriptionSID Source # 
NFData TranscriptionSID Source # 

Methods

rnf :: TranscriptionSID -> () #

IsSID TranscriptionSID Source # 
Get1 TranscriptionSID Transcription Source # 
type Rep TranscriptionSID Source # 
type Rep TranscriptionSID = D1 * (MetaData "TranscriptionSID" "Twilio.Types.SIDs" "twilio-0.2.0.1-Cwy6vZAHYb886DlZ9eauoR" True) (C1 * (MetaCons "TranscriptionSID" PrefixI True) (S1 * (MetaSel (Just Symbol "getTranscriptionSID") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (SID T R))))

newtype UsageTriggerSID Source #

Constructors

UsageTriggerSID 

Fields

Instances

Bounded UsageTriggerSID Source # 
Eq UsageTriggerSID Source # 
Data UsageTriggerSID Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> UsageTriggerSID -> c UsageTriggerSID #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c UsageTriggerSID #

toConstr :: UsageTriggerSID -> Constr #

dataTypeOf :: UsageTriggerSID -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c UsageTriggerSID) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c UsageTriggerSID) #

gmapT :: (forall b. Data b => b -> b) -> UsageTriggerSID -> UsageTriggerSID #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> UsageTriggerSID -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> UsageTriggerSID -> r #

gmapQ :: (forall d. Data d => d -> u) -> UsageTriggerSID -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> UsageTriggerSID -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> UsageTriggerSID -> m UsageTriggerSID #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> UsageTriggerSID -> m UsageTriggerSID #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> UsageTriggerSID -> m UsageTriggerSID #

Ord UsageTriggerSID Source # 
Read UsageTriggerSID Source # 
Show UsageTriggerSID Source # 
Ix UsageTriggerSID Source # 
IsString UsageTriggerSID Source # 
Generic UsageTriggerSID Source # 
Hashable UsageTriggerSID Source # 
ToJSON UsageTriggerSID Source # 
FromJSON UsageTriggerSID Source # 
NFData UsageTriggerSID Source # 

Methods

rnf :: UsageTriggerSID -> () #

IsSID UsageTriggerSID Source # 
Get1 UsageTriggerSID UsageTrigger Source # 
type Rep UsageTriggerSID Source # 
type Rep UsageTriggerSID = D1 * (MetaData "UsageTriggerSID" "Twilio.Types.SIDs" "twilio-0.2.0.1-Cwy6vZAHYb886DlZ9eauoR" True) (C1 * (MetaCons "UsageTriggerSID" PrefixI True) (S1 * (MetaSel (Just Symbol "getUsageTriggerSID") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (SID U T))))

newtype MessagingServiceSID Source #

Instances

Bounded MessagingServiceSID Source # 
Eq MessagingServiceSID Source # 
Data MessagingServiceSID Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> MessagingServiceSID -> c MessagingServiceSID #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c MessagingServiceSID #

toConstr :: MessagingServiceSID -> Constr #

dataTypeOf :: MessagingServiceSID -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c MessagingServiceSID) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c MessagingServiceSID) #

gmapT :: (forall b. Data b => b -> b) -> MessagingServiceSID -> MessagingServiceSID #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> MessagingServiceSID -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> MessagingServiceSID -> r #

gmapQ :: (forall d. Data d => d -> u) -> MessagingServiceSID -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> MessagingServiceSID -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> MessagingServiceSID -> m MessagingServiceSID #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> MessagingServiceSID -> m MessagingServiceSID #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> MessagingServiceSID -> m MessagingServiceSID #

Ord MessagingServiceSID Source # 
Read MessagingServiceSID Source # 
Show MessagingServiceSID Source # 
Ix MessagingServiceSID Source # 
IsString MessagingServiceSID Source # 
Generic MessagingServiceSID Source # 
Hashable MessagingServiceSID Source # 
ToJSON MessagingServiceSID Source # 
FromJSON MessagingServiceSID Source # 
NFData MessagingServiceSID Source # 

Methods

rnf :: MessagingServiceSID -> () #

IsSID MessagingServiceSID Source # 
type Rep MessagingServiceSID Source # 
type Rep MessagingServiceSID = D1 * (MetaData "MessagingServiceSID" "Twilio.Types.SIDs" "twilio-0.2.0.1-Cwy6vZAHYb886DlZ9eauoR" True) (C1 * (MetaCons "MessagingServiceSID" PrefixI True) (S1 * (MetaSel (Just Symbol "getMessagingServiceSID") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (SID M G))))

Smart Constructors