smalltalk
/
osmo-st-all
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-all/osmo-st-sip/callagent/transactions/SIPTransaction.st

441 lines
14 KiB
Smalltalk

"
(C) 2011,2014 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 [
| sem useragent initial_dialog state timeout success failure notification
cseq branch retransmit_time fail_time removal
authorization last_was_auth proxy_authorization last_was_proxy_auth |
<category: 'OsmoSIP-Callagent'>
SIPTransaction class >> stateInitial [ <category: 'states'> ^ #initial ]
SIPTransaction class >> stateTrying [ <category: 'states'> ^ #trying ]
SIPTransaction class >> stateProceeding [ <category: 'states'> ^ #proceeding ]
SIPTransaction class >> stateCompleted [ <category: 'states'> ^ #completed ]
SIPTransaction class >> stateTerminated [ <category: 'states'> ^ #terminated ]
SIPTransaction class >> stateCanceled [ <category: 'states'> ^ #canceled ]
Grammar := nil.
SIPTransaction class >> createWith: aDialog on: aUA cseq: aCseq [
<category: 'creation'>
^ self new
initialize;
userAgent: aUA;
initialDialog: aDialog;
setupTransaction: aCseq;
yourself.
]
SIPTransaction class >> grammar [
<category: 'private'>
^ Grammar ifNil: [Grammar := SIPGrammar new]
]
SIPTransaction class >> verifyGrammar: aData [
<category: 'private'>
self grammar parse: aData onError: [:e |
e logException: 'Outgoing data has parsing error' area: #sip.
e signal
]
]
initialize [
<category: 'creation'>
sem := RecursionLock new.
last_was_auth := false.
last_was_proxy_auth := false.
]
initialDialog: aDialog [
<category: 'creation'>
initial_dialog := aDialog
]
userAgent: aUA [
<category: 'creation'>
useragent := aUA
]
state [
<category: 'state'>
^ state ifNil: [^ self class stateInitial]
]
changeState: aState [
<category: 'state'>
"I could verify the state change here"
sem critical: [
state := aState.
].
]
onTimeout: aTimeout [
<category: 'setup'>
timeout := aTimeout
]
onSuccess: aSuc [
<category: 'setup'>
success := aSuc
]
onFailure: aFail [
<category: 'setup'>
failure := aFail
]
onNotification: aNot [
<category: 'setup'>
notification := aNot
]
setupTransaction: aCseq [
<category: 'private'>
"I setup the transaction"
useragent addTransaction: self.
cseq := aCseq.
branch := useragent class generateBranch.
]
queueData: aData dialog: aDialog [
<category: 'private'>
"validate the output"
self class verifyGrammar: aData.
useragent queueData: aData dialog: aDialog.
]
branch [
<category: 'accessing'>
^ branch
]
respNotification: aResp dialog: aDialog [
<category: 'private-dispatch'>
self changeState: self class stateProceeding.
notification ifNotNil: [
notification value: aResp value: aDialog]
]
respSuccess: aResp dialog: aDialog [
<category: 'private-dispatch'>
self changeState: self class stateCompleted.
self removeTransaction.
^ success isNil
ifTrue: [true]
ifFalse: [success value: aResp value: aDialog].
]
respFailure: aResp dialog: aDialog [
<category: 'private-dispatch'>
self removeTransaction.
failure ifNotNil: [
failure value: aResp value: aDialog]
]
wrongAuth: aResp dialog: aDialog [
<category: 'private-dispatch'>
self logError: ('<1p>(<2p>) response lacks WWW-Authenticate'
expandMacrosWith: self class with: self branch) area: #sip.
self removeTransaction.
failure ifNotNil: [
failure value: aResp value: aDialog]
]
respAuthRequired: aResp dialog: aDialog [
| auth |
<category: 'private-dispatch'>
"We are running in circles so better cancel it"
last_was_auth ifTrue: [
^self respFailure: aResp dialog: aDialog].
last_was_auth := true.
auth := aResp parameter: 'WWW-Authenticate' ifAbsent: [nil].
auth ifNil: [^self wrongAuth: aResp dialog: aDialog].
((auth at: 'algorithm' ifAbsent: ['MD5']) = 'MD5')
ifFalse: [^self wrongAuth: aResp dialog: aDialog].
"Respond with an ACK"
self queueData: (self createAck: branch dialog: aDialog) asDatagram
dialog: aDialog.
authorization := SIPAuthorization new
username: initial_dialog identity username;
realm: (auth at: 'realm');
nonce: (auth at: 'nonce');
uri: initial_dialog destinationAddress;
yourself.
authorization
calculateResponse: initial_dialog identity password
operation: self class operationName.
"Increase CSeq and generate a new branch"
cseq := cseq + 1.
branch := useragent class generateBranch.
"Now start again with the auth part"
self retransmit.
]
respProxyAuthRequired: aResp dialog: aDialog [
| auth |
<category: 'private-dispatch'>
"TODO... fix the duplication"
"We are running in circles so better cancel it. Not quite correct
though. There could be multiple proxies. So we should compare the
realm, nonce, etc. We would actually need to have a list of proxy
auths for full spec compliance."
last_was_proxy_auth ifTrue: [
^self respFailure: aResp dialog: aDialog].
last_was_proxy_auth := true.
auth := aResp parameter: 'Proxy-Authenticate' ifAbsent: [nil].
auth ifNil: [^self wrongAuth: aResp dialog: aDialog].
((auth at: 'algorithm' ifAbsent: ['MD5']) = 'MD5')
ifFalse: [^self wrongAuth: aResp dialog: aDialog].
((auth at: 'qop' ifAbsent: ['auth']) = 'auth')
ifFalse: [^self wrongAuth: aResp dialog: aDialog].
"Respond with an ACK"
self queueData: (self createAck: branch dialog: aDialog) asDatagram
dialog: aDialog.
proxy_authorization := SIPProxyAuthorization new
username: initial_dialog identity proxyUsername;
realm: (auth at: 'realm');
nonce: (auth at: 'nonce');
qop: (auth at: 'qop' ifAbsent: ['auth']);
cnonce: SIPURandom newClientNonce;
uri: initial_dialog destinationAddress;
yourself.
"Increase CSeq and generate a new branch"
cseq := cseq + 1.
branch := useragent class generateBranch.
"Now start again with the auth part"
self retransmit.
]
checkSequenceNumber: aReq [
| new_cseq |
<category: 'private-dispatch'>
"I have to verify the sequence numbers..."
new_cseq := (aReq parameter: 'CSeq' ifAbsent: [
self logError: ('<1p>(<2p>) response lacks CSeq.'
expandMacrosWith: self class with: self branch) area: #sip.
^ false
]) number.
cseq = new_cseq ifFalse: [
self logError: ('<1p>(<2p>) wrong cseq:. <1p> <2p>.' expandMacrosWithArguments:
{self class. self branch. cseq. new_cseq}) area: #sip.
^ false
].
^ true
]
stopRetransmitTimer [
<category: 'private'>
"I stop the retransmit timers, e.g. because there was a request,
or there was a timeout, or someone canceled things."
sem critical: [
retransmit_time cancel.
fail_time cancel.
]
]
newData: aResp [
| dialog |
<category: 'private-dispatch'>
(self checkSequenceNumber: aResp) ifFalse: [^ false].
"Store all dialogs.... and match them..."
dialog := initial_dialog newFromRequest: aResp.
"Forget the authorization now"
authorization := nil.
self stopRetransmitTimer.
self dispatchDialog: dialog response: aResp.
]
dispatchDialog: dialog response: aResp [
| code |
<category: 'private-dispatch'>
code := aResp code asInteger.
code < 200 ifTrue: [
"Ignore 100 TRYING"
^ self respNotification: aResp dialog: dialog
].
code = 200 ifTrue: [
last_was_auth := false.
last_was_proxy_auth := false.
^ self respSuccess: aResp dialog: dialog
].
code = 401 ifTrue: [
last_was_proxy_auth := false.
^self respAuthRequired: aResp dialog: dialog.
].
code = 407 ifTrue: [
last_was_auth := false.
^self respProxyAuthRequired: aResp dialog: dialog.
].
code > 200 ifTrue: [
last_was_auth := false.
last_was_proxy_auth := false.
^ self respFailure: aResp dialog: dialog
]
]
start [
sem critical: [
self state = self class stateInitial ifFalse: [
^ self error: 'Can not restart.'
].
"Enter the state, remember the timeout"
self changeState: self class stateTrying.
fail_time := Osmo.TimerScheduler instance
scheduleInSeconds: 60 block:
[sem critical: [self timedout]].
self retransmit.
]
]
retransmit [
<category: 'timeout'>
retransmit_time := Osmo.TimerScheduler instance
scheduleInSeconds: 10 block:
[sem critical: [self retransmit]].
self transmit.
]
timedout [
<category: 'timeout'>
useragent removeTransaction: self.
self stopRetransmitTimer.
timeout value.
]
removeTransaction [
<category: 'timeout'>
"We want to remove things but we might get a late reply due a packet loss."
removal ifNil: [
removal := Osmo.TimerScheduler instance
scheduleInSeconds: 50 block:
[sem critical: [useragent removeTransaction: self]]].
]
addAuthorizationTo: aRequest [
<category: 'authentication'>
authorization ifNotNil: [
aRequest addParameter: 'Authorization' value: authorization].
proxy_authorization ifNotNil: [
proxy_authorization incrementClientNonce.
proxy_authorization
calculateResponse: initial_dialog identity proxyPassword
operation: self class operationName.
aRequest addParameter: 'Proxy-Authorization' value: proxy_authorization].
]
createInvite: sdp [
| invite |
<category: 'invite'>
invite := (SIPInviteRequest from: initial_dialog)
sdp: sdp;
addParameter: 'Via' value: (useragent generateVia: branch);
addParameter: 'CSeq' value: ('<1p> <2s>'
expandMacrosWith: cseq with: 'INVITE');
addParameter: 'Allow' value: 'ACK,BYE';
addParameter: 'Call-ID' value: initial_dialog callId;
yourself.
self addAuthorizationTo: invite.
useragent injectDefaults: invite.
^ invite
]
createAck: aBranch dialog: aDialog [
| ack |
<category: 'ack'>
ack := (SIPACKRequest from: aDialog)
addParameter: 'Via' value: (useragent generateVia: aBranch);
addParameter: 'CSeq' value: ('<1p> <2s>'
expandMacrosWith: cseq with: 'ACK');
addParameter: 'Call-ID' value: aDialog callId;
yourself.
self addAuthorizationTo: ack.
useragent injectDefaults: ack.
^ ack
]
createBye: aDialog [
| bye |
<category: 'invite'>
bye := (SIPByeRequest from: aDialog)
addParameter: 'Via' value: (useragent generateVia: branch);
addParameter: 'CSeq' value: ('<1p> <2s>'
expandMacrosWith: cseq with: 'BYE');
addParameter: 'Call-ID' value: aDialog callId;
yourself.
self addAuthorizationTo: bye.
useragent injectDefaults: bye.
^ bye
]
createCancel [
| cancel |
<category: 'cancel'>
cancel := (SIPCancelRequest from: initial_dialog)
addParameter: 'Via' value: (useragent generateVia: branch);
addParameter: 'CSeq' value: ('<1p> <2s>'
expandMacrosWith: cseq with: 'CANCEL');
addParameter: 'Call-ID' value: initial_dialog callId;
yourself.
self addAuthorizationTo: cancel.
useragent injectDefaults: cancel.
^ cancel.
]
]