smalltalk
/
osmo-st-sip
Archived
1
0
Fork 0
This repository has been archived on 2022-02-17. You can view files and clone it, but cannot push or open issues or pull requests.
osmo-st-sip/grammar/SIPQuotedStringParser.st

99 lines
3.3 KiB
Smalltalk

"
(C) 2011-2014 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 <http://www.gnu.org/licenses/>.
"
PP.PPParser subclass: SIPQuotedStringParser [
<category: 'OsmoSIP-Grammar'>
<comment: 'The simple rule for PetitParser is a performance
issue on ARMv5te and we can do better here.
From RFC3161:
quoted-string = SWS DQUOTE *(qdtext / quoted-pair ) DQUOTE
qdtext = LWS / %x21 / %x23-5B / %x5D-7E
/ UTF8-NONASCII
quoted-pair = "\" (%x00-09 / %x0B-0C
/ %x0E-7F)
LWS = [*WSP CRLF] 1*WSP ; linear whitespace
SWS = [LWS] ; sep whitespace'>
skipWhitespace: aStream [
[aStream atEnd] whileFalse: [
| c |
c := aStream uncheckedPeek.
c = ##(Character tab) ifTrue: [aStream next].
c = ##(Character space) ifTrue: [aStream next].
^self
]
]
parseToClosingQuote: aStream startingAt: aStartPointer [
| 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]]].
aStream pointer: aStartPointer.
^PPFailure message: 'Expected closing quote' at: aStream position
]
parseOn: aStream [
| startPtr |
startPtr := aStream pointer.
"Skip whitespace"
self skipWhitespace: aStream.
"Check for the opening space"
aStream atEnd ifTrue: [
aStream pointer: startPtr.
^PPFailure message: 'No space for opening quote' at: aStream position].
aStream uncheckedPeek = $" ifFalse: [
aStream pointer: startPtr.
^PPFailure message: 'No opening quote' at: aStream position].
aStream skip: 1.
^self parseToClosingQuote: aStream startingAt: startPtr.
]
]