twiml-0.2.1.0: TwiML library for Haskell

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

Text.XML.Twiml.Types

Contents

Description

 

Synopsis

Documentation

data Digit Source #

The ‘digits’ attribute lets you play DTMF tones during a call. See https://www.twilio.com/docs/api/twiml/play#attributes-digits.

Constructors

D0

0

D1

1

D2

2

D3

3

D4

4

D5

5

D6

6

D7

7

D8

8

D9

9

W

w

Instances

Bounded Digit Source # 
Enum Digit Source # 
Eq Digit Source # 

Methods

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

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

Data Digit Source # 

Methods

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

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

toConstr :: Digit -> Constr #

dataTypeOf :: Digit -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord Digit Source # 

Methods

compare :: Digit -> Digit -> Ordering #

(<) :: Digit -> Digit -> Bool #

(<=) :: Digit -> Digit -> Bool #

(>) :: Digit -> Digit -> Bool #

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

max :: Digit -> Digit -> Digit #

min :: Digit -> Digit -> Digit #

Read Digit Source # 
Show Digit Source # 

Methods

showsPrec :: Int -> Digit -> ShowS #

show :: Digit -> String #

showList :: [Digit] -> ShowS #

Generic Digit Source # 

Associated Types

type Rep Digit :: * -> * #

Methods

from :: Digit -> Rep Digit x #

to :: Rep Digit x -> Digit #

NFData Digit Source # 

Methods

rnf :: Digit -> () #

ToAttrValue Digit Source # 
ToAttrValue [Digit] Source # 
type Rep Digit Source # 
type Rep Digit = D1 * (MetaData "Digit" "Text.XML.Twiml.Types" "twiml-0.2.1.0-8vOgp92H6HZKjscJQqq5Ao" False) ((:+:) * ((:+:) * ((:+:) * (C1 * (MetaCons "D0" PrefixI False) (U1 *)) (C1 * (MetaCons "D1" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "D2" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "D3" PrefixI False) (U1 *)) (C1 * (MetaCons "D4" PrefixI False) (U1 *))))) ((:+:) * ((:+:) * (C1 * (MetaCons "D5" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "D6" PrefixI False) (U1 *)) (C1 * (MetaCons "D7" PrefixI False) (U1 *)))) ((:+:) * (C1 * (MetaCons "D8" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "D9" PrefixI False) (U1 *)) (C1 * (MetaCons "W" PrefixI False) (U1 *))))))

data Key Source #

Constructors

K0

0

K1

1

K2

2

K3

3

K4

4

K5

5

K6

6

K7

7

K8

8

K9

9

KStar

*

KPound

#

Instances

Bounded Key Source # 

Methods

minBound :: Key #

maxBound :: Key #

Enum Key Source # 

Methods

succ :: Key -> Key #

pred :: Key -> Key #

toEnum :: Int -> Key #

fromEnum :: Key -> Int #

enumFrom :: Key -> [Key] #

enumFromThen :: Key -> Key -> [Key] #

enumFromTo :: Key -> Key -> [Key] #

enumFromThenTo :: Key -> Key -> Key -> [Key] #

Eq Key Source # 

Methods

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

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

Data Key Source # 

Methods

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

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

toConstr :: Key -> Constr #

dataTypeOf :: Key -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord Key Source # 

Methods

compare :: Key -> Key -> Ordering #

(<) :: Key -> Key -> Bool #

(<=) :: Key -> Key -> Bool #

(>) :: Key -> Key -> Bool #

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

max :: Key -> Key -> Key #

min :: Key -> Key -> Key #

Read Key Source # 
Show Key Source # 

Methods

showsPrec :: Int -> Key -> ShowS #

show :: Key -> String #

showList :: [Key] -> ShowS #

Generic Key Source # 

Associated Types

type Rep Key :: * -> * #

Methods

from :: Key -> Rep Key x #

to :: Rep Key x -> Key #

NFData Key Source # 

Methods

rnf :: Key -> () #

ToAttrValue Key Source # 
HasFinishOnKey RecordAttributes (Maybe Key) Source # 
HasFinishOnKey GatherAttributes (Maybe Key) Source # 
type Rep Key Source # 
type Rep Key = D1 * (MetaData "Key" "Text.XML.Twiml.Types" "twiml-0.2.1.0-8vOgp92H6HZKjscJQqq5Ao" False) ((:+:) * ((:+:) * ((:+:) * (C1 * (MetaCons "K0" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "K1" PrefixI False) (U1 *)) (C1 * (MetaCons "K2" PrefixI False) (U1 *)))) ((:+:) * (C1 * (MetaCons "K3" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "K4" PrefixI False) (U1 *)) (C1 * (MetaCons "K5" PrefixI False) (U1 *))))) ((:+:) * ((:+:) * (C1 * (MetaCons "K6" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "K7" PrefixI False) (U1 *)) (C1 * (MetaCons "K8" PrefixI False) (U1 *)))) ((:+:) * (C1 * (MetaCons "K9" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "KStar" PrefixI False) (U1 *)) (C1 * (MetaCons "KPound" PrefixI False) (U1 *))))))

