More than 256 literals referenced

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

More than 256 literals referenced

David T. Lewis
Something changed in trunk a couple of days ago that results in a 'More than
256 literals referenced' error in a filein script that previously did not
display this problem (see attached). It does not seem to be anything in the
Compiler package (I reverted back a half dozen versions, no change), so I'm
looking at the CI builds for reference. The problem appears in the image from
SqueakTrunk build #213 and later, and is not  present in the image from
build #212 and earlier.

I spotted the problem in the CogVM build job, which has been failing for a
couple of days. The failures are due to the above issue, and the script file
that fails on filein is http://build.squeak.org/job/CogVM/ws/VMCogUnixBuild.st
The problem showed up in the CogVM job by coincidence and is not related to
the VM.

Filing this VMCogUnixBuild.st into an updated trunk image will reproduce
the problem.

Dave




Syntax Error.png (36K) Download Attachment
Reply | Threaded
Open this post in threaded view
|

Re: More than 256 literals referenced

Nicolas Cellier
I must say I was pretty surprised to see such a long method compiled at all...
Sorry, I know it's not very helpful, but couldn't the script be split
with chunk format?

Nicolas

2013/3/14 David T. Lewis <[hidden email]>:

> Something changed in trunk a couple of days ago that results in a 'More than
> 256 literals referenced' error in a filein script that previously did not
> display this problem (see attached). It does not seem to be anything in the
> Compiler package (I reverted back a half dozen versions, no change), so I'm
> looking at the CI builds for reference. The problem appears in the image from
> SqueakTrunk build #213 and later, and is not  present in the image from
> build #212 and earlier.
>
> I spotted the problem in the CogVM build job, which has been failing for a
> couple of days. The failures are due to the above issue, and the script file
> that fails on filein is http://build.squeak.org/job/CogVM/ws/VMCogUnixBuild.st
> The problem showed up in the CogVM job by coincidence and is not related to
> the VM.
>
> Filing this VMCogUnixBuild.st into an updated trunk image will reproduce
> the problem.
>
> Dave
>
>
>
>

Reply | Threaded
Open this post in threaded view
|

Re: More than 256 literals referenced

David T. Lewis
On Thu, Mar 14, 2013 at 01:00:20AM +0100, Nicolas Cellier wrote:
> I must say I was pretty surprised to see such a long method compiled at all...
> Sorry, I know it's not very helpful, but couldn't the script be split
> with chunk format?

Yes of course. I am not trying to fix the script. The script is only of interest
because it seems to have caught a problem associated with recent image changes
within the last few days.

Of course I should turn it into a unit test.

Dave

p.s. The reason that the script is written in this manner (way too long) is
that I wanted it be something that would be readable and executable when
imported into a workspace, but that would also run from start to finish to
build a VM when filed in as a script. There is a similar script for the
interpreter VM, although that one is not triggering the bug at the moment.

>
> Nicolas
>
> 2013/3/14 David T. Lewis <[hidden email]>:
> > Something changed in trunk a couple of days ago that results in a 'More than
> > 256 literals referenced' error in a filein script that previously did not
> > display this problem (see attached). It does not seem to be anything in the
> > Compiler package (I reverted back a half dozen versions, no change), so I'm
> > looking at the CI builds for reference. The problem appears in the image from
> > SqueakTrunk build #213 and later, and is not  present in the image from
> > build #212 and earlier.
> >
> > I spotted the problem in the CogVM build job, which has been failing for a
> > couple of days. The failures are due to the above issue, and the script file
> > that fails on filein is http://build.squeak.org/job/CogVM/ws/VMCogUnixBuild.st
> > The problem showed up in the CogVM job by coincidence and is not related to
> > the VM.
> >
> > Filing this VMCogUnixBuild.st into an updated trunk image will reproduce
> > the problem.
> >
> > Dave
> >
> >
> >
> >

Reply | Threaded
Open this post in threaded view
|

