OSErrorHolder.st
author Claus Gittinger <cg@exept.de>
Mon, 20 Feb 2006 23:44:21 +0100
changeset 9164 60e5713be9c8
parent 7593 e7550b9ef84a
child 9165 2809fd6c37cf
permissions -rw-r--r--
some COM errors

"
 COPYRIGHT (c) 1997 by eXept Software AG / Claus Gittinger
	      All Rights Reserved

 This software is furnished under a license and may be used
 only in accordance with the terms of that license and with the
 inclusion of the above copyright notice.   This software may not
 be provided or otherwise made available to, or used by, any
 other person.  No title to or ownership of the software is
 hereby transferred.
"



"{ Package: 'stx:libbasic' }"

Object subclass:#OSErrorHolder
	instanceVariableNames:'errorSymbol errorCategory'
	classVariableNames:'Signals OSErrorSignal'
	poolDictionaries:''
	category:'OS-Support'
!

!OSErrorHolder class methodsFor:'documentation'!

copyright
"
 COPYRIGHT (c) 1997 by eXept Software AG / Claus Gittinger
	      All Rights Reserved

 This software is furnished under a license and may be used
 only in accordance with the terms of that license and with the
 inclusion of the above copyright notice.   This software may not
 be provided or otherwise made available to, or used by, any
 other person.  No title to or ownership of the software is
 hereby transferred.
"


!

documentation
"
    This class represents low level operating system errors.
    We do not use error numbers, because there may be different errnos
    for the same error on different systems.

    [instance variables:]
        errorSymbol             symbol associated with this error
        errorCategory           symbol defining the error category.
                                This is in fact a symbol that returns a
                                Signal when sent to myself.

        While the errorSymbol may be different on different platforms,
        the errorCategories (which refer to the Signals that will be raised) 
        are identical.
        You can get an OS independent error message for an error by sending
        #errorCategoryString.

    [author:]
        Stefan Vogel

    [see also:]
        OperatingSystem
"
! !

!OSErrorHolder class methodsFor:'Signal constants'!

allocRetrySignal
    ^ Signals at:#allocRetrySignal
!

badAccessorSignal
    ^ Signals at:#badAccessorSignal
!

badArgumentsSignal
    ^ Signals at:#badArgumentsSignal
!

classNotRegisteredSignal
    ^ Signals at:#classNotRegisteredSignal
!

coNotInitializedSignal
    ^ Signals at:#coNotInitializedSignal
!

existingReferentSignal
    ^ Signals at:#existingReferentSignal
!

illegalOperationSignal
    ^ Signals at:#illegalOperationSignal
!

inaccessibleSignal
    ^ Signals at:#inaccessibleSignal
!

inappropriateOperationSignal
    ^ Signals at:#inappropriateOperationSignal
!

inappropriateReferentSignal
    ^ Signals at:#inappropriateReferentSignal
!

invalidArgumentsSignal
    "return the signal for invalid arguments (e.g. right class, wrong value)."

    ^ OsInvalidArgumentsError
!

needRetrySignal
    ^ Signals at:#needRetrySignal
!

noAggregationSignal
    ^ Signals at:#noAggregationSignal
!

noDataSignal
    ^ Signals at:#noDataSignal
!

noInterfaceSignal
    ^ Signals at:#noInterfaceSignal
!

noMemorySignal
    ^ Signals at:#noMemorySignal
!

noPermissionsSignal
    ^ Signals at:#noPermissionsSignal
!

noResourcesSignal
    ^ Signals at:#noResourcesSignal
!

nonexistentSignal
    "return the signal for non existing referents (i.e. device, file etc.)."

    ^ Signals at:#nonexistentSignal
!

notReadySignal
    ^ Signals at:#notReadySignal
!

peerFaultSignal
    ^ Signals at:#peerFaultSignal
!

rangeErrorSignal
    ^ Signals at:#rangeErrorSignal
!

transferFaultSignal
    ^ Signals at:#transferFaultSignal
!

transientErrorSignal
    ^ Signals at:#transientErrorSignal
!

unavailableReferentSignal
    ^ Signals at:#unavailableReferentSignal
!

underSpecifiedSignal
    ^ Signals at:#underSpecifiedSignal
!

unknownNameSignal
    ^ Signals at:#unknownNameSignal
!

unpreparedOperationSignal
    ^ Signals at:#unpreparedOperationSignal
!

unsupportedOperationSignal
    ^ Signals at:#unsupportedOperationSignal
!

volumeFullSignal
    ^ Signals at:#volumeFullSignal
!

wrongSubtypeForOperationSignal
    ^ Signals at:#wrongSubtypeForOperationSignal
! !

!OSErrorHolder class methodsFor:'accessing'!

errorSignal
    ^ OperatingSystem errorSignal

    "Created: 25.1.1997 / 18:07:55 / cg"
! !

!OSErrorHolder class methodsFor:'class initialization'!

