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

mgcp: Add a MGCPCall object, attempt to allocate a call between two endpoints

This commit is contained in:
Holger Hans Peter Freyther 2010-09-21 23:56:50 +08:00
parent 0cb5496a1e
commit 014eea75fa
4 changed files with 118 additions and 1 deletions

71
callagent/MGCPCall.st Normal file
View File

@ -0,0 +1,71 @@
"Copyright"
Object subclass: MGCPCall [
| sourceGW sourceEndPoint destGW destEndPoint |
<category: 'mgcp-callagent'>
<comment: 'I represent a call between two endpoints'>
MGCPCall class >> initWith: aSource dest: aDest [
<category: 'setup'>
"I will try to find free endpoints and then initialize a call
object or return nil"
(self new)
sourceGateway: aSource;
destGateway: aDest;
allocate;
yourself.
]
sourceGateway: aSource [
sourceGW := aSource.
]
destGateway: aDest [
destGW := aDest.
]
allocate [
<category: 'management'>
"Allocate two endpoints on both sides of the call"
self addToBeFinalized.
sourceEndPoint := sourceGW allocateEndpoint.
destEndPoint := destGW allocateEndpoint.
]
finalized [
(sourceEndPoint isNil not or: [destEndPoint isNil not])
ifTrue: [
self error: 'Should have been freed.'
].
super finalized
]
isAllocated [
sourceEndPoint isNil: [
^ false
]
destEndPoint isNil: [
^ false
]
^ true
]
releaseCall [
sourceEndPoint ifNotNil: [
sourceGW releaseEndpoint: sourceEndPoint.
]
destEndPoint ifNotNil: [
destGW releaseEndpoint: destEndPoint.
]
sourceGW := nil.
destGW := nil.
sourceEndPoint := nil.
destEndPoint := nil.
]
]

View File

@ -23,6 +23,15 @@ Object subclass: MGCPCallAgent [
addGateway: aGateway [
<category: 'setup'>
gateways add: aGateway.
aGateway gateway: self.
]
setup: sourceGw dest: destGw [
<category: 'call-control'>
"Create a new call and allocate it"
^ (MGCPCall initWith: sourceGw dest: destGw)
allocate;
yourself.
]
handleData: aData [

View File

@ -8,4 +8,16 @@ Object subclass: MGCPEndpoint [
initialize [
used := false.
]
isAvailable [
<category: 'accessing'>
"Check if an endpoint is available, e.g. not used
and not blocked for something else"
^ used not
]
claim [
used := true.
]
]

View File

@ -1,7 +1,7 @@
"Copyright"
Object subclass: MGCPGateway [
| endpoints address |
| endpoints address gateway lastUsed |
<category: 'mgcp-callagent'>
<comment: 'One gateway...'>
@ -19,6 +19,7 @@ Object subclass: MGCPGateway [
initialize: anAddress number: aNumber [
address := anAddress.
endpoints := Array new: aNumber.
lastUsed := 0.
(1 to: aNumber)
do: [:each | endpoints at: each put: MGCPEndpoint new. ].
@ -34,4 +35,28 @@ Object subclass: MGCPGateway [
^ endpoints at: aNumber.
]
gateway: aGateway [
<category: 'private'>
gateway := aGateway.
]
allocateEndpoint [
<category: 'management'>
| claim |
"Attempt to allocate the endpoint"
claim := [:each | | endp |
endp := endpoints at: each.
endp isAvailable ifTrue: [
endp claim.
lastUsed := each.
^ lastUsed
].
lastUsed + 1 to: endpoints size do: claim.
1 to: lastUsed + 1 do: claim.
"found nothing"
^ nil
]