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.Sms

Description

The example in this file assumes

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

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

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

Synopsis

Documentation

sms :: IsTwimlLike f Sms => String -> SmsAttributes -> TwimlLike f Sms () Source #

Example:

>>> :{
let example :: VoiceTwiml
    example =
      voiceResponse $ do
        say "Our store is located at 123 Easy St." def
        sms "Store Location: 123 Easy St." $ def
                & action .~ parseURL "/smsHandler.php"
                & method .~ Just POST
        end
      where Twiml.Syntax{..} = def
:}
>>> putStr $ show example
<?xml version="1.0" encoding="UTF-8"?>
<Response>
  <Say>Our store is located at 123 Easy St.</Say>
  <Sms action="/smsHandler.php" method="POST">Store Location: 123 Easy St.</Sms>
</Response>

data Sms Source #

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

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 # 
type Rep SmsAttributes = D1 * (MetaData "SmsAttributes" "Text.XML.Twiml.Internal.Twiml" "twiml-0.2.1.0-8vOgp92H6HZKjscJQqq5Ao" False) (C1 * (MetaCons "SmsAttributes" PrefixI True) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "_smsTo") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe String))) (S1 * (MetaSel (Just Symbol "_smsFrom") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe String)))) ((:*:) * (S1 * (MetaSel (Just Symbol "_smsAction") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe URL))) ((:*:) * (S1 * (MetaSel (Just Symbol "_smsMethod") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Method))) (S1 * (MetaSel (Just Symbol "_smsStatusCallback") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe URL)))))))