Re: More than 256 literals referenced

Casey Ransberger-2
Oh, that's cool. So you have a script that builds an interpreter, and folks (once the bug's fixed) can read it, run it, learn from it, tweak it, etc? 

I like.

On Wed, Mar 13, 2013 at 5:24 PM, David T. Lewis <[hidden email]> wrote:
On Thu, Mar 14, 2013 at 01:00:20AM +0100, Nicolas Cellier wrote:
> I must say I was pretty surprised to see such a long method compiled at all...
> Sorry, I know it's not very helpful, but couldn't the script be split
> with chunk format?

Yes of course. I am not trying to fix the script. The script is only of interest
because it seems to have caught a problem associated with recent image changes
within the last few days.

Of course I should turn it into a unit test.

Dave

p.s. The reason that the script is written in this manner (way too long) is
that I wanted it be something that would be readable and executable when
imported into a workspace, but that would also run from start to finish to
build a VM when filed in as a script. There is a similar script for the
interpreter VM, although that one is not triggering the bug at the moment.

>
> Nicolas
>
> 2013/3/14 David T. Lewis <[hidden email]>:
> > Something changed in trunk a couple of days ago that results in a 'More than
> > 256 literals referenced' error in a filein script that previously did not
> > display this problem (see attached). It does not seem to be anything in the
> > Compiler package (I reverted back a half dozen versions, no change), so I'm
> > looking at the CI builds for reference. The problem appears in the image from
> > SqueakTrunk build #213 and later, and is not  present in the image from
> > build #212 and earlier.
> >
> > I spotted the problem in the CogVM build job, which has been failing for a
> > couple of days. The failures are due to the above issue, and the script file
> > that fails on filein is http://build.squeak.org/job/CogVM/ws/VMCogUnixBuild.st
> > The problem showed up in the CogVM job by coincidence and is not related to
> > the VM.
> >
> > Filing this VMCogUnixBuild.st into an updated trunk image will reproduce
> > the problem.
> >
> > Dave
> >
> >
> >
> >




--
Casey Ransberger


Reply | Threaded
Open this post in threaded view
|

Re: More than 256 literals referenced

Eliot Miranda-2
In reply to this post by David T. Lewis
Hi David,

    one thing you can do is make that large brace expression a set of literal arrays.  e.g.

installSS := Installer ss.
installSqueak := Installer squeak.
"Use the following array of arrays to reduce total number of literals
is this script, allows log message for each package load."
{
{ installSS . 'Speech' . 'SharedPool-Speech' } .
{ installSqueak . 'FFI' . 'FFI-Pools' } .
{ installSS . 'Alien' . 'Alien' } .
{ installSqueak . 'VMMaker' . 'Balloon-Engine-Pools' } .
{ installSqueak . 'VMMaker' . vmmBranch } .
{ installSqueak . 'VMMaker' . 'Cog' } .
{ installSS . 'Alien' . 'Alien-VMMaker-Plugins' } .
{ installSS . 'OSProcessPlugin' . osppBranch } .
{ installSS . 'AioPlugin' . 'VMConstruction-Plugins-AioPlugin' } .
{ installSS . 'XDCP' . 'VMConstruction-Plugins-XDisplayControlPlugin' } .
{ installSS . 'Balloon3D' . 'Balloon3D-Constants' } .
{ installSS . 'Balloon3D' . 'Balloon3D-Plugins' } .
{ installSS . 'FreeTypePlus' . 'FreeType' } .
{ installSS . 'FreetypePlugin' . 'Freetype-Plugin' } .
{ installSS . 'dbus' . 'DBus-Plugin' } .
{ installSS . 'Rome' . 'Rome-Base' } .
{ installSS . 'Rome' . 'Rome-PluginCanvas' } .
{ installSS . 'Rome' . 'Rome-Plugin' }
} do: [ :package |
log value: 'install ', package third.
(package first project: package second) install: package third.
].

