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

385 lines
11 KiB
Smalltalk

"
(C) 2011-2012 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/>.
"
SIPRequest extend [
sipDispatchNewDialog: aDialog on: aUserAgent [
<category: 'OsmoSIP-Callagent'>
self logError: 'Unknown action for ', self class name area: #sip.
]
]
SIPByeRequest extend [
sipDispatchNewDialog: aDialog on: aUserAgent [
<category: 'OsmoSIP-Callagent'>
self logNotice: 'Unknown call ', self class name area: #sip.
aUserAgent
respondWith: 481
phrase: 'Call/Transaction Does Not Existing'
on: self
dialog: aDialog.
]
]
SIPOptionsRequest extend [
sipDispatchNewDialog: aDialog on: aUserAgent [
<category: 'OsmoSIP-Callagent'>
aUserAgent
respondWith: 481
phrase: 'Call Leg/Transaction Does Not Exist'
on: self
dialog: aDialog.
]
]
Object subclass: SIPTransport [
| handler |
<category: 'OsmoSIP-Callagent'>
<comment: 'I am the baseclass for a transport'>
SIPTransport class >> type [
<category: 'accessing'>
^ self subclassResponsibility
]
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 <1p>'
expandMacrosWith: 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 net |
<category: 'OsmoSIP-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.
net := Osmo.OsmoUDPSocket new
name: 'SIPTransport';
onData: [:data |self handleData: data];
yourself
]
queueDatagram: aDatagram [
<category: 'output'>
net queueData: aDatagram.
]
stop [
<category: 'lifetime'>
net stop.
socket := nil.
]
start [
net start: socket.
]
]
Object subclass: SIPUserAgentBase [
| transport name |
<category: 'OsmoSIP-Callagent'>
<comment: 'I am a user agent base'>
SIPUserAgentBase class >> createOn: aTransport [
<category: 'factory'>
^ self new
transport: aTransport;
yourself
]
SIPUserAgentBase class >> branchStart [
<category: 'ids'>
"magic marker..."
^ 'z9hG4bK'
]
SIPUserAgentBase class >> generateBranch [
| data |
data := '<1p>,<2p>' expandMacrosWithArguments:
{DateTime now asUTC asSeconds. Random between: 0 and: 99999}.
^ self branchStart, (SIPBase64 encode: data).
]
SIPUserAgentBase class >> generateCSeq [
<category: 'helper'>
"CSeq must be < 2^31 but Random only allows 2^29"
^ Random between: 1 and: (1 raisedTo: 29).
]
injectDefaults: aRequest [
aRequest addParameter: 'Max-Forwards' value: '70'.
aRequest addParameter: 'User-Agent' value: self name.
]
generateVia: aBranch [
<category: 'ids'>
^ (WriteStream on: String new)
nextPutAll: 'SIP/2.0/';
nextPutAll: transport type;
nextPutAll: ' ';
nextPutAll: transport address printString;
nextPutAll: ':';
nextPutAll: transport port asString;
nextPutAll: ';branch=';
nextPutAll: aBranch;
contents.
]
name [
<category: 'accessing'>
^ name ifNil: ['OsmoST-SIP 0.34']
]
transport: aTransport [
transport ifNotNil: [transport handler: nil].
transport := aTransport.
transport handler: self.
]
transport [
<category: 'accessing'>
^ transport
]
queueData: aData dialog: aDialog [
| datagram |
<category: 'output'>
datagram := Sockets.Datagram
data: aData
address: (Sockets.SocketAddress
byName: aDialog destIp)
port: aDialog destPort.
transport queueDatagram: datagram.
]
]
SIPUserAgentBase subclass: SIPUserAgent [
| dialogs transactions retransmit sem parser |
<category: 'OsmoSIP-Callagent'>
<comment: 'I am a user agent base'>
SIPUserAgent class >> new [
<category: 'creation'>
^ super new
initialize;
yourself
]
initialize [
<category: 'creation'>
sem := Semaphore forMutualExclusion.
]
dialogs [
<category: 'private'>
^ dialogs ifNil: [dialogs := OrderedCollection new]
]
registerDialog: aDialog [
<category: 'dialogs'>
sem critical: [
self dialogs add: aDialog]
]
unregisterDialog: aDialog [
<category: 'dialogs'>
sem critical: [
self dialogs remove: aDialog ifAbsent: [
self logError: ('<1p> dialog <2p> is not present.' expandMacrosWithArguments:
{self. aDialog}) area: #sip]]
]
transactions [
<category: 'private'>
^ transactions ifNil: [transactions := OrderedCollection new]
]
addTransaction: aTransaction [
<category: 'transactions'>
sem critical: [
self transactions add: aTransaction]
]
removeTransaction: aTransaction [
<category: 'transactions'>
sem critical: [
self transactions remove: aTransaction ifAbsent: [
self logError: ('<1p> transaction <2p> is not present.'
expandMacrosWithArguments: {self. aTransaction}) area: #sip.]].
]
dispatchRequest: aReq data: aDatagram [
| dialogs dialog |
<category: 'dispatch'>
dialog := (SIPDialog fromMessage: aReq)
destIp: aDatagram address displayString;
destPort: aDatagram port;
yourself.
dialogs := sem critical: [self dialogs copy].
dialogs do: [:each |
(each isCompatible: dialog) ifTrue: [
each newRequest: aReq.
^ self
]].
self newDialog: dialog request: aReq.
]
dispatchResponse: aReq [
| branch trans |
<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
].
trans := sem critical: [self transactions copy].
trans do: [:each |
each branch = branch ifTrue: [
each newData: aReq.
].
]
]
transportData: aTransport data: aData [
<category: 'private'>
OsmoDispatcher dispatchBlock: [self transportDataInternal: aData].
]
parser [
<category: 'parser'>
^ parser ifNil: [parser := SIPParser new]
]
transportDataInternal: aData [
| req data |
<category: 'private'>
[
data := aData data copyFrom: 1 to: aData size.
req := self parser parse: data asString onError: [:e |
data printNl.
self logError: ('Failed to parse: "<1p>" with <2p>'
expandMacrosWithArguments: {data asString. e}) area: #sip.
^ false
].
req isRequest
ifTrue: [self dispatchRequest: req data: aData]
ifFalse: [self dispatchResponse: req].
] on: Error do: [:e |
e logException: ('Parsing error <1p>' expandMacrosWith: e tag) area: #sip.
]
]
respondWith: aCode phrase: aPhrase on: aRequest dialog: dialog [
| resp via cseq |
<category: 'Sending'>
via := aRequest parameter: 'Via' ifAbsent: [^ self].
cseq := aRequest parameter: 'CSeq' ifAbsent: [^ self].
resp := (SIPResponse code: aCode with: aPhrase)
addParameter: 'Via' value: (self generateVia: via branch);
addParameter: 'From' value: dialog generateTo;
addParameter: 'To' value: dialog generateFrom;
addParameter: 'Call-ID' value: dialog callId;
addParameter: 'CSeq' value: ('<1p> <2s>'
expandMacrosWith: cseq with: cseq method);
addParameter: 'Allow' value: 'ACK,BYE';
yourself.
self injectDefaults: resp.
self queueData: resp asDatagram dialog: dialog.
]
newDialog: aDialog request: aRequest [
<category: 'We have a new dialog'>
"This might be a re-transmit of a BYE. So we will use the
double dispatch to check what we should do with this dialog."
aRequest sipDispatchNewDialog: aDialog on: self.
]
]