Hi guys

I have nonstartable Pharo 1.3 image, is there any way to get it started?

This image was running all the time, being on the net directly (Aida
based web development image) and snapshoting every hour.

The problem happens at such snapshot, raising Not enough space for
external objects/too many semaphores error and block. After I killed it,
snapshoted image is not startable anymore, more exactly: it starts in
blank window and stays unresponsive.

Is this too many semaphores error related to too many open sockets
problem we discussed not to long ago?

Any help greatly appreciated. Not to mention finding a bug and removing
it forever, because Pharo should become stable as a rock, as VW for
instance is :)

Best regards
Janko


PharoDebug.log:

THERE_BE_DRAGONS_HERE
Error: Not enough space for external objects, set a larger size at startup!
4 October 2011 4:00:01 am

VM: unix - i686 - linux-gnu - Croquet Closure Cog VM [CoInterpreter
VMMaker-oscog.35]
Image: Pharo1.3 [Latest update: #13299]

SmalltalkImage(Object)>>error:
        Receiver: Smalltalk
        Arguments and temporary variables:
                aString:        'Not enough space for external objects, set a 
larger size at
startup!'...etc...
        Receiver's instance variables:
                globals:        a SystemDictionary(lots of globals)
                deferredStartupActions:         nil


SmalltalkImage>>maxExternalSemaphores:
        Receiver: Smalltalk
        Arguments and temporary variables:
                aSize:  520
                inProduction:   false
        Receiver's instance variables:
                globals:        a SystemDictionary(lots of globals)
                deferredStartupActions:         nil


ExternalSemaphoreTable class>>freedSlotsIn:ratherThanIncreaseSizeTo:
        Receiver: ExternalSemaphoreTable
        Arguments and temporary variables:
                externalObjects:        an Array(a Semaphore() a Semaphore() a 
Semaphore() a
Semaphore...etc...
                newSize:        520
                needToGrow:     false
                maxSize:        512
        Receiver's instance variables:
                superclass:     Object
                methodDict:     a MethodDictionary()
                format:         2
                instanceVariables:      nil
                organization:   ('as yet unclassified')

                subclasses:     nil
                name:   #ExternalSemaphoreTable
                classPool:      a Dictionary(#ProtectAdd->a Semaphore() 
#ProtectRemove->a
Semaphore(...etc...
                sharedPools:    nil
                environment:    a SystemDictionary(lots of globals)
                category:       #'System-Support'
                traitComposition:       {}
                localSelectors:         nil


ExternalSemaphoreTable class>>collectionBasedOn:withRoomFor:
        Receiver: ExternalSemaphoreTable
        Arguments and temporary variables:
                externalObjects:        an Array(a Semaphore() a Semaphore() a 
Semaphore() a
Semaphore...etc...
                anObject:       a Semaphore()
                newObjects:     nil
                newSize:        520
        Receiver's instance variables:
                superclass:     Object
                methodDict:     a MethodDictionary()
                format:         2
                instanceVariables:      nil
                organization:   ('as yet unclassified')

                subclasses:     nil
                name:   #ExternalSemaphoreTable
                classPool:      a Dictionary(#ProtectAdd->a Semaphore() 
#ProtectRemove->a
Semaphore(...etc...
                sharedPools:    nil
                environment:    a SystemDictionary(lots of globals)
                category:       #'System-Support'
                traitComposition:       {}
                localSelectors:         nil


ExternalSemaphoreTable class>>safelyRegisterExternalObject:
        Receiver: ExternalSemaphoreTable
        Arguments and temporary variables:
                anObject:       a Semaphore()
                objects:        an Array(a Semaphore() a Semaphore() a 
Semaphore() a
Semaphore(a Proce...etc...
                firstEmptyIndex:        nil
                obj:    nil
                sz:     nil
                newObjects:     nil
        Receiver's instance variables:
                superclass:     Object
                methodDict:     a MethodDictionary()
                format:         2
                instanceVariables:      nil
                organization:   ('as yet unclassified')

                subclasses:     nil
                name:   #ExternalSemaphoreTable
                classPool:      a Dictionary(#ProtectAdd->a Semaphore() 
#ProtectRemove->a
Semaphore(...etc...
                sharedPools:    nil
                environment:    a SystemDictionary(lots of globals)
                category:       #'System-Support'
                traitComposition:       {}
                localSelectors:         nil


[self safelyRegisterExternalObject: anObject] in ExternalSemaphoreTable
class>>registerExternalObject:
        Receiver: ExternalSemaphoreTable
        Arguments and temporary variables:
                anObject:       a Semaphore()
        Receiver's instance variables:
                superclass:     Object
                methodDict:     a MethodDictionary()
                format:         2
                instanceVariables:      nil
                organization:   ('as yet unclassified')

                subclasses:     nil
                name:   #ExternalSemaphoreTable
                classPool:      a Dictionary(#ProtectAdd->a Semaphore() 
#ProtectRemove->a
Semaphore(...etc...
                sharedPools:    nil
                environment:    a SystemDictionary(lots of globals)
                category:       #'System-Support'
                traitComposition:       {}
                localSelectors:         nil


[caught := true.
        self wait.
        blockValue := mutuallyExcludedBlock value] in Semaphore>>critical:
        Receiver: a Semaphore()
        Arguments and temporary variables:
<<error during printing>
        Receiver's instance variables:
                firstLink:      nil
                lastLink:       nil
                excessSignals:  0


BlockClosure>>ensure:
        Receiver: [caught := true.
        self wait.
        blockValue := mutuallyExcludedBlock value]
        Arguments and temporary variables:
                aBlock:         [caught
                ifTrue: [self signal]]
                complete:       nil
                returnValue:    nil
        Receiver's instance variables:
                outerContext:   Semaphore>>critical:
                startpc:        42
                numArgs:        0


Semaphore>>critical:
        Receiver: a Semaphore()
        Arguments and temporary variables:
<<error during printing>
        Receiver's instance variables:
                firstLink:      nil
                lastLink:       nil
                excessSignals:  0


ExternalSemaphoreTable class>>registerExternalObject:
        Receiver: ExternalSemaphoreTable
        Arguments and temporary variables:
                anObject:       a Semaphore()
        Receiver's instance variables:
                superclass:     Object
                methodDict:     a MethodDictionary()
                format:         2
                instanceVariables:      nil
                organization:   ('as yet unclassified')

                subclasses:     nil
                name:   #ExternalSemaphoreTable
                classPool:      a Dictionary(#ProtectAdd->a Semaphore() 
#ProtectRemove->a
Semaphore(...etc...
                sharedPools:    nil
                environment:    a SystemDictionary(lots of globals)
                category:       #'System-Support'
                traitComposition:       {}
                localSelectors:         nil


SmalltalkImage>>registerExternalObject:
        Receiver: Smalltalk
        Arguments and temporary variables:
                anObject:       a Semaphore()
        Receiver's instance variables:
                globals:        a SystemDictionary(lots of globals)
                deferredStartupActions:         nil


InputEventPollingFetcher(InputEventFetcher)>>startUp
        Receiver: an InputEventPollingFetcher
        Arguments and temporary variables:

        Receiver's instance variables:
                eventHandlers:  an OrderedCollection(an InputEventSensor an
UserInterruptHandler...etc...
                fetcherProcess:         a Process in [delaySemaphore wait] in 
Delay>>wait
                inputSemaphore:         a Semaphore()


InputEventPollingFetcher class(InputEventFetcher class)>>startUp
        Receiver: InputEventPollingFetcher
        Arguments and temporary variables:

        Receiver's instance variables:
                superclass:     InputEventFetcher
                methodDict:     a
MethodDictionary(#terminateEventLoop->(InputEventPollingFetcher>>...etc...
                format:         136
                instanceVariables:      nil
                organization:   ('events' waitForInput)
('initialize-release' terminateEventLoop)...etc...
                subclasses:     nil
                name:   #InputEventPollingFetcher
                classPool:      a Dictionary(#EventPollDelay->a Delay(10 msecs; 
9 msecs
remaining) )...etc...
                sharedPools:    nil
                environment:    a SystemDictionary(lots of globals)
                category:       #'Kernel-Processes'
                traitComposition:       {}
                localSelectors:         nil


InputEventPollingFetcher class(Behavior)>>startUp:
        Receiver: InputEventPollingFetcher
        Arguments and temporary variables:
                resuming:       false
        Receiver's instance variables:
                superclass:     InputEventFetcher
                methodDict:     a
MethodDictionary(#terminateEventLoop->(InputEventPollingFetcher>>...etc...
                format:         136
                instanceVariables:      nil
                organization:   ('events' waitForInput)
('initialize-release' terminateEventLoop)...etc...
                subclasses:     nil
                name:   #InputEventPollingFetcher
                classPool:      a Dictionary(#EventPollDelay->a Delay(10 msecs; 
9 msecs
remaining) )...etc...
                sharedPools:    nil
                environment:    a SystemDictionary(lots of globals)
                category:       #'Kernel-Processes'
                traitComposition:       {}
                localSelectors:         nil


[:name |
| class |
class := self
                                at: name
                                ifAbsent: [].
        class isNil
                ifTrue: [removals add: name]
                ifFalse: [class perform: startUpOrShutDown with: argument]] in
SmalltalkImage>>send:toClassesNamedIn:with:
        Receiver: Smalltalk
        Arguments and temporary variables:
                startUpOrShutDown:      #InputEventPollingFetcher
                argument:       #startUp:
                removals:       false
                name:   an OrderedCollection()
                class:  InputEventPollingFetcher
        Receiver's instance variables:
                globals:        a SystemDictionary(lots of globals)
                deferredStartupActions:         nil


OrderedCollection>>do:
        Receiver: an OrderedCollection(#Delay #OSPlatform #DisplayScreen
#Cursor #InputEventFetcher #Process...etc...
        Arguments and temporary variables:
                aBlock:         [:name |
| class |
class := self
                                at: name
                                ifAbsent: [].
        class...etc...
                index:  60
        Receiver's instance variables:
                array:  #(nil nil nil nil nil nil nil nil nil nil nil nil nil 
nil nil
nil nil ni...etc...
                firstIndex:     36
                lastIndex:      74


SmalltalkImage>>send:toClassesNamedIn:with:
        Receiver: Smalltalk
        Arguments and temporary variables:
                startUpOrShutDown:      #startUp:
                startUpOrShutDownList:  an OrderedCollection(#Delay #OSPlatform
#DisplayScreen #...etc...
                argument:       false
                removals:       an OrderedCollection()
        Receiver's instance variables:
                globals:        a SystemDictionary(lots of globals)
                deferredStartupActions:         nil


SmalltalkImage>>processStartUpList:
        Receiver: Smalltalk
        Arguments and temporary variables:
                resuming:       false
        Receiver's instance variables:
                globals:        a SystemDictionary(lots of globals)
                deferredStartupActions:         nil


[self processStartUpList: resuming.
        resuming
                ifTrue: [self recordStartupStamp]] in 
SmalltalkImage>>snapshot:andQuit:
        Receiver: Smalltalk
        Arguments and temporary variables:
                resuming:       false
        Receiver's instance variables:
                globals:        a SystemDictionary(lots of globals)
                deferredStartupActions:         nil


BlockClosure>>ensure:
        Receiver: [self processStartUpList: resuming.
        resuming
                ifTrue: [self recordStartupStamp]]
        Arguments and temporary variables:
                aBlock:         [Default := self]
                complete:       nil
                returnValue:    nil
        Receiver's instance variables:
                outerContext:   SmalltalkImage>>snapshot:andQuit:
                startpc:        185
                numArgs:        0


MorphicUIManager(UIManager)>>boot:during:
        Receiver: a MorphicUIManager
        Arguments and temporary variables:
                bootingFromDisk:        false
                aBlock:         [self processStartUpList: resuming.
        resuming
                ifTrue: [self recordSta...etc...
        Receiver's instance variables:
                interactiveParser:      nil


SmalltalkImage>>snapshot:andQuit:
        Receiver: Smalltalk
        Arguments and temporary variables:
                save:   true
                quit:   false
                snapshotResult:         false
                resuming:       false
        Receiver's instance variables:
                globals:        a SystemDictionary(lots of globals)
                deferredStartupActions:         nil


SmalltalkImage>>saveSession
        Receiver: Smalltalk
        Arguments and temporary variables:

        Receiver's instance variables:
                globals:        a SystemDictionary(lots of globals)
                deferredStartupActions:         nil


[SmalltalkImage current saveSession] in AIDASite class>>imageSnapshot
        Receiver: AIDASite
        Arguments and temporary variables:

        Receiver's instance variables:
                superclass:     SwazooSite
                methodDict:     a MethodDictionary(size 203)
                format:         156
                instanceVariables:      #('style' 'settings' 'systemServices'
'userServices' 'timest...etc...
                organization:   ('private-serving' activityAnnouncers 
addAllowHeaderTo:
addDontCa...etc...
                subclasses:     nil
                name:   #AIDASite
                classPool:      a Dictionary(#Default->an AIDASite 
#Dialect->#Pharo
#HourlySnapshot-...etc...
                sharedPools:    nil
                environment:    a SystemDictionary(lots of globals)
                category:       #'Aida-Core'
                traitComposition:       {}
                localSelectors:         nil


Time class>>millisecondsToRun:
        Receiver: Time
        Arguments and temporary variables:
                timedBlock:     [SmalltalkImage current saveSession]
                initialMilliseconds:    155447683
        Receiver's instance variables:
                superclass:     Magnitude
                methodDict:     a MethodDictionary(#<->(Time>>#< "a
CompiledMethod(736624640)") #=-...etc...
                format:         134
                instanceVariables:      #('seconds' 'nanos')
                organization:   ('ansi protocol' < = duration hash hour hour12 
hour24
meridianAbb...etc...
                subclasses:     nil
                name:   #Time
                classPool:      nil
                sharedPools:    an OrderedCollection(ChronologyConstants)
                environment:    a SystemDictionary(lots of globals)
                category:       #'Kernel-Chronology'
                traitComposition:       nil
                localSelectors:         nil


AIDASite class>>imageSnapshot
        Receiver: AIDASite
        Arguments and temporary variables:
                elapsed:        nil
        Receiver's instance variables:
                superclass:     SwazooSite
                methodDict:     a MethodDictionary(size 203)
                format:         156
                instanceVariables:      #('style' 'settings' 'systemServices'
'userServices' 'timest...etc...
                organization:   ('private-serving' activityAnnouncers 
addAllowHeaderTo:
addDontCa...etc...
                subclasses:     nil
                name:   #AIDASite
                classPool:      a Dictionary(#Default->an AIDASite 
#Dialect->#Pharo
#HourlySnapshot-...etc...
                sharedPools:    nil
                environment:    a SystemDictionary(lots of globals)
                category:       #'Aida-Core'
                traitComposition:       {}
                localSelectors:         nil


[AIDASite preImageSnapshot; imageSnapshot] in AIDASite>>initHourlySnapshot
        Receiver: an AIDASite
        Arguments and temporary variables:

        Receiver's instance variables:
                enabled:        true
                uriPattern:     an OrderedCollection(a SiteIdentifier)
                parent:         a ServerRootComposite
                children:       an OrderedCollection()
                name:   'aidademo'
                serving:        true
                style:  a WasteStyle
                settings:       a Dictionary(#afterLogin->#lastPage
#contextProcesses->false #countin...etc...
                systemServices:         a Dictionary(#Admin->a WebAdmin 
#Authenticator->a
DefaultAuthen...etc...
                userServices:   a Dictionary(#Blog->a Blog #Repository->a
WasteRepository #SiteCo...etc...
                timestamps:     an IdentityDictionary(#Created->3491250844
#LastRequest->3494848717...etc...
                counters:       an IdentityDictionary(#NewVisitors->a WebCounter
#NotFound->a WebCoun...etc...
                other:  a Dictionary(#activityAnnouncers->a Dictionary() )


[self block value] in WebScheduledEvent>>run
        Receiver: a WebScheduledEvent
        Arguments and temporary variables:

        Receiver's instance variables:
                parent:         a WebScheduler
                timestamp:      a SpTimestamp
                period:         #hour->0
                method:         nil
                object:         nil
                block:  [AIDASite preImageSnapshot; imageSnapshot]


[self value.
        Processor terminateActive] in BlockClosure>>newProcess
        Receiver: [self block value]
        Arguments and temporary variables:

        Receiver's instance variables:
                outerContext:   WebScheduledEvent>>run
                startpc:        78
                numArgs:        0



--- The full stack ---
SmalltalkImage(Object)>>error:
SmalltalkImage>>maxExternalSemaphores:
ExternalSemaphoreTable class>>freedSlotsIn:ratherThanIncreaseSizeTo:
ExternalSemaphoreTable class>>collectionBasedOn:withRoomFor:
ExternalSemaphoreTable class>>safelyRegisterExternalObject:
[self safelyRegisterExternalObject: anObject] in ExternalSemaphoreTable
class>>registerExternalObject:
[caught := true.
        self wait.
        blockValue := mutuallyExcludedBlock value] in Semaphore>>critical:
BlockClosure>>ensure:
Semaphore>>critical:
ExternalSemaphoreTable class>>registerExternalObject:
SmalltalkImage>>registerExternalObject:
InputEventPollingFetcher(InputEventFetcher)>>startUp
InputEventPollingFetcher class(InputEventFetcher class)>>startUp
InputEventPollingFetcher class(Behavior)>>startUp:
[:name |
| class |
class := self
                                at: name
                                ifAbsent: [].
        class isNil
                ifTrue: [removals add: name]
                ifFalse: [class perform: startUpOrShutDown with: argument]] in
SmalltalkImage>>send:toClassesNamedIn:with:
OrderedCollection>>do:
SmalltalkImage>>send:toClassesNamedIn:with:
SmalltalkImage>>processStartUpList:
[self processStartUpList: resuming.
        resuming
                ifTrue: [self recordStartupStamp]] in 
SmalltalkImage>>snapshot:andQuit:
BlockClosure>>ensure:
MorphicUIManager(UIManager)>>boot:during:
SmalltalkImage>>snapshot:andQuit:
SmalltalkImage>>saveSession
[SmalltalkImage current saveSession] in AIDASite class>>imageSnapshot
Time class>>millisecondsToRun:
AIDASite class>>imageSnapshot
[AIDASite preImageSnapshot; imageSnapshot] in AIDASite>>initHourlySnapshot
[self block value] in WebScheduledEvent>>run
[self value.
        Processor terminateActive] in BlockClosure>>newProcess
------------------------------------------------------------




-- 
Janko Mivšek
Aida/Web
Smalltalk Web Application Server
http://www.aidaweb.si

Reply via email to