GDBMIParser.st
author Jan Vrany <jan.vrany@fit.cvut.cz>
Wed, 01 Oct 2014 09:38:44 +0100
changeset 52 0618438f6ba5
parent 45 deb908479a37
child 55 437ee6413c74
permissions -rw-r--r--
Report async execution event immediately. GDB 7.7.1 (and possibly other versions too) does not write '(gdb)' terminator after an async execution events (even though specification says it should). Thus, report any execution record immediately.

"{ Encoding: utf8 }"

"{ Package: 'jv:libgdbs' }"

Object subclass:#GDBMIParser
	instanceVariableNames:'source lookahead token token2CommandMappingBlock recorder'
	classVariableNames:''
	poolDictionaries:'GDBCommandStatus'
	category:'GDB-Private'
!


!GDBMIParser class methodsFor:'instance creation'!

on: aStringOrStream
    ^ self new on: aStringOrStream

    "Created: / 27-05-2014 / 23:50:01 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!GDBMIParser methodsFor:'accessing'!

recorder
    ^ recorder
!

recorder:something
    recorder := something.
!

token2CommandMappingBlock: aBlock
    token2CommandMappingBlock := aBlock.

    "Created: / 19-06-2014 / 21:34:52 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!GDBMIParser methodsFor:'initialization'!

on: aStringOrStream
    source := aStringOrStream readStream

    "Created: / 27-05-2014 / 23:50:24 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!GDBMIParser methodsFor:'parsing'!

parseCString
    self expect: $".
    ^ self parseCStringRest: ''.

    "Created: / 27-05-2014 / 23:51:35 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified (format): / 18-06-2014 / 07:19:09 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

parseCStringEscape: char
    |ascii c |

    char == $" ifTrue:[
	^ $".
    ].

    char == $b ifTrue:[
	^ Character backspace
    ].
    char == $t ifTrue:[
	^ Character tab
    ].
    char == $n ifTrue:[
	^ Character cr
    ].
    char == $r ifTrue:[
	^ Character return
    ].
    char == $f ifTrue:[
	^ Character newPage
    ].

"/    char == $u ifTrue:[
"/        ascii := 0.
"/        c := source peekOrNil.
"/        4 timesRepeat:[
"/            (c isDigitRadix:16) ifFalse:[
"/                self syntaxError:'invalid hex character constant'
"/                        position:source position-2 to:(source position - 1).
"/                ^ Character value:ascii
"/            ].
"/            ascii := (ascii bitShift:4).
"/            ascii := ascii + c digitValue.
"/            source next. c := source peekOrNil.
"/        ].
"/        ^ Character value:ascii
"/    ].
    char == $x ifTrue:[
	ascii := 0.
	c := self peekOrNil.
	2 timesRepeat:[
	    (c isDigitRadix:16) ifFalse:[
		self error:'Invalid hex character escape'.
		^ Character value:ascii
	    ].
	    ascii := (ascii bitShift:4).
	    ascii := ascii + c digitValue.
	    self next. c := self peekOrNil.
	].
	^ Character value:ascii
    ].
    "OctalEscape ::= \ OctalDigit |
		     \ OctalDigit OctalDigit
		     \ ZeroToThree OctalDigit OctalDigit"

    (char between:$0 and:$3) ifTrue:[
	ascii := char digitValue.
	c := self peekOrNil.
	(c between: $0 and: $7) ifTrue:[
	    self next.
	    ascii := (ascii bitShift:3).
	    ascii := ascii + c digitValue.
	].
	c := self peekOrNil.
	(c between: $0 and: $7) ifTrue:[
	    self next.
	    ascii := (ascii bitShift:3).
	    ascii := ascii + c digitValue.
	].
	^ Character value:ascii
    ].
    (char between:$4 and: $7) ifTrue:[
	ascii := char digitValue.
	c := self peekOrNil.
	(c between: $0 and: $7) ifTrue:[
	    self next.
	    ascii := (ascii bitShift:3).
	    ascii := ascii + c digitValue.
	].
	^ Character value:ascii
    ].

    ^ char

    "Created: / 28-05-2014 / 00:02:40 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

