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 |
each verb = verb
ifTrue: [^each parseFromDict: nodes]].
^self error: 'Unknown command verb "%1"' % {verb}.
^self error: ('Unknown command verb "<1s>"' expandMacrosWith: verb).
]
MGCPCommandBase class >> parseFromDict: nodes [
@ -123,7 +123,12 @@ Object subclass: MGCPCommandBase [
"write the header"
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.
"write the parameters"

View File

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

View File

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