=>
"Use the following array of arrays to reduce total number of literals
is this script, allows log message for each package load."
#(
#( ss 'Speech' 'SharedPool-Speech' )
#( squeak 'FFI' 'FFI-Pools' )
#( ss 'Alien' 'Alien' )
#( squeak 'VMMaker' 'Balloon-Engine-Pools' )
#( squeak 'VMMaker' vmmBranch )
#( squeak 'VMMaker' 'Cog' )
#( ss 'Alien' 'Alien-VMMaker-Plugins' )
#( ss 'OSProcessPlugin' osppBranch )
#( ss 'AioPlugin' 'VMConstruction-Plugins-AioPlugin' )
#( ss 'XDCP' 'VMConstruction-Plugins-XDisplayControlPlugin' )
#( ss 'Balloon3D' 'Balloon3D-Constants' )
#( ss 'Balloon3D' 'Balloon3D-Plugins' )
#( ss 'FreeTypePlus' 'FreeType' )
#( ss 'FreetypePlugin' 'Freetype-Plugin' )
#( ss 'dbus' 'DBus-Plugin' )
#( ss 'Rome' 'Rome-Base' )
#( ss 'Rome' 'Rome-PluginCanvas' )
#( ss 'Rome' 'Rome-Plugin' )
) do: [ :package |
log value: 'install ', package third.
((Installer perform: package first) project: package second) install: package third.
].

On Wed, Mar 13, 2013 at 4:48 PM, David T. Lewis <[hidden email]> wrote:
Something changed in trunk a couple of days ago that results in a 'More than
256 literals referenced' error in a filein script that previously did not
display this problem (see attached). It does not seem to be anything in the
Compiler package (I reverted back a half dozen versions, no change), so I'm
looking at the CI builds for reference. The problem appears in the image from
SqueakTrunk build #213 and later, and is not  present in the image from
build #212 and earlier.

I spotted the problem in the CogVM build job, which has been failing for a
couple of days. The failures are due to the above issue, and the script file
that fails on filein is http://build.squeak.org/job/CogVM/ws/VMCogUnixBuild.st
The problem showed up in the CogVM job by coincidence and is not related to
the VM.

Filing this VMCogUnixBuild.st into an updated trunk image will reproduce
the problem.

Dave


However, I have an instruction set that lifts the 256 literal limit to 65535 ;) 

--
best,
Eliot


Reply | Threaded
Open this post in threaded view
|

Re: More than 256 literals referenced

Igor Stasenko
On 14 March 2013 18:28, Eliot Miranda <[hidden email]> wrote:

>
> However, I have an instruction set that lifts the 256 literal limit to 65535
> ;)
>
no,please don't..
lets keep forcing people to be smart and do not put a huge datasets
into methods :)


> --
> best,
> Eliot
>
>
>



--
Best regards,
Igor Stasenko.

Reply | Threaded
Open this post in threaded view
|

Re: More than 256 literals referenced

Bert Freudenberg
In reply to this post by Eliot Miranda-2
On 2013-03-14, at 18:28, Eliot Miranda <[hidden email]> wrote:

> On Wed, Mar 13, 2013 at 4:48 PM, David T. Lewis <[hidden email]> wrote:
>> Something changed in trunk a couple of days ago that results in a 'More than
>> 256 literals referenced' error in a filein script that previously did not
>> display this problem (see attached). It does not seem to be anything in the
>> Compiler package (I reverted back a half dozen versions, no change), so I'm
>> looking at the CI builds for reference. The problem appears in the image from
>> SqueakTrunk build #213 and later, and is not  present in the image from
>> build #212 and earlier.
>>
>> I spotted the problem in the CogVM build job, which has been failing for a
>> couple of days. The failures are due to the above issue, and the script file
>> that fails on filein is http://build.squeak.org/job/CogVM/ws/VMCogUnixBuild.st
>> The problem showed up in the CogVM job by coincidence and is not related to
>> the VM.
>>
>> Filing this VMCogUnixBuild.st into an updated trunk image will reproduce
>> the problem.
>>
>> Dave
>>
>
> However, I have an instruction set that lifts the 256 literal limit to 65535 ;)