parseCStringRest: alreadyRead
    | buffer inString nextChar |

    buffer := (String new: 50) writeStream.
    buffer nextPutAll: alreadyRead.
    nextChar := self next.
    inString := true.
    [inString] whileTrue:[
        nextChar isNil ifTrue:[
            self error: 'Unexpected end of input'.
        ].
        nextChar == $\ ifTrue:[
            nextChar := self next.
            nextChar := self parseCStringEscape:nextChar.
        ] ifFalse:[
            (nextChar == $") ifTrue:[
                (self peekOrNil == $") ifTrue:[
                    self next
                ] ifFalse:[
                    inString := false
                ]
            ].
        ].
        inString ifTrue:[
            buffer nextPut:nextChar.
            nextChar := self next
        ]
    ].
    ^ buffer contents

    "Created: / 18-06-2014 / 07:17:34 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

parseNl
    | c |

    c := self peek.
    (c == Character return or:[ c == Character cr ]) ifTrue:[
	self next
    ].

    "Created: / 30-05-2014 / 09:52:36 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 31-05-2014 / 00:38:17 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

parseNonBlankSequence
    ^ String streamContents:[ :buffer | 
        [ self peek isNil or: [ self peek isSeparator ] ] whileFalse:[
            buffer nextPut: self next.
        ]
    ]

    "Created: / 24-06-2014 / 23:19:40 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