data Method Source #

Constructors

GET 
POST 

Instances

Bounded Method Source # 
Enum Method Source # 
Eq Method Source # 

Methods

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

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

Data Method Source # 

Methods

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

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

toConstr :: Method -> Constr #

dataTypeOf :: Method -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord Method Source # 
Read Method Source # 
Show Method Source # 
Generic Method Source # 

Associated Types

type Rep Method :: * -> * #

Methods

from :: Method -> Rep Method x #

to :: Rep Method x -> Method #

NFData Method Source # 

Methods

rnf :: Method -> () #

ToAttrValue Method Source # 
HasMethod ClientAttributes (Maybe Method) Source # 
HasMethod NumberAttributes (Maybe Method) Source # 
HasMethod QueueAttributes (Maybe Method) Source # 
HasMethod SipAttributes (Maybe Method) Source # 
HasMethod DialAttributes (Maybe Method) Source # 
HasMethod EnqueueAttributes (Maybe Method) Source # 
HasMethod MessageAttributes (Maybe Method) Source # 
HasMethod RecordAttributes (Maybe Method) Source # 
HasMethod RedirectAttributes (Maybe Method) Source # 
HasMethod GatherAttributes (Maybe Method) Source # 
HasMethod SmsAttributes (Maybe Method) Source # 
HasWaitMethod ConferenceAttributes (Maybe Method) Source # 
HasWaitMethod EnqueueAttributes (Maybe Method) Source # 
type Rep Method Source # 
type Rep Method = D1 * (MetaData "Method" "Text.XML.Twiml.Types" "twiml-0.2.1.0-8vOgp92H6HZKjscJQqq5Ao" False) ((:+:) * (C1 * (MetaCons "GET" PrefixI False) (U1 *)) (C1 * (MetaCons "POST" PrefixI False) (U1 *)))

data URL Source #

Instances

Eq URL Source # 

Methods

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

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

Data URL Source # 

Methods

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

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

toConstr :: URL -> Constr #

dataTypeOf :: URL -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord URL Source # 

Methods

compare :: URL -> URL -> Ordering #

(<) :: URL -> URL -> Bool #

(<=) :: URL -> URL -> Bool #

(>) :: URL -> URL -> Bool #

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

max :: URL -> URL -> URL #

min :: URL -> URL -> URL #

Read URL Source # 
Show URL Source # 

Methods

showsPrec :: Int -> URL -> ShowS #

show :: URL -> String #

showList :: [URL] -> ShowS #

Generic URL Source # 

Associated Types

type Rep URL :: * -> * #

Methods

from :: URL -> Rep URL x #

to :: Rep URL x -> URL #

NFData URL Source # 

Methods

rnf :: URL -> () #

ToAttrValue URL Source # 
ToSomeNode URL Source # 
HasAction DialAttributes (Maybe URL) Source # 
HasAction EnqueueAttributes (Maybe URL) Source # 
HasAction MessageAttributes (Maybe URL) Source # 
HasAction RecordAttributes (Maybe URL) Source # 
HasAction GatherAttributes (Maybe URL) Source # 
HasAction SmsAttributes (Maybe URL) Source # 
HasTranscribeCallback RecordAttributes (Maybe URL) Source # 
HasStatusCallback MessageAttributes (Maybe URL) Source # 
HasStatusCallback SmsAttributes (Maybe URL) Source # 
HasUrl ClientAttributes (Maybe URL) Source # 
HasUrl NumberAttributes (Maybe URL) Source # 
HasUrl QueueAttributes (Maybe URL) Source # 
HasUrl SipAttributes (Maybe URL) Source # 
HasWaitURL ConferenceAttributes (Maybe URL) Source # 
HasWaitURL EnqueueAttributes (Maybe URL) Source # 
type Rep URL Source # 
type Rep URL = D1 * (MetaData "URL" "Text.XML.Twiml.Types" "twiml-0.2.1.0-8vOgp92H6HZKjscJQqq5Ao" True) (C1 * (MetaCons "URL" PrefixI True) (S1 * (MetaSel (Just Symbol "getURL") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * String)))

data Voice Source #

Constructors

Man (Maybe Lang) 
Woman (Maybe Lang) 
Alice (Maybe LangAlice) 

Instances

Eq Voice Source # 

Methods

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

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

Data Voice Source # 

Methods

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

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

toConstr :: Voice -> Constr #

dataTypeOf :: Voice -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord Voice Source # 

Methods

compare :: Voice -> Voice -> Ordering #