That would be very useful for this case indeed, plus maybe a double-extended jump bytecode. Then the only remaining limit would be the number of temps.

- Bert -


Reply | Threaded
Open this post in threaded view
|

Re: More than 256 literals referenced

Eliot Miranda-2


On Fri, Mar 15, 2013 at 5:40 AM, Bert Freudenberg <[hidden email]> wrote:
On 2013-03-14, at 18:28, Eliot Miranda <[hidden email]> wrote:

> On Wed, Mar 13, 2013 at 4:48 PM, David T. Lewis <[hidden email]> wrote:
>> Something changed in trunk a couple of days ago that results in a 'More than
>> 256 literals referenced' error in a filein script that previously did not
>> display this problem (see attached). It does not seem to be anything in the
>> Compiler package (I reverted back a half dozen versions, no change), so I'm
>> looking at the CI builds for reference. The problem appears in the image from
>> SqueakTrunk build #213 and later, and is not  present in the image from
>> build #212 and earlier.
>>
>> I spotted the problem in the CogVM build job, which has been failing for a
>> couple of days. The failures are due to the above issue, and the script file
>> that fails on filein is http://build.squeak.org/job/CogVM/ws/VMCogUnixBuild.st
>> The problem showed up in the CogVM job by coincidence and is not related to
>> the VM.
>>
>> Filing this VMCogUnixBuild.st into an updated trunk image will reproduce
>> the problem.
>>
>> Dave
>>
>
> However, I have an instruction set that lifts the 256 literal limit to 65535 ;)

That would be very useful for this case indeed, plus maybe a double-extended jump bytecode. Then the only remaining limit would be the number of temps.

The jump limit is lifted, also to 64k.  How big would you want to see temps? It is already 64, which is quite high.
--
Eliot


Reply | Threaded
Open this post in threaded view
|

Re: More than 256 literals referenced

Bert Freudenberg
On 2013-03-15, at 18:55, Eliot Miranda <[hidden email]> wrote:

> On Fri, Mar 15, 2013 at 5:40 AM, Bert Freudenberg <[hidden email]> wrote:
> On 2013-03-14, at 18:28, Eliot Miranda <[hidden email]> wrote:
>
> > However, I have an instruction set that lifts the 256 literal limit to 65535 ;)
>
> That would be very useful for this case indeed, plus maybe a double-extended jump bytecode. Then the only remaining limit would be the number of temps.
>
> The jump limit is lifted, also to 64k.  

Nice!

> How big would you want to see temps? It is already 64, which is quite high.

Well, I have one code generation example that used 254 temps, which I had to split over several methods, and spill shared temps over into inst vars.

Although, if the limit had been 256, there would still have been that nagging feeling that every little change might break it ...

This doesn't necessarily need a VM change. The compiler could reserve the 64th temp for an array and compile accesses as at:/at:put:.

That would also avoid having to have another context size.


- Bert -


Reply | Threaded
Open this post in threaded view
|

Re: More than 256 literals referenced

David T. Lewis
In reply to this post by Eliot Miranda-2
On Thu, Mar 14, 2013 at 10:28:06AM -0700, Eliot Miranda wrote:
> Hi David,
>
>     one thing you can do is make that large brace expression a set of
> literal arrays.  e.g.
>

Good idea, thank you!

Dave