parseOutput
    "
    output → ( out-of-band-record )* [ result-record ] '(gdb)' nl
    out-of-band-record → async-record | stream-record

    "

    | peek events |

    events := GDBEventSet new.

    peek := self peek.
    peek == Character space ifTrue:[ self next ].
    peek := self peek.
    peek == Character cr ifTrue:[ self next ].
    [
        token := nil.
        peek := self peek.
        peek isNil ifTrue:[ 
            source atEnd ifTrue:[ ^ events ].
        ].
        peek isDigit ifTrue:[ self parseToken. peek := self peek ].
        peek ~~ $(
    ] whileTrue:[
        ('*+=' includes: self peek) ifTrue:[
            | event |

            event := self parseAsyncRecord.
            events add: event.
            "Sigh, GDB 7.7.1 does not write '(gdb)' terminator after an
             async execution events (even though specification says it should). 
             Thus, report any execution record immediately"
            event isExecutionEvent ifTrue:[
                events last token: token.
                recorder notNil ifTrue:[ 
                    recorder recordResponseEnd.
                ].
                ^ events
            ].
        ] ifFalse:[
            ('~@&' includes: self peek) ifTrue:[
                events add: self parseStreamRecord.
            ] ifFalse:[
                peek == $^ ifTrue:[
                    events add: self parseResultRecord.
                ] ifFalse:[
                    self error:'Invalid MI record'.
                ].
            ].
        ].
        events last token: token.
    ].
    self expect: '(gdb)'.
    [ self peek == Character space ] whileTrue:[ self next ].
    self parseNl.
    recorder notNil ifTrue:[ 
        recorder recordResponseEnd.
    ].
    ^ events

    "Created: / 30-05-2014 / 09:52:36 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 01-10-2014 / 09:36:32 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

parseResultClass
    "
    result-class → 'done' | 'running' | 'connected' | 'error' | 'exit'
    "
    | c1 c2 |

    c1 := self peek.
    c1 == $d ifTrue:[
	self expect: 'done'.
	^ CommandStatusDone.
    ].
    c1 == $r ifTrue:[
	self expect: 'running'.
	^ CommandStatusDone.
    ].
    c1 == $c ifTrue:[
	self expect: 'connected'.
	^ CommandStatusConnected.
    ].
    c1 == $e ifTrue:[
	self next.
	c2 := self peek.
	c2 == $x ifTrue:[
	    self expect: 'xit'.
	    ^ CommandStatusExit.
	].
	c2 == $r ifTrue:[
	    self expect: 'rror'.
	    ^ CommandStatusError.
	].
    ].
    ^ self error:'Unsupported result class'

    "Created: / 31-05-2014 / 00:16:31 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 01-06-2014 / 23:21:11 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

parseResultRecord
    "
    result-record → '^' result-class ( ',' result )* nl
    "

    | command result descriptor propertyName propertyDescriptor propertyValue |

    self expect: $^.
    result := GDBCommandResult new.
    result status: self parseResultClass.
    descriptor := GDBMAContainer new.
    (token notNil and:[ token2CommandMappingBlock notNil ]) ifTrue:[ 
        command := token2CommandMappingBlock value: token. 
        command notNil ifTrue:[
            result command: command.
            descriptor := command resultDescription.        
        ].
    ].
    [ self peek == $, ] whileTrue:[
        self next. "/ eat $,
        propertyName := self parseVariable.
        propertyDescriptor := descriptor propertyDescriptorAt: propertyName.
        self expect: $=.
        propertyDescriptor isNil ifTrue:[ 
            propertyValue := self parseValue.
        ] ifFalse:[ 
            propertyValue := propertyDescriptor parseUsingGDBMIParser:self. 
        ]. 
        result propertyAt: propertyName put: propertyValue.
     ].             
    self parseNl.
    ^ GDBCommandResultEvent new result: result.

    "Created: / 30-05-2014 / 09:52:35 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 23-09-2014 / 23:37:16 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

parseToken
    token := 0.
    [ self peek isDigit ] whileTrue:[ 
        token := (token * 10) + (self next codePoint - $0 codePoint).
    ].

    "Created: / 28-05-2014 / 00:14:57 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 03-06-2014 / 00:49:16 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!GDBMIParser methodsFor:'parsing-async events'!

parseAsyncRecord
    "
    async-record → exec-async-output | status-async-output | notify-async-output
    "
    self peek == $* ifTrue:[
        self next.
        ^ self parseAsyncRecord: GDBExecutionEvent.
    ].
    self peek == $+ ifTrue:[
        self next.
        ^ self parseAsyncRecord: GDBStatusEvent .
    ].
    self peek == $= ifTrue:[
        self next.
        ^ self parseAsyncRecord: GDBNotificationEvent.
    ].

    ^ self error: 'Invalid async-record'

    "Created: / 30-05-2014 / 09:57:30 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 02-06-2014 / 22:19:35 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

parseAsyncRecord: eventClassBase
    "
    async-output → async-class ( ',' result )* nl
    "

    | type eventClass event propertyName propertyDescriptor descriptor propertyValue |

    type := self parseString.
    eventClass := eventClassBase eventClassForType: type.
    event := eventClass new.
    event type: type.
    descriptor := eventClass description.
    [ self peek == $, ] whileTrue:[
        self next. "/ eat $,
        propertyName := self parseVariable.
        propertyDescriptor := descriptor propertyDescriptorAt: propertyName.
        self expect: $=.
        propertyDescriptor isNil ifTrue:[ 
            propertyValue := self parseValue.
        ] ifFalse:[ 
            propertyValue := propertyDescriptor parseUsingGDBMIParser:self. 
        ]. 
        event propertyAt: propertyName put: propertyValue.
    ].
    self parseNl.

    ^ event

    "Created: / 01-06-2014 / 23:43:36 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 19-06-2014 / 21:43:35 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!GDBMIParser methodsFor:'parsing-commands'!

parseCommand

    self peek isDigit ifTrue:[ 
        self parseToken
    ].

    ^ self peek == $- ifTrue:[ 
        self parseCommandMI
    ] ifFalse:[ 
        self parseCommandCLI
    ].

    "Created: / 24-06-2014 / 23:08:58 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

parseCommandCLI
    "raise an error: this method should be implemented (TODO)"

    ^ GDBCLICommand new
        token: token;
        value: self nextLine;
        yourself

    "Created: / 24-06-2014 / 23:10:19 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

parseCommandMI
    "raise an error: this method should be implemented (TODO)"

    | operation className class args |

    self next. "/ eat $-.
    operation := self parseVariable.
    className := ('GDBMI_' , (operation copyReplaceAll: $- with: $_)) asSymbol.
    class := Smalltalk at: className.
    args := OrderedCollection new.
    [ self peek isNil or:[ self peek == Character cr ] ] whileFalse:[  
        self skipSeparators.
        self peek == $" ifTrue:[ 
            args add: self parseCString
        ] ifFalse:[ 
            args add: self parseNonBlankSequence
        ].
    ].
    self next. "/ eat CR.
    ^ (class arguments: args asArray) token: token.

    "Created: / 24-06-2014 / 23:10:18 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 26-08-2014 / 08:02:03 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!GDBMIParser methodsFor:'parsing-misc'!

