aboutsummaryrefslogtreecommitdiffstats
diff options
context:
space:
mode:
authorHolger Hans Peter Freyther <zecke@selfish.org>2011-06-24 12:03:34 +0200
committerHolger Hans Peter Freyther <zecke@selfish.org>2011-06-24 20:08:23 +0200
commitdc2a6faf2b853bc52029d7179cb6c1a93b071f48 (patch)
tree52dfed69946dd1c577e349517c8558ce19a5b6a0
parent56f86debceee818709a5a329cea4e509d6cc8f76 (diff)
callagent: Test the allocation of an endpoint from the trunk
-rw-r--r--callagent/MGCPTrunk.st30
-rw-r--r--callagent/Tests.st28
2 files changed, 57 insertions, 1 deletions
diff --git a/callagent/MGCPTrunk.st b/callagent/MGCPTrunk.st
index b58ddb3..52d8351 100644
--- a/callagent/MGCPTrunk.st
+++ b/callagent/MGCPTrunk.st
@@ -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 [
diff --git a/callagent/Tests.st b/callagent/Tests.st
index db76558..8479564 100644
--- a/callagent/Tests.st
+++ b/callagent/Tests.st
@@ -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'.
+ ]
]