" (C) 2010-2012 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 . " PackageLoader fileInPackage: 'Sockets'; fileInPackage: 'OsmoNetwork'. Object subclass: MGCPCallAgentBase [ | net trunks sem addr port | MGCPCallAgentBase class >> startOn: anAddress [ ^ (self new) initialize: anAddress port: 2727; yourself. ] MGCPCallAgentBase class >> startOn: anAddress port: aPort [ ^ self new initialize: anAddress port: aPort; yourself. ] initialize: anAddress port: aPort [ sem := Semaphore forMutualExclusion. trunks := OrderedCollection new. addr := anAddress. port := aPort. net := Osmo.OsmoUDPSocket new name: 'MGCPCallAgent'; onData: [:data | OsmoDispatcher dispatchBlock: [self handleData: data]]; yourself. ] addTrunk: aTrunk [ sem critical: [ trunks add: aTrunk. ]. ] handleData: aData [ ^ self subclassResponsibility ] start [ | socket | self stop. socket := (Sockets.DatagramSocket local: addr port: port) bufferSize: 2048; yourself. net start: socket. ] stop [ net stop ] queueData: aDatagram [ net queueData: aDatagram. ] ] MGCPCallAgentBase subclass: MGCPCallAgent [ | transactions parser | initialize: anAddress port: aPort [ super initialize: anAddress port: aPort. transactions := OrderedCollection new. ] addTransaction: aTransaction [ sem critical: [ aTransaction transactionId: self generateTransactionId. transactions add: aTransaction. ] ] removeTransactionInternal: aTransaction [ sem critical: [transactions remove: aTransaction]. ] transactionIdIsUsed: anId [ ^ transactions anySatisfy: [:each | each transactionId = anId] ] generateTransactionId [ | ran | "I need to generate a transaction identifier. I assume proper locking" "Check if the below could ever succeed" (transactions size - 500000) > (999999999 - 100000000) ifTrue: [ ^ self error: 'No free transaction ID.'. ]. [ ran := Random between: 100000000 and: 999999999. self transactionIdIsUsed: ran ] whileTrue. ^ ran. ] parser [ ^ parser ifNil: [parser := MGCPParser new] ] handleData: aData [ [ | res data id trans | data := aData data copyFrom: 1 to: aData size. res := self parser parse: data asString onError: [ ^ self error: 'Parse error ', data asByteArray printString. ]. id := res transactionId asInteger. trans := sem critical: [transactions copy]. trans do: [:each | each transactionId = id ifTrue: [ each response: res. ] ] ] on: Error do: [:e | e logException: 'Incoming data ', e tag area: #mgcp. ] ] ]