| Safe Haskell | None |
|---|
Text.XML.Twiml.Verbs.Record
Contents
- data Record p
- record :: (Twiml p t, p :/~ Gather') => t -> Record p
- record' :: (Twiml p t, p :/~ Gather') => RecordAttributes -> t -> Record p
- data RecordAttributes = RecordAttributes {}
- defaultRecordAttributes :: RecordAttributes
- recordAttributes :: Lens' (Record p) RecordAttributes
- maxLength :: Lens (Record p) (Record p) (Maybe Natural) Natural
- transcribe :: Lens (Record p) (Record p) (Maybe Bool) Bool
- transcribeCallback :: Lens (Record p) (Record p) (Maybe URL) URL
- playBeep :: Lens (Record p) (Record p) (Maybe Bool) Bool
- action :: HasAction t => Lens t t (Maybe URL) URL
- method :: HasMethod t => Lens t t (Maybe Method) Method
- timeout :: HasTimeout t => Lens t t (Maybe Natural) Natural
- finishOnKey :: HasFinishOnKey t => Lens t t (Maybe Key) Key
<Record>
This example
module Example where
import Control.Lens
import Text.XML.Twiml
example
= respond
. (record <&> timeout .~ 10
<&> transcribe .~ True)
$ end
produces the following TwiML response:
<?xml version="1.0" encoding="UTF-8"?> <Response> <Record timeout="10" transcribe="true" /> </Response>
Constructors
Attributes
data RecordAttributes Source
Constructors
| RecordAttributes | |
Fields | |
Lenses
finishOnKey :: HasFinishOnKey t => Lens t t (Maybe Key) KeySource