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

misc: Provide proper categories for the classes

This commit is contained in:
Holger Hans Peter Freyther 2011-09-27 17:59:10 +02:00
parent 141f7c640f
commit 637f2f821e
12 changed files with 67 additions and 15 deletions

View File

@ -22,7 +22,7 @@ I am helping to get things started on the first image resume
PackageLoader fileInPackage: #OsmoMSC. PackageLoader fileInPackage: #OsmoMSC.
Object subclass: Loader [ Object subclass: Loader [
<category: 'MSC-Loader'> <category: 'OsmoMSC-Loader'>
<comment: 'I wait for the image to resume and then I start the <comment: 'I wait for the image to resume and then I start the
MSC example application and put it into the OsmoMSC namespace.'> MSC example application and put it into the OsmoMSC namespace.'>

View File

@ -20,8 +20,9 @@ PackageLoader fileInPackage: #Sockets.
Object subclass: BSCConfigItem [ Object subclass: BSCConfigItem [
| peer token name lac connected | | peer token name lac connected |
<category: 'MSC-BSC'>
<comment: 'I hold the configuration for one BJSC Item. It consists of the <category: 'OsmoMSC-BSC'>
<comment: 'I hold the configuration for one BSC Item. It consists of the
peer address, the lac, if it is connected'> peer address, the lac, if it is connected'>
BSCConfigItem class >> initWith: aPeer name: aName [ BSCConfigItem class >> initWith: aPeer name: aName [
@ -63,7 +64,8 @@ peer address, the lac, if it is connected'>
Object subclass: BSCConfig [ Object subclass: BSCConfig [
| bscList | | bscList |
<category: 'MSC-BSC'>
<category: 'OsmoMSC-BSC'>
<comment: 'I know the BSCs that can connect to me'> <comment: 'I know the BSCs that can connect to me'>
removeBSC: aPeer [ removeBSC: aPeer [

View File

@ -22,6 +22,8 @@ PackageLoader
OsmoGSM.SCCPHandler subclass: BSCSCCPHandler [ OsmoGSM.SCCPHandler subclass: BSCSCCPHandler [
| bsc msc | | bsc msc |
<category: 'OsmoMSC-BSC'>
<comment: 'I handle SCCP for the MSC/BSC connection'> <comment: 'I handle SCCP for the MSC/BSC connection'>
BSCSCCPHandler class >> initWith: aBSC msc: aMSC [ BSCSCCPHandler class >> initWith: aBSC msc: aMSC [
@ -59,6 +61,8 @@ OsmoGSM.SCCPHandler subclass: BSCSCCPHandler [
Object subclass: BSCConnection [ Object subclass: BSCConnection [
| config msc trunk | | config msc trunk |
<category: 'OsmoMSC-BSC'>
BSCConnection class >> createOn: aConfig msc: aMsc [ BSCConnection class >> createOn: aConfig msc: aMsc [
<category: 'creation'> <category: 'creation'>
^ self new ^ self new
@ -95,6 +99,8 @@ Object subclass: BSCConnection [
BSCConnection subclass: BSCIPAConnection [ BSCConnection subclass: BSCIPAConnection [
| socket demuxer writeQueue muxer dispatcher sccp tx terminated ipa | | socket demuxer writeQueue muxer dispatcher sccp tx terminated ipa |
<category: 'OsmoMSC-BSC'>
<comment: 'I represent one Connection to a BSC and use the IPA <comment: 'I represent one Connection to a BSC and use the IPA
protocol to exchange messages. I will be executed from within protocol to exchange messages. I will be executed from within
a thread and can do a blocking read from in here.'> a thread and can do a blocking read from in here.'>

View File

@ -21,6 +21,7 @@ PackageLoader fileInPackage: 'Sockets'.
Object subclass: BSCListener [ Object subclass: BSCListener [
| ip port socket handler | | ip port socket handler |
<category: 'OsmoMSC-BSC'>
<comment: 'I listen for incoming BSC connections and will <comment: 'I listen for incoming BSC connections and will
authenticate them based on a definable criteria. Right now authenticate them based on a definable criteria. Right now
this is based on IP address'> this is based on IP address'>

View File

@ -18,36 +18,42 @@
OsmoGSM.GSM48MSG extend [ OsmoGSM.GSM48MSG extend [
dispatchMoCall: aCon [ dispatchMoCall: aCon [
<category: '*-OsmoMSC-GSM'>
aCon moUnknown: self. aCon moUnknown: self.
] ]
] ]
OsmoGSM.GSM48CCConnectAck extend [ OsmoGSM.GSM48CCConnectAck extend [
dispatchMoCall: aCon [ dispatchMoCall: aCon [
<category: '*-OsmoMSC-GSM'>
aCon moConnectAck: self. aCon moConnectAck: self.
] ]
] ]
OsmoGSM.GSM48CCDisconnect extend [ OsmoGSM.GSM48CCDisconnect extend [
dispatchMoCall: aCon [ dispatchMoCall: aCon [
<category: '*-OsmoMSC-GSM'>
aCon moDisconnect: self. aCon moDisconnect: self.
] ]
] ]
OsmoGSM.GSM48CCRelease extend [ OsmoGSM.GSM48CCRelease extend [
dispatchMoCall: aCon [ dispatchMoCall: aCon [
<category: '*-OsmoMSC-GSM'>
aCon moRelease: self. aCon moRelease: self.
] ]
] ]
OsmoGSM.GSM48CCReleaseCompl extend [ OsmoGSM.GSM48CCReleaseCompl extend [
dispatchMoCall: aCon [ dispatchMoCall: aCon [
<category: '*-OsmoMSC-GSM'>
aCon moReleaseCompl: self. aCon moReleaseCompl: self.
] ]
] ]
OsmoGSM.GSM48CCStatus extend [ OsmoGSM.GSM48CCStatus extend [
dispatchMoCall: aCon [ dispatchMoCall: aCon [
<category: '*-OsmoMSC-GSM'>
aCon moStatus: self. aCon moStatus: self.
] ]
] ]
@ -55,6 +61,7 @@ OsmoGSM.GSM48CCStatus extend [
OsmoGSM.GSM48CCSetup extend [ OsmoGSM.GSM48CCSetup extend [
openTransactionOn: aCon sapi: aSapi [ openTransactionOn: aCon sapi: aSapi [
| tran | | tran |
<category: '*-OsmoMSC-GSM'>
tran := (GSMMOCall on: aSapi with: self ti) tran := (GSMMOCall on: aSapi with: self ti)
con: aCon; con: aCon;
yourself. yourself.
@ -65,6 +72,8 @@ OsmoGSM.GSM48CCSetup extend [
GSMTransaction subclass: GSMMOCall [ GSMTransaction subclass: GSMMOCall [
| state wait_for_ass remoteLeg | | state wait_for_ass remoteLeg |
<category: 'OsmoMSC-GSM'>
<comment: 'I handle Mobile-Originated calls as of 5.2.1 of GSM 04.08. I should <comment: 'I handle Mobile-Originated calls as of 5.2.1 of GSM 04.08. I should
represent the states found in Figure 5.1b/3GPP TS 04.08: Overview call controll represent the states found in Figure 5.1b/3GPP TS 04.08: Overview call controll
protocol/Network side. Right now the set of states is incomplete and is mixed protocol/Network side. Right now the set of states is incomplete and is mixed

View File

@ -20,16 +20,19 @@ PackageLoader fileInPackage: 'OsmoGSM'.
OsmoGSM.BSSAPMessage extend [ OsmoGSM.BSSAPMessage extend [
dispatchTrans: aCon [ dispatchTrans: aCon [
<category: '*-OsmoMSC-GSM'>
aCon bssapUnknownData: self aCon bssapUnknownData: self
] ]
] ]
OsmoGSM.BSSAPManagement extend [ OsmoGSM.BSSAPManagement extend [
dispatchTrans: aCon [ dispatchTrans: aCon [
<category: '*-OsmoMSC-GSM'>
self dispatchMAP: aCon. self dispatchMAP: aCon.
] ]
dispatchMAP: aCon [ dispatchMAP: aCon [
<category: '*-OsmoMSC-GSM'>
(Dictionary from: { (Dictionary from: {
OsmoGSM.GSM0808Helper msgComplL3 -> #mapLayer3:. OsmoGSM.GSM0808Helper msgComplL3 -> #mapLayer3:.
OsmoGSM.GSM0808Helper msgClearReq -> #mapClearReq:. OsmoGSM.GSM0808Helper msgClearReq -> #mapClearReq:.
@ -47,18 +50,22 @@ OsmoGSM.BSSAPManagement extend [
OsmoGSM.BSSAPDTAP extend [ OsmoGSM.BSSAPDTAP extend [
dispatchTrans: aCon [ dispatchTrans: aCon [
<category: '*-OsmoMSC-GSM'>
aCon dispatchDTAP: self. aCon dispatchDTAP: self.
] ]
] ]
OsmoGSM.GSM48MSG extend [ OsmoGSM.GSM48MSG extend [
openTransactionOn: aCon sapi: aSapi [ openTransactionOn: aCon sapi: aSapi [
<category: '*-OsmoMSC-GSM'>
self logError: 'Can not open transaction for %1' % {self class} area: #bsc. self logError: 'Can not open transaction for %1' % {self class} area: #bsc.
] ]
] ]
Object subclass: GSMTransaction [ Object subclass: GSMTransaction [
| sapi ti con | | sapi ti con |
<category: 'OsmoMSC-GSM'>
<comment: 'I am the base for everything that goes on in a <comment: 'I am the base for everything that goes on in a
GSM transaction on a given SAPI'> GSM transaction on a given SAPI'>
@ -119,12 +126,14 @@ GSM transaction on a given SAPI'>
] ]
GSMTransaction subclass: GSMLURequest [ GSMTransaction subclass: GSMLURequest [
<category: 'OsmoMSC-GSM'>
<comment: 'I handle a Location Updating Request'> <comment: 'I handle a Location Updating Request'>
] ]
OsmoGSM.SCCPConnectionBase subclass: GSMProcessor [ OsmoGSM.SCCPConnectionBase subclass: GSMProcessor [
| transactions state endp connId mgcp_trans | | transactions state endp connId mgcp_trans |
<category: 'OsmoMSC-GSM'>
<comment: 'I am driving a SCCP Connection. This consists of being <comment: 'I am driving a SCCP Connection. This consists of being
hosting various transactions and dispatching to them.'> hosting various transactions and dispatching to them.'>
<import: OsmoGSM> <import: OsmoGSM>

View File

@ -22,7 +22,8 @@ data that will be used inside the HLR.
Object subclass: HLRSubscriber [ Object subclass: HLRSubscriber [
|imsi msisdn vlrnumber auKey name | |imsi msisdn vlrnumber auKey name |
<category: 'osmo-msc'>
<category: 'OsmoMSC-HLR'>
<comment: 'I am one subscriber in the HLR'> <comment: 'I am one subscriber in the HLR'>
imsi [ <category: 'accessing'> ^ imsi ] imsi [ <category: 'accessing'> ^ imsi ]
@ -33,7 +34,7 @@ Object subclass: HLRSubscriber [
] ]
Object subclass: HLR [ Object subclass: HLR [
<category: 'osmo-msc'> <category: 'OsmoMSC-HLR'>
<comment: 'I am a HLR and I can find subscribers'> <comment: 'I am a HLR and I can find subscribers'>
findSubscriberByIMSI: aIMSI [ findSubscriberByIMSI: aIMSI [
@ -48,7 +49,8 @@ Object subclass: HLR [
HLR subclass: HLRLocalCollection [ HLR subclass: HLRLocalCollection [
| subs | | subs |
<category: 'osmo-msc-simple'>
<category: 'OsmoMSC-HLR'>
<comment: 'I am a very simple local HLR'> <comment: 'I am a very simple local HLR'>
findSubscriberByIMSI: aIMSI [ findSubscriberByIMSI: aIMSI [

View File

@ -19,7 +19,8 @@
PackageLoader fileInPackage: 'OsmoLogging'. PackageLoader fileInPackage: 'OsmoLogging'.
Osmo.LogArea subclass: LogAreaBSC [ Osmo.LogArea subclass: LogAreaBSC [
<category: 'osmo-msc-logging'> <category: 'OsmoMSC-Logging'>
LogAreaBSC class >> areaName [ ^ #bsc ] LogAreaBSC class >> areaName [ ^ #bsc ]
LogAreaBSC class >> areaDescription [ ^ 'BSC Connectivty' ] LogAreaBSC class >> areaDescription [ ^ 'BSC Connectivty' ]
LogAreaBSC class >> default [ LogAreaBSC class >> default [
@ -31,7 +32,8 @@ Osmo.LogArea subclass: LogAreaBSC [
] ]
Osmo.LogArea subclass: LogAreaHLR [ Osmo.LogArea subclass: LogAreaHLR [
<category: 'osmo-msc-logging'> <category: 'OsmoMSC-Logging'>
LogAreaHLR class >> areaName [ ^ #hlr ] LogAreaHLR class >> areaName [ ^ #hlr ]
LogAreaHLR class >> areaDescription [ ^ 'HLR work' ] LogAreaHLR class >> areaDescription [ ^ 'HLR work' ]
LogAreaHLR class >> default [ LogAreaHLR class >> default [
@ -41,7 +43,8 @@ Osmo.LogArea subclass: LogAreaHLR [
] ]
Osmo.LogArea subclass: LogAreaVLR [ Osmo.LogArea subclass: LogAreaVLR [
<category: 'osmo-msc-logging'> <category: 'OsmoMSC-Logging'>
LogAreaVLR class >> areaName [ ^ #vlr ] LogAreaVLR class >> areaName [ ^ #vlr ]
LogAreaVLR class >> areaDescription [ ^ 'VLR work' ] LogAreaVLR class >> areaDescription [ ^ 'VLR work' ]
LogAreaVLR class >> default [ LogAreaVLR class >> default [
@ -51,7 +54,8 @@ Osmo.LogArea subclass: LogAreaVLR [
] ]
Osmo.LogArea subclass: LogAreaMSC [ Osmo.LogArea subclass: LogAreaMSC [
<category: 'osmo-msc-logging'> <category: 'OsmoMSC-Logging'>
LogAreaMSC class >> areaName [ ^ #msc ] LogAreaMSC class >> areaName [ ^ #msc ]
LogAreaMSC class >> areaDescription [ ^ 'MSC work' ] LogAreaMSC class >> areaDescription [ ^ 'MSC work' ]
LogAreaMSC class >> default [ LogAreaMSC class >> default [

View File

@ -22,7 +22,8 @@ PackageLoader
Object subclass: MSCConfig [ Object subclass: MSCConfig [
| ip port mgcp sip_ip sip_port | | ip port mgcp sip_ip sip_port |
<category: 'MSC-IP'>
<category: 'OsmoMSC-MSC'>
<comment: 'I contain a very simple MSC config for IP based BSCs'> <comment: 'I contain a very simple MSC config for IP based BSCs'>
bscIP: aIP [ bscIP: aIP [
@ -79,6 +80,7 @@ Object subclass: MSCConfig [
Object subclass: MSCBSCConnectionHandler [ Object subclass: MSCBSCConnectionHandler [
| msc connections | | msc connections |
<category: 'OsmoMSC-MSC'>
<comment: 'I take incoming connections, find a handler for them and <comment: 'I take incoming connections, find a handler for them and
will register them. I will be passed to the BSCListener'> will register them. I will be passed to the BSCListener'>
@ -157,6 +159,8 @@ Object subclass: MSCBSCConnectionHandler [
Object subclass: MSCApplication [ Object subclass: MSCApplication [
| hlr vlr config bscListener bscConfig bscConHandler mgcp sip | | hlr vlr config bscListener bscConfig bscConHandler mgcp sip |
<category: 'OsmoMSC-MSC'>
<comment: 'I am a MSC as I have the VLR/HLR and other instances'> <comment: 'I am a MSC as I have the VLR/HLR and other instances'>
hlr [ ^ hlr ifNil: [HLRLocalCollection new]] hlr [ ^ hlr ifNil: [HLRLocalCollection new]]

View File

@ -20,7 +20,8 @@ PackageLoader fileInPackage: 'OsmoSIP'.
Osmo.SIPCall subclass: SIPMTCall [ Osmo.SIPCall subclass: SIPMTCall [
| remoteLeg sdp_alert | | remoteLeg sdp_alert |
<category: 'sip'>
<category: 'OsmoMSC-SIP'>
<comment: 'I represent a SIP terminated call. It is called Mobile <comment: 'I represent a SIP terminated call. It is called Mobile
Terminated to stay with the GSM speech.'> Terminated to stay with the GSM speech.'>

View File

@ -21,7 +21,8 @@ This is the interface to the VLR
Object subclass: VLRSubscriber [ Object subclass: VLRSubscriber [
|imsi tmsi msisdn lac| |imsi tmsi msisdn lac|
<category: 'osmo-msc'>
<category: 'OsmoMSC-VLR'>
<comment: 'I am one subscriber in the VLR'> <comment: 'I am one subscriber in the VLR'>
@ -32,7 +33,7 @@ Object subclass: VLRSubscriber [
] ]
Object subclass: VLR [ Object subclass: VLR [
<category: 'osmo-msc'> <category: 'OsmoMSC-VLR'>
<comment: 'I hold the active subscribers'> <comment: 'I hold the active subscribers'>
activeSubscribers [ activeSubscribers [
@ -73,6 +74,7 @@ Object subclass: VLR [
] ]
Object subclass: HLRResolver [ Object subclass: HLRResolver [
<category: 'OsmoMSC-HLR'>
insertSubscriber: aIMSI [ insertSubscriber: aIMSI [
^ self subclassResponsibility ^ self subclassResponsibility
] ]
@ -81,6 +83,8 @@ Object subclass: HLRResolver [
VLR subclass: VLRLocalCollection [ VLR subclass: VLRLocalCollection [
| subs resolver | | subs resolver |
<category: 'OsmoMSC-VLR'>
VLRLocalCollection class >> initWith: aResolver [ VLRLocalCollection class >> initWith: aResolver [
^ self new ^ self new
instVarNamed: #resolver put: aResolver; instVarNamed: #resolver put: aResolver;

View File

@ -19,6 +19,8 @@
PackageLoader fileInPackage: 'SUnit'. PackageLoader fileInPackage: 'SUnit'.
TestCase subclass: HLRTest [ TestCase subclass: HLRTest [
<category: 'OsmoMSC-Tests'>
testHLRFind [ testHLRFind [
| hlr sub | | hlr sub |
hlr := HLRLocalCollection new. hlr := HLRLocalCollection new.
@ -35,10 +37,14 @@ TestCase subclass: HLRTest [
] ]
HLRResolver subclass: HLRDummyResolver [ HLRResolver subclass: HLRDummyResolver [
<category: 'OsmoMSC-Tests'>
insertSubscriber: aIMSI [ ^ true ] insertSubscriber: aIMSI [ ^ true ]
] ]
TestCase subclass: VLRTest [ TestCase subclass: VLRTest [
<category: 'OsmoMSC-Tests'>
testVLRFind [ testVLRFind [
| vlr sub1 sub2 | | vlr sub1 sub2 |
vlr := VLRLocalCollection initWith: HLRDummyResolver new. vlr := VLRLocalCollection initWith: HLRDummyResolver new.
@ -58,6 +64,7 @@ TestCase subclass: VLRTest [
] ]
TestCase subclass: BSCConfigTest [ TestCase subclass: BSCConfigTest [
<category: 'OsmoMSC-Tests'>
<comment: 'I will test the BSCConfig'> <comment: 'I will test the BSCConfig'>
testConfigItem [ testConfigItem [
@ -107,6 +114,7 @@ TestCase subclass: BSCConfigTest [
] ]
TestCase subclass: BSCListenerTest [ TestCase subclass: BSCListenerTest [
<category: 'OsmoMSC-Tests'>
<comment: 'Test some basic socket functionality'> <comment: 'Test some basic socket functionality'>
testListenAndStop [ testListenAndStop [
@ -136,6 +144,7 @@ TestCase subclass: BSCListenerTest [
] ]
TestCase subclass: MSCBSCConnectionHandlerTest [ TestCase subclass: MSCBSCConnectionHandlerTest [
<category: 'OsmoMSC-Tests'>
<comment: 'I should test the feature that each config can only <comment: 'I should test the feature that each config can only
be connected once but that is not done yet. It requires some work be connected once but that is not done yet. It requires some work
on socket code. TODO!!!'> on socket code. TODO!!!'>
@ -155,6 +164,7 @@ TestCase subclass: MSCBSCConnectionHandlerTest [
] ]
TestCase subclass: BSCIPAConnectionTest [ TestCase subclass: BSCIPAConnectionTest [
<category: 'OsmoMSC-Tests'>
<comment: 'I just do some simple smoke testing here'> <comment: 'I just do some simple smoke testing here'>
testSmoke [ testSmoke [