STCompiler input bug?

Previous Topic Next Topic
 
classic Classic list List threaded Threaded
6 messages Options
Reply | Threaded
Open this post in threaded view
|

STCompiler input bug?

Holger Freyther
Hi,

when using the STCompiler I end up with a MessageNotUnderstood error:

STInST.STEvaluationDriver new parseSmalltalk: '[:each :ablock | (each) ifTrue:
ablock]!' with: STInST.STFileInParser


In STCompiler>>#compileBoolean: aNode will be '(each) ifTrue:..' the arguments
is the RBVariableNode and RBVariableNode does not understand arguments/body.
So somehow the bytecode for STCompiler>>#acceptVariableNode would need to end
up in bc1 and bc2?




_______________________________________________
help-smalltalk mailing list
[hidden email]
https://lists.gnu.org/mailman/listinfo/help-smalltalk
Reply | Threaded
Open this post in threaded view
|

Re: STCompiler input bug?

MrGwen
On 24/09/2011 11:27, Holger Hans Peter Freyther wrote:

> Hi,
>
> when using the STCompiler I end up with a MessageNotUnderstood error:
>
> STInST.STEvaluationDriver new parseSmalltalk: '[:each :ablock | (each) ifTrue:
> ablock]!' with: STInST.STFileInParser
>
>
> In STCompiler>>#compileBoolean: aNode will be '(each) ifTrue:..' the arguments
> is the RBVariableNode and RBVariableNode does not understand arguments/body.
> So somehow the bytecode for STCompiler>>#acceptVariableNode would need to end
> up in bc1 and bc2?
>
>
>
>
> _______________________________________________
> help-smalltalk mailing list
> [hidden email]
> https://lists.gnu.org/mailman/listinfo/help-smalltalk
Hi Zecke,

Can you try the following patch (ok not perfect but it works for me)
I've made some other changes for the compiler:

STInST.STCompiler class extend [
     evaluate: aNode parser: aParser [
<category: 'evaluation'>
         | cm methodNode sequenceNode |
     sequenceNode := aNode isSequence ifFalse: [ RBSequenceNode
statements: {aNode} ] ifTrue: [ aNode ].
         sequenceNode addReturn.
         methodNode := (RBMethodNode new)
                     arguments: #();
                     body: sequenceNode;
                     selector: #Doit;
                     source: nil;
                     yourself.
         cm := self
                     compile: methodNode
                     asMethodOf: UndefinedObject
                     classified: nil
                     parser: aParser
                     environment: Namespace current.
     ^nil perform: cm
     ]
]

STInST.STCompiler evaluate: (STInST.RBParser parseExpression: '[:each
:ablock | (each) ifTrue: ablock]') parser: STInST.RBParser new

Gwen

_______________________________________________
help-smalltalk mailing list
[hidden email]
https://lists.gnu.org/mailman/listinfo/help-smalltalk

stcompiler.patch (630 bytes) Download Attachment
Reply | Threaded
Open this post in threaded view
|

Re: STCompiler input bug?

Paolo Bonzini-2
In reply to this post by Holger Freyther
On 09/24/2011 11:27 AM, Holger Hans Peter Freyther wrote:

>
> when using the STCompiler I end up with a MessageNotUnderstood error:
>
> STInST.STEvaluationDriver new parseSmalltalk: '[:each :ablock | (each) ifTrue:
> ablock]!' with: STInST.STFileInParser
>
>
> In STCompiler>>#compileBoolean: aNode will be '(each) ifTrue:..' the arguments
> is the RBVariableNode and RBVariableNode does not understand arguments/body.
> So somehow the bytecode for STCompiler>>#acceptVariableNode would need to end
> up in bc1 and bc2?

ablock would need to be replaced with [ablock value].  Alternatively, you
can just avoid inlining #ifTrue: in this case:

