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

callagent: Test the allocation of an endpoint from the trunk

This commit is contained in:
Holger Hans Peter Freyther 2011-06-24 12:03:34 +02:00
parent 56f86debce
commit dc2a6faf2b
2 changed files with 57 additions and 1 deletions

View File

@ -17,7 +17,7 @@
"
Object subclass: MGCPTrunkBase [
| ip ports sem |
| ip ports sem last |
<comment: 'I represent a trunk for a Gateway'>
<category: 'MGCP-Callagent'>
@ -54,13 +54,41 @@ Object subclass: MGCPTrunkBase [
^ ports at: aNr
]
lastUsed [
<category: 'private'>
^ last ifNil: [0]
]
endpointName: aNr [
<category: 'accessing'>
^ self subclassResponsibility
]
critical: aBlock [
<category: 'accessing'>
sem critical: aBlock.
]
allocateEndpointIfFailure: aBlock [
| alloc |
<category: 'allocation'>
"You need to hold the lock to do any changes here"
alloc := [:each |
(self endpointAt: each) isUnused ifTrue: [
last := each.
^ (self endpointAt: each)
reserve;
yourself
]].
"Go from last to end, and then from start to last."
self lastUsed + 1 to: ports size do: alloc.
1 to: self lastUsed do: alloc.
"And give up now"
^ aBlock value.
]
]
MGCPTrunkBase subclass: MGCPVirtualTrunk [

View File

@ -230,4 +230,32 @@ TestCase subclass: MGCPEndpointAllocTest [
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'.
]
]