parseResult
    "
    result → variable = value
    "

    | name value |

    name := self parseVariable.
    self expect: $=.
    value := self parseValue.
    ^ name -> value

    "Created: / 30-05-2014 / 10:15:55 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 31-05-2014 / 00:39:51 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

parseString
    ^ String streamContents:[:s|
        [ self peek notNil and:[self peek isLetterOrDigit or:['-_' includes: self peek ] ] ] whileTrue:[
            s nextPut: self next.
        ]
    ].

    "Created: / 30-05-2014 / 10:32:02 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 24-06-2014 / 23:30:54 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

parseVariable
    "
    variable → string
    "
    ^ self parseString

    "Created: / 30-05-2014 / 10:31:11 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!GDBMIParser methodsFor:'parsing-stream output'!

parseStreamRecord
    "
    stream-record → console-stream-output | target-stream-output | log-stream-output
    "

    self peek == $~ ifTrue:[
        self next.
        ^ self parseStreamRecord: GDBConsoleOutputEvent.
    ].
    self peek == $@ ifTrue:[
        self next.
        ^ self parseStreamRecord: GDBTargetOutputEvent.
    ].
    self peek == $& ifTrue:[
        self next.
        ^ self parseStreamRecord: GDBLogOutputEvent.
    ].
    self error:'Invalid stream record'

    "Created: / 30-05-2014 / 09:57:31 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 02-06-2014 / 22:21:29 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

parseStreamRecord: eventClass
    | value |

    value := self parseCString.
    self parseNl.
    ^ eventClass new value: value; yourself

    "Created: / 01-06-2014 / 23:41:55 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!GDBMIParser methodsFor:'parsing-utils'!

expect: aStringOrChar

    | c |
    aStringOrChar isCharacter ifTrue:[
	(self atEnd or:[(c := self next) ~= aStringOrChar]) ifTrue:[
	    self error:('Expected ''%1'' got ''%2''.' bindWith: aStringOrChar with: c).
	].
	^self.
    ].
    aStringOrChar isString ifTrue:[
	aStringOrChar do:[:expected|
	    (self atEnd or:[(c := self next) ~= expected]) ifTrue:[
		self error:('Expected ''%1''.' bindWith: aStringOrChar).
	    ].
	].
	^self.
    ].

    self error:'Invalid expected value'.

    "Created: / 19-11-2012 / 20:08:33 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 28-05-2014 / 00:17:06 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

expectLineEnd
    self expect: Character cr.

    "Created: / 19-11-2012 / 20:06:21 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

expectSpace
    self expect: Character space.

    "Created: / 19-11-2012 / 20:06:27 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!GDBMIParser methodsFor:'parsing-values'!

parseConst
    "
    const → c-string
    "

    ^ self parseCString.

    "Created: / 30-05-2014 / 10:36:04 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

parseList
    "
    list → '[]' | '[' value ( ',' value )* ']' | '[' result ( ',' result )* ']'
    "

    | list |

    self expect: $[.
    list := self parseListBody.
    self expect: $].
    ^ list

    "Created: / 30-05-2014 / 10:36:06 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 17-06-2014 / 22:14:55 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

