> # "helllooo" foo
>
> prints
> #foo
>
> is this correct?

Probably not, but the standard compiler accepts it. So I had to patch
the parser of the refactoring engine to accept a whole series of
degraded constructs. Below a small collection of tests documenting
some of these strange things:

testSymbolLiteral
        | tree |
        #(('# foo' #foo) ('#"bar"foo' #foo) ('##foo' #foo) ('###foo' #foo)
('#foo:' #foo:) ('#foo::' #'foo::') ('#foo::bar' #'foo::bar')
('#foo::bar:' #'foo::bar:') ('#foo::bar::' #'foo::bar::')) do: [ :pair
|
                tree := RBParser parseExpression: pair first.
                self assert: tree value = pair second.
                self assert: tree start = 1.
                self assert: tree stop = pair first size ]

testStatements
        | tree |
        #(('' 0 0) ('.' 0 1) ('| bar |' 0 0) ('| bar | .' 0 1) ('| bar | ..'
0 2) ('foo. bar' 2 1) ('foo. bar.' 2 2) ('foo. bar. .' 2 3) ('. foo.
bar' 2 2)) do: [ :each |
                tree := RBParser parseExpression: each first.
                self assert: tree statements size = each second.
                self assert: tree periods size = each last ]

testNumberParsing
        | numbers node |
        numbers := #(('1' 1) ('-1' -1) ('123' 123) ('123' 123) ('-123' -123)
('1.1' 1.1) ('-1.1' -1.1) ('1.23' 1.23) ('-1.23' -1.23) ('1e3' 1e3)
('1d3' 1d3) ('1q3' 1q3) ('-1e3' -1e3) ('1e-3' 1e-3) ('-1e-3' -1e-3)
('2r1e8'  2r1e8) ('-2r1e8' -2r1e8) ('2r1e-8' 2r1e-8) ('-2r1e-8'
-2r1e-8) ('0.50s2' 0.50s2) ('0.500s3' 0.500s3) ('0.050s3' 0.050s3)).
        numbers do: [ :spec |
                node := RBParser parseExpression: spec first.
                self assert: node token source = spec first.
                self assert: node value = spec second ]

Lukas

-- 
Lukas Renggli
www.lukas-renggli.ch

_______________________________________________
Pharo-project mailing list
[email protected]
http://lists.gforge.inria.fr/cgi-bin/mailman/listinfo/pharo-project

Reply via email to