twiml-0.2.0.1: TwiML library for Haskell

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

Text.XML.Twiml.Internal.Twiml

Contents

Description

This module defines all of the TwiML verbs and nouns in a single place (mainly due to a few mutually-recursive definitions). This modules also exposeses the internals of each TwiML's attributes.

Prefer the definitions re-exported by the Text.XML.Twiml and Text.XML.Twiml.Verbs modules to those exported here.

Synopsis

TwiML

newtype MessagingVerbsF i a Source #

Constructors

MessagingVerbsF 

Instances

Functor (MessagingVerbsF i) Source # 

Methods

fmap :: (a -> b) -> MessagingVerbsF i a -> MessagingVerbsF i b #

(<$) :: a -> MessagingVerbsF i b -> MessagingVerbsF i a #

Show1 [Type] MessagingVerbsF Source # 

Methods

show1 :: Show a => f i a -> String Source #

Functor1 [Type] MessagingVerbsF Source # 

Methods

fmap1 :: (a -> b) -> f i a -> f i b Source #

(Functor (f i), (:<:) (f i) ((:+:) * (MessageF i) ((:+:) * (RedirectF i) ((:+:) * (SmsF i) (EndF i))))) => (f i) :<: (MessagingVerbsF i) Source # 

Methods

inj :: f i a -> MessagingVerbsF i a Source #

prj :: MessagingVerbsF i a -> Maybe (f i a) Source #

Show a => Show (MessagingVerbsF i a) Source # 
Generic (MessagingVerbsF i a) Source # 

Associated Types

type Rep (MessagingVerbsF i a) :: * -> * #

Methods

from :: MessagingVerbsF i a -> Rep (MessagingVerbsF i a) x #

to :: Rep (MessagingVerbsF i a) x -> MessagingVerbsF i a #

ToXML a => ToXML (MessagingVerbsF i a) Source # 

Methods

toXML :: MessagingVerbsF i a -> [Element] Source #

ToXML (IxFree Type MessagingVerbsF i Void) Source # 
type Rep (MessagingVerbsF i a) Source # 
type Rep (MessagingVerbsF i a) = D1 (MetaData "MessagingVerbsF" "Text.XML.Twiml.Internal.Twiml" "twiml-0.2.0.1-LqGlAW9ysp41vRhevhGKAu" True) (C1 (MetaCons "MessagingVerbsF" PrefixI True) (S1 (MetaSel (Just Symbol "getMessagingVerbsF") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 ((:+:) * (MessageF i) ((:+:) * (RedirectF i) ((:+:) * (SmsF i) (EndF i))) a))))

newtype VoiceVerbsF i a Source #

Constructors

VoiceVerbsF 

Fields

Instances

Functor (VoiceVerbsF i) Source # 

Methods

fmap :: (a -> b) -> VoiceVerbsF i a -> VoiceVerbsF i b #

(<$) :: a -> VoiceVerbsF i b -> VoiceVerbsF i a #

Show1 [Type] VoiceVerbsF Source # 

Methods

show1 :: Show a => f i a -> String Source #

Functor1 [Type] VoiceVerbsF Source # 

Methods

fmap1 :: (a -> b) -> f i a -> f i b Source #

(Functor (f i), (:<:) (f i) ((:+:) * (SayF i) ((:+:) * (PlayF i) ((:+:) * (GatherF i) ((:+:) * (SmsF i) ((:+:) * (DialF i) ((:+:) * (EnqueueF i) ((:+:) * (LeaveF i) ((:+:) * (HangupF i) ((:+:) * (RecordF i) ((:+:) * (RedirectF i) ((:+:) * (RejectF i) ((:+:) * (PauseF i) (EndF i)))))))))))))) => (f i) :<: (VoiceVerbsF i) Source # 

Methods

inj :: f i a -> VoiceVerbsF i a Source #

prj :: VoiceVerbsF i a -> Maybe (f i a) Source #

Show a => Show (VoiceVerbsF i a) Source # 

Methods

showsPrec :: Int -> VoiceVerbsF i a -> ShowS #

show :: VoiceVerbsF i a -> String #

showList :: [VoiceVerbsF i a] -> ShowS #

Generic (VoiceVerbsF i a) Source # 

Associated Types

type Rep (VoiceVerbsF i a) :: * -> * #

Methods

from :: VoiceVerbsF i a -> Rep (VoiceVerbsF i a) x #

to :: Rep (VoiceVerbsF i a) x -> VoiceVerbsF i a #

ToXML a => ToXML (VoiceVerbsF i a) Source # 

Methods

toXML :: VoiceVerbsF i a -> [Element] Source #

ToXML (IxFree Type VoiceVerbsF i Void) Source # 
type Rep (VoiceVerbsF i a) Source # 
type Rep (VoiceVerbsF i a) = D1 (MetaData "VoiceVerbsF" "Text.XML.Twiml.Internal.Twiml" "twiml-0.2.0.1-LqGlAW9ysp41vRhevhGKAu" True) (C1 (MetaCons "VoiceVerbsF" PrefixI True) (S1 (MetaSel (Just Symbol "getVoiceVerbsF") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 ((:+:) * (SayF i) ((:+:) * (PlayF i) ((:+:) * (GatherF i) ((:+:) * (SmsF i) ((:+:) * (DialF i) ((:+:) * (EnqueueF i) ((:+:) * (LeaveF i) ((:+:) * (HangupF i) ((:+:) * (RecordF i) ((:+:) * (RedirectF i) ((:+:) * (RejectF i) ((:+:) * (PauseF i) (EndF i)))))))))))) a))))

