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

Merge branch 'master' of git://git.osmocom.org/smalltalk/osmo-st-mgcp

This commit is contained in:
Holger Hans Peter Freyther 2013-05-23 17:38:41 +02:00
commit 20024e496b
11 changed files with 28 additions and 20 deletions

View File

@ -22,7 +22,7 @@ PackageLoader
Object subclass: MGCPCallAgentBase [
| net trunks sem addr port |
<category: 'MGCP-Callagent'>
<category: 'OsmoMGCP-Callagent'>
<comment: 'I am responsible for the networking'>
MGCPCallAgentBase class >> startOn: anAddress [
@ -89,7 +89,7 @@ Object subclass: MGCPCallAgentBase [
MGCPCallAgentBase subclass: MGCPCallAgent [
| transactions parser |
<category: 'MGCP-Callagent'>
<category: 'OsmoMGCP-Callagent'>
<comment: 'I deal with transactions and timeouts'>
initialize: anAddress port: aPort [

View File

@ -21,7 +21,7 @@ Object subclass: MGCPCommand [
<comment: 'I am a command send to a MGCP gateway. I know my timeout
and such. Each MGCPGateWay can have a MGCPCommand subclass to specify
certain things. E.g. the endpoint numbering is different'>
<category: 'MGCP-callagent'>
<category: 'OsmoMGCP-callagent'>
MGCPCommand class >> create: anEndpoint callId: aCallId [
^ (self new)
@ -102,7 +102,7 @@ Object subclass: MGCPCommand [
MGCPCommand subclass: MGCPCRCXCommand [
<comment: 'I represent a CRCX message'>
<category: 'MGCP-callagent'>
<category: 'OsmoMGCP-Callagent'>
MGCPCRCXCommand class >> verb [
<category: 'verb'>
@ -120,7 +120,7 @@ MGCPCommand subclass: MGCPCRCXCommand [
MGCPCommand subclass: MGCPMDCXCommand [
<comment: 'I represent a MDCX message'>
<category: 'MGCP-Callagent'>
<category: 'OsmoMGCP-Callagent'>
MGCPMDCXCommand class >> verb [
<category: 'verb'>
@ -137,7 +137,7 @@ MGCPCommand subclass: MGCPMDCXCommand [
MGCPCommand subclass: MGCPDLCXCommand [
<comment: 'I represent a DLCX message'>
<category: 'MGCP-Callagent'>
<category: 'OsmoMGCP-Callagent'>
MGCPDLCXCommand class >> verb [
<category: 'verb'>
@ -152,7 +152,7 @@ MGCPCommand subclass: MGCPDLCXCommand [
MGCPCommand subclass: MGCPAUEPComamnd [
<comment: 'I represent an AUEP message'>
<category: 'MGCP-Callagent'>
<category: 'OsmoMGCP-Callagent'>
MGCPAUEPComamnd class >> verb [
<category: 'verb'>
@ -168,7 +168,7 @@ MGCPCommand subclass: MGCPAUEPComamnd [
MGCPCommand subclass: MGCPOsmoRSIPCommand [
<comment: 'I represent an Osmocom Extension to MGCP to reset remote
mediagateways. The spec is working the other way around.'>
<category: 'MGCP-Callagent'>
<category: 'OsmoMGCP-Callagent'>
MGCPOsmoRSIPCommand class >> verb [
<category: 'verb'>

View File

@ -18,7 +18,7 @@
Object subclass: MGCPEndpoint [
| nr trunk state callid connid sdp|
<category: 'MGCP-Callagent'>
<category: 'OsmoMGCP-Callagent'>
<comment: 'I am one endpoint. I have a state...'>
MGCPEndpoint class >> stateUnused [ <category: 'states'> ^ #unused ]

View File

@ -19,7 +19,7 @@
PackageLoader fileInPackage: #OsmoLogging.
Osmo.LogArea subclass: MGCPLogArea [
<category: 'mgcp-logarea'>
<category: 'OsmoMGCP-Logging'>
MGCPLogArea class >> areaName [ ^ #mgcp ]
MGCPLogArea class >> areaDescription [

View File

@ -17,7 +17,7 @@
"
MGCPGrammar subclass: MGCPParser [
<category: 'MGCP-Parser'>
<category: 'OsmoMGCP-Parser'>
<comment: 'I parse responses for now.'>
MGCPMessage [

View File

@ -19,7 +19,7 @@
Object subclass: MGCPResponse [
| code transaction params sdp |
<category: 'MGCP-Response'>
<category: 'OsmoMGCP-Response'>
<comment: 'I provide a nicer way to look at responses'>
MGCPResponse class >> fromDict: aDict [

View File

@ -23,7 +23,7 @@ PackageLoader
Object subclass: MGCPTransactionBase [
| callagent t_retransmit t_expire t_remove sem |
<comment: 'I handle timers for the transaction'>
<category: 'MGCP-Callagent'>
<category: 'OsmoMGCP-Callagent'>
MGCPTransactionBase class >> on: aCallagent [
^ self new
@ -95,7 +95,7 @@ Object subclass: MGCPTransactionBase [
MGCPTransactionBase subclass: MGCPTransaction [
| result timeout id command endpoint state |
<comment: 'I am a transaction...'>
<category: 'MGCP-Callagent'>
<category: 'OsmoMGCP-Callagent'>
MGCPTransaction class >> on: endpoint of: callagent [
| res |

View File

@ -19,7 +19,7 @@
Object subclass: MGCPTrunkBase [
| ip ports sem last |
<comment: 'I represent a trunk for a Gateway'>
<category: 'MGCP-Callagent'>
<category: 'OsmoMGCP-Callagent'>
MGCPTrunkBase class >> new [
<category: 'creation'>
@ -103,7 +103,7 @@ Object subclass: MGCPTrunkBase [
MGCPTrunkBase subclass: MGCPVirtualTrunk [
<comment: 'I represent a @mgw virtual trunk'>
<category: 'MGCP-Callagent'>
<category: 'OsmoMGCP-Callagent'>
MGCPVirtualTrunk class >> createWithDest: anIP numberPorts: nr [
<category: 'factory'>
@ -132,7 +132,7 @@ MGCPTrunkBase subclass: MGCPVirtualTrunk [
MGCPTrunkBase subclass: MGCPDSTrunk [
| trunk |
<comment: 'I represent an E1 trunk with 32 endpoints'>
<category: 'MGCP-Callagent'>
<category: 'OsmoMGCP-Callagent'>
MGCPDSTrunk class >> createWithDest: anIP trunkNr: aNr [
<category: 'factory'>

View File

@ -18,6 +18,7 @@
TestCase subclass: MGCPCommandTest [
| trunk callagent |
<category: 'OsmoMGCP-Callagent-Tests'>
callagent [
^ callagent ifNil: [
@ -146,6 +147,7 @@ TestCase subclass: MGCPCommandTest [
MGCPCallAgent subclass: MGCPMockNoTransmitAgent [
| send |
<category: 'OsmoMGCP-Callagent-Tests'>
MGCPMockNoTransmitAgent class >> new [
^ super new
@ -169,6 +171,7 @@ MGCPCallAgent subclass: MGCPMockNoTransmitAgent [
MGCPMockNoTransmitAgent subclass: MGCPTransmitSecond [
| drop |
<category: 'OsmoMGCP-Callagent-Tests'>
initialize [
drop := true.
@ -185,12 +188,15 @@ MGCPMockNoTransmitAgent subclass: MGCPTransmitSecond [
]
MGCPTransaction subclass: MGCPShortTransaction [
<category: 'OsmoMGCP-Callagent-Tests'>
MGCPShortTransaction class >> retransmitTime [ ^ 1 ]
MGCPShortTransaction class >> expireTime [ ^ 6 ]
]
TestCase subclass: MGCPTransactionTest [
| trunk callagent dropAgent |
<category: 'OsmoMGCP-Callagent-Tests'>
timeoutCallagent [
^ callagent ifNil: [
@ -268,6 +274,8 @@ TestCase subclass: MGCPTransactionTest [
]
TestCase subclass: MGCPEndpointAllocTest [
<category: 'OsmoMGCP-Callagent-Tests'>
testStateTransition [
| trunk endp |
@ -342,7 +350,7 @@ TestCase subclass: MGCPEndpointAllocTest [
]
PP.PPCompositeParserTest subclass: MGCPParserTest [
<category: 'parsing tests'>
<category: 'OsmoMGCP-Callagent-Tests'>
parserClass [
^MGCPParser

View File

@ -20,7 +20,7 @@ PackageLoader fileInPackage: 'PetitParser'.
PP.PPCompositeParser subclass: MGCPGrammar [
| MGCPMessage EOL One_WSP MGCPMessage MGCPCommandLine MGCPVerb transaction_id endpointName MGCPversion MGCPParameter MGCPCommand ParameterValue SDPRecord SDPLine SDPinformation MGCPResponseLine responseCode responseString packageName |
<category: 'MGCP-Core'>
<category: 'OsmoMGCP-Core'>
<comment: 'I am a the Grammar of the Media Gateway Control Protocol'>
start [

View File

@ -20,7 +20,7 @@ PackageLoader fileInPackage: 'PetitParserTests'.
PP.PPCompositeParserTest subclass: MGCPGrammarTest [
<comment: 'I test some parts of the grammar'>
<category: 'MGCP-Tests'>
<category: 'OsmoMGCP-Core-Tests'>
MGCPGrammarTest class >> packageNamesUnderTest [
<category: 'accessing'>