parseListBody
    | value object |

    object := OrderedCollection new.
    self peek ~~ $] ifTrue:[
        [
            ('"{[' includes: self peek) ifFalse:[ 
                self parseVariable.
                self expect: $=.
            ].
            value := self parseValue.
            object add: value.
        ] doWhile:[
            (self peek == $,) ifTrue:[ self next. true ] ifFalse:[ false ]     
        ].
    ].
    ^ object asArray

    "Created: / 17-06-2014 / 22:14:06 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 19-06-2014 / 09:32:37 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

parseTuple
    | object |

    self expect: ${.
    object := self parseTupleBody.
    self expect: $}.
    ^ object

    "Created: / 30-05-2014 / 10:36:05 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified (comment): / 14-06-2014 / 02:28:21 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

parseTupleBody
    | name value dict |

    dict := Dictionary new.
    self peek ~~ $} ifTrue:[
        name := self parseVariable.
        self expect: $=.
        value := self parseValue.
        dict at: name put: value.
        [ self peek == $, ] whileTrue:[
            self next.
            name := self parseVariable.
            self expect: $=.
            value := self parseValue.
            dict at: name put: value.
        ].
    ].
    ^ dict

    "Created: / 14-06-2014 / 02:19:56 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

parseValue
    "
    value → const | tuple | list
    "

    self peek == $" ifTrue:[
	^ self parseConst
    ].
    self peek == ${ ifTrue:[
	^ self parseTuple.
    ].
    self peek == $[ ifTrue:[
	^ self parseList
    ].
    self error:'Invalid value'

    "Created: / 30-05-2014 / 10:31:12 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!GDBMIParser methodsFor:'parsing-values-typed'!

parseValueAsBoolean
    "
    bool → 'y' | 'n' | value
    "

    self peek == $" ifTrue:[
        | c |

        self expect: $".
        c := self next.
        (c ~~ $y and:[ c ~~ $n ]) ifTrue:[ 
            ^ self parseCStringRest: c asString.  
        ].
        self peek ~~ $" ifTrue:[ 
            ^ self parseCStringRest: c asString.  
        ].
        self next.
        ^ c == $y
    ].
    ^ self parseValue

    "Created: / 18-06-2014 / 07:33:59 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 18-06-2014 / 20:55:01 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

parseValueAsInstanceOf: class
    | description |

    class == Boolean ifTrue:[ 
        description := Magritte::MABooleanDescription new.
    ] ifFalse:[
    class == Integer ifTrue:[ 
        description := Magritte::MANumberDescription new
    ] ifFalse:[
    class == String ifTrue:[ 
        description := Magritte::MAStringDescription new
    ] ifFalse:[
        description := class description. 
    ]]].     

    ^ self parseValueAsListOf: class describedBy: description.

    "Created: / 18-06-2014 / 20:28:39 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 23-09-2014 / 23:16:57 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

parseValueAsInstanceOf: class describedBy: descriptor
    | object propertyName propertyValue propertyDescriptor |

    self peek ~~ ${ ifTrue:[ ^ self parseValue ].
    self next. "/ eat ${
    object := class new.
    self peek ~~ $} ifTrue:[
        [ 
            propertyName := self parseVariable.
            propertyDescriptor := descriptor propertyDescriptorAt: propertyName.
            self expect: $=.
            propertyDescriptor isNil ifTrue:[ 
                propertyValue := self parseValue.
            ] ifFalse:[ 
                propertyValue := propertyDescriptor parseUsingGDBMIParser:self. 
            ].
            object propertyAt: propertyName put: propertyValue
        ] doWhile: [ 
            (self peek == $,) ifTrue:[ self next. true ] ifFalse:[ false ]
        ].
    ].
    self expect: $}.
    ^ object

    "Created: / 18-06-2014 / 20:28:39 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 18-06-2014 / 23:34:57 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