diff --git a/packages/stinst/parser/STCompiler.st b/packages/stinst/parser/STCompiler.st
index 620e019..4235d41 100644
--- a/packages/stinst/parser/STCompiler.st
+++ b/packages/stinst/parser/STCompiler.st
@@ -795,6 +795,7 @@ indexed'' bytecode. The resulting stream is
  | bc1 ret1 bc2 selector |
  aNode arguments do:
  [:each |
+ each isBlock ifFalse: [^false].
  (each arguments isEmpty and: [each body temporaries isEmpty])
     ifFalse: [^false].
  bc1 isNil

Paolo

_______________________________________________
help-smalltalk mailing list
[hidden email]
https://lists.gnu.org/mailman/listinfo/help-smalltalk
Reply | Threaded
Open this post in threaded view
|

Re: STCompiler input bug?

Holger Freyther
On 09/24/2011 03:19 PM, Paolo Bonzini wrote:

> diff --git a/packages/stinst/parser/STCompiler.st b/packages/stinst/parser/STCompiler.st
> index 620e019..4235d41 100644
> --- a/packages/stinst/parser/STCompiler.st
> +++ b/packages/stinst/parser/STCompiler.st
> @@ -795,6 +795,7 @@ indexed'' bytecode. The resulting stream is
>   | bc1 ret1 bc2 selector |
>   aNode arguments do:
>   [:each |
> + each isBlock ifFalse: [^false].
>   (each arguments isEmpty and: [each body temporaries isEmpty])
>      ifFalse: [^false].
>   bc1 isNil

Hi,

I am now at two other issues:

1.)

PackageLoader fileInPackage: #Compiler; fileInPackage: #Sockets

Loading package Sockets
Object: 'CObject' error: did not understand #value
Smalltalk.MessageNotUnderstood(Smalltalk.Exception)>>signal (ExcHandling.st:254)
Smalltalk.String(Smalltalk.Object)>>doesNotUnderstand: #value (SysExcept.st:1442)
Smalltalk.CType>>cObjectType (CType.st:227)
Smalltalk.CType>>storeOn: (CType.st:260)
Smalltalk.WriteStream(Smalltalk.Stream)>>store: (Stream.st:510)
Smalltalk.CPtrCType>>storeOn: (CType.st:363)
Smalltalk.WriteStream(Smalltalk.Stream)>>store: (Stream.st:510)
[] in CAddrInfoStruct class(Smalltalk.CCompound
class)>>declaration:inject:into: (CStruct.st:164)
Smalltalk.Array(Smalltalk.SequenceableCollection)>>do: (SeqCollect.st:827)
CAddrInfoStruct class(Smalltalk.CCompound class)>>declaration:inject:into:
(CStruct.st:147)
CAddrInfoStruct class(Smalltalk.CStruct class)>>declaration: (CStruct.st:249)
Smalltalk.UndefinedObject>>executeStatements (source not available:1)
[] in STInST.STEvaluationDriver>>evaluate:
(Parser.star#VFS.ZipFile/STEvaluationDriver.st:210)
PackageLoader


2.)

If sockets is loaded by gst-remote before the Compiler package when loading
the OsmoMSC... I end with:

PackageLoader fileInPackage: #Sockets; fileInPackage: #Compiler;
fileInPackage: #OsmoMSC


Loading package OsmoCore
Loading package OsmoLogging
Loading package OsmoMGCP
Object: RBVariableNode new "<0x403fa060>" error: did not understand #arguments
Smalltalk.MessageNotUnderstood(Smalltalk.Exception)>>signal (ExcHandling.st:254)
STInST.RBVariableNode(Smalltalk.Object)>>doesNotUnderstand: #arguments
(SysExcept.st:1442)
STInST.STCompiler>>compileLoop: (Parser.star#VFS.ZipFile/STCompiler.st:783)
STInST.STCompiler>>acceptMessageNode: (Parser.star#VFS.ZipFile/STCompiler.st:647)



aNode: 'RBMessageNode(self lastUsed + 1 to: ports size do: alloc)'
^^^^^^^^^^^^

        (block arguments size = 1 and: [block body temporaries isEmpty])
            ifFalse: [^false].

so it needs a similar check if it is a block... or can act like a block?






STInST.RBMessageNode>>acceptVisitor:
(Parser.star#VFS.ZipFile/RBParseNodes.st:2092)
optimized [] in STInST.STCompiler>>compileStatements:
(Parser.star#VFS.ZipFile/STCompiler.st:566)
Smalltalk.OrderedCollection(Smalltalk.SequenceableCollection)>>keysAndValuesDo: (SeqCollect.st:887)
STInST.STCompiler>>compileStatements: (Parser.star#VFS.ZipFile/STCompiler.st:559)
STInST.STCompiler>>acceptMethodNode: (Parser.star#VFS.ZipFile/STCompiler.st:468)
STInST.RBMethodNode>>acceptVisitor: (Parser.star#VFS.ZipFile/RBParseNodes.st:1420)
STInST.STCompiler(STInST.RBProgramNodeVisitor)>>visitNode:
(Parser.star#VFS.ZipFile/RBParseNodes.st:49)
STInST.STCompiler class>>compile:asMethodOf:classified:parser:environment:
(Parser.star#VFS.ZipFile/STCompiler.st:161)
STInST.STCompiler class>>compile:asMethodOf:classified:parser:
(Parser.star#VFS.ZipFile/STCompiler.st:152)
STInST.STCompiler class>>compile:for:classified:parser:
(Parser.star#VFS.ZipFile/STCompiler.st:142)
STInST.STEvaluationDriver>>compile:
(Parser.star#VFS.ZipFile/STEvaluationDriver.st:192)
STInST.GSTFileInParser(STInST.STFileParser)>>compile:
(Parser.star#VFS.ZipFile/STFileParser.st:91)
STInST.GSTFileInParser>>parseMethodSource:on:
(Parser.star#VFS.ZipFile/GSTParser.st:320)
STInST.GSTFileInParser>>parseMethodSource:
(Parser.star#VFS.ZipFile/GSTParser.st:296)
STInST.GSTFileInParser>>parseClassBodyElement:withinExtend:
(Parser.star#VFS.ZipFile/GSTParser.st:230)
STInST.GSTFileInParser>>parseClassBody: (Parser.star#VFS.ZipFile/GSTParser.st:169)
STInST.GSTFileInParser>>parseClass: (Parser.star#VFS.ZipFile/GSTParser.st:157)
STInST.GSTFileInParser>>parseDeclaration:
(Parser.star#VFS.ZipFile/GSTParser.st:95)
STInST.GSTFileInParser>>parseDoit (Parser.star#VFS.ZipFile/GSTParser.st:82)
STInST.GSTFileInParser>>parseDoits (Parser.star#VFS.ZipFile/GSTParser.st:67)
STInST.GSTFileInParser(STInST.STFileInParser)>>parseSmalltalk
(Parser.star#VFS.ZipFile/STFileParser.st:282)
STInST.GSTFileInParser class(STInST.STFileParser
class)>>parseSmalltalkStream:with:onError:
(Parser.star#VFS.ZipFile/STFileParser.st:70)
STInST.GSTFileInParser class(STInST.STFileParser
class)>>parseSmalltalkStream:with: (Parser.star#VFS.ZipFile/STFileParser.st:60)
STInST.STEvaluationDriver(STInST.STParsingDriver)>>parseSmalltalkStream:with:
(Parser.star#VFS.ZipFile/STFileParser.st:181)
optimized [] in Smalltalk.Stream>>fileInLine:file:at:
(Compiler.star#VFS.ZipFile/StartCompiler.st:69)
Smalltalk.BlockClosure>>ensure: (BlkClosure.st:268)
Kernel.LimitedStream(Smalltalk.Stream)>>fileInLine:file:at:
(Compiler.star#VFS.ZipFile/StartCompiler.st:65)
Kernel.LimitedStream(Smalltalk.Stream)>>fileInLine:file:fileName:at:
(Compiler.star#VFS.ZipFile/StartCompiler.st:76)
Kernel.LimitedStream>>fileIn (VFSZip.st:352)
optimized [] in Smalltalk.FilePath>>fileIn (FilePath.st:662)
[] in VFS.StoredZipMember(Smalltalk.FilePath)>>withReadStreamDo: (FilePath.st:655)
Smalltalk.BlockClosure>>ensure: (BlkClosure.st:268)
VFS.StoredZipMember(Smalltalk.FilePath)>>withReadStreamDo: (FilePath.st:654)
VFS.StoredZipMember(Smalltalk.FilePath)>>fileIn (FilePath.st:662)
optimized [] in Smalltalk.Package>>primFileIn (PkgLoader.st:1564)
Smalltalk.OrderedCollection>>do: (OrderColl.st:67)
[] in Smalltalk.Package>>primFileIn (PkgLoader.st:1564)
Smalltalk.BlockClosure>>ensure: (BlkClosure.st:268)
Smalltalk.Package>>primFileIn (PkgLoader.st:1550)
Kernel.StarPackage>>primFileIn (PkgLoader.st:1076)
optimized [] in Smalltalk.PackageLoader class>>fileInPackages: (PkgLoader.st:1880)
Smalltalk.OrderedCollection>>do: (OrderColl.st:67)
Smalltalk.PackageLoader class>>fileInPackages: (PkgLoader.st:1873)
Smalltalk.PackageLoader class>>fileInPackage: (PkgLoader.st:1861)
Smalltalk.UndefinedObject>>executeStatements (a String:1)


_______________________________________________
help-smalltalk mailing list
[hidden email]
https://lists.gnu.org/mailman/listinfo/help-smalltalk
Reply | Threaded
Open this post in threaded view
|

Re: STCompiler input bug?

Holger Freyther
On 09/24/2011 07:37 PM, Holger Hans Peter Freyther wrote:

>
> aNode: 'RBMessageNode(self lastUsed + 1 to: ports size do: alloc)'
> ^^^^^^^^^^^^
>
> (block arguments size = 1 and: [block body temporaries isEmpty])
>    ifFalse: [^false].
>
> so it needs a similar check if it is a block... or can act like a block?
>


diff --git a/packages/stinst/parser/STCompiler.st
b/packages/stinst/parser/STCompiler.st
index 4235d41..74fc9a8 100644
--- a/packages/stinst/parser/STCompiler.st
+++ b/packages/stinst/parser/STCompiler.st
@@ -780,6 +780,7 @@ indexed'' bytecode. The resulting stream is
                stop := step.   "to:"
                step := block.  "by:"
                block := each   "do:"].
+       block isBlock ifFalse: [^false].
        (block arguments size = 1 and: [block body temporaries isEmpty])
            ifFalse: [^false].
        stop isNil

_______________________________________________
help-smalltalk mailing list
[hidden email]
https://lists.gnu.org/mailman/listinfo/help-smalltalk
Reply | Threaded
Open this post in threaded view
|

Re: STCompiler input bug?

Paolo Bonzini-2
In reply to this post by Holger Freyther
> PackageLoader fileInPackage: #Compiler; fileInPackage: #Sockets

Here is a quick fix.  It loses some optimization, but better correct
than fast. :)

Paolo

_______________________________________________
help-smalltalk mailing list
[hidden email]
https://lists.gnu.org/mailman/listinfo/help-smalltalk

fix-class-tags.patch (1K) Download Attachment