| Copyright | (C) 2014-15 Mark Andrus Roberts |
|---|---|
| License | BSD-style (see the file LICENSE) |
| Maintainer | Mark Andrus Roberts <markandrusroberts@gmail.com> |
| Stability | provisional |
| Safe Haskell | None |
| Language | Haskell98 |
Text.XML.Twiml.Verbs.Dial
Description
The examples in this file assume
{-# LANGUAGE RebindableSyntax #-}
{-# LANGUAGE RecordWildCards #-}
import Prelude
import Text.XML.Twiml
import qualified Text.XML.Twiml.Syntax as Twiml
For more information, refer to Twilio's TwiML Reference for <Dial>.
- dial :: IsTwimlLike f Dial => String -> DialAttributes -> TwimlLike f Dial ()
- dial' :: IsTwimlLike f Dial => Either DialNoun String -> DialAttributes -> TwimlLike f Dial ()
- data Dial
- data DialF i a
- data DialAttributes
- dialNoun :: TwimlLike DialNounF i Void -> DialNoun
- data DialNoun
- data DialNounF i a
- client :: IsTwimlLike f Client => String -> ClientAttributes -> TwimlLike f Client a
- data Client
- data ClientF i a
- data ClientAttributes
- conference :: IsTwimlLike f Conference => String -> ConferenceAttributes -> TwimlLike f Conference a
- data Conference
- data ConferenceF i a
- data ConferenceAttributes
- number :: IsTwimlLike f Number => String -> NumberAttributes -> TwimlLike f Number a
- data Number
- data NumberF i a
- data NumberAttributes
- queue :: IsTwimlLike f Queue => String -> QueueAttributes -> TwimlLike f Queue a
- data Queue
- data QueueF i a
- data QueueAttributes
- sip :: IsTwimlLike f Sip => URL -> SipAttributes -> TwimlLike f Sip a
- data Sip
- data SipF i a
- data SipAttributes
Documentation
dial :: IsTwimlLike f Dial => String -> DialAttributes -> TwimlLike f Dial () Source
Dial a number. Example:
example :: VoiceTwiml
example =
response $ do
dial "415-123-4567" def
say "Goodbye" def
end
where Twiml.Syntax{..} = def>>>show example<?xml version="1.0" encoding="UTF-8"?> <Response> <Dial>415-123-4567</Dial> <Say>Goodbye</Say> </Response>
dial' :: IsTwimlLike f Dial => Either DialNoun String -> DialAttributes -> TwimlLike f Dial () Source
Dial a number or DialNoun. Example:
example :: VoiceTwiml
example =
response $ do
dial' (Left $ Number def "+15558675309") $ def
& callerId .~ Just "+15551112222"
end
where Twiml.Syntax{..} = def>>>show example<?xml version="1.0" encoding="UTF-8"?> <Response> <Dial callerId="+15551112222"> <Number>+15558675309</Number> </Dial> </Response>
data DialAttributes Source
Instances
Nouns
Instances
| Functor (DialNounF i) Source | |
| Show1 [*] DialNounF Source | |
| Functor1 [*] DialNounF Source | |
| (:<:) (f i) ((:+:) * (ClientF i) ((:+:) * (ConferenceF i) ((:+:) * (NumberF i) ((:+:) * (QueueF i) (SipF i))))) => (f i) :<: (DialNounF i) Source | |
| Show a => Show (DialNounF i a) Source | |
| Generic (DialNounF i a) Source | |
| ToXML a => ToXML (DialNounF i a) Source | |
| ToXML (IxFree * DialNounF i Void) Source | |
| type Rep (DialNounF i a) Source |
Client
client :: IsTwimlLike f Client => String -> ClientAttributes -> TwimlLike f Client a Source
data ClientAttributes Source
Instances
Conference
conference :: IsTwimlLike f Conference => String -> ConferenceAttributes -> TwimlLike f Conference a Source
data Conference Source
data ConferenceF i a Source
Instances
| Functor (ConferenceF i) Source | |
| Functor1 [*] ConferenceF Source | |
| Show a => Show (ConferenceF i a) Source | |
| ToXML (ConferenceF i a) Source |
data ConferenceAttributes Source
Instances
Number
number :: IsTwimlLike f Number => String -> NumberAttributes -> TwimlLike f Number a Source
data NumberAttributes Source
Instances
Queue
queue :: IsTwimlLike f Queue => String -> QueueAttributes -> TwimlLike f Queue a Source
data QueueAttributes Source
Instances
Sip
sip :: IsTwimlLike f Sip => URL -> SipAttributes -> TwimlLike f Sip a Source
data SipAttributes Source
Instances