smalltalk
/
osmo-st-sip
Archived
1
0
Fork 0

callagent: Add SIP UserAgent/Transport/Transaction code

The code is not yet fully working, it is missing sending
the request, dealing with timeouts, parsing the response,
callbacks and everything.
This commit is contained in:
Holger Hans Peter Freyther 2011-06-13 14:00:21 +02:00
parent b3d88db189
commit c9362c643e
8 changed files with 514 additions and 26 deletions

31
DESIGN Normal file
View File

@ -0,0 +1,31 @@
Some simple notes on SIP
- SIPGrammar parses and Request/Response
- SIPRequest is base to requests
- SIPResponse is the response class
- SIPDialog holds state of a dialogue
- to/from/to tag/from tag...
- call id... maybe SDP...
- SIPTransport is base class for the transport
- SIPUdpTransport sends and listens on UDP
- SIPUserAgent
- Holds a SIPTransport
- Generates various ids and fills requests
- Will dispatch response to the transaction
- SIPTransactionBase is the base for transactions
- SIPInviteTransaction is to create a call
Timeouts/Retransmission:
- good question, next question.. not solved yet
Limitations:
- Multiple Via's are not supported
- No retranmission, no response parsing..

189
callagent/SIPCallAgent.st Normal file
View File

@ -0,0 +1,189 @@
"
(C) 2011 by Holger Hans Peter Freyther
All Rights Reserved
This program is free software: you can redistribute it and/or modify
it under the terms of the GNU Affero General Public License as
published by the Free Software Foundation, either version 3 of the
License, or (at your option) any later version.
This program is distributed in the hope that it will be useful,
but WITHOUT ANY WARRANTY; without even the implied warranty of
MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
GNU Affero General Public License for more details.
You should have received a copy of the GNU Affero General Public License
along with this program. If not, see <http://www.gnu.org/licenses/>.
"
Object subclass: SIPTransport [
| queue sem handler |
<category: 'SIP-Callagent'>
<comment: 'I am the baseclass for a transport'>
SIPTransport class >> type [
<category: 'accessing'>
^ self subclassResponsibility
]
SIPTransport class >> new [
<category: 'creation'>
^ super new
initialize;
yourself
]
initialize [
queue := SharedQueue new.
sem := Semaphore forMutualExclusion.
]
queueData: aDatagram [
queue nextPut: aDatagram.
]
handleData: aData [
<category: 'private'>
[
handler isNil
ifTrue: [self logError: 'No handler for data.' area: #sip]
ifFalse: [handler transportData: self data: aData]
] on: Error do: [:e |
self logException: 'HandleData %1' % {e tag} area: #sip
]
]
handler: aHandler [
<category: 'configuration'>
handler := aHandler
]
address [
<category: 'accessing'>
^ self subclassResponsibility
]
type [
<category: 'accessing'>
^ self class type
]
]
SIPTransport subclass: SIPUdpTransport [
| socket rx tx |
<category: 'SIP-Callagent'>
<comment: 'I should share some things with MGCPCallAgent'>
SIPUdpTransport class >> type [
<category: 'accessing'>
^ 'UDP'
]
SIPUdpTransport class >> startOn: anAddress [
<category: 'factory'>
^ (self new)
initialize: anAddress;
yourself
]
address [
<category: 'accessing'>
^ socket address
]
initialize: anAddress [
sem := Semaphore forMutualExclusion.
socket := Sockets.DatagramSocket local: anAddress port: 5060.
]
start [
"Receive datagrams from the socket..."
rx := [
[ | data |
data := socket next.
data ifNotNil: [
sem critical: [self handleData: data].
].
] repeat.
] fork.
"Send data to the MGWs"
tx := [
[ | data |
data := queue next.
socket nextPut: data.
] repeat.
] fork.
]
]
Object subclass: SIPUserAgent [
| transport name last_cseq transactions |
<category: 'SIP-Callagent'>
<comment: 'I am a user agent'>
SIPUserAgent class >> createOn: aTransport [
<category: 'factory'>
^ self new
instVarNamed: #last_cseq put: 0;
transport: aTransport;
yourself
]
SIPUserAgent class >> branchStart [
<category: 'ids'>
"magic marker..."
^ 'z9hG4bK'
]
SIPUserAgent class >> generateBranch [
| data |
data := '%1,%2' % {DateTime now asUTC asSeconds. Random between: 0 and: 99999}.
^ SIPBase64 encode: data.
]
injectDefaults: aRequest [
aRequest addParameter: 'Max-Forwards' value: '70'.
aRequest addParameter: 'User-Agent' value: self name.
]
generateVia: aBranch [
<category: 'ids'>
^ 'SIP/2.0/%1 %2;branch=%3%4' %
{transport type. transport address.
self class branchStart. aBranch}
]
generateCSeq [
<category: 'helper'>
last_cseq := (last_cseq + 1) \\ (2 raisedTo: 31).
^ last_cseq
]
name [
<category: 'accessing'>
^ name ifNil: ['OsmoST-SIP 0.34']
]
transport: aTransport [
transport ifNotNil: [transport handler: nil].
transport := aTransport.
transport handler: self.
]
transportData: aTransport data: aData [
self notYetImplemented
]
transactions [
<category: 'private'>
^ transactions ifNil: [transactions := OrderedCollection new]
]
addTransaction: aTransaction [
self transactions add: aTransaction
]
]

95
callagent/SIPDialog.st Normal file
View File

@ -0,0 +1,95 @@
"
(C) 2011 by Holger Hans Peter Freyther
All Rights Reserved
This program is free software: you can redistribute it and/or modify
it under the terms of the GNU Affero General Public License as
published by the Free Software Foundation, either version 3 of the
License, or (at your option) any later version.
This program is distributed in the hope that it will be useful,
but WITHOUT ANY WARRANTY; without even the implied warranty of
MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
GNU Affero General Public License for more details.
You should have received a copy of the GNU Affero General Public License
along with this program. If not, see <http://www.gnu.org/licenses/>.
"
Object subclass: SIPDialog [
| from from_tag to to_tag dest_ip dest_port is_client call_id |
<comment: 'I represent a dialog between two parties'>
<category: 'SIP-Callagent'>
SIPDialog class >> generateTag [
^ SIPRandomHelper generateTag
]
SIPDialog class >> generateCallId [
^ SIPRandomHelper generateCallId
]
SIPDialog class >> fromUser: aFrom host: aHost port: aPort [
<category: 'factory'>
^ self new
instVarNamed: #from put: aFrom;
instVarNamed: #from_tag put: self generateTag;
instVarNamed: #dest_ip put: aHost;
instVarNamed: #dest_port put: aPort;
instVarNamed: #is_client put: true;
instVarNamed: #call_id put: self generateCallId;
yourself
]
isClient [
<category: 'direction'>
^ is_client
]
from: aFrom [
<category: 'accessing'>
from := aFrom
]
fromTag: aTag [
<category: 'accessing'>
from_tag := aTag
]
to: aTo [
<category: 'accessing'>
to := aTo
]
toTag: aTag [
<category: 'accessing'>
]
callId [
^ call_id
]
generateTo [
<category: 'message'>
^ to_tag isNil
ifTrue: ['<%1>' % {to}]
ifFalse: ['<%1>;tag=%2' % {to. to_tag}]
]
generateFrom [
<category: 'message'>
^ from_tag isNil
ifTrue: ['<%1>' % {from}]
ifFalse: ['<%1>;tag=%2' % {from. from_tag}]
]
destinationAddress [
^ is_client
ifTrue: [to]
ifFalse: [from]
]
from [
^ from
]
]

View File

@ -16,6 +16,8 @@
along with this program. If not, see <http://www.gnu.org/licenses/>.
"
PackageLoader fileInPackage: 'Sockets'.
Object subclass: SIPBase64 [
SIPBase64 class >> encode: aString [
^ (Base64MimeConverter mimeEncode: aString readStream) contents
@ -53,3 +55,19 @@ Object subclass: SIPSecureRandom [
]
]
]
Object subclass: SIPRandomHelper [
<comment: 'I help with generating numbers'>
SIPRandomHelper class >> generateTag [
<category: 'random'>
^ SIPBase64 encode: '%1%2' % {
DateTime now asSeconds. SIPSecureRandom nextInt}
]
SIPRandomHelper class >> generateCallId [
^ '%1@%2' % {
SIPBase64 encode: SIPSecureRandom nextInt asString.
Sockets.SocketAddress localHostName.}
]
]

View File

@ -19,23 +19,23 @@
"TODO: Compare with MGCPCommands and share code..."
Object subclass: SIPRequest [
| addr parameters sdp |
| addr parameters sdp dialog |
<comment: 'I should share a parent with MGCPCommand'>
<category: 'SIP-Callagent'>
sipAddr: anAddr [
<category: 'accessing'>
addr := anAddr
SIPRequest class >> from: aDialog [
^ self new
instVarNamed: #dialog put: aDialog;
yourself
]
sipAddr [
<category: 'accessing'>
^ addr
dialog [
^ dialog
]
parameters [
<category: 'accessing'>
^ parameters ifNil: [parameters := OrderedCollection new]
^ parameters ifNil: [parameters := Dictionary new]
]
sdp: aSDP [
@ -44,8 +44,9 @@ Object subclass: SIPRequest [
]
addParameter: name value: aValue [
"TODO: What about multiple Via's...?"
<category: 'accessing'>
self parameters add: '%1: %2' % {name. aValue}
self parameters at: name put: aValue.
]
asDatagram [
@ -53,45 +54,74 @@ Object subclass: SIPRequest [
out := WriteStream on: (String new).
out
nextPutAll: '%1 %2 SIP/2.0' % {self class verb. self sipAddr};
nextPutAll: '%1 %2 SIP/2.0' % {self class verb. dialog destinationAddress};
cr; nl.
self parameters do: [:each |
out nextPutAll: each; cr; nl
self parameters keysAndValuesDo: [:key :value |
out
nextPutAll: key;
nextPutAll: ': ';
nextPutAll: value;
cr; nl.
].
out cr; nl.
self addDefaults: out.
sdp ifNotNil: [
out nextPutAll: sdp
sdp isNil
ifTrue: [out cr; nl.]
ifFalse: [
out
nextPutAll: 'Content-Type: application/sdp'; cr; nl;
nextPutAll: 'Content-Length: '; nextPutAll: sdp size asString; cr; nl;
cr; nl;
nextPutAll: sdp.
].
^ out contents
]
]
SIPRequest subclass: SIPInviteCommand [
<category: 'SIP-Callagent'>
SIPInviteCommand class >> verb [
<category: 'verb'>
^ 'INVITE'
addDefaults: out [
self parameters at: 'To' ifAbsent: [
out
nextPutAll: 'To: %1' % {dialog generateTo}; cr;nl].
self parameters at: 'From' ifAbsent: [
out
nextPutAll: 'From: %1' % {dialog generateFrom}; cr;nl].
]
]
SIPRequest subclass: SIPCancelCommand [
SIPRequest subclass: SIPInviteRequest [
<category: 'SIP-Callagent'>
SIPCancelCommand class >> verb [
SIPInviteRequest class >> verb [
<category: 'verb'>
^ 'INVITE'
]
addDefaults: out [
super addDefaults: out.
self parameters at: 'Contact' ifAbsent: [
out nextPutAll: 'Contact: ';
nextPutAll: dialog from;
cr; nl.
].
]
]
SIPRequest subclass: SIPCancelRequest [
<category: 'SIP-Callagent'>
SIPCancelRequest class >> verb [
<category: 'verb'>
^ 'CANCEL'
]
]
SIPRequest subclass: SIPByeCommand [
SIPRequest subclass: SIPByeRequest [
<category: 'SIP-Callagent'>
SIPByeCommand class >> verb [
SIPByeRequest class >> verb [
<category: 'verb'>
^ 'BYE'
]

View File

@ -0,0 +1,116 @@
"
(C) 2011 by Holger Hans Peter Freyther
All Rights Reserved
This program is free software: you can redistribute it and/or modify
it under the terms of the GNU Affero General Public License as
published by the Free Software Foundation, either version 3 of the
License, or (at your option) any later version.
This program is distributed in the hope that it will be useful,
but WITHOUT ANY WARRANTY; without even the implied warranty of
MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
GNU Affero General Public License for more details.
You should have received a copy of the GNU Affero General Public License
along with this program. If not, see <http://www.gnu.org/licenses/>.
"
Object subclass: SIPTransaction [
| useragent dialog state timeout success failure cseq branch |
SIPTransaction class >> stateInitial [ ^ 0 ]
SIPTransaction class >> stateTrying [ ^ 1 ]
SIPTransaction class >> stateProceeding [ ^ 2 ]
SIPTransaction class >> stateCompleted [ ^ 3 ]
SIPTransaction class >> stateTerminated [ ^ 4 ]
dialog: aDialog [
dialog := aDialog
]
userAgent: aUA [
<category: 'accessing'>
useragent := aUA
]
state [
^ state ifNil: [^ self class stateInitial]
]
timeout: aTimeout [
timeout := aTimeout
]
success: aSuc [
success := aSuc
]
failure: aFail [
failure := aFail
]
setupTransaction [
"I setup the transaction"
useragent addTransaction: self.
cseq := useragent generateCSeq.
branch := useragent class generateBranch.
]
]
SIPTransaction subclass: SIPInviteTransaction [
| sdp t1 |
<category: 'RFC3161 17.2.1'>
"200ms to get TRYING or OK"
SIPInviteTransaction class >> createWith: aDialog on: aUA with: aSDP [
^ self new
instVarNamed: #sdp put: aSDP;
userAgent: aUA;
dialog: aDialog;
setupTransaction;
yourself.
]
start [
| invite |
state = self class stateInitial ifFalse: [
^ self error: 'Can not restart.'
].
"Enter the state, remember the timeout"
state := self class stateTrying.
t1 := DateTime now.
invite := self createInvite.
]
checkTimeout: now [
"Check if a timeout has happened"
self state = self class stateTrying ifTrue: [
t1 > now ifTrue: [
^ true
]
].
^ false
]
createInvite [
| invite |
<category: 'invite'>
invite := (SIPInviteRequest from: dialog)
sdp: sdp;
addParameter: 'Via' value: (useragent generateVia: branch);
addParameter: 'CSeq' value: '%1 %2' % {cseq. 'INVITE'};
addParameter: 'Allow' value: 'ACK,BYE';
addParameter: 'Call-ID' value: dialog callId;
yourself.
useragent injectDefaults: invite.
^ invite
]
]

View File

@ -2,6 +2,15 @@
<name>OsmoSIP</name>
<namespace>Osmo</namespace>
<filein>callagent/Base64MimeConverter.st</filein>
<filein>callagent/SIPCallAgent.st</filein>
<filein>callagent/SIPDialog.st</filein>
<filein>callagent/SIPLogArea.st</filein>
<filein>callagent/SIPRandom.st</filein>
<filein>callagent/SIPRequests.st</filein>
<filein>callagent/SIPResponse.st</filein>
<filein>callagent/SIPTransactions.st</filein>
<filein>grammar/SIPGrammar.st</filein>
<test>