initialize
    "init signals etc."

    |s|

    OSErrorSignal isNil ifTrue:[
        OSErrorSignal := OsError.
        OSErrorSignal notifierString:'OperatingSystem error'.

        Signals := Dictionary new:28.

        OsNoResourcesError notifierString:'Not enough resources'.
        Signals at:#noResourcesSignal put:OsNoResourcesError.

        OsIllegalOperation notifierString:'Illegal Operation'.
        Signals at:#illegalOperationSignal put:OsIllegalOperation. 

        OsInvalidArgumentsError notifierString:'Invalid Arguments'.
        Signals at:#invalidArgumentsSignal put:OsInvalidArgumentsError. 

        OsInaccessibleError notifierString:'Referent inaccessible'.
        Signals at:#inaccessibleSignal put:OsInaccessibleError. 

        OsTransferFaultError notifierString:'Transfer fault'.
        Signals at:#transferFaultSignal put:OsTransferFaultError. 

        OsNeedRetryError notifierString:'Retry Operation'.
        Signals at:#needRetrySignal put:OsNeedRetryError. 

false ifTrue:[
        "/ Information signals

        s := self setupSignal:#informationSignal parent:OSErrorSignal 
                     notifier:'Information'.
        self setupSignal:#operationStartedSignal parent:s 
                     notifier:'Operation started'.
].
        "/ Retry signals

        self setupSignal:#notReadySignal parent:OsNeedRetryError 
                     notifier:' -- referent not ready'.
        self setupSignal:#transientErrorSignal parent:OsNeedRetryError 
                     notifier:' -- transient error'.
        self setupSignal:#allocRetrySignal parent:OsNeedRetryError 
                     notifier:' -- allocation failure'.

        "/ Resource signals

        self setupSignal:#noMemorySignal parent:OsNoResourcesError 
                     notifier:' -- memory'.

        "/ Transfer faults

        self setupSignal:#noDataSignal parent:OsTransferFaultError 
                     notifier:'Data unavailable/EOF reached'.
        self setupSignal:#peerFaultSignal parent:OsTransferFaultError 
                     notifier:'Communication with peer failed'.
        self setupSignal:#volumeFullSignal parent:OsTransferFaultError 
                     notifier:'Volume full'.

        "/ Inaccesible faults

        self setupSignal:#nonexistentSignal parent:OsInaccessibleError 
                     notifier:'File does not exist'.
        self setupSignal:#unavailableReferentSignal parent:OsInaccessibleError 
                     notifier:' currently'.
        self setupSignal:#noPermissionsSignal parent:OsInaccessibleError 
                     notifier:'Permission denied'.
        self setupSignal:#existingReferentSignal parent:OsInaccessibleError 
                     notifier:' -- already exists or currently in use'.
        self setupSignal:#inappropriateReferentSignal parent:OsInaccessibleError 
                     notifier:' -- operation inappropriate'.

        "/ Illegal operations

        self setupSignal:#inappropriateOperationSignal parent:OsIllegalOperation 
                     notifier:'Inappropriate operation'.
        self setupSignal:#wrongSubtypeForOperationSignal parent:OsIllegalOperation 
                     notifier:' -- wrong subtype'.
        self setupSignal:#unsupportedOperationSignal parent:OsIllegalOperation 
                     notifier:' -- on this platform'.
        self setupSignal:#unpreparedOperationSignal parent:OsIllegalOperation 
                     notifier:' -- wrong sequence'.

        "/ Illegal arguments

        self setupSignal:#badArgumentsSignal parent:OsInvalidArgumentsError 
                     notifier:' -- wrong class'.
        self setupSignal:#badAccessorSignal parent:OsInvalidArgumentsError 
                     notifier:' -- accessor invalid'.
        self setupSignal:#rangeErrorSignal parent:OsInvalidArgumentsError 
                     notifier:' -- out of range'.
        self setupSignal:#underSpecifiedSignal parent:OsInvalidArgumentsError 
                     notifier:' -- operation not fully specified'.

        "/ COM errors
        self setupSignal:#coNotInitializedSignal parent:OsIllegalOperation 
                     notifier:'COM not initialized'.
        self setupSignal:#noInterfaceSignal parent:OsIllegalOperation 
                     notifier:'No such interface'.
        self setupSignal:#classNotRegisteredSignal parent:OsIllegalOperation 
                     notifier:'Class not registered'.
        self setupSignal:#noAggregationSignal parent:OsIllegalOperation 
                     notifier:'No Aggregation'.
        self setupSignal:#unknownNameSignal parent:OsIllegalOperation 
                     notifier:'Unknown member name'.
   ].

   "
    OSErrorSignal := nil.
    self initialize
   "
!

setupSignal:aSymbol parent:parentSignal notifier:aString
    "setup a signal, which can be retrieved by sending aSymbol to self.
     Return the new signal"

    |s|

    Signals at:aSymbol
           put:(s := parentSignal newSignal
                        notifierString:aString;
                        nameClass:self message:aSymbol).
    ^ s
! !

!OSErrorHolder methodsFor:'accessing'!

errorSymbol:sym errorCategory:typ
    errorSymbol := sym.
    errorCategory := typ.
! !

!OSErrorHolder methodsFor:'error reporting'!

reportError
    "Report an error."
    "Delegate to the receiver's error reporter."

    (self class perform:errorCategory) raiseWith:self.
self halt.
"/    ^ self errorReporter reportOn:self
! !

!OSErrorHolder methodsFor:'others'!

errorString 
    ^ OperatingSystem errorStringForSymbol:errorSymbol
!

errorSymbol 
    ^ errorSymbol
! !

!OSErrorHolder class methodsFor:'documentation'!

version
    ^ '$Header: /cvs/stx/stx/libbasic/OSErrorHolder.st,v 1.8 2006-02-20 22:44:21 cg Exp $'
! !

OSErrorHolder initialize!