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

Contents

Description

The examples in this file assume

{-# 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 <Dial>.

Synopsis

Documentation

dial :: IsTwimlLike f Dial => String -> DialAttributes -> TwimlLike f Dial () Source #

Dial a number. Example:

>>> :{
let example1 :: VoiceTwiml
    example1 =
      voiceResponse $ do
        dial "415-123-4567" def
        say "Goodbye" def
        end
      where Twiml.Syntax{..} = def
:}
>>> putStr $ show example1
<?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:

>>> :{
let example2 :: VoiceTwiml
    example2 =
      voiceResponse $ do
        dial' (Left . dialNoun $ number "+15558675309" def) $
          def & callerId .~ Just "+15551112222"
        end
      where Twiml.Syntax{..} = def
:}
>>> putStr $ show example2
<?xml version="1.0" encoding="UTF-8"?>
<Response>
  <Dial callerId="+15551112222">
    <Number>+15558675309</Number>
  </Dial>
</Response>

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

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 # 

Nouns

data DialNounF i a Source #

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.1.0-8vOgp92H6HZKjscJQqq5Ao" 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 :: [Type]) a Source #

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 #

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.1.0-8vOgp92H6HZKjscJQqq5Ao" 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 :: [Type]) 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.1.0-8vOgp92H6HZKjscJQqq5Ao" 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 :: [Type]) a Source #

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 #

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 :: [Type]) a Source #

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 #

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.1.0-8vOgp92H6HZKjscJQqq5Ao" 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 :: [Type]) a Source #

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 #