(<) :: Voice -> Voice -> Bool #

(<=) :: Voice -> Voice -> Bool #

(>) :: Voice -> Voice -> Bool #

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

max :: Voice -> Voice -> Voice #

min :: Voice -> Voice -> Voice #

Read Voice Source # 
Show Voice Source # 

Methods

showsPrec :: Int -> Voice -> ShowS #

show :: Voice -> String #

showList :: [Voice] -> ShowS #

Generic Voice Source # 

Associated Types

type Rep Voice :: * -> * #

Methods

from :: Voice -> Rep Voice x #

to :: Rep Voice x -> Voice #

NFData Voice Source # 

Methods

rnf :: Voice -> () #

ToAttrValue Voice Source # 
HasVoice SayAttributes (Maybe Voice) Source # 
type Rep Voice Source # 

data Lang Source #

Instances

Eq Lang Source # 

Methods

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

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

Data Lang Source # 

Methods

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

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

toConstr :: Lang -> Constr #

dataTypeOf :: Lang -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord Lang Source # 

Methods

compare :: Lang -> Lang -> Ordering #

(<) :: Lang -> Lang -> Bool #

(<=) :: Lang -> Lang -> Bool #

(>) :: Lang -> Lang -> Bool #

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

max :: Lang -> Lang -> Lang #

min :: Lang -> Lang -> Lang #

Read Lang Source # 
Show Lang Source # 

Methods

showsPrec :: Int -> Lang -> ShowS #

show :: Lang -> String #

showList :: [Lang] -> ShowS #

Generic Lang Source # 

Associated Types

type Rep Lang :: * -> * #

Methods

from :: Lang -> Rep Lang x #

to :: Rep Lang x -> Lang #

NFData Lang Source # 

Methods

rnf :: Lang -> () #

ToAttrValue Lang Source # 
type Rep Lang Source # 
type Rep Lang = D1 * (MetaData "Lang" "Text.XML.Twiml.Types" "twiml-0.2.1.0-8vOgp92H6HZKjscJQqq5Ao" False) ((:+:) * ((:+:) * (C1 * (MetaCons "English" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "EnglishUK" PrefixI False) (U1 *)) (C1 * (MetaCons "Spanish" PrefixI False) (U1 *)))) ((:+:) * (C1 * (MetaCons "French" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "German" PrefixI False) (U1 *)) (C1 * (MetaCons "Italian" PrefixI False) (U1 *)))))

data LangAlice Source #

Constructors

DaDK

Danish, Denmark

DeDE

German, Germany

EnAU

English, Australia

EnCA

English, Canada

EnGB

English, UK

EnIN

English, India

EnUS

English, United States

CaES

Catalan, Spain

EsES

Spanish, Spain

EsMX

Spanish, Mexico

FiFI

Finnish, Finland

FrCA

French, Canada

FrFR

French, France

ItIT

Italian, Italy

JaJP

Japanese, Japan

KoKR

Korean, Korea

NbNO

Norwegian, Norway

NlNL

Dutch, Netherlands

PlPL

Polish-Poland

PtBR

Portuguese, Brazil

PtPT

Portuguese, Portugal

RuRU

Russian, Russia

SvSE

Swedish, Sweden

ZhCN

Chinese (Mandarin)

ZhHK

Chinese (Cantonese)

ZhTW

Chinese (Taiwanese Mandarin)

Instances

Eq LangAlice Source # 
Data LangAlice Source # 

Methods

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

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

toConstr :: LangAlice -> Constr #

dataTypeOf :: LangAlice -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord LangAlice Source # 
Read LangAlice Source # 
Show LangAlice Source # 
Generic LangAlice Source # 

Associated Types

type Rep LangAlice :: * -> * #

NFData LangAlice Source # 

Methods

rnf :: LangAlice -> () #

