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 HaskellNone
LanguageHaskell98

Text.XML.Twiml.Verbs.Play

Description

The example in this file assumes

{-# LANGUAGE RebindableSyntax #-}
{-# LANGUAGE RecordWildCards #-}

import Prelude
import Control.Lens
import Data.Default
import Data.Maybe
import Text.XML.Twiml
import qualified Text.XML.Twiml.Syntax as Twiml

For more information, refer to Twilio's TwiML Reference for <Play>.

Synopsis

Documentation

play :: IsTwimlLike f Play => URL -> PlayAttributes -> TwimlLike f Play () Source #

Example:

>>> :{
let example1 :: VoiceTwiml
    example1 =
      voiceResponse $ do
        play (fromJust $ parseURL "https://api.twilio.com/cowbell.mp3") def
        end
      where Twiml.Syntax{..} = def
:}
>>> putStr $ show example1
<?xml version="1.0" encoding="UTF-8"?>
<Response>
  <Play>https://api.twilio.com/cowbell.mp3</Play>
</Response>

play' :: IsTwimlLike f Play => Maybe URL -> PlayAttributes -> TwimlLike f Play () Source #

Example:

>>> :{
let example2 :: VoiceTwiml
    example2 =
      voiceResponse $ do
        play' Nothing $ def & digits .~ Just [W, W, W, W, D3]
        end
      where Twiml.Syntax{..} = def
:}
>>> putStr $ show example2
<?xml version="1.0" encoding="UTF-8"?>
<Response>
  <Play digits="wwww3" />
</Response>

data PlayF (i :: [Type]) a Source #

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 #

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 #