> installSS := Installer ss.
> installSqueak := Installer squeak.
> "Use the following array of arrays to reduce total number of literals
> is this script, allows log message for each package load."
> {
> { installSS . 'Speech' . 'SharedPool-Speech' } .
> { installSqueak . 'FFI' . 'FFI-Pools' } .
> { installSS . 'Alien' . 'Alien' } .
> { installSqueak . 'VMMaker' . 'Balloon-Engine-Pools' } .
> { installSqueak . 'VMMaker' . vmmBranch } .
> { installSqueak . 'VMMaker' . 'Cog' } .
> { installSS . 'Alien' . 'Alien-VMMaker-Plugins' } .
> { installSS . 'OSProcessPlugin' . osppBranch } .
> { installSS . 'AioPlugin' . 'VMConstruction-Plugins-AioPlugin' } .
> { installSS . 'XDCP' . 'VMConstruction-Plugins-XDisplayControlPlugin' } .
> { installSS . 'Balloon3D' . 'Balloon3D-Constants' } .
> { installSS . 'Balloon3D' . 'Balloon3D-Plugins' } .
> { installSS . 'FreeTypePlus' . 'FreeType' } .
> { installSS . 'FreetypePlugin' . 'Freetype-Plugin' } .
> { installSS . 'dbus' . 'DBus-Plugin' } .
> { installSS . 'Rome' . 'Rome-Base' } .
> { installSS . 'Rome' . 'Rome-PluginCanvas' } .
> { installSS . 'Rome' . 'Rome-Plugin' }
> } do: [ :package |
> log value: 'install ', package third.
> (package first project: package second) install: package third.
> ].
>
> =>
> "Use the following array of arrays to reduce total number of literals
> is this script, allows log message for each package load."
> #(
> #( ss 'Speech' 'SharedPool-Speech' )
> #( squeak 'FFI' 'FFI-Pools' )
> #( ss 'Alien' 'Alien' )
> #( squeak 'VMMaker' 'Balloon-Engine-Pools' )
> #( squeak 'VMMaker' vmmBranch )
> #( squeak 'VMMaker' 'Cog' )
> #( ss 'Alien' 'Alien-VMMaker-Plugins' )
> #( ss 'OSProcessPlugin' osppBranch )
> #( ss 'AioPlugin' 'VMConstruction-Plugins-AioPlugin' )
> #( ss 'XDCP' 'VMConstruction-Plugins-XDisplayControlPlugin' )
> #( ss 'Balloon3D' 'Balloon3D-Constants' )
> #( ss 'Balloon3D' 'Balloon3D-Plugins' )
> #( ss 'FreeTypePlus' 'FreeType' )
> #( ss 'FreetypePlugin' 'Freetype-Plugin' )
> #( ss 'dbus' 'DBus-Plugin' )
> #( ss 'Rome' 'Rome-Base' )
> #( ss 'Rome' 'Rome-PluginCanvas' )
> #( ss 'Rome' 'Rome-Plugin' )
> ) do: [ :package |
> log value: 'install ', package third.
> ((Installer perform: package first) project: package second) install:
> package third.
> ].
>
> On Wed, Mar 13, 2013 at 4:48 PM, David T. Lewis <[hidden email]> wrote:
>
> > Something changed in trunk a couple of days ago that results in a 'More
> > than
> > 256 literals referenced' error in a filein script that previously did not
> > display this problem (see attached). It does not seem to be anything in the
> > Compiler package (I reverted back a half dozen versions, no change), so I'm
> > looking at the CI builds for reference. The problem appears in the image
> > from
> > SqueakTrunk build #213 and later, and is not  present in the image from
> > build #212 and earlier.
> >
> > I spotted the problem in the CogVM build job, which has been failing for a
> > couple of days. The failures are due to the above issue, and the script
> > file
> > that fails on filein is
> > http://build.squeak.org/job/CogVM/ws/VMCogUnixBuild.st
> > The problem showed up in the CogVM job by coincidence and is not related to
> > the VM.
> >
> > Filing this VMCogUnixBuild.st into an updated trunk image will reproduce
> > the problem.
> >
> > Dave
> >
>
>
> However, I have an instruction set that lifts the 256 literal limit to
> 65535 ;)
>
> --
> best,
> Eliot

