" (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 . " Object subclass: MGCPTrunkBase [ | ip ports sem last | MGCPTrunkBase class >> new [ ^ super new initialize; yourself ] initialize [ sem := RecursionLock new. ] destIp [ ^ ip ] destIP: aDest [ ip := aDest ] numbersPorts: nrPorts [ ports := Array new: nrPorts. 1 to: nrPorts do: [:each | ports at: each put: (MGCPEndpoint initWith: each trunk: self)]. ] endpointAt: aNr [ ^ ports at: aNr ] lastUsed [ ^ last ifNil: [0] ] endpointName: aNr [ ^ self subclassResponsibility ] multiplexFor: aNr [ ^ self subclassResponsibility. ] timeslotFor: aNr [ ^ self subclassResponsibility. ] critical: aBlock [ sem critical: aBlock. ] allocateEndpointIfFailure: aBlock [ | alloc | "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 [ MGCPVirtualTrunk class >> createWithDest: anIP numberPorts: nr [ ^ self new destIP: anIP; numbersPorts: nr yourself ] endpointName: aNr [ ^ '%1@mgw' % {((aNr radix: 16) copyFrom: 4) asLowercase} ] multiplexFor: aNr [ ^ aNr // 32 ] timeslotFor: aNr [ ^ aNr \\ 32 ] ] MGCPTrunkBase subclass: MGCPDSTrunk [ | trunk | MGCPDSTrunk class >> createWithDest: anIP trunkNr: aNr [ ^ self new destIP: anIP; numbersPorts: 31; trunkNr: aNr; yourself ] trunkNr: aNr [ trunk := aNr. ] endpointName: aNr [ ^ 'ds/e1-%1/%2@mgw' % {trunk. aNr} ] multiplexFor: aNr [ ^ trunk ] timeslotFor: aNr [ ^ aNr \\ 32 ] ]