ToAttrValue LangAlice Source # 
type Rep LangAlice Source # 
type Rep LangAlice = D1 * (MetaData "LangAlice" "Text.XML.Twiml.Types" "twiml-0.2.1.0-8vOgp92H6HZKjscJQqq5Ao" False) ((:+:) * ((:+:) * ((:+:) * ((:+:) * (C1 * (MetaCons "DaDK" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "DeDE" PrefixI False) (U1 *)) (C1 * (MetaCons "EnAU" PrefixI False) (U1 *)))) ((:+:) * (C1 * (MetaCons "EnCA" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "EnGB" PrefixI False) (U1 *)) (C1 * (MetaCons "EnIN" PrefixI False) (U1 *))))) ((:+:) * ((:+:) * (C1 * (MetaCons "EnUS" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "CaES" PrefixI False) (U1 *)) (C1 * (MetaCons "EsES" PrefixI False) (U1 *)))) ((:+:) * ((:+:) * (C1 * (MetaCons "EsMX" PrefixI False) (U1 *)) (C1 * (MetaCons "FiFI" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "FrCA" PrefixI False) (U1 *)) (C1 * (MetaCons "FrFR" PrefixI False) (U1 *)))))) ((:+:) * ((:+:) * ((:+:) * (C1 * (MetaCons "ItIT" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "JaJP" PrefixI False) (U1 *)) (C1 * (MetaCons "KoKR" PrefixI False) (U1 *)))) ((:+:) * (C1 * (MetaCons "NbNO" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "NlNL" PrefixI False) (U1 *)) (C1 * (MetaCons "PlPL" PrefixI False) (U1 *))))) ((:+:) * ((:+:) * (C1 * (MetaCons "PtBR" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "PtPT" PrefixI False) (U1 *)) (C1 * (MetaCons "RuRU" PrefixI False) (U1 *)))) ((:+:) * ((:+:) * (C1 * (MetaCons "SvSE" PrefixI False) (U1 *)) (C1 * (MetaCons "ZhCN" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "ZhHK" PrefixI False) (U1 *)) (C1 * (MetaCons "ZhTW" PrefixI False) (U1 *)))))))

data Transport Source #

Constructors

TCP 
UDP 

Instances

Bounded Transport Source # 
Enum Transport Source # 
Eq Transport Source # 
Data Transport Source # 

Methods

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

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

toConstr :: Transport -> Constr #

dataTypeOf :: Transport -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord Transport Source # 
Read Transport Source # 
Show Transport Source # 
Generic Transport Source # 

Associated Types

type Rep Transport :: * -> * #

NFData Transport Source # 

Methods

rnf :: Transport -> () #

ToAttrValue Transport Source # 
HasTransport SipAttributes (Maybe Transport) Source # 
type Rep Transport Source # 
type Rep Transport = D1 * (MetaData "Transport" "Text.XML.Twiml.Types" "twiml-0.2.1.0-8vOgp92H6HZKjscJQqq5Ao" False) ((:+:) * (C1 * (MetaCons "TCP" PrefixI False) (U1 *)) (C1 * (MetaCons "UDP" PrefixI False) (U1 *)))

data ConferenceBeep Source #

Constructors

Yes 
No 
OnExit 
OnEnter 

Instances

Bounded ConferenceBeep Source # 
Enum ConferenceBeep Source # 
Eq ConferenceBeep Source # 
Data ConferenceBeep Source # 

Methods

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

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

toConstr :: ConferenceBeep -> Constr #

dataTypeOf :: ConferenceBeep -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord ConferenceBeep Source # 
Read ConferenceBeep Source # 
Show ConferenceBeep Source # 
Generic ConferenceBeep Source # 

Associated Types

type Rep ConferenceBeep :: * -> * #

NFData ConferenceBeep Source # 

Methods

rnf :: ConferenceBeep -> () #

ToAttrValue ConferenceBeep Source # 
type Rep ConferenceBeep Source # 
type Rep ConferenceBeep = D1 * (MetaData "ConferenceBeep" "Text.XML.Twiml.Types" "twiml-0.2.1.0-8vOgp92H6HZKjscJQqq5Ao" False) ((:+:) * ((:+:) * (C1 * (MetaCons "Yes" PrefixI False) (U1 *)) (C1 * (MetaCons "No" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "OnExit" PrefixI False) (U1 *)) (C1 * (MetaCons "OnEnter" PrefixI False) (U1 *))))

data Reason Source #

The reason attribute takes the values "rejected" and "busy." This tells Twilio what message to play when rejecting a call. Selecting "busy" will play a busy signal to the caller, while selecting "rejected" will play a standard not-in-service response. See https://www.twilio.com/docs/api/twiml/reject#attributes-reason.

Constructors

Rejected 
Busy 

Instances

Bounded Reason Source # 
Enum Reason Source # 
Eq Reason Source # 

Methods

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

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

Data Reason Source # 

Methods

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

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

toConstr :: Reason -> Constr #

dataTypeOf :: Reason -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord Reason Source # 
Read Reason Source # 
Show Reason Source # 
Generic Reason Source # 

Associated Types

type Rep Reason :: * -> * #

Methods

from :: Reason -> Rep Reason x #

to :: Rep Reason x -> Reason #

NFData Reason Source # 

Methods

rnf :: Reason -> () #

ToAttrValue Reason Source # 
HasReason RejectAttributes (Maybe Reason) Source # 
type Rep Reason Source # 
type Rep Reason = D1 * (MetaData "Reason" "Text.XML.Twiml.Types" "twiml-0.2.1.0-8vOgp92H6HZKjscJQqq5Ao" False) ((:+:) * (C1 * (MetaCons "Rejected" PrefixI False) (U1 *)) (C1 * (MetaCons "Busy" PrefixI False) (U1 *)))

Orphan instances