type family Base d where ... Source #

Base maps the empty data declaration for a TwiML verb to its corresponding base functor.

type IsTwimlLike f i = (Functor1 f, Base i '[i] :<: f '[i]) Source #

type TwimlLike f i = TwimlLike' f '[i] Source #

Nouns

newtype DialNounF i a Source #

Constructors

DialNounF 

Fields

Instances

Functor (DialNounF i) Source # 

Methods

fmap :: (a -> b) -> DialNounF i a -> DialNounF i b #

(<$) :: a -> DialNounF i b -> DialNounF i a #

Show1 [Type] DialNounF Source # 

Methods

show1 :: Show a => f i a -> String Source #

Functor1 [Type] DialNounF Source # 

Methods

fmap1 :: (a -> b) -> f i a -> f i b Source #

(Functor (f i), (:<:) (f i) ((:+:) * (ClientF i) ((:+:) * (ConferenceF i) ((:+:) * (NumberF i) ((:+:) * (QueueF i) (SipF i)))))) => (f i) :<: (DialNounF i) Source # 

Methods

inj :: f i a -> DialNounF i a Source #

prj :: DialNounF i a -> Maybe (f i a) Source #

Show a => Show (DialNounF i a) Source # 

Methods

showsPrec :: Int -> DialNounF i a -> ShowS #

show :: DialNounF i a -> String #

showList :: [DialNounF i a] -> ShowS #

Generic (DialNounF i a) Source # 

Associated Types

type Rep (DialNounF i a) :: * -> * #

Methods

from :: DialNounF i a -> Rep (DialNounF i a) x #

to :: Rep (DialNounF i a) x -> DialNounF i a #

ToXML (DialNounF i a) Source # 

Methods

toXML :: DialNounF i a -> [Element] Source #

ToXML (IxFree Type DialNounF i Void) Source # 
type Rep (DialNounF i a) Source # 
type Rep (DialNounF i a) = D1 (MetaData "DialNounF" "Text.XML.Twiml.Internal.Twiml" "twiml-0.2.0.1-LqGlAW9ysp41vRhevhGKAu" True) (C1 (MetaCons "DialNounF" PrefixI True) (S1 (MetaSel (Just Symbol "getDialNounF") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 ((:+:) * (ClientF i) ((:+:) * (ConferenceF i) ((:+:) * (NumberF i) ((:+:) * (QueueF i) (SipF i)))) a))))

Client

data ClientF i a Source #

Constructors

(Proxy i ~ Proxy '[Client]) => ClientF String ClientAttributes 

Instances

Functor (ClientF i) Source # 

Methods

fmap :: (a -> b) -> ClientF i a -> ClientF i b #

(<$) :: a -> ClientF i b -> ClientF i a #

Functor1 [Type] ClientF Source # 

Methods

fmap1 :: (a -> b) -> f i a -> f i b Source #

Show a => Show (ClientF i a) Source # 

Methods

showsPrec :: Int -> ClientF i a -> ShowS #

show :: ClientF i a -> String #

showList :: [ClientF i a] -> ShowS #

ToXML (ClientF i a) Source # 

Methods

toXML :: ClientF i a -> [Element] Source #

data ClientAttributes Source #

Constructors

ClientAttributes 

Instances

Eq ClientAttributes Source # 
Data ClientAttributes Source # 

Methods

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

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

toConstr :: ClientAttributes -> Constr #

dataTypeOf :: ClientAttributes -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord ClientAttributes Source # 
Read ClientAttributes Source # 
Show ClientAttributes Source # 
Generic ClientAttributes Source # 
Default ClientAttributes Source # 
NFData ClientAttributes Source # 

Methods

rnf :: ClientAttributes -> () #

ToAttrs ClientAttributes Source # 
HasMethod ClientAttributes (Maybe Method) Source # 
HasUrl ClientAttributes (Maybe URL) Source # 
type Rep ClientAttributes Source # 
type Rep ClientAttributes = D1 (MetaData "ClientAttributes" "Text.XML.Twiml.Internal.Twiml" "twiml-0.2.0.1-LqGlAW9ysp41vRhevhGKAu" False) (C1 (MetaCons "ClientAttributes" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_clientUrl") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe URL))) (S1 (MetaSel (Just Symbol "_clientMethod") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Method)))))

Conference

data ConferenceF i a Source #

Instances

Functor (ConferenceF i) Source # 

Methods

fmap :: (a -> b) -> ConferenceF i a -> ConferenceF i b #

(<$) :: a -> ConferenceF i b -> ConferenceF i a #

Functor1 [Type] ConferenceF Source # 

Methods

fmap1 :: (a -> b) -> f i a -> f i b Source #

Show a => Show (ConferenceF i a) Source # 

Methods

showsPrec :: Int -> ConferenceF i a -> ShowS #

show :: ConferenceF i a -> String #

showList :: [ConferenceF i a] -> ShowS #

ToXML (ConferenceF i a) Source # 

Methods

toXML :: ConferenceF i a -> [Element] Source #

data ConferenceAttributes Source #

Instances

Eq ConferenceAttributes Source # 
Data ConferenceAttributes Source # 

Methods

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

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

toConstr :: ConferenceAttributes -> Constr #

dataTypeOf :: ConferenceAttributes -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord ConferenceAttributes Source # 
Read ConferenceAttributes Source # 
Show ConferenceAttributes Source # 
Generic ConferenceAttributes Source # 
Default ConferenceAttributes Source # 
NFData ConferenceAttributes Source # 

Methods

rnf :: ConferenceAttributes -> () #

ToAttrs ConferenceAttributes Source # 
HasWaitURL ConferenceAttributes (Maybe URL) Source # 
HasWaitMethod ConferenceAttributes (Maybe Method) Source # 
HasStartOnEnter ConferenceAttributes (Maybe Bool) Source # 
HasMuted ConferenceAttributes (Maybe Bool) Source # 
HasMaxParticipants ConferenceAttributes (Maybe Natural) Source # 
HasEndOnExit ConferenceAttributes (Maybe Bool) Source # 
HasBeep ConferenceAttributes (Maybe Bool) Source # 
type Rep ConferenceAttributes Source # 
type Rep ConferenceAttributes = D1 (MetaData "ConferenceAttributes" "Text.XML.Twiml.Internal.Twiml" "twiml-0.2.0.1-LqGlAW9ysp41vRhevhGKAu" False) (C1 (MetaCons "ConferenceAttributes" PrefixI True) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_conferenceMuted") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Bool))) ((:*:) (S1 (MetaSel (Just Symbol "_conferenceBeep") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Bool))) (S1 (MetaSel (Just Symbol "_conferenceStartOnEnter") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Bool))))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_conferenceEndOnExit") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Bool))) (S1 (MetaSel (Just Symbol "_conferenceWaitURL") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe URL)))) ((:*:) (S1 (MetaSel (Just Symbol "_conferenceWaitMethod") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Method))) (S1 (MetaSel (Just Symbol "_conferenceMaxParticipants") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Natural)))))))

