I tried in 10107 image to put a self halt
but it does not show up.

I will try to find how I can reproduce your bug

On Oct 27, 2008, at 9:27 PM, Stéphane Ducasse wrote:

Can you try

to paste that method in ProjectLauncher

startUpAfterLogin
        | scriptName loader isUrl |
        Preferences readDocumentAtStartup ifTrue: [
                HTTPClient isRunningInBrowser ifTrue:[
                        self setupFromParameters.
                        scriptName := self parameterAt: 'src'.
                        CodeLoader defaultBaseURL: (self parameterAt: 'Base').
                ] ifFalse:[
scriptName := (SmalltalkImage current getSystemAttribute: 2) ifNil:[''].
                        scriptName := scriptName convertFromSystemString.
                        scriptName isEmpty ifFalse:[
                                "figure out if script name is a URL by itself"
                                isUrl := (scriptName asLowercase 
beginsWith:'http://') or:[
                                                (scriptName asLowercase 
beginsWith:'file://') or:[
                                                (scriptName asLowercase 
beginsWith:'ftp://')]].
                                isUrl ifFalse:[scriptName := 
'file:',scriptName]].
                ]. ]
        ifFalse: [ scriptName := '' ].

        scriptName isEmptyOrNil
ifTrue:[^Preferences eToyFriendly ifTrue: [self currentWorld addGlobalFlaps]].
        self halt.


        loader := CodeLoader new.
        loader loadSourceFiles: (Array with: scriptName).
        (scriptName asLowercase endsWith: '.pr')
                ifTrue:[self installProjectFrom: loader]
                ifFalse:[loader installSourceFiles].

Preferences eToyFriendly should be false so I do not understand why the codeloader would be invoked. May be this is not that. Right now I cannot find a way to invoke squeak from the command line.

Stef


On Oct 27, 2008, at 8:55 PM, Damien Cassou wrote:

On Mon, Oct 27, 2008 at 8:25 PM, Stéphane Ducasse
<[EMAIL PROTECTED]> wrote:
may be the codeLoader removal I did yesterday with marcus when I fixed the
etoyFriendly Preferences in Project.

This is important that you try to fix this bug as soon as possible so
that I can go on generating dev images.

--
Damien Cassou
Peter von der Ahé: «I'm beginning to see why Gilad wished us good
luck». (http://blogs.sun.com/ahe/entry/override_snafu)
_______________________________________________
Pharo-project mailing list
Pharo-project@lists.gforge.inria.fr
http://lists.gforge.inria.fr/cgi-bin/mailman/listinfo/pharo-project


_______________________________________________
Pharo-project mailing list
Pharo-project@lists.gforge.inria.fr
http://lists.gforge.inria.fr/cgi-bin/mailman/listinfo/pharo-project



_______________________________________________
Pharo-project mailing list
Pharo-project@lists.gforge.inria.fr
http://lists.gforge.inria.fr/cgi-bin/mailman/listinfo/pharo-project

Reply via email to