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

pharo: Do not use >>% format but the pharp command

This commit is contained in:
Holger Hans Peter Freyther 2015-07-25 21:49:26 +02:00
parent e32d2ac2be
commit 8174b683cb
3 changed files with 19 additions and 14 deletions

View File

@ -29,7 +29,7 @@ Object subclass: MGCPCommandBase [
self allSubclassesDo: [:each | self allSubclassesDo: [:each |
each verb = verb each verb = verb
ifTrue: [^each parseFromDict: nodes]]. ifTrue: [^each parseFromDict: nodes]].
^self error: 'Unknown command verb "%1"' % {verb}. ^self error: ('Unknown command verb "<1s>"' expandMacrosWith: verb).
] ]
MGCPCommandBase class >> parseFromDict: nodes [ MGCPCommandBase class >> parseFromDict: nodes [
@ -123,7 +123,12 @@ Object subclass: MGCPCommandBase [
"write the header" "write the header"
out out
nextPutAll: '%1 %2 %3 MGCP 1.0' % {self class verb. transaction. endp}; nextPutAll: self class verb;
nextPutAll: ' ';
nextPutAll: transaction asString;
nextPutAll: ' ';
nextPutAll: endp;
nextPutAll: ' MGCP 1.0';
cr; nl. cr; nl.
"write the parameters" "write the parameters"

View File

@ -87,8 +87,8 @@ Object subclass: MGCPEndpoint [
requireState: aState [ requireState: aState [
<category: 'allocation'> <category: 'allocation'>
state = aState ifFalse: [ state = aState ifFalse: [
^ self error: 'MGCPEndpoint(%1) not %2.' ^ self error: ('MGCPEndpoint(<1p>) not <2p>.'
% {self endpointName. aState}. expandMacrosWithArguments: {self endpointName. aState}).
]. ].
] ]

View File

@ -179,13 +179,13 @@ MGCPTransactionBase subclass: MGCPTransaction [
response: aRes [ response: aRes [
"Handle response but only once" "Handle response but only once"
state = self class stateStarted ifFalse: [ state = self class stateStarted ifFalse: [
^ self logError: 'Transaction(ID:%1 verb:%2) already terminated' ^ self logError: ('Transaction(ID:<1p> verb:<2s>) already terminated'
% {id. command class verb} area: #mgcp. expandMacrosWithArguments: {id. command class verb}) area: #mgcp.
]. ].
"Remember things for the future" "Remember things for the future"
self logNotice: 'Transaction(ID:%1 verb:%2) got a response.' self logNotice: ('Transaction(ID:<1p> verb:<2s>) got a response.'
% {id. command class verb} area: #mgcp. expandMacrosWithArguments: {id. command class verb}) area: #mgcp.
state := self class stateFinished. state := self class stateFinished.
self completed. self completed.
@ -197,16 +197,16 @@ MGCPTransactionBase subclass: MGCPTransaction [
transactionRemoved [ transactionRemoved [
<category: 'maintaining'> <category: 'maintaining'>
self logNotice: 'Transaction(ID:%1 verb:%2) is finished. %3' self logNotice: ('Transaction(ID:<1p> verb:<2s>) is finished. <3p>'
% {id. command class verb. DateTime now} area: #mgcp. expandMacrosWithArguments: {id. command class verb. DateTime now}) area: #mgcp.
self callagent removeTransactionInternal: self. self callagent removeTransactionInternal: self.
] ]
transactionExpired [ transactionExpired [
<category: 'maintaining'> <category: 'maintaining'>
self logNotice: 'Transaction(ID:%1 verb:%2) expired. %3' self logNotice: ('Transaction(ID:<1p> verb:<2s>) expired. <3p>'
% {id. command class verb. DateTime now} area: #mgcp. expandMacrosWithArguments: {id. command class verb. DateTime now}) area: #mgcp.
state := self class stateFinished. state := self class stateFinished.
self stopRetransmitTimer. self stopRetransmitTimer.
@ -217,8 +217,8 @@ MGCPTransactionBase subclass: MGCPTransaction [
transactionRetransmit [ transactionRetransmit [
<category: 'maintaining'> <category: 'maintaining'>
self logNotice: 'Transaction(ID:%1 verb:%2) retransmit.' self logNotice: ('Transaction(ID:<1p> verb:<2s>) retransmit.'
% {id. command class verb} area: #mgcp. expandMacrosWithArguments: {id. command class verb}) area: #mgcp.
self sendData. self sendData.
] ]
] ]