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

pharo: Update the conversion code

PetitParser has a PPContext in newer versions but the GST code
is older and doesn't have it. Provide an alternative impl.

Provide >>#do: for the SIPVia for Pharo to print the data

Avoid importing MIMERWStream as it is dead in Pharo
This commit is contained in:
Holger Hans Peter Freyther 2015-07-23 21:37:26 +02:00
parent 439f34e675
commit 54d9f2059b
3 changed files with 151 additions and 34 deletions

View File

@ -8,12 +8,14 @@ CONVERT_RULES = -r'Osmo.LogManager->LogManager' \
-r'Osmo.TimerScheduler->TimerScheduler' \
-r'Osmo.OsmoUDPSocket->OsmoUDPSocket' \
-r'Sockets.StreamSocket->SocketStream' \
-r'Osmo.SIPParser->SIPParser' \
-r'DateTime->DateAndTime' \
-r'Character nl->Character lf' \
-r'(Duration milliseconds: ``@args1) -> (Duration milliSeconds: ``@args1)' \
-r'PP.PPCompositeParser->PPCompositeParser' \
-r'PP.PPCompositeParserTest->PPCompositeParserTest' \
-r'PP.PPPredicateObjectParser->PPPredicateObjectParser' \
-r'PP.PPCharSetPredicate->PPCharSetPredicate' \
-r'Osmo.MessageBuffer->MessageBuffer' \
-r'SystemExceptions.NotFound->NotFound' \
-r'(``@object substrings: ``@args1)->(``@object subStrings: ``@args1)' \
@ -27,23 +29,61 @@ CONVERT_RULES = -r'Osmo.LogManager->LogManager' \
# -r'(``@object => ``@args1)->(``@object ==> ``@args1)'
GRAMMAR = \
grammar/SIPGrammar.st grammar/SIPGrammarTest.st
grammar/SIPQuotedStringParser.st \
grammar/SIPGrammar.st grammar/SIPGrammarTest.st \
grammar/SIPQuotedStringParserTest.st
CALLAGENT = \
callagent/Base64MimeConverter.st \
callagent/Extensions.st \
callagent/SIPLogArea.st \
callagent/SIPDialog.st \
callagent/SIPParams.st \
callagent/SIPParser.st \
callagent/SIPRandom.st \
callagent/SIPRequests.st \
callagent/misc/SIPBase64.st \
callagent/misc/SIPRandomHelper.st \
callagent/misc/SIPURandom.st \
callagent/parameters/Extensions.st \
callagent/parameters/SIPParam.st \
callagent/parameters/SIPGenericParam.st \
callagent/parameters/SIPCSeq.st \
callagent/parameters/SIPToFromParam.st \
callagent/parameters/SIPVia.st \
callagent/requests/SIPRequest.st \
callagent/requests/SIPACKRequest.st \
callagent/requests/SIPByeRequest.st \
callagent/requests/SIPCancelRequest.st \
callagent/requests/SIPInviteRequest.st \
callagent/requests/SIPOptionsRequest.st \
callagent/requests/SIPRegisterRequest.st \
callagent/parser/Extensions.st \
callagent/parser/SIPParser.st \
callagent/SIPResponse.st \
callagent/SIPTransactions.st \
callagent/SIPCallAgent.st \
callagent/SIPCall.st \
callagent/SIPParserTest.st \
callagent/Tests.st
callagent/SIPIdentity.st \
callagent/transactions/SIPTransaction.st \
callagent/transactions/SIPByeTransaction.st \
callagent/transactions/SIPInviteTransaction.st \
callagent/transactions/SIPRegisterTransaction.st \
callagent/useragent/Extensions.st \
callagent/useragent/SIPUserAgentBase.st \
callagent/useragent/SIPUserAgent.st \
callagent/session/Extensions.st \
callagent/session/SIPSessionBase.st \
callagent/session/SIPCallBase.st \
callagent/session/SIPCall.st \
callagent/session/SIPIncomingCall.st \
callagent/transport/SIPTransport.st \
callagent/transport/SIPUdpTransport.st \
callagent/authorization/SIPDigest.st \
callagent/authorization/SIPAuthorization.st \
callagent/authorization/SIPProxyAuthorization.st \
callagent/tests/SIPParserTest.st \
callagent/tests/Tests.st \
callagent/tests/SIPCallAgentTest.st \
callagent/tests/SIPDigestTest.st \
callagent/tests/SIPTransportMock.st \
callagent/tests/SIPRegisterTransactionTest.st \
callagent/tests/SIPInviteTest.st \
callagent/tests/SIPBase64Test.st
PHARO_COMPAT = pharo-porting/compat_for_pharo.st
PHARO_CHANGES = pharo-porting/changes_for_pharo.st
@ -54,6 +94,8 @@ all:
convert:
$(GST_CONVERT) $(CONVERT_RULES) -F squeak -f gst \
-C-MIMERWStream \
-C-MimeConverter \
-o fileout.st $(PHARO_COMPAT) \
$(GRAMMAR) $(CALLAGENT) \
$(PHARO_CHANGES)