>


Reply | Threaded
Open this post in threaded view
|

Re: More than 256 literals referenced

Nicolas Cellier
In reply to this post by Eliot Miranda-2
Here is what I did in VW to ByteCodeStream (or a subclass): I added an
inst. var. to reduceLiterals to handle case when there are too many
literals:

pushStatic: binding
        reduceLiterals
                ifTrue:
                        [self pushConstant: binding.
                        self sendNoCheck: #value numArgs: 0]
                ifFalse: [super pushStatic: binding]

pushConstant: lit
        reduceLiterals ifTrue: [^self pushReducedConstant: lit].
        super pushConstant: lit.

pushReducedConstant: lit
        | classIndex newClassArray litIndex |
        self push.
        lit == nil
                ifTrue:
                        [code nextPut: OpLoadNil.
                        ^self].
        lit == true
                ifTrue:
                        [code nextPut: OpLoadTrue.
                        ^self].
        lit == false
                ifTrue:
                        [code nextPut: OpLoadFalse.
                        ^self].
        lit isInteger
                ifTrue:
                        [(lit >= 0 and: [lit <= 2])
                                ifTrue:
                                        [code nextPut: OpLoadZero + lit.
                                        ^self].
                        (lit >= 0 and: [lit <= 255])
                                ifTrue:
                                        [code nextPut: OpLoadByte with: lit.
                                        ^self].
                        (lit >= -32768 and: [lit < 32768])
                                ifTrue:
                                        [code
                                                nextPut: OpLoadTwoBytes
                                                with: ((lit bitShift: -8)
                                                                bitAnd: 255)
                                                with: (lit bitAnd: 255).
                                        ^self]].
        ((lit isMemberOf: Character)
                and: [lit asInteger between: 0 and: 255])
                ifTrue:
                        [code nextPut: OpLoadCharacter with: lit asInteger.
                        ^self].
        classIndex := literals at: lit class
                                ifAbsentPut:
                                        ["Add the literal class array to the collection"
                                        literalCollection addLast: Array new.
                                        literalCollection size - 1].
        classIndex > MaxLiteralIndex
                ifTrue:
                        Transcript cr; show: 'compilation failure: too many literal classes...'.
                        self class literalLimitSignal raiseWith: topNode body].
        classIndex <= MaxLoadLiteral
                ifTrue: [code nextPut: OpLoadLiteral + classIndex]
                ifFalse: [code nextPut: OpXLoadLiteral with: classIndex].
        newClassArray := literalCollection at: classIndex + 1.
        litIndex := newClassArray indexOf: lit ifAbsent: [0].
        litIndex = 0
                ifTrue:
                        [newClassArray := newClassArray copyWith: lit.
                        literalCollection at: classIndex + 1 put: newClassArray.
                        litIndex := newClassArray size].
        self pushBigIndex: litIndex.
        self sendNoCheck: #at: numArgs: 1

