smalltalk
/
osmo-st-sip
Archived
1
0
Fork 0
This repository has been archived on 2022-02-17. You can view files and clone it, but cannot push or open issues or pull requests.
osmo-st-sip/callagent/SIPCallAgent.st

283 lines
6.8 KiB
Smalltalk

"
(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/>.
"
PackageLoader fileInPackage: 'Sockets'.
Object subclass: SIPTransport [
| queue 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
]
closeSocket [
]
initialize [
queue := SharedQueue new.
]
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
]
port [
<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 port: aPort [
<category: 'factory'>
^ (self new)
initialize: anAddress port: aPort;
yourself
]
SIPUdpTransport class >> startOn: anAddress [
^ self startOn: anAddress port: 5060.
]
address [
<category: 'accessing'>
^ socket address
]
port [
<category: 'accessing'>
^ socket port
]
initialize: anAddress port: aPort [
socket := Sockets.DatagramSocket local: anAddress port: aPort.
socket
bufferSize: 2048;
addToBeFinalized.
]
closeSocket [
socket close.
]
start [
"Receive datagrams from the socket..."
rx := [
[ | data |
data := socket next.
data ifNotNil: [
self handleData: data.
].
] repeat.
] fork.
"Send data to the MGWs"
tx := [
[ | data |
data := queue next.
socket nextPut: data.
] repeat.
] fork.
]
]
Object subclass: SIPUserAgentBase [
| transport name last_cseq |
<category: 'SIP-Callagent'>
<comment: 'I am a user agent base'>
SIPUserAgentBase class >> createOn: aTransport [
<category: 'factory'>
^ self new
instVarNamed: #last_cseq put: 0;
transport: aTransport;
yourself
]
SIPUserAgentBase class >> branchStart [
<category: 'ids'>
"magic marker..."
^ 'z9hG4bK'
]
SIPUserAgentBase class >> generateBranch [
| data |
data := '%1,%2' % {DateTime now asUTC asSeconds. Random between: 0 and: 99999}.
^ self branchStart, (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:%3;branch=%4' %
{transport type. transport address. transport port. 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.
]
queueData: aDatagram [
transport queueData: aDatagram.
]
]
SIPUserAgentBase subclass: SIPUserAgent [
| transactions retransmit sem |
<category: 'SIP-Callagent'>
<comment: 'I am a user agent base'>
transactions [
<category: 'private'>
^ transactions ifNil: [transactions := OrderedCollection new]
]
checkTimeout [
<category: 'transactions'>
self transactions do: [:trans |
[trans checkTimeout] on: Error do: [:e |
e logException: 'Exception on timeout: %1' % {e tag} area: #sip.
]
]
]
addTransaction: aTransaction [
<category: 'transactions'>
sem critical: [
self transactions add: aTransaction]
]
start [
<category: 'process'>
sem := Semaphore forMutualExclusion.
retransmit := [
[
(Delay forMilliseconds: 500) wait.
sem critical: [self checkTimeout].
] repeat
] fork.
]
dispatchRequest: aReq [
<category: 'dispatch'>
self logError: 'Requests are not implemented yet' area: #sip.
self notYetImplemented.
]
dispatchResponse: aReq [
| branch |
<category: 'dispatch'>
branch := (aReq parameter: 'Via') branch.
"Check if the new RFC is implemented"
(branch copyFrom: 1 to: 7) = self class branchStart ifFalse: [
self logError: 'Branch does not start with magic cookie' area: #sip.
^ false
].
self transactions do: [:trans |
trans branch = branch ifTrue: [
trans newData: aReq.
].
]
]
transportData: aTransport data: aData [
| req data |
[
data := aData data copyFrom: 1 to: aData size.
req := SIPParser parse: data asString.
sem critical: [
req isRequest
ifTrue: [self dispatchRequest: req]
ifFalse: [self dispatchResponse: req]].
] on: Error do: [:e |
e logException: 'Parsing error %1' % {e tag} area: #sip.
]
]
]