View File

@ -29,5 +29,9 @@ Object subclass: SIPParam [
nextPutAllOn: astream [
^ data nextPutAllOn: astream
]
do: ablock [
^ data do: ablock
]
]

View File

@ -2,33 +2,104 @@
SIPURandom class extend [
nextByte [
<category: 'random'>
| file |
"Pharo has a weird kind of stream support"
file := (FileStream readOnlyFileNamed: '/dev/urandom')
binary; yourself.
[
^ file next value.
] ensure: [
file close.
]
^(RAND rand: 1) first.
]
nextInt [
<category: 'random'>
| file |
file := (FileStream readOnlyFileNamed: '/dev/urandom')
binary; yourself.
[
| data |
data := ByteArray new: 4.
1 to: data size do: [:each |
data at: each put: file next value.
].
^ data uintAt: 1
] ensure: [
file close.
]
^(RAND rand: 4) asInteger
]
]
SIPUserAgentBase class extend [
generateCSeq [
<category: 'helper'>
"For pharo just use the random we have"
^(RAND rand: 4) asInteger abs
]
]
SIPQuotedStringParser extend [
skipWhitespace: aStream [
[aStream atEnd] whileFalse: [
| c |
c := aStream uncheckedPeek.
c = Character tab ifTrue: [aStream next].
c = Character space ifTrue: [aStream next].
^self
]
]
parseOn: aContext [
| memento startPosition result |
startPosition := aContext position.
memento := aContext remember.
"Skip whitespace"
self skipWhitespace: aContext.
"Check for the opening space"
aContext atEnd ifTrue: [
result := PPFailure message: 'No space for opening quote' context: aContext.
aContext restore: memento.
^result].
aContext uncheckedPeek = $" ifFalse: [
result := PPFailure message: 'No opening quote' context: aContext.
aContext restore: memento.
^result].
aContext skip: 1.
result := self parseToClosingQuote: aContext.
result isPetitFailure ifTrue: [
aContext restore: memento].
^result
]
parseToClosingQuote: aStream [
| text inQuote finish parsed |
text := WriteStream on: String new.
inQuote := false.
parsed := false.
finish := aStream atEnd.
[finish] whileFalse: ["Did we have an escape?"
inQuote
ifTrue: [
"TODO: Check if that is a valid sequence"
text nextPut: aStream next.
inQuote := false.
finish := aStream atEnd]
ifFalse: [
| c |
c := aStream uncheckedPeek.
c = $"
ifTrue: [
aStream skip: 1.
parsed := true.
^text contents]
ifFalse: [
c = $\ ifTrue: [inQuote := true].
text nextPut: c.
aStream skip: 1.
finish := aStream atEnd]]].
^PPFailure message: 'Expected closing quote' context: aStream
]
]
Base64LikeConverter class extend [
mimeEncode: aStream [
"Return a ReadWriteStream of characters. The data of aStream is encoded as 65 innocuous characters. (See class comment). 3 bytes in aStream goes to 4 bytes in output."
| me |
me := self new dataStream: aStream.
me
mimeStream: (ReadWriteStream on: (String new: (aStream size + 20) * 4 // 3)).
me mimeEncode.
me mimeStream position: 0.
^me mimeStream
]
]