smalltalk
/
osmo-st-mgcp
Archived
1
0
Fork 0
This repository has been archived on 2022-02-17. You can view files and clone it, but cannot push or open issues or pull requests.
osmo-st-mgcp/callagent/MGCPTrunk.st

161 lines
3.7 KiB
Smalltalk

"
(C) 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 <http://www.gnu.org/licenses/>.
"
Object subclass: MGCPTrunkBase [
| ip ports sem last |
<comment: 'I represent a trunk for a Gateway'>
<category: 'OsmoMGCP-Callagent'>
MGCPTrunkBase class >> new [
<category: 'creation'>
^self basicNew initialize
]
initialize [
sem := RecursionLock new.
]
destIp [
<category: 'accessing'>
^ ip
]
destIP: aDest [
<category: 'private'>
ip := aDest
]
numbersPorts: nrPorts [
<category: 'private'>
ports := Array new: nrPorts.
1 to: nrPorts do: [:each |
ports at: each put: (MGCPEndpoint initWith: each trunk: self)].
]
endpointAt: aNr [
<category: 'private'>
^ ports at: aNr
]
lastUsed [
<category: 'private'>
^ last ifNil: [0]
]
endpointName: aNr [
<category: 'accessing'>
^ self subclassResponsibility
]
multiplexFor: aNr [
<category: 'accessing'>
^ self subclassResponsibility.
]
timeslotFor: 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 [
<comment: 'I represent a @mgw virtual trunk'>
<category: 'OsmoMGCP-Callagent'>
MGCPVirtualTrunk class >> createWithDest: anIP numberPorts: nr [
<category: 'factory'>
^ self new
destIP: anIP;
numbersPorts: nr
yourself
]
endpointName: aNr [
<category: 'accessing'>
^ '%1@mgw' % {((aNr radix: 16) copyFrom: 4) asLowercase}
]
multiplexFor: aNr [
<category: 'accessing'>
^ aNr // 32
]
timeslotFor: aNr [
<category: 'accessing'>
^ aNr \\ 32
]
]
MGCPTrunkBase subclass: MGCPDSTrunk [
| trunk |
<comment: 'I represent an E1 trunk with 32 endpoints'>
<category: 'OsmoMGCP-Callagent'>
MGCPDSTrunk class >> createWithDest: anIP trunkNr: aNr [
<category: 'factory'>
^ self new
destIP: anIP;
numbersPorts: 31;
trunkNr: aNr;
yourself
]
trunkNr: aNr [
trunk := aNr.
]
endpointName: aNr [
<category: 'accessing'>
^ 'ds/e1-%1/%2@mgw' % {trunk. aNr}
]
multiplexFor: aNr [
^ trunk
]
timeslotFor: aNr [
^ aNr \\ 32
]
]