Number

data NumberF i a Source #

Constructors

(Proxy i ~ Proxy '[Number]) => NumberF String NumberAttributes 

Instances

Functor (NumberF i) Source # 

Methods

fmap :: (a -> b) -> NumberF i a -> NumberF i b #

(<$) :: a -> NumberF i b -> NumberF i a #

Functor1 [Type] NumberF Source # 

Methods

fmap1 :: (a -> b) -> f i a -> f i b Source #

Show a => Show (NumberF i a) Source # 

Methods

showsPrec :: Int -> NumberF i a -> ShowS #

show :: NumberF i a -> String #

showList :: [NumberF i a] -> ShowS #

ToXML (NumberF i a) Source # 

Methods

toXML :: NumberF i a -> [Element] Source #

data NumberAttributes Source #

Constructors

NumberAttributes 

Instances

Eq NumberAttributes Source # 
Data NumberAttributes Source # 

Methods

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

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

toConstr :: NumberAttributes -> Constr #

dataTypeOf :: NumberAttributes -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord NumberAttributes Source # 
Read NumberAttributes Source # 
Show NumberAttributes Source # 
Generic NumberAttributes Source # 
Default NumberAttributes Source # 
NFData NumberAttributes Source # 

Methods

rnf :: NumberAttributes -> () #

ToAttrs NumberAttributes Source # 
HasMethod NumberAttributes (Maybe Method) Source # 
HasUrl NumberAttributes (Maybe URL) Source # 
type Rep NumberAttributes Source # 

Queue

data QueueF i a Source #

Constructors

(Proxy i ~ Proxy '[Queue]) => QueueF String QueueAttributes 

Instances

Functor (QueueF i) Source # 

Methods

fmap :: (a -> b) -> QueueF i a -> QueueF i b #

(<$) :: a -> QueueF i b -> QueueF i a #

Functor1 [Type] QueueF Source # 

Methods

fmap1 :: (a -> b) -> f i a -> f i b Source #

Show a => Show (QueueF i a) Source # 

Methods

showsPrec :: Int -> QueueF i a -> ShowS #

show :: QueueF i a -> String #

showList :: [QueueF i a] -> ShowS #

ToXML (QueueF i a) Source # 

Methods

toXML :: QueueF i a -> [Element] Source #

data QueueAttributes Source #

Constructors

QueueAttributes 

Instances

Eq QueueAttributes Source # 
Data QueueAttributes Source # 

Methods

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

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

toConstr :: QueueAttributes -> Constr #

dataTypeOf :: QueueAttributes -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord QueueAttributes Source # 
Read QueueAttributes Source # 
Show QueueAttributes Source # 
Generic QueueAttributes Source # 
Default QueueAttributes Source # 
NFData QueueAttributes Source # 

Methods

rnf :: QueueAttributes -> () #

ToAttrs QueueAttributes Source # 
HasMethod QueueAttributes (Maybe Method) Source # 
HasUrl QueueAttributes (Maybe URL) Source # 
type Rep QueueAttributes Source # 
type Rep QueueAttributes = D1 (MetaData "QueueAttributes" "Text.XML.Twiml.Internal.Twiml" "twiml-0.2.0.1-LqGlAW9ysp41vRhevhGKAu" False) (C1 (MetaCons "QueueAttributes" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_queueUrl") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe URL))) (S1 (MetaSel (Just Symbol "_queueMethod") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Method)))))

Sip

data Sip Source #

data SipF i a Source #

Constructors

(Proxy i ~ Proxy '[Sip]) => SipF URL SipAttributes 

Instances

Functor (SipF i) Source # 

Methods

fmap :: (a -> b) -> SipF i a -> SipF i b #

(<$) :: a -> SipF i b -> SipF i a #

Functor1 [Type] SipF Source # 

Methods

fmap1 :: (a -> b) -> f i a -> f i b Source #

Show a => Show (SipF i a) Source # 

Methods

showsPrec :: Int -> SipF i a -> ShowS #

show :: SipF i a -> String #

showList :: [SipF i a] -> ShowS #

ToXML (SipF i a) Source # 

Methods

toXML :: SipF i a -> [Element] Source #

data SipAttributes Source #

Instances

Eq SipAttributes Source # 
Data SipAttributes Source # 

Methods

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

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

toConstr :: SipAttributes -> Constr #

dataTypeOf :: SipAttributes -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord SipAttributes Source # 
Read SipAttributes Source # 
Show SipAttributes Source # 
Generic SipAttributes Source # 

Associated Types

type Rep SipAttributes :: * -> * #

Default SipAttributes Source # 

Methods

def :: SipAttributes #

NFData SipAttributes Source # 

Methods

rnf :: SipAttributes -> () #

ToAttrs SipAttributes Source # 
HasMethod SipAttributes (Maybe Method) Source # 
HasUrl SipAttributes (Maybe URL) Source # 
HasUsername SipAttributes (Maybe String) Source # 
HasTransport SipAttributes (Maybe Transport) Source # 
HasPassword SipAttributes (Maybe String) Source # 
HasHeaders SipAttributes (Maybe String) Source # 
type Rep SipAttributes Source # 

Verbs

Dial

data DialF i a Source #

Constructors

(Proxy i ~ Proxy '[Dial]) => DialF EitherDialNounString DialAttributes a 

Instances

Functor (DialF i) Source # 

Methods

fmap :: (a -> b) -> DialF i a -> DialF i b #

(<$) :: a -> DialF i b -> DialF i a #

Functor1 [Type] DialF Source # 

Methods

fmap1 :: (a -> b) -> f i a -> f i b Source #

Show a => Show (DialF i a) Source # 

Methods

showsPrec :: Int -> DialF i a -> ShowS #

show :: DialF i a -> String #

showList :: [DialF i a] -> ShowS #

ToXML a => ToXML (DialF i a) Source # 

Methods

toXML :: DialF i a -> [Element] Source #

data DialAttributes Source #

Instances

Eq DialAttributes Source # 
Data DialAttributes Source # 

Methods

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

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

toConstr :: DialAttributes -> Constr #

dataTypeOf :: DialAttributes -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord DialAttributes Source # 
Read DialAttributes Source # 
Show DialAttributes Source # 
Generic DialAttributes Source # 

Associated Types

type Rep DialAttributes :: * -> * #

Default DialAttributes Source # 

Methods

def :: DialAttributes #

NFData DialAttributes Source # 

Methods

rnf :: DialAttributes -> () #

ToAttrs DialAttributes Source # 
HasTimeout DialAttributes (Maybe Natural) Source # 
HasMethod DialAttributes (Maybe Method) Source # 
HasAction DialAttributes (Maybe URL) Source # 
HasTimeLimit DialAttributes (Maybe Natural) Source # 
HasRecord' DialAttributes (Maybe Bool) Source # 
HasHangupOnStar DialAttributes (Maybe Bool) Source # 
HasCallerId DialAttributes (Maybe String) Source # 
type Rep DialAttributes Source # 

End

data End Source #

data EndF i a Source #

Constructors

(Proxy i ~ Proxy '[End]) => EndF 

Instances

Functor (EndF i) Source # 

Methods

fmap :: (a -> b) -> EndF i a -> EndF i b #

(<$) :: a -> EndF i b -> EndF i a #

Functor1 [Type] EndF Source # 

Methods

fmap1 :: (a -> b) -> f i a -> f i b Source #

Show a => Show (EndF i a) Source # 

Methods

showsPrec :: Int -> EndF i a -> ShowS #

show :: EndF i a -> String #

showList :: [EndF i a] -> ShowS #

ToXML (EndF i a) Source # 

Methods

toXML :: EndF i a -> [Element] Source #

Enqueue

data EnqueueF i a Source #

Constructors

(Proxy i ~ Proxy '[Enqueue]) => EnqueueF String EnqueueAttributes a 

Instances

Functor (EnqueueF i) Source # 

Methods

fmap :: (a -> b) -> EnqueueF i a -> EnqueueF i b #

(<$) :: a -> EnqueueF i b -> EnqueueF i a #

Functor1 [Type] EnqueueF Source # 

Methods

fmap1 :: (a -> b) -> f i a -> f i b Source #

Show a => Show (EnqueueF i a) Source # 

Methods

showsPrec :: Int -> EnqueueF i a -> ShowS #

show :: EnqueueF i a -> String #

showList :: [EnqueueF i a] -> ShowS #

ToXML a => ToXML (EnqueueF i a) Source # 

Methods

toXML :: EnqueueF i a -> [Element] Source #

data EnqueueAttributes Source #

Instances

Eq EnqueueAttributes Source # 
Data EnqueueAttributes Source # 

Methods

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

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

toConstr :: EnqueueAttributes -> Constr #

dataTypeOf :: EnqueueAttributes -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord EnqueueAttributes Source # 
Read EnqueueAttributes Source # 
Show EnqueueAttributes Source # 
Generic EnqueueAttributes Source # 
Default EnqueueAttributes Source # 
NFData EnqueueAttributes Source # 

Methods

rnf :: EnqueueAttributes -> () #

ToAttrs EnqueueAttributes Source # 
HasMethod EnqueueAttributes (Maybe Method) Source # 
HasAction EnqueueAttributes (Maybe URL) Source # 
HasWaitURL EnqueueAttributes (Maybe URL) Source # 
HasWaitMethod EnqueueAttributes (Maybe Method) Source # 
type Rep EnqueueAttributes Source # 
type Rep EnqueueAttributes = D1 (MetaData "EnqueueAttributes" "Text.XML.Twiml.Internal.Twiml" "twiml-0.2.0.1-LqGlAW9ysp41vRhevhGKAu" False) (C1 (MetaCons "EnqueueAttributes" PrefixI True) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_enqueueAction") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe URL))) (S1 (MetaSel (Just Symbol "_enqueueMethod") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Method)))) ((:*:) (S1 (MetaSel (Just Symbol "_enqueueWaitURL") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe URL))) (S1 (MetaSel (Just Symbol "_enqueueWaitMethod") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Method))))))

Hangup

data GatherF i a where Source #

Constructors

GatherF :: Nest i In Gather => GatherAttributes -> IxFree VoiceVerbsF i Void -> a -> GatherF '[Gather] a 

Instances

Functor (GatherF i) Source # 

Methods

fmap :: (a -> b) -> GatherF i a -> GatherF i b #

(<$) :: a -> GatherF i b -> GatherF i a #

Functor1 [Type] GatherF Source # 

Methods

fmap1 :: (a -> b) -> f i a -> f i b Source #

Show a => Show (GatherF i a) Source # 

Methods

showsPrec :: Int -> GatherF i a -> ShowS #

show :: GatherF i a -> String #

showList :: [GatherF i a] -> ShowS #

ToXML a => ToXML (GatherF i a) Source # 

Methods

toXML :: GatherF i a -> [Element] Source #

data GatherAttributes Source #

Instances

Eq GatherAttributes Source # 
Data GatherAttributes Source # 

Methods

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

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

toConstr :: GatherAttributes -> Constr #

dataTypeOf :: GatherAttributes -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord GatherAttributes Source # 
Read GatherAttributes Source # 
Show GatherAttributes Source # 
Generic GatherAttributes Source # 
Default GatherAttributes Source # 
NFData GatherAttributes Source # 

Methods

rnf :: GatherAttributes -> () #

ToAttrs GatherAttributes Source # 
HasTimeout GatherAttributes (Maybe Natural) Source # 
HasNumDigits GatherAttributes (Maybe Natural) Source # 
HasMethod GatherAttributes (Maybe Method) Source # 
HasFinishOnKey GatherAttributes (Maybe Key) Source # 
HasAction GatherAttributes (Maybe URL) Source # 
type Rep GatherAttributes Source # 
type Rep GatherAttributes = D1 (MetaData "GatherAttributes" "Text.XML.Twiml.Internal.Twiml" "twiml-0.2.0.1-LqGlAW9ysp41vRhevhGKAu" False) (C1 (MetaCons "GatherAttributes" PrefixI True) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_gatherAction") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe URL))) (S1 (MetaSel (Just Symbol "_gatherMethod") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Method)))) ((:*:) (S1 (MetaSel (Just Symbol "_gatherTimeout") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Natural))) ((:*:) (S1 (MetaSel (Just Symbol "_gatherFinishOnKey") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Key))) (S1 (MetaSel (Just Symbol "_gatherNumDigits") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Natural)))))))

type family Nest a i b where ... Source #

Equations

Nest i In Gather = (Record i, Gather i, Sms i, Dial i, Enqueue i, Leave i, Hangup i, Redirect i, Reject i) 

data In Source #

Hangup

data HangupF i a Source #

Constructors

(Proxy i ~ Proxy '[Hangup]) => HangupF 

Instances

Functor (HangupF i) Source # 

Methods

fmap :: (a -> b) -> HangupF i a -> HangupF i b #

(<$) :: a -> HangupF i b -> HangupF i a #

Functor1 [Type] HangupF Source # 

Methods

fmap1 :: (a -> b) -> f i a -> f i b Source #

Show a => Show (HangupF i a) Source # 

Methods

showsPrec :: Int -> HangupF i a -> ShowS #

show :: HangupF i a -> String #

showList :: [HangupF i a] -> ShowS #

ToXML (HangupF i a) Source # 

Methods

toXML :: HangupF i a -> [Element] Source #

Leave

data LeaveF i a Source #

Constructors

(Proxy i ~ Proxy '[Leave]) => LeaveF 

Instances

Functor (LeaveF i) Source # 

Methods

fmap :: (a -> b) -> LeaveF i a -> LeaveF i b #

(<$) :: a -> LeaveF i b -> LeaveF i a #

Functor1 [Type] LeaveF Source # 

Methods

fmap1 :: (a -> b) -> f i a -> f i b Source #

Show a => Show (LeaveF i a) Source # 

Methods

showsPrec :: Int -> LeaveF i a -> ShowS #

show :: LeaveF i a -> String #

showList :: [LeaveF i a] -> ShowS #

ToXML (LeaveF i a) Source # 

Methods

toXML :: LeaveF i a -> [Element] Source #

Message

data MessageF i a Source #

Constructors

(Proxy i ~ Proxy '[Message]) => MessageF String MessageAttributes a 

Instances

Functor (MessageF i) Source # 

Methods

fmap :: (a -> b) -> MessageF i a -> MessageF i b #

(<$) :: a -> MessageF i b -> MessageF i a #

Functor1 [Type] MessageF Source # 

Methods

fmap1 :: (a -> b) -> f i a -> f i b Source #

Show a => Show (MessageF i a) Source # 

Methods

showsPrec :: Int -> MessageF i a -> ShowS #

show :: MessageF i a -> String #

showList :: [MessageF i a] -> ShowS #

ToXML a => ToXML (MessageF i a) Source # 

Methods

toXML :: MessageF i a -> [Element] Source #

data MessageAttributes Source #

Instances

Eq MessageAttributes Source # 
Data MessageAttributes Source # 

Methods

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

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

toConstr :: MessageAttributes -> Constr #

dataTypeOf :: MessageAttributes -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord MessageAttributes Source # 
Read MessageAttributes Source # 
Show MessageAttributes Source # 
Generic MessageAttributes Source # 
Default MessageAttributes Source # 
NFData MessageAttributes Source # 

Methods

rnf :: MessageAttributes -> () #

ToAttrs MessageAttributes Source # 
HasMethod MessageAttributes (Maybe Method) Source # 
HasAction MessageAttributes (Maybe URL) Source # 
HasTo MessageAttributes (Maybe String) Source # 
HasStatusCallback MessageAttributes (Maybe URL) Source # 
HasFrom MessageAttributes (Maybe String) Source # 
type Rep MessageAttributes Source # 
type Rep MessageAttributes = D1 (MetaData "MessageAttributes" "Text.XML.Twiml.Internal.Twiml" "twiml-0.2.0.1-LqGlAW9ysp41vRhevhGKAu" False) (C1 (MetaCons "MessageAttributes" PrefixI True) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_messageTo") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe String))) (S1 (MetaSel (Just Symbol "_messageFrom") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe String)))) ((:*:) (S1 (MetaSel (Just Symbol "_messageAction") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe URL))) ((:*:) (S1 (MetaSel (Just Symbol "_messageMethod") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Method))) (S1 (MetaSel (Just Symbol "_messageStatusCallback") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe URL)))))))

Pause

data PauseF i a Source #

Constructors

(Proxy i ~ Proxy '[Pause]) => PauseF PauseAttributes a 

Instances

Functor (PauseF i) Source # 

Methods

fmap :: (a -> b) -> PauseF i a -> PauseF i b #

(<$) :: a -> PauseF i b -> PauseF i a #

Functor1 [Type] PauseF Source # 

Methods

fmap1 :: (a -> b) -> f i a -> f i b Source #

Show a => Show (PauseF i a) Source # 

Methods

showsPrec :: Int -> PauseF i a -> ShowS #

show :: PauseF i a -> String #

showList :: [PauseF i a] -> ShowS #

ToXML a => ToXML (PauseF i a) Source # 

Methods

toXML :: PauseF i a -> [Element] Source #

data PauseAttributes Source #

Constructors

PauseAttributes 

Instances

Eq PauseAttributes Source # 
Data PauseAttributes Source # 

Methods

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

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

toConstr :: PauseAttributes -> Constr #

dataTypeOf :: PauseAttributes -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord PauseAttributes Source # 
Read PauseAttributes Source # 
Show PauseAttributes Source # 
Generic PauseAttributes Source # 
Default PauseAttributes Source # 
NFData PauseAttributes Source # 

Methods

rnf :: PauseAttributes -> () #

ToAttrs PauseAttributes Source # 
HasDuration PauseAttributes (Maybe Natural) Source # 
type Rep PauseAttributes Source # 
type Rep PauseAttributes = D1 (MetaData "PauseAttributes" "Text.XML.Twiml.Internal.Twiml" "twiml-0.2.0.1-LqGlAW9ysp41vRhevhGKAu" False) (C1 (MetaCons "PauseAttributes" PrefixI True) (S1 (MetaSel (Just Symbol "_pauseDuration") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Natural))))

Play

data PlayF i a Source #

Constructors

(Proxy i ~ Proxy '[Play]) => PlayF MaybeURL PlayAttributes a 

Instances

Functor (PlayF i) Source # 

Methods

fmap :: (a -> b) -> PlayF i a -> PlayF i b #

(<$) :: a -> PlayF i b -> PlayF i a #

Functor1 [Type] PlayF Source # 

Methods

fmap1 :: (a -> b) -> f i a -> f i b Source #

Show a => Show (PlayF i a) Source # 

Methods

showsPrec :: Int -> PlayF i a -> ShowS #

show :: PlayF i a -> String #

showList :: [PlayF i a] -> ShowS #

ToXML a => ToXML (PlayF i a) Source # 

Methods

toXML :: PlayF i a -> [Element] Source #

data PlayAttributes Source #

Constructors

PlayAttributes 

Fields

Instances

Eq PlayAttributes Source # 
Data PlayAttributes Source # 

Methods

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

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

toConstr :: PlayAttributes -> Constr #

dataTypeOf :: PlayAttributes -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord PlayAttributes Source # 
Read PlayAttributes Source # 
Show PlayAttributes Source # 
Generic PlayAttributes Source # 

Associated Types

type Rep PlayAttributes :: * -> * #

Default PlayAttributes Source # 

Methods

def :: PlayAttributes #

NFData PlayAttributes Source # 

Methods

rnf :: PlayAttributes -> () #

ToAttrs PlayAttributes Source # 
HasLoop PlayAttributes (Maybe Natural) Source # 
type Rep PlayAttributes Source # 

Record

data RecordF i a Source #

Constructors

(Proxy i ~ Proxy '[Record]) => RecordF RecordAttributes a 

Instances

Functor (RecordF i) Source # 

Methods

fmap :: (a -> b) -> RecordF i a -> RecordF i b #

(<$) :: a -> RecordF i b -> RecordF i a #

Functor1 [Type] RecordF Source # 

Methods

fmap1 :: (a -> b) -> f i a -> f i b Source #

Show a => Show (RecordF i a) Source # 

Methods

showsPrec :: Int -> RecordF i a -> ShowS #

show :: RecordF i a -> String #

showList :: [RecordF i a] -> ShowS #

ToXML a => ToXML (RecordF i a) Source # 

Methods

toXML :: RecordF i a -> [Element] Source #

data RecordAttributes Source #

Instances

Eq RecordAttributes Source # 
Data RecordAttributes Source # 

Methods

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

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

toConstr :: RecordAttributes -> Constr #

dataTypeOf :: RecordAttributes -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord RecordAttributes Source # 
Read RecordAttributes Source # 
Show RecordAttributes Source # 
Generic RecordAttributes Source # 
Default RecordAttributes Source # 
NFData RecordAttributes Source # 

Methods

rnf :: RecordAttributes -> () #

ToAttrs RecordAttributes Source # 
HasTimeout RecordAttributes (Maybe Natural) Source # 
HasMethod RecordAttributes (Maybe Method) Source # 
HasFinishOnKey RecordAttributes (Maybe Key) Source # 
HasAction RecordAttributes (Maybe URL) Source # 
HasTranscribeCallback RecordAttributes (Maybe URL) Source # 
HasTranscribe RecordAttributes (Maybe Bool) Source # 
HasPlayBeep RecordAttributes (Maybe Bool) Source # 
HasMaxLength RecordAttributes (Maybe Natural) Source # 
type Rep RecordAttributes Source # 

Redirect

data RedirectF i a Source #

Instances

Functor (RedirectF i) Source # 

Methods

fmap :: (a -> b) -> RedirectF i a -> RedirectF i b #

(<$) :: a -> RedirectF i b -> RedirectF i a #

Functor1 [Type] RedirectF Source # 

Methods

fmap1 :: (a -> b) -> f i a -> f i b Source #

Show a => Show (RedirectF i a) Source # 

Methods

showsPrec :: Int -> RedirectF i a -> ShowS #

show :: RedirectF i a -> String #

showList :: [RedirectF i a] -> ShowS #

ToXML (RedirectF i a) Source # 

Methods

toXML :: RedirectF i a -> [Element] Source #

data RedirectAttributes Source #

Constructors

RedirectAttributes 

Instances

Eq RedirectAttributes Source # 
Data RedirectAttributes Source # 

Methods

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

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

toConstr :: RedirectAttributes -> Constr #

dataTypeOf :: RedirectAttributes -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord RedirectAttributes Source # 
Read RedirectAttributes Source # 
Show RedirectAttributes Source # 
Generic RedirectAttributes Source # 
Default RedirectAttributes Source # 
NFData RedirectAttributes Source # 

Methods

rnf :: RedirectAttributes -> () #

ToAttrs RedirectAttributes Source # 
HasMethod RedirectAttributes (Maybe Method) Source # 
type Rep RedirectAttributes Source # 
type Rep RedirectAttributes = D1 (MetaData "RedirectAttributes" "Text.XML.Twiml.Internal.Twiml" "twiml-0.2.0.1-LqGlAW9ysp41vRhevhGKAu" False) (C1 (MetaCons "RedirectAttributes" PrefixI True) (S1 (MetaSel (Just Symbol "_redirectMethod") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Method))))

Reject

data RejectF i a Source #

Constructors

(Proxy i ~ Proxy '[Reject]) => RejectF RejectAttributes 

Instances

Functor (RejectF i) Source # 

Methods

fmap :: (a -> b) -> RejectF i a -> RejectF i b #

(<$) :: a -> RejectF i b -> RejectF i a #

Functor1 [Type] RejectF Source # 

Methods

fmap1 :: (a -> b) -> f i a -> f i b Source #

Show a => Show (RejectF i a) Source # 

Methods

showsPrec :: Int -> RejectF i a -> ShowS #

show :: RejectF i a -> String #

showList :: [RejectF i a] -> ShowS #

ToXML (RejectF i a) Source # 

Methods

toXML :: RejectF i a -> [Element] Source #

data RejectAttributes Source #

Constructors

RejectAttributes 

Fields

Instances

Eq RejectAttributes Source # 
Data RejectAttributes Source # 

Methods

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

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

toConstr :: RejectAttributes -> Constr #

dataTypeOf :: RejectAttributes -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord RejectAttributes Source # 
Read RejectAttributes Source # 
Show RejectAttributes Source # 
Generic RejectAttributes Source # 
Default RejectAttributes Source # 
NFData RejectAttributes Source # 

Methods

rnf :: RejectAttributes -> () #

ToAttrs RejectAttributes Source # 
HasReason RejectAttributes (Maybe Reason) Source # 
type Rep RejectAttributes Source # 
type Rep RejectAttributes = D1 (MetaData "RejectAttributes" "Text.XML.Twiml.Internal.Twiml" "twiml-0.2.0.1-LqGlAW9ysp41vRhevhGKAu" False) (C1 (MetaCons "RejectAttributes" PrefixI True) (S1 (MetaSel (Just Symbol "_rejectReason") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Reason))))

Say

data Say Source #

data SayF i a Source #

Constructors

(Proxy i ~ Proxy '[Say]) => SayF String SayAttributes a 

Instances

Functor (SayF i) Source # 

Methods

fmap :: (a -> b) -> SayF i a -> SayF i b #

(<$) :: a -> SayF i b -> SayF i a #

Functor1 [Type] SayF Source # 

Methods

fmap1 :: (a -> b) -> f i a -> f i b Source #

Show a => Show (SayF i a) Source # 

Methods

showsPrec :: Int -> SayF i a -> ShowS #

show :: SayF i a -> String #

showList :: [SayF i a] -> ShowS #

ToXML a => ToXML (SayF i a) Source # 

Methods

toXML :: SayF i a -> [Element] Source #

data SayAttributes Source #

Constructors

SayAttributes 

Fields

Instances

Eq SayAttributes Source # 
Data SayAttributes Source # 

Methods

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

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

toConstr :: SayAttributes -> Constr #

dataTypeOf :: SayAttributes -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord SayAttributes Source # 
Read SayAttributes Source # 
Show SayAttributes Source # 
Generic SayAttributes Source # 

Associated Types

type Rep SayAttributes :: * -> * #

Default SayAttributes Source # 

Methods

def :: SayAttributes #

NFData SayAttributes Source # 

Methods

rnf :: SayAttributes -> () #

ToAttrs SayAttributes Source # 
HasVoice SayAttributes (Maybe Voice) Source # 
HasLoop SayAttributes (Maybe Natural) Source # 
type Rep SayAttributes Source # 
type Rep SayAttributes = D1 (MetaData "SayAttributes" "Text.XML.Twiml.Internal.Twiml" "twiml-0.2.0.1-LqGlAW9ysp41vRhevhGKAu" False) (C1 (MetaCons "SayAttributes" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_sayVoice") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Voice))) (S1 (MetaSel (Just Symbol "_sayLoop") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Natural)))))

Sms

data Sms Source #

data SmsF i a Source #

Constructors

(Proxy i ~ Proxy '[Sms]) => SmsF String SmsAttributes a 

Instances

Functor (SmsF i) Source # 

Methods

fmap :: (a -> b) -> SmsF i a -> SmsF i b #

(<$) :: a -> SmsF i b -> SmsF i a #

Functor1 [Type] SmsF Source # 

Methods

fmap1 :: (a -> b) -> f i a -> f i b Source #

Show a => Show (SmsF i a) Source # 

Methods

showsPrec :: Int -> SmsF i a -> ShowS #

show :: SmsF i a -> String #

showList :: [SmsF i a] -> ShowS #

ToXML a => ToXML (SmsF i a) Source # 

Methods

toXML :: SmsF i a -> [Element] Source #

data SmsAttributes Source #

Instances

Eq SmsAttributes Source # 
Data SmsAttributes Source # 

Methods

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

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

toConstr :: SmsAttributes -> Constr #

dataTypeOf :: SmsAttributes -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord SmsAttributes Source # 
Read SmsAttributes Source # 
Show SmsAttributes Source # 
Generic SmsAttributes Source # 

Associated Types

type Rep SmsAttributes :: * -> * #

Default SmsAttributes Source # 

Methods

def :: SmsAttributes #

NFData SmsAttributes Source # 

Methods

rnf :: SmsAttributes -> () #

ToAttrs SmsAttributes Source # 
HasMethod SmsAttributes (Maybe Method) Source # 
HasAction SmsAttributes (Maybe URL) Source # 
HasTo SmsAttributes (Maybe String) Source # 
HasStatusCallback SmsAttributes (Maybe URL) Source # 
HasFrom SmsAttributes (Maybe String) Source # 
type Rep SmsAttributes Source #