pushBigIndex: index
        "Decompose the index in order to avoid it to be added into literalCollection
        with current byteCode set it must remain < 32768"
        | q r |
        index < 32768 ifTrue: [^self pushConstant: index].
        q := index // 32768.
        r := index - (q * 32768).
        self pushConstant: 32767; pushConstant: 1; sendNoCheck: #+ numArgs: 1.
        q = 1 ifFalse: [self pushBigIndex: q; sendNoCheck: #* numArgs: 1].
        r = 0 ifFalse: [self pushConstant: r; sendNoCheck: #+ numArgs: 1].

initialize
        reduceLiterals := false.
        super initialize

doReduceLiterals
        outerStream isNil ifFalse: [outerStream doReduceLiterals].
        reduceLiterals := true

newBlockScope
        | inner |
        inner := super newBlockScope.
        reduceLiterals ifTrue: [inner doReduceLiterals].
        inner visibleGlobals: visibleGlobals.
        ^inner

testLiteralsSize
        literalCollection size > 256 ifTrue: [reduceLiterals
                        ifTrue: [self class literalLimitSignal raiseWith: topNode body]
                        ifFalse: [self doReduceLiterals; restartCompilation]]

I tried above approach in Squeak, and begun a blog post about it, but
modifications are much more invasive...

I remember I also used an array when there were too many temps, but
can't find it...
Maybe it was in vw2.5.2...

Nicolas

2013/3/15 Eliot Miranda <[hidden email]>:

>
>
> On Fri, Mar 15, 2013 at 5:40 AM, Bert Freudenberg <[hidden email]>
> wrote:
>>
>> On 2013-03-14, at 18:28, Eliot Miranda <[hidden email]> wrote:
>>
>> > On Wed, Mar 13, 2013 at 4:48 PM, David T. Lewis <[hidden email]>
>> > wrote:
>> >> Something changed in trunk a couple of days ago that results in a 'More
>> >> than
>> >> 256 literals referenced' error in a filein script that previously did
>> >> not
>> >> display this problem (see attached). It does not seem to be anything in
>> >> the
>> >> Compiler package (I reverted back a half dozen versions, no change), so
>> >> I'm
>> >> looking at the CI builds for reference. The problem appears in the
>> >> image from
>> >> SqueakTrunk build #213 and later, and is not  present in the image from
>> >> build #212 and earlier.
>> >>
>> >> I spotted the problem in the CogVM build job, which has been failing
>> >> for a
>> >> couple of days. The failures are due to the above issue, and the script
>> >> file
>> >> that fails on filein is
>> >> http://build.squeak.org/job/CogVM/ws/VMCogUnixBuild.st
>> >> The problem showed up in the CogVM job by coincidence and is not
>> >> related to
>> >> the VM.
>> >>
>> >> Filing this VMCogUnixBuild.st into an updated trunk image will
>> >> reproduce
>> >> the problem.
>> >>
>> >> Dave
>> >>
>> >
>> > However, I have an instruction set that lifts the 256 literal limit to
>> > 65535 ;)
>>
>> That would be very useful for this case indeed, plus maybe a
>> double-extended jump bytecode. Then the only remaining limit would be the
>> number of temps.
>
>
> The jump limit is lifted, also to 64k.  How big would you want to see temps?
> It is already 64, which is quite high.
> --
> Eliot
>
>
>

Reply | Threaded
Open this post in threaded view
|

Re: More than 256 literals referenced

David T. Lewis
In reply to this post by David T. Lewis
On Wed, Mar 13, 2013 at 07:48:26PM -0400, David T. Lewis wrote:
> Something changed in trunk a couple of days ago that results in a 'More than
> 256 literals referenced' error in a filein script that previously did not
> display this problem (see attached). It does not seem to be anything in the
> Compiler package (I reverted back a half dozen versions, no change), so I'm
> looking at the CI builds for reference. The problem appears in the image from
> SqueakTrunk build #213 and later, and is not  present in the image from
> build #212 and earlier.
>

I put Tests-dtl.193 in the inbox (and attached change set) to document the
problem. The issue appears to be related to binding classes in closures,
and I'm not entirely certain if it is a bug or a reasonable side effect of
some other change. In any case, the failing test makes it easier to see
the issue, so perhaps someone more familiar with the compiler can have a
look to see if it is a real problem.

Dave


> I spotted the problem in the CogVM build job, which has been failing for a
> couple of days. The failures are due to the above issue, and the script file
> that fails on filein is http://build.squeak.org/job/CogVM/ws/VMCogUnixBuild.st
> The problem showed up in the CogVM job by coincidence and is not related to
> the VM.
>
> Filing this VMCogUnixBuild.st into an updated trunk image will reproduce
> the problem.
>
> Dave
>



CompilerTest-maxLiterals-dtl.1.cs (2K) Download Attachment