parsers/smalltalk/PPSmalltalkWhitespaceParser.st
changeset 417 3c0a91182e65
parent 390 17ba167b8ee1
child 421 7e08b31e0dae
--- a/parsers/smalltalk/PPSmalltalkWhitespaceParser.st	Thu Nov 06 02:22:56 2014 +0000
+++ b/parsers/smalltalk/PPSmalltalkWhitespaceParser.st	Fri Nov 07 02:14:26 2014 +0000
@@ -8,6 +8,7 @@
 !
 
 
+
 !PPSmalltalkWhitespaceParser methodsFor:'analysis'!
 
 isNullable
@@ -24,13 +25,31 @@
 !PPSmalltalkWhitespaceParser methodsFor:'parsing'!
 
 parseOn: aPPContext
-	[ [aPPContext atEnd not and: [ separator value: aPPContext uncheckedPeek ] ]
-		whileTrue: [ aPPContext next ].
-		
-	 aPPContext atEnd not and: [ aPPContext uncheckedPeek = $" ] ] whileTrue: [
-		aPPContext next.
-		aPPContext upTo: $".
-	].
+        "Skip any leading whitespace"
+        [ [aPPContext atEnd not and: [ separator value: aPPContext uncheckedPeek ] ]
+                whileTrue: [ aPPContext next ].
+
+        "Check for comment"
+         aPPContext atEnd not and: [ aPPContext uncheckedPeek = $" ] ] whileTrue: [
+                aPPContext next.
+                "Check for Smalltalk/X EOL comment"
+                aPPContext uncheckedPeek == $/ ifTrue:[
+                    | c |
+                    aPPContext next.
+                    [ aPPContext atEnd not 
+                        and:[ (c := aPPContext uncheckedPeek) ~~ (Character codePoint: 15r0A) 
+                        and: [ c ~~ (Character codePoint: 15r0D) ] ] ] whileTrue:[ 
+                            aPPContext next.
+                        ].
+                    (c == (Character codePoint: 15r0D) and:[ aPPContext atEnd not and:[ aPPContext uncheckedPeek == (Character codePoint: 15r0A) ] ] ) ifTrue:[ 
+                        aPPContext next
+                    ].
+                ] ifFalse:[ 
+                    aPPContext upTo: $".
+                ]
+        ].
+
+    "Modified: / 07-11-2014 / 01:18:42 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 ! !
 
 !PPSmalltalkWhitespaceParser class methodsFor:'documentation'!