parsers/smalltalk/PPSmalltalkWhitespaceParser.st
changeset 417 3c0a91182e65
parent 390 17ba167b8ee1
child 421 7e08b31e0dae
equal deleted inserted replaced
416:b0fd54ee0412 417:3c0a91182e65
     4 	instanceVariableNames:'separator'
     4 	instanceVariableNames:'separator'
     5 	classVariableNames:''
     5 	classVariableNames:''
     6 	poolDictionaries:''
     6 	poolDictionaries:''
     7 	category:'PetitSmalltalk-Core'
     7 	category:'PetitSmalltalk-Core'
     8 !
     8 !
       
     9 
     9 
    10 
    10 
    11 
    11 !PPSmalltalkWhitespaceParser methodsFor:'analysis'!
    12 !PPSmalltalkWhitespaceParser methodsFor:'analysis'!
    12 
    13 
    13 isNullable
    14 isNullable
    22 ! !
    23 ! !
    23 
    24 
    24 !PPSmalltalkWhitespaceParser methodsFor:'parsing'!
    25 !PPSmalltalkWhitespaceParser methodsFor:'parsing'!
    25 
    26 
    26 parseOn: aPPContext
    27 parseOn: aPPContext
    27 	[ [aPPContext atEnd not and: [ separator value: aPPContext uncheckedPeek ] ]
    28         "Skip any leading whitespace"
    28 		whileTrue: [ aPPContext next ].
    29         [ [aPPContext atEnd not and: [ separator value: aPPContext uncheckedPeek ] ]
    29 		
    30                 whileTrue: [ aPPContext next ].
    30 	 aPPContext atEnd not and: [ aPPContext uncheckedPeek = $" ] ] whileTrue: [
    31 
    31 		aPPContext next.
    32         "Check for comment"
    32 		aPPContext upTo: $".
    33          aPPContext atEnd not and: [ aPPContext uncheckedPeek = $" ] ] whileTrue: [
    33 	].
    34                 aPPContext next.
       
    35                 "Check for Smalltalk/X EOL comment"
       
    36                 aPPContext uncheckedPeek == $/ ifTrue:[
       
    37                     | c |
       
    38                     aPPContext next.
       
    39                     [ aPPContext atEnd not 
       
    40                         and:[ (c := aPPContext uncheckedPeek) ~~ (Character codePoint: 15r0A) 
       
    41                         and: [ c ~~ (Character codePoint: 15r0D) ] ] ] whileTrue:[ 
       
    42                             aPPContext next.
       
    43                         ].
       
    44                     (c == (Character codePoint: 15r0D) and:[ aPPContext atEnd not and:[ aPPContext uncheckedPeek == (Character codePoint: 15r0A) ] ] ) ifTrue:[ 
       
    45                         aPPContext next
       
    46                     ].
       
    47                 ] ifFalse:[ 
       
    48                     aPPContext upTo: $".
       
    49                 ]
       
    50         ].
       
    51 
       
    52     "Modified: / 07-11-2014 / 01:18:42 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    34 ! !
    53 ! !
    35 
    54 
    36 !PPSmalltalkWhitespaceParser class methodsFor:'documentation'!
    55 !PPSmalltalkWhitespaceParser class methodsFor:'documentation'!
    37 
    56 
    38 version_HG
    57 version_HG