GDBParser.st
changeset 7 7a51f98e7162
parent 6 d935bc59f6f4
child 8 7f4882e2562a
equal deleted inserted replaced
6:d935bc59f6f4 7:7a51f98e7162
       
     1 "{ Encoding: utf8 }"
       
     2 
       
     3 "{ Package: 'jv:libgdbs' }"
       
     4 
       
     5 Object subclass:#GDBParser
       
     6 	instanceVariableNames:'source lookahead token'
       
     7 	classVariableNames:''
       
     8 	poolDictionaries:'GDBCommandStatus'
       
     9 	category:'GDB-Private'
       
    10 !
       
    11 
       
    12 !GDBParser class methodsFor:'instance creation'!
       
    13 
       
    14 on: aStringOrStream
       
    15     ^ self new on: aStringOrStream
       
    16 
       
    17     "Created: / 27-05-2014 / 23:50:01 / Jan Vrany <jan.vrany@fit.cvut.cz>"
       
    18 ! !
       
    19 
       
    20 !GDBParser methodsFor:'initialization'!
       
    21 
       
    22 on: aStringOrStream
       
    23     source := aStringOrStream readStream
       
    24 
       
    25     "Created: / 27-05-2014 / 23:50:24 / Jan Vrany <jan.vrany@fit.cvut.cz>"
       
    26 ! !
       
    27 
       
    28 !GDBParser methodsFor:'parsing'!
       
    29 
       
    30 parseCString
       
    31     | buffer inString nextChar |
       
    32 
       
    33     self expect: $".
       
    34     nextChar := self next.
       
    35     buffer := (String new: 50) writeStream.
       
    36     inString := true.
       
    37     [inString] whileTrue:[
       
    38 	nextChar isNil ifTrue:[
       
    39 	    self error: 'Unexpected end of input'.
       
    40 	].
       
    41 	nextChar == $\ ifTrue:[
       
    42 	    nextChar := self next.
       
    43 	    nextChar := self parseCStringEscape:nextChar.
       
    44 	] ifFalse:[
       
    45 	    (nextChar == $") ifTrue:[
       
    46 		(self peekOrNil == $") ifTrue:[
       
    47 		    self next
       
    48 		] ifFalse:[
       
    49 		    inString := false
       
    50 		]
       
    51 	    ].
       
    52 	].
       
    53 	inString ifTrue:[
       
    54 	    buffer nextPut:nextChar.
       
    55 	    nextChar := self next
       
    56 	]
       
    57     ].
       
    58     ^ buffer contents
       
    59 
       
    60     "Created: / 27-05-2014 / 23:51:35 / Jan Vrany <jan.vrany@fit.cvut.cz>"
       
    61 !
       
    62 
       
    63 parseCStringEscape: char
       
    64     |ascii c |
       
    65 
       
    66     char == $" ifTrue:[
       
    67 	^ $".
       
    68     ].
       
    69 
       
    70     char == $b ifTrue:[
       
    71 	^ Character backspace
       
    72     ].
       
    73     char == $t ifTrue:[
       
    74 	^ Character tab
       
    75     ].
       
    76     char == $n ifTrue:[
       
    77 	^ Character cr
       
    78     ].
       
    79     char == $r ifTrue:[
       
    80 	^ Character return
       
    81     ].
       
    82     char == $f ifTrue:[
       
    83 	^ Character newPage
       
    84     ].
       
    85 
       
    86 "/    char == $u ifTrue:[
       
    87 "/        ascii := 0.
       
    88 "/        c := source peekOrNil.
       
    89 "/        4 timesRepeat:[
       
    90 "/            (c isDigitRadix:16) ifFalse:[
       
    91 "/                self syntaxError:'invalid hex character constant'
       
    92 "/                        position:source position-2 to:(source position - 1).
       
    93 "/                ^ Character value:ascii
       
    94 "/            ].
       
    95 "/            ascii := (ascii bitShift:4).
       
    96 "/            ascii := ascii + c digitValue.
       
    97 "/            source next. c := source peekOrNil.
       
    98 "/        ].
       
    99 "/        ^ Character value:ascii
       
   100 "/    ].
       
   101     char == $x ifTrue:[
       
   102 	ascii := 0.
       
   103 	c := self peekOrNil.
       
   104 	2 timesRepeat:[
       
   105 	    (c isDigitRadix:16) ifFalse:[
       
   106 		self error:'Invalid hex character escape'.
       
   107 		^ Character value:ascii
       
   108 	    ].
       
   109 	    ascii := (ascii bitShift:4).
       
   110 	    ascii := ascii + c digitValue.
       
   111 	    self next. c := self peekOrNil.
       
   112 	].
       
   113 	^ Character value:ascii
       
   114     ].
       
   115     "OctalEscape ::= \ OctalDigit |
       
   116 		     \ OctalDigit OctalDigit
       
   117 		     \ ZeroToThree OctalDigit OctalDigit"
       
   118 
       
   119     (char between:$0 and:$3) ifTrue:[
       
   120 	ascii := char digitValue.
       
   121 	c := self peekOrNil.
       
   122 	(c between: $0 and: $7) ifTrue:[
       
   123 	    self next.
       
   124 	    ascii := (ascii bitShift:3).
       
   125 	    ascii := ascii + c digitValue.
       
   126 	].
       
   127 	c := self peekOrNil.
       
   128 	(c between: $0 and: $7) ifTrue:[
       
   129 	    self next.
       
   130 	    ascii := (ascii bitShift:3).
       
   131 	    ascii := ascii + c digitValue.
       
   132 	].
       
   133 	^ Character value:ascii
       
   134     ].
       
   135     (char between:$4 and: $7) ifTrue:[
       
   136 	ascii := char digitValue.
       
   137 	c := self peekOrNil.
       
   138 	(c between: $0 and: $7) ifTrue:[
       
   139 	    self next.
       
   140 	    ascii := (ascii bitShift:3).
       
   141 	    ascii := ascii + c digitValue.
       
   142 	].
       
   143 	^ Character value:ascii
       
   144     ].
       
   145 
       
   146     ^ char
       
   147 
       
   148     "Created: / 28-05-2014 / 00:02:40 / Jan Vrany <jan.vrany@fit.cvut.cz>"
       
   149 !
       
   150 
       
   151 parseNl
       
   152     | c |
       
   153 
       
   154     c := self peek.
       
   155     (c == Character return or:[ c == Character cr ]) ifTrue:[
       
   156 	self next
       
   157     ].
       
   158 
       
   159     "Created: / 30-05-2014 / 09:52:36 / Jan Vrany <jan.vrany@fit.cvut.cz>"
       
   160     "Modified: / 31-05-2014 / 00:38:17 / Jan Vrany <jan.vrany@fit.cvut.cz>"
       
   161 !
       
   162 
       
   163 parseOutput
       
   164     "
       
   165     output → ( out-of-band-record )* [ result-record ] '(gdb)' nl
       
   166     out-of-band-record → async-record | stream-record
       
   167 
       
   168     "
       
   169 
       
   170     | peek events |
       
   171 
       
   172     events := GDBEventSet new.
       
   173     [
       
   174         peek := self peek.
       
   175         peek isDigit ifTrue:[ self parseToken. peek := self peek ].
       
   176         peek ~~ $(
       
   177     ] whileTrue:[
       
   178         ('*+=' includes: self peek) ifTrue:[
       
   179             events add: self parseAsyncRecord.
       
   180         ] ifFalse:[
       
   181             ('~@&' includes: self peek) ifTrue:[
       
   182                 events add: self parseStreamRecord.
       
   183             ] ifFalse:[
       
   184                 peek == $^ ifTrue:[
       
   185                     events add: self parseResultRecord.
       
   186                 ] ifFalse:[
       
   187                     self error:'Invalid MI record'.
       
   188                 ].
       
   189             ].
       
   190         ].
       
   191     ].
       
   192     self expect: '(gdb)'.
       
   193     self parseNl.
       
   194     ^ events
       
   195 
       
   196     "Created: / 30-05-2014 / 09:52:36 / Jan Vrany <jan.vrany@fit.cvut.cz>"
       
   197     "Modified: / 02-06-2014 / 22:21:54 / Jan Vrany <jan.vrany@fit.cvut.cz>"
       
   198 !
       
   199 
       
   200 parseResultClass
       
   201     "
       
   202     result-class → 'done' | 'running' | 'connected' | 'error' | 'exit'
       
   203     "
       
   204     | c1 c2 |
       
   205 
       
   206     c1 := self peek.
       
   207     c1 == $d ifTrue:[
       
   208 	self expect: 'done'.
       
   209 	^ CommandStatusDone.
       
   210     ].
       
   211     c1 == $r ifTrue:[
       
   212 	self expect: 'running'.
       
   213 	^ CommandStatusDone.
       
   214     ].
       
   215     c1 == $c ifTrue:[
       
   216 	self expect: 'connected'.
       
   217 	^ CommandStatusConnected.
       
   218     ].
       
   219     c1 == $e ifTrue:[
       
   220 	self next.
       
   221 	c2 := self peek.
       
   222 	c2 == $x ifTrue:[
       
   223 	    self expect: 'xit'.
       
   224 	    ^ CommandStatusExit.
       
   225 	].
       
   226 	c2 == $r ifTrue:[
       
   227 	    self expect: 'rror'.
       
   228 	    ^ CommandStatusError.
       
   229 	].
       
   230     ].
       
   231     ^ self error:'Unsupported result class'
       
   232 
       
   233     "Created: / 31-05-2014 / 00:16:31 / Jan Vrany <jan.vrany@fit.cvut.cz>"
       
   234     "Modified: / 01-06-2014 / 23:21:11 / Jan Vrany <jan.vrany@fit.cvut.cz>"
       
   235 !
       
   236 
       
   237 parseResultRecord
       
   238     "
       
   239     result-record → '^' result-class ( ',' result )* nl
       
   240     "
       
   241 
       
   242     | result |
       
   243 
       
   244     self expect: $^.
       
   245     result := GDBCommandResult new.
       
   246     result status: self parseResultClass.
       
   247     self peek == $, ifTrue:[
       
   248         self next.
       
   249         result value: self parseResult.
       
   250     ].
       
   251     self parseNl.
       
   252     ^ GDBCommandResultEvent new result: result.
       
   253 
       
   254     "Created: / 30-05-2014 / 09:52:35 / Jan Vrany <jan.vrany@fit.cvut.cz>"
       
   255     "Modified: / 02-06-2014 / 22:22:33 / Jan Vrany <jan.vrany@fit.cvut.cz>"
       
   256 !
       
   257 
       
   258 parseToken
       
   259 
       
   260     "Created: / 28-05-2014 / 00:14:57 / Jan Vrany <jan.vrany@fit.cvut.cz>"
       
   261 ! !
       
   262 
       
   263 !GDBParser methodsFor:'parsing-async events'!
       
   264 
       
   265 parseAsyncRecord
       
   266     "
       
   267     async-record → exec-async-output | status-async-output | notify-async-output
       
   268     "
       
   269     self peek == $* ifTrue:[
       
   270         self next.
       
   271         ^ self parseAsyncRecord: GDBExecutionEvent.
       
   272     ].
       
   273     self peek == $+ ifTrue:[
       
   274         self next.
       
   275         ^ self parseAsyncRecord: GDBStatusEvent .
       
   276     ].
       
   277     self peek == $= ifTrue:[
       
   278         self next.
       
   279         ^ self parseAsyncRecord: GDBNotificationEvent.
       
   280     ].
       
   281 
       
   282     ^ self error: 'Invalid async-record'
       
   283 
       
   284     "Created: / 30-05-2014 / 09:57:30 / Jan Vrany <jan.vrany@fit.cvut.cz>"
       
   285     "Modified: / 02-06-2014 / 22:19:35 / Jan Vrany <jan.vrany@fit.cvut.cz>"
       
   286 !
       
   287 
       
   288 parseAsyncRecord: eventClass
       
   289     "
       
   290     async-output → async-class ( ',' result )* nl
       
   291     "
       
   292 
       
   293     | type data |
       
   294 
       
   295     type := self parseString.
       
   296     data := Array streamContents:[ :s |
       
   297 	[ self peek == $, ] whileTrue:[
       
   298 	    self next.
       
   299 	    s nextPut: self parseResult.
       
   300 	]
       
   301     ].
       
   302     self parseNl.
       
   303 
       
   304     ^ eventClass new
       
   305 	type: type;
       
   306 	data: data;
       
   307 	yourself
       
   308 
       
   309     "Created: / 01-06-2014 / 23:43:36 / Jan Vrany <jan.vrany@fit.cvut.cz>"
       
   310 ! !
       
   311 
       
   312 !GDBParser methodsFor:'parsing-misc'!
       
   313 
       
   314 parseResult
       
   315     "
       
   316     result → variable = value
       
   317     "
       
   318 
       
   319     | name value |
       
   320 
       
   321     name := self parseVariable.
       
   322     self expect: $=.
       
   323     value := self parseValue.
       
   324     ^ name -> value
       
   325 
       
   326     "Created: / 30-05-2014 / 10:15:55 / Jan Vrany <jan.vrany@fit.cvut.cz>"
       
   327     "Modified: / 31-05-2014 / 00:39:51 / Jan Vrany <jan.vrany@fit.cvut.cz>"
       
   328 !
       
   329 
       
   330 parseString
       
   331     ^ String streamContents:[:s|
       
   332 	[ self peek isLetter or:['-' includes: self peek ] ]  whileTrue:[
       
   333 	    s nextPut: self next.
       
   334 	]
       
   335     ].
       
   336 
       
   337     "Created: / 30-05-2014 / 10:32:02 / Jan Vrany <jan.vrany@fit.cvut.cz>"
       
   338     "Modified: / 31-05-2014 / 00:33:59 / Jan Vrany <jan.vrany@fit.cvut.cz>"
       
   339 !
       
   340 
       
   341 parseVariable
       
   342     "
       
   343     variable → string
       
   344     "
       
   345     ^ self parseString
       
   346 
       
   347     "Created: / 30-05-2014 / 10:31:11 / Jan Vrany <jan.vrany@fit.cvut.cz>"
       
   348 ! !
       
   349 
       
   350 !GDBParser methodsFor:'parsing-stream output'!
       
   351 
       
   352 parseStreamRecord
       
   353     "
       
   354     stream-record → console-stream-output | target-stream-output | log-stream-output
       
   355     "
       
   356 
       
   357     self peek == $~ ifTrue:[
       
   358         self next.
       
   359         ^ self parseStreamRecord: GDBConsoleOutputEvent.
       
   360     ].
       
   361     self peek == $@ ifTrue:[
       
   362         self next.
       
   363         ^ self parseStreamRecord: GDBTargetOutputEvent.
       
   364     ].
       
   365     self peek == $& ifTrue:[
       
   366         self next.
       
   367         ^ self parseStreamRecord: GDBLogOutputEvent.
       
   368     ].
       
   369     self error:'Invalid stream record'
       
   370 
       
   371     "Created: / 30-05-2014 / 09:57:31 / Jan Vrany <jan.vrany@fit.cvut.cz>"
       
   372     "Modified: / 02-06-2014 / 22:21:29 / Jan Vrany <jan.vrany@fit.cvut.cz>"
       
   373 !
       
   374 
       
   375 parseStreamRecord: eventClass
       
   376     | value |
       
   377 
       
   378     value := self parseCString.
       
   379     self parseNl.
       
   380     ^ eventClass new value: value; yourself
       
   381 
       
   382     "Created: / 01-06-2014 / 23:41:55 / Jan Vrany <jan.vrany@fit.cvut.cz>"
       
   383 ! !
       
   384 
       
   385 !GDBParser methodsFor:'parsing-utils'!
       
   386 
       
   387 expect: aStringOrChar
       
   388 
       
   389     | c |
       
   390     aStringOrChar isCharacter ifTrue:[
       
   391 	(self atEnd or:[(c := self next) ~= aStringOrChar]) ifTrue:[
       
   392 	    self error:('Expected ''%1'' got ''%2''.' bindWith: aStringOrChar with: c).
       
   393 	].
       
   394 	^self.
       
   395     ].
       
   396     aStringOrChar isString ifTrue:[
       
   397 	aStringOrChar do:[:expected|
       
   398 	    (self atEnd or:[(c := self next) ~= expected]) ifTrue:[
       
   399 		self error:('Expected ''%1''.' bindWith: aStringOrChar).
       
   400 	    ].
       
   401 	].
       
   402 	^self.
       
   403     ].
       
   404 
       
   405     self error:'Invalid expected value'.
       
   406 
       
   407     "Created: / 19-11-2012 / 20:08:33 / Jan Vrany <jan.vrany@fit.cvut.cz>"
       
   408     "Modified: / 28-05-2014 / 00:17:06 / Jan Vrany <jan.vrany@fit.cvut.cz>"
       
   409 !
       
   410 
       
   411 expectLineEnd
       
   412     self expect: Character cr.
       
   413 
       
   414     "Created: / 19-11-2012 / 20:06:21 / Jan Vrany <jan.vrany@fit.cvut.cz>"
       
   415 !
       
   416 
       
   417 expectSpace
       
   418     self expect: Character space.
       
   419 
       
   420     "Created: / 19-11-2012 / 20:06:27 / Jan Vrany <jan.vrany@fit.cvut.cz>"
       
   421 ! !
       
   422 
       
   423 !GDBParser methodsFor:'parsing-values'!
       
   424 
       
   425 parseConst
       
   426     "
       
   427     const → c-string
       
   428     "
       
   429 
       
   430     ^ self parseCString.
       
   431 
       
   432     "Created: / 30-05-2014 / 10:36:04 / Jan Vrany <jan.vrany@fit.cvut.cz>"
       
   433 !
       
   434 
       
   435 parseList
       
   436     "
       
   437     list → '[]' | '[' value ( ',' value )* ']' | '[' result ( ',' result )* ']'
       
   438     "
       
   439 
       
   440     self expect: $[.
       
   441     self peek == $] ifTrue:[
       
   442 	self next.
       
   443 	^ #()
       
   444     ] ifFalse:[
       
   445 	^ Array streamContents:[ :s|
       
   446 	    s nextPut: self parseValue.
       
   447 	    [ self peek == $, ] whileTrue:[
       
   448 		self next.
       
   449 		s nextPut: self parseValue.
       
   450 	    ].
       
   451 	    self expect: $].
       
   452 	].
       
   453     ].
       
   454 
       
   455     "Created: / 30-05-2014 / 10:36:06 / Jan Vrany <jan.vrany@fit.cvut.cz>"
       
   456 !
       
   457 
       
   458 parseTuple
       
   459     "raise an error: this method should be implemented (TODO)"
       
   460 
       
   461     | object |
       
   462 
       
   463     object := GDBTuple new.
       
   464     self expect: ${.
       
   465     self peek == $} ifTrue:[
       
   466 	self next.
       
   467     ] ifFalse:[
       
   468 	| name value |
       
   469 
       
   470 	name := self parseVariable.
       
   471 	self expect: $=.
       
   472 	value := self parseValue.
       
   473 	object propertyAt: name put: value.
       
   474 	[ self peek == $, ] whileTrue:[
       
   475 	    self next.
       
   476 	    name := self parseVariable.
       
   477 	    self expect: $=.
       
   478 	    value := self parseValue.
       
   479 	    object propertyAt: name put: value.
       
   480 	].
       
   481 	self expect: $}.
       
   482     ].
       
   483     ^ object
       
   484 
       
   485     "Created: / 30-05-2014 / 10:36:05 / Jan Vrany <jan.vrany@fit.cvut.cz>"
       
   486     "Modified: / 31-05-2014 / 00:35:03 / Jan Vrany <jan.vrany@fit.cvut.cz>"
       
   487 !
       
   488 
       
   489 parseValue
       
   490     "
       
   491     value → const | tuple | list
       
   492     "
       
   493 
       
   494     self peek == $" ifTrue:[
       
   495 	^ self parseConst
       
   496     ].
       
   497     self peek == ${ ifTrue:[
       
   498 	^ self parseTuple.
       
   499     ].
       
   500     self peek == $[ ifTrue:[
       
   501 	^ self parseList
       
   502     ].
       
   503     self error:'Invalid value'
       
   504 
       
   505     "Created: / 30-05-2014 / 10:31:12 / Jan Vrany <jan.vrany@fit.cvut.cz>"
       
   506 ! !
       
   507 
       
   508 !GDBParser methodsFor:'streaming'!
       
   509 
       
   510 atEnd
       
   511     ^ source atEnd
       
   512 
       
   513     "Created: / 28-05-2014 / 00:17:06 / Jan Vrany <jan.vrany@fit.cvut.cz>"
       
   514 !
       
   515 
       
   516 next
       
   517     | next |
       
   518     lookahead notNil ifTrue:[
       
   519 	next := lookahead.
       
   520 	lookahead := nil.
       
   521 	^ next.
       
   522     ].
       
   523     ^ source next.
       
   524 
       
   525     "Created: / 23-10-2012 / 10:57:24 / Jan Vrany <jan.vrany@fit.cvut.cz>"
       
   526     "Modified: / 28-05-2014 / 00:23:33 / Jan Vrany <jan.vrany@fit.cvut.cz>"
       
   527 !
       
   528 
       
   529 nextLine
       
   530     lookahead := nil.
       
   531     ^source nextLine
       
   532 
       
   533     "Created: / 23-10-2012 / 11:05:47 / Jan Vrany <jan.vrany@fit.cvut.cz>"
       
   534     "Modified: / 28-05-2014 / 00:21:12 / Jan Vrany <jan.vrany@fit.cvut.cz>"
       
   535 !
       
   536 
       
   537 peek
       
   538     lookahead notNil ifTrue:[
       
   539 	^ lookahead
       
   540     ].
       
   541     ^ lookahead := source next.
       
   542 
       
   543     "Created: / 28-05-2014 / 00:18:32 / Jan Vrany <jan.vrany@fit.cvut.cz>"
       
   544 !
       
   545 
       
   546 peekOrNil
       
   547     lookahead notNil ifTrue:[ ^ lookahead ].
       
   548     source atEnd ifTrue:[ ^ nil ].
       
   549     ^ self peek
       
   550 
       
   551     "Created: / 28-05-2014 / 00:15:32 / Jan Vrany <jan.vrany@fit.cvut.cz>"
       
   552 !
       
   553 
       
   554 skipSeparators
       
   555     lookahead := nil.
       
   556     source skipSeparators
       
   557 
       
   558     "Created: / 19-11-2012 / 20:05:04 / Jan Vrany <jan.vrany@fit.cvut.cz>"
       
   559     "Modified: / 28-05-2014 / 00:21:17 / Jan Vrany <jan.vrany@fit.cvut.cz>"
       
   560 ! !
       
   561