parseValueAsInteger
    "
    bool → ''' [0-9]+ ''' | value
    "

    self peek == $" ifTrue:[
        | c v |

        self expect: $".
        c := self next.
        v := 0.
        c isDigit ifTrue:[ 
            [ c isDigit ] whileTrue:[ 
                v := (v * 10) + (c codePoint - $0 codePoint).
                c := self next.
            ].
            c == $" ifTrue:[ 
                ^ v
            ] ifFalse:[ 
                ^ self parseCStringRest:v printString , c  
            ].
        ].
        ^ self parseCStringRest: c asString
    ].
    ^ self parseValue

    "Created: / 18-06-2014 / 07:39:22 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

parseValueAsListOf: class
    | description |

    class == Boolean ifTrue:[ 
        description := Magritte::MABooleanDescription new.
    ] ifFalse:[
    class == Integer ifTrue:[ 
        description := Magritte::MANumberDescription new
    ] ifFalse:[
    class == String ifTrue:[ 
        description := Magritte::MAStringDescription new
    ] ifFalse:[
        description := class description. 
    ]]].     

    ^ self parseValueAsListOf: class describedBy: description.

    "Created: / 18-06-2014 / 21:00:02 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 23-09-2014 / 23:17:03 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

parseValueAsListOf:class describedBy:descriptor
    | list |

    self peek ~~ $[ ifTrue:[ ^ self parseValue ].
    self next. "/ eat ${
    self peek ~~ $] ifTrue:[
        list := OrderedCollection new.
        [ 
            self peek isAlphaNumeric ifTrue:[ 
                self parseVariable.
                self expect: $=. 
            ].
            list add: (descriptor parseUsingGDBMIParser:self)
        ] doWhile: [ 
            (self peek == $,) ifTrue:[ self next. true ] ifFalse:[ false ]
        ].
    ].
    self expect: $].
    ^ list

    "Created: / 18-06-2014 / 21:00:08 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 17-09-2014 / 08:03:15 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

parseValueAsString
    ^ self parseCString

    "Created: / 23-09-2014 / 22:22:11 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!GDBMIParser methodsFor:'streaming'!

atEnd
    ^ lookahead isNil and:[ source atEnd ].

    "Created: / 28-05-2014 / 00:17:06 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 14-06-2014 / 02:27:07 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

next
    | next |
    lookahead notNil ifTrue:[
        next := lookahead.
        lookahead := nil.
        ^ next.
    ].
    next := source next.
    recorder notNil ifTrue:[ 
        recorder recordResponseChar: next.
    ].
    ^ next

    "Created: / 23-10-2012 / 10:57:24 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 22-06-2014 / 21:56:02 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

nextLine
    | line |

    line := lookahead notNil 
                ifTrue:[ lookahead asString ,  source nextLine ] 
                ifFalse:[ source nextLine ].
    lookahead := nil.
    recorder notNil ifTrue:[ 
        recorder recordResponse: line.  
    ].
    ^ line

    "Created: / 23-10-2012 / 11:05:47 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 24-06-2014 / 23:28:55 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

peek
    lookahead notNil ifTrue:[
        ^ lookahead
    ].
    lookahead := source next.
    recorder notNil ifTrue:[ 
        lookahead notNil ifTrue:[
            recorder recordResponseChar: lookahead.
        ].
    ].
    ^ lookahead

    "Created: / 28-05-2014 / 00:18:32 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 23-06-2014 / 09:34:33 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

peekOrNil
    lookahead notNil ifTrue:[ ^ lookahead ].
    source atEnd ifTrue:[ ^ nil ].
    ^ self peek

    "Created: / 28-05-2014 / 00:15:32 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

skipSeparators
    [ self peek notNil and:[ self peek isSeparator ] ] whileTrue:[ self next ]

    "Created: / 19-11-2012 / 20:05:04 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 24-06-2014 / 23:31:08 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!GDBMIParser class methodsFor:'documentation'!

version_HG

    ^ '$Changeset: <not expanded> $'
! !