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

gsm: Introduce the concept of an authenticator for a channel

The role of the authenticator is to collect information about
the subscriber and allow the GSMProcessor to accept the service,
enable encryptionor whatever is needed.
This commit is contained in:
Holger Hans Peter Freyther 2012-10-28 10:36:06 +01:00
parent e0ddeacc00
commit 259976e68a
2 changed files with 156 additions and 9 deletions

78
src/GSMAuthenticator.st Normal file
View File

@ -0,0 +1,78 @@
"
(C) 2010-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/>.
"
Object subclass: GSMAuthenticatorBase [
| connection onAccept onReject |
<category: 'OsmoMSC-GSM-Authentication'>
<comment: 'I am the base class for authenticating a given
subscriber. My subclasses can either allow everyone, store
the IMSI and IMEI or be fully GSM compliant and ask a HLR
for an authentication tuple.'>
connection: aCon [
<category: 'creation'>
connection := aCon.
]
onAccept: aBlock [
<category: 'creation'>
"Called when the connection is accepted"
onAccept := aBlock
]
onReject: aBlock [
<category: 'creation'>
"Called when the connection is rejected"
onReject := aBlock
]
start: aMsg [
<category: 'auth'>
"Start authentication with the initial message."
^ self subclassResponsibility
]
onData: aMsg [
<category: 'auth'>
"Called with data from the GSM connection"
^ self subclassResponsibility
]
cancel [
<category: 'auth'>
"The GSM Connection has failed cancel everything."
^ self subclassResponsibility
]
]
GSMAuthenticatorBase subclass: GSMNullAuthenticator [
<category: 'OsmoMSC-GSM-Authentication'>
<comment: 'I accept everything...'>
start: aMsg [
onAccept value: self.
]
onData: aMsg [
^ self shouldNotImplement
]
cancel [
"Nothing"
]
]

View File

@ -1,5 +1,5 @@
"
(C) 2010-2011 by Holger Hans Peter Freyther
(C) 2010-2012 by Holger Hans Peter Freyther
All Rights Reserved
This program is free software: you can redistribute it and/or modify
@ -127,7 +127,7 @@ GSM transaction on a given SAPI'>
]
OsmoGSM.SCCPConnectionBase subclass: GSMProcessor [
| transactions state endp connId mgcp_trans |
| transactions state endp connId mgcp_trans auth pending |
<category: 'OsmoMSC-GSM'>
<comment: 'I am driving a SCCP Connection. This consists of being
@ -136,8 +136,14 @@ hosting various transactions and dispatching to them.'>
GSMProcessor class >> stateInitial [<category: 'states'> ^ 0 ]
GSMProcessor class >> stateAcked [<category: 'states'> ^ 1 ]
GSMProcessor class >> stateRelease [<category: 'states'> ^ 2 ]
GSMProcessor class >> stateError [<category: 'states'> ^ 3 ]
GSMProcessor class >> stateAuth [<category: 'states'> ^ 2 ]
GSMProcessor class >> stateRelease [<category: 'states'> ^ 3 ]
GSMProcessor class >> stateError [<category: 'states'> ^ 4 ]
GSMProcessor class >> authenticator [
<category: 'authenticator'>
^ GSMNullAuthenticator
]
GSMProcessor class >> createAssignment: aMul timeslot: aTs [
| ass |
@ -218,9 +224,11 @@ hosting various transactions and dispatching to them.'>
mapClearCompl: aData [
<category: 'BSSMAP'>
sem critical: [
self verifyState: [state = self class stateRelease].
self releaseAudio.
self release.
self
verifyState: [state = self class stateRelease];
releaseAudio;
releaseAuth;
release.
].
]
@ -242,7 +250,9 @@ hosting various transactions and dispatching to them.'>
].
transactions := OrderedCollection new.
self releaseAudio.
self
releaseAudio;
releaseAuth.
].
]
@ -300,7 +310,31 @@ hosting various transactions and dispatching to them.'>
openTransaction: aTran with: aMsg [
<category: 'transaction'>
self addTransaction: aTran.
aTran start: aMsg.
"The authentication has happend, just start the transaction."
self state = self class stateAuth ifTrue: [
^ aTran start: aMsg
].
"An authentication is pending."
auth isNil ifFalse: [
self logNotice: 'GSMProc(srcref:%1) auth pending.'
% {self srcRef} area: #bsc.
pending add: (aTran -> aMsg).
^ true.
].
"Remember to launch this transaction"
pending := OrderedCollection new
add: (aTran -> aMsg);
yourself.
auth := self class authenticator new
connection: self;
onAccept: [:auth | self takeLocks: [ self authenticationAccepted]];
onReject: [:auth | self takeLocks: [ self authenticationRejected]];
yourself.
auth start.
]
addTransaction: aTran [
@ -331,6 +365,11 @@ hosting various transactions and dispatching to them.'>
<category: 'private'>
"Must be locked"
"Pass everything to the authenticator if present."
auth isNil ifFalse: [
^ auth onData: aMsg.
].
"Find an active transaction for this"
transactions do: [:each |
(each sapi = aSapi and: [each ti = aMsg ti]) ifTrue: [
@ -397,6 +436,16 @@ hosting various transactions and dispatching to them.'>
selectAudioRoute: self plan: aPlan leg: aLeg
]
releaseAuth [
<category: 'auth'>
auth isNil
ifTrue: [^true].
"Give up on the authentication."
auth cancel.
auth := nil.
]
releaseAudio [
"I try to release things right now."
<category: 'audio'>
@ -654,4 +703,24 @@ hosting various transactions and dispatching to them.'>
mdcxTimeout: aTimeout [
]
authenticationAccepted [
<category: 'auth'>
"Must be locked"
auth := nil.
pending do: [:each |
each key start: each value].
pending := nil.
]
authenticationRejected [
<category: 'auth'>
"Must be locked"
"TODO"
"Send a CM Service Request to the phone"
"Close down the connection. FIXME: use a better error value"
self clearCommand: 0.
]
]