" (C) 2010-2011 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 . " TestCase subclass: MGCPCommandTest [ | trunk callagent | callagent [ ^ callagent ifNil: [ callagent := MGCPCallAgent startOn: '127.0.0.1' port: 0. callagent addTrunk: self trunk; yourself]. ] trunk [ ^ trunk ifNil: [ trunk := MGCPVirtualTrunk createWithDest: '127.0.0.1' numberPorts: 31] ] endpoint [ ^ self trunk endpointAt: 20. ] exampleSDP [ ^ (WriteStream on: String new) nextPutAll: 'v=0'; cr; nl; nextPutAll: 'o=- 258696477 0 IN IP4 172.16.1.107'; cr; nl; nextPutAll: 'c=IN IP4 172.16.1.107'; cr; nl; nextPutAll: 't=0 0'; cr; nl; nextPutAll: 'm=audio 6666 RTP/AVP 127'; cr; nl; nextPutAll: 'a=rtpmap:127 GSM-EFR/8000/1'; cr; nl; nextPutAll: 'a=ptime:20'; cr; nl; nextPutAll: 'a=recvonly'; cr; nl; nextPutAll: 'm=image 4402 udptl t38'; cr; nl; nextPutAll: 'a=T38FaxVersion:0'; cr; nl; nextPutAll: 'a=T38MaxBitRate:14400'; cr; nl; contents ] exampleMDCX [ ^ (WriteStream on: String new) nextPutAll: 'MDCX 808080 14@mgw MGCP 1.0'; cr; nl; nextPutAll: 'C: 4a84ad5d25f'; cr; nl; nextPutAll: 'L: p:20, a:GSM-EFR, nt:IN'; cr; nl; nextPutAll: 'M: recvonly'; cr; nl; cr; nl; nextPutAll: self exampleSDP; contents ] exampleCRCX [ ^ (WriteStream on: String new) nextPutAll: 'CRCX 808080 14@mgw MGCP 1.0'; cr; nl; nextPutAll: 'C: 4a84ad5d25f'; cr; nl; nextPutAll: 'L: p:20, a:GSM-EFR, nt:IN'; cr; nl; nextPutAll: 'M: recvonly'; cr; nl; contents ] testCRCXCreation [ | crcx trans | trans := MGCPTransaction on: self endpoint of: self callagent. trans transactionId: '808080'. crcx := (MGCPCRCXCommand createCRCX: self endpoint callId: '4a84ad5d25f') parameterAdd: 'L: p:20, a:GSM-EFR, nt:IN'; parameterAdd: 'M: recvonly'; yourself. trans command: crcx. self assert: crcx asDatagram = self exampleCRCX. ] testEndPointName [ | trunk | trunk := MGCPDSTrunk createWithDest: '0.0.0.0' trunkNr: 1. "I test the endpoint name on hex part.." self assert: (MGCPVirtualTrunk new endpointName: 16rA) = 'a@mgw'. self assert: (trunk endpointName: 16rA) = 'ds/e1-1/10@mgw'. ] testMultiplexTimeslot [ | trunk | trunk := MGCPDSTrunk createWithDest: '0.0.0.0' trunkNr: 3. self assert: (self trunk endpointAt: 1) multiplex = 0. self assert: (self trunk endpointAt: 1) timeslot = 1. self assert: (self trunk endpointAt: 31) multiplex = 0. self assert: (self trunk endpointAt: 31) timeslot = 31. self assert: (trunk endpointAt: 1) multiplex = 3. self assert: (trunk endpointAt: 31) timeslot = 31. ] testMDCXWithSDP [ | mdcx trans | trans := MGCPTransaction on: self endpoint of: self callagent. trans transactionId: '808080'. mdcx := (MGCPMDCXCommand createMDCX: self endpoint callId: '4a84ad5d25f') parameterAdd: 'L: p:20, a:GSM-EFR, nt:IN'; parameterAdd: 'M: recvonly'; sdp: self exampleSDP; yourself. trans command: mdcx. mdcx asDatagram printNl. self assert: mdcx asDatagram = self exampleMDCX. ] tearDown [ self callagent stop. ] ] MGCPCallAgent subclass: MGCPMockNoTransmitAgent [ | send | MGCPMockNoTransmitAgent class >> new [ ^ super new initialize; yourself ] initialize [ send := Semaphore new. ] queueData: aDatagram [ send signal ] sends [ [^send signals] ensure: [send := Semaphore new] ] ] MGCPMockNoTransmitAgent subclass: MGCPTransmitSecond [ | drop | initialize [ drop := true. ^ super initialize. ] queueData: aData [ super queueData: aData. drop ifTrue: [drop := false] ifFalse: [drop := true. transactions first response: 3.]. ] ] MGCPTransaction subclass: MGCPShortTransaction [ MGCPShortTransaction class >> retransmitTime [ ^ 1 ] MGCPShortTransaction class >> expireTime [ ^ 6 ] ] TestCase subclass: MGCPTransactionTest [ | trunk callagent dropAgent | timeoutCallagent [ ^ callagent ifNil: [ callagent := MGCPMockNoTransmitAgent startOn: '127.0.0.1' port: 0. callagent addTrunk: self trunk; yourself]. ] dropAgent [ ^ dropAgent ifNil: [ dropAgent := MGCPTransmitSecond startOn: '127.0.0.1' port: 0. dropAgent addTrunk: self trunk; yourself]. ] trunk [ ^ trunk ifNil: [ trunk := MGCPVirtualTrunk createWithDest: '127.0.0.1' numberPorts: 32] ] endpoint [ ^ self trunk endpointAt: 20. ] testTimeout [ | crcx trans result timeout | trans := MGCPShortTransaction on: self endpoint of: self timeoutCallagent. crcx := (MGCPCRCXCommand createCRCX: self endpoint callId: '4a84ad5d25f') parameterAdd: 'L: p:20, a:GSM-EFR, nt:IN'; parameterAdd: 'M: recvonly'; yourself. trans command: crcx. result := Semaphore new. timeout := Semaphore new. trans onResult: [:a :b | result signal]; onTimeout: [:each | timeout signal]; start. timeout wait. self assert: result signals = 0. self assert: timeout signals = 0. self assert: self timeoutCallagent sends > 6. ] testSuccess [ | crcx trans result timeout | trans := MGCPShortTransaction on: self endpoint of: self dropAgent. crcx := (MGCPCRCXCommand createCRCX: self endpoint callId: '4a84ad5d25f') parameterAdd: 'L: p:20, a:GSM-EFR, nt:IN'; parameterAdd: 'M: recvonly'; yourself. trans command: crcx. result := Semaphore new. timeout := Semaphore new. trans onResult: [:a :b | result signal]; onTimeout: [:each | timeout signal]; start. result wait. self assert: result signals = 0. self assert: timeout signals = 0. self assert: self dropAgent sends >= 2. ] tearDown [ self timeoutCallagent stop. self dropAgent stop. ] ] TestCase subclass: MGCPEndpointAllocTest [ testStateTransition [ | trunk endp | trunk := MGCPVirtualTrunk createWithDest: '127.0.0.1' numberPorts: 32. endp := trunk endpointAt: 1. "Initial..." self assert: endp isUnused. "Reserve..." endp reserve. self assert: endp isReserved. self should: [endp reserve] raise: Error. self should: [endp free] raise: Error. self should: [endp unblock] raise: Error. self deny: endp tryBlock. "Move to used..." endp used. self assert: endp isUsed. self should: [endp reserve] raise: Error. self should: [endp used] raise: Error. self should: [endp unblock] raise: Error. self deny: endp tryBlock. "Move to free..." endp free. self assert: endp isUnused. self should: [endp used] raise: Error. self should: [endp unblock] raise: Error. self assert: endp tryBlock. "Now try to block it..." self assert: endp isBlocked. self should: [endp reserve] raise: Error. self should: [endp free] raise: Error. self should: [endp used] raise: Error. self deny: endp tryBlock. "Now unblock and restore" endp unblock. self assert: endp isUnused. ] testAllocation [ | trunk endp | trunk := MGCPVirtualTrunk createWithDest: '127.0.0.1' numberPorts: 32. 1 to: 32 do: [:each | self assert: ((trunk allocateEndpointIfFailure: []) used; isUsed). ]. "test an allocation failure" self assert: (trunk allocateEndpointIfFailure: [true]). "now free some endpoints" (trunk endpointAt: 20) free. (trunk endpointAt: 5) free. endp := (trunk allocateEndpointIfFailure: []). self assert: endp endpointName = '5@mgw'. "last_used should be five now" (trunk endpointAt: 4) free. endp := (trunk allocateEndpointIfFailure: []). self assert: endp endpointName = '14@mgw'. endp := (trunk allocateEndpointIfFailure: []). self assert: endp endpointName = '4@mgw'. ] ] PP.PPCompositeParserTest subclass: MGCPParserTest [ parserClass [ ^MGCPParser ] testRespParse [ | nl res sdp | nl := Character cr asString, Character nl asString. sdp := 'v=0', nl, 'o=- 258696477 0 IN IP4 172.16.1.107', nl, 's=-', nl, 'c=IN IP4 172.16.1.107', nl, 't=0 0', nl, 'm=audio 6666 RTP/AVP 127', nl, 'a=rtpmap:127 GSM-EFR/8000/1', nl, 'a=ptime:20', nl, 'a=recvonly', nl, 'm=image 4402 udptl t38', nl, 'a=T38FaxVersion:0', nl, 'a=T38MaxBitRate:14400', nl. res := self parse: '200 32323 OK', nl, 'I: 233434', nl, nl, sdp. self assert: res code = 200. self assert: res isSuccess. self assert: res transactionId = '32323'. self assert: res sdp = sdp. self assert: (res parameterAt: 'I' ifAbsent: []) = '233434'. ] testFailureResp [ | nl res | nl := Character cr asString, Character nl asString. res := self parse: '400 32323 OK', nl. self deny: res isSuccess. self assert: res sdp isNil. ] ]