Infinity.st
author Claus Gittinger <cg@exept.de>
Mon, 19 May 2003 10:24:25 +0200
changeset 7294 c4e6d095a150
parent 6501 51344e42c38c
child 7443 3407302dc4d9
permissions -rw-r--r--
category changes

"{ Package: 'stx:goodies' }"

"       NAME            infinity
	AUTHOR          manchester
	FUNCTION        Provides a class of infinities
	ST-VERSION      2.2
	PREREQUISITES   
	CONFLICTS
	DISTRIBUTION    world
	VERSION         1
	DATE    22 Jan 1989
SUMMARY
This is a set of changes that implements infinity in the Number hierarchy.  
I obtained the original changes from the author of an article in comp.lang.smalltalk.
I have just installed it in my image and I have found two small omissions
which are corrected in what is below; there might be others.  Arithmetic
between infinities is not defined but magnitude comparisons are implemented.

Claus: fixed some minor bugs (args to errorUndefinedResult:) and some
       wrong comments.
       Changed retry:coercing: to match ST/X
"!

!Point methodsFor: 'testing'!

isFinite
	^x isFinite and: [y isFinite]!

isInfinite
	^x isInfinite or: [y isInfinite]! !

!Number methodsFor: 'testing'!

isFinite
	^true!

isInfinite
	^false! !

!Number methodsFor: 'coercing'!

retry: aSymbol coercing: aNumber
    "Arithmetic represented by the symbol, aSymbol,
    could not be performed with the receiver and the argument,
    aNumber, because of the differences in representation.  Coerce either
    the receiver or the argument, depending on which has higher generality, and
    try again.  If the symbol is the equals sign, answer false if the argument
    is not a Number.  If the generalities are the same, create an error message."

    |myGenerality otherGenerality|

    (aSymbol == #=) ifTrue:[
	(aNumber respondsTo:#generality) ifFalse:[^ false]
    ] ifFalse:[
	(aNumber respondsTo:#generality) ifFalse:[
	    self error:'retry:coercing: argument is not a number'.
	    ^ self
	]
    ].
    myGenerality := self generality.
    otherGenerality := aNumber generality.
    (myGenerality > otherGenerality) ifTrue:[
	^ self perform:aSymbol with:(self coerce:aNumber)
    ].
    (myGenerality < otherGenerality) ifTrue:[
	aNumber isInfinite ifTrue: [
	    ^ aNumber retryReverseOf:aSymbol with:self
	].
	^ (aNumber coerce:self) perform:aSymbol with:aNumber
    ].
    self error:'retry:coercing: oops - same generality'
! !

Number subclass: #Infinity
	instanceVariableNames: 'positive '
	classVariableNames: 'NegativeInfinity PositiveInfinity '
	poolDictionaries: ''
	category: 'Magnitude-Numbers'!

Infinity comment:
'I have two instances representing positive and negative infinity.

Instance Variables :-
	positive <Boolean>      :       if true the instance represents positive
					infinity. if false, negative infinity'
!

!Infinity class methodsFor: 'documentation'!

copyright
"
 This is a Manchester Goodie.  It is distributed freely on condition
 that you observe these conditions in respect of the whole Goodie, and on
 any significant part of it which is separately transmitted or stored:
	* You must ensure that every copy includes this notice, and that
	  source and author(s) of the material are acknowledged.
	* These conditions must be imposed on anyone who receives a copy.
	* The material shall not be used for commercial gain without the prior
	  written consent of the author(s).

 For more information about the Manchester Goodies Library (from which 
 this file was distributed) send e-mail:
	To: goodies-lib@cs.man.ac.uk
	Subject: help 

 This is an additional goody-class, which is NOT covered by the
 ST/X license. It has been packaged with the ST/X distribution to
 make your live easier instead. NO WARRANTY.
"
!

documentation
"
    This is a set of changes that implements infinity in the Number hierarchy.  
    I obtained the original changes from the author of an article in comp.lang.smalltalk.
    Arithmetic between infinities is not defined but magnitude comparisons are implemented.

    Claus: fixed some minor bugs (args to errorUndefinedResult:) and some wrong comments.
	   Changed retry:coercing: to match ST/X

    I have two instances representing positive and negative infinity.

    Instance Variables :-
	positive <Boolean>      :       if true the instance represents positive
					infinity. if false, negative infinity
"
!

examples
"

    1 + Infinity positive
    Infinity positive + 1     
    Infinity positive + Infinity positive     

    Infinity negative - 1
    Infinity negative + Infinity negative
    Infinity negative + Infinity negative

"
!

info
"       
	NAME            infinity
	AUTHOR          manchester
	FUNCTION        Provides a class of infinities
	ST-VERSION      2.2
	PREREQUISITES   
	CONFLICTS
	DISTRIBUTION    world
	VERSION         1
	DATE            22 Jan 1989
SUMMARY
This is a set of changes that implements infinity in the Number hierarchy.  
I obtained the original changes from the author of an article in comp.lang.smalltalk.
I have just installed it in my image and I have found two small omissions
which are corrected in what is below; there might be others.  Arithmetic
between infinities is not defined but magnitude comparisons are implemented.
"
! !

!Infinity methodsFor: 'arithmetic'!

* aNumber
	"Multiply the receiver by the argument and answer with the result."

	aNumber isInfinite ifTrue: [
	    self errorUndefinedResult: #*
	].
	^self
!

+ aNumber
	"Add the receiver by the argument and answer with the result."

	(aNumber isInfinite and: [aNumber ~~ self]) ifTrue: [
	    self errorUndefinedResult: #+
	].
	^self
!

- aNumber
	"subtracet aNumber from the receiver answer with the result."

	(aNumber isInfinite) ifTrue: [
	    self errorUndefinedResult: #-
	].
	^self
!

/ aNumber
	"Divide the receiver by the argument and answer with the result."

	(aNumber isInfinite or: [aNumber = 0]) ifTrue: [
	    self errorUndefinedResult: #/
	].
	^self
! !

!Infinity methodsFor: 'comparing'!

< aNumber
	"Positive infinity is greater than any number than positive infinity.
	 Analogously, negative infinity is less than any other number other
	 than negative infinity"

	aNumber == self ifTrue: [^false].
	^ positive not!

= aNumber
	^aNumber == self
! !

!Infinity methodsFor: 'testing'!

isFinite
	^false
!

isInfinite
	^true
! !

!Infinity methodsFor: 'coercing'!

generality
	"Infinities are more general than scalars, but not more general than
	 vectors (e.g. Points)"
	^85
!

retryReverseOf: aSymbol with: aNumber
	(aSymbol == #* or: [aSymbol == #+]) ifTrue: [
	    ^self perform: aSymbol with: aNumber
	].
	(aSymbol == #/ and: [aNumber isFinite]) ifTrue: [^0].
	(aSymbol == #< and: [aNumber isFinite]) ifTrue: [^positive].
	(aSymbol == #> and: [ aNumber isFinite ]) ifTrue: [^positive not].
	(aSymbol == #= and: [ aNumber isFinite ])ifTrue: [ ^false ]. 
	self errorUndefinedResult: aSymbol
! !

!Infinity methodsFor: 'printing'!

printOn: aStream
	aStream nextPutAll: self class name.
	aStream nextPutAll:(positive
				ifTrue: [' positive']
				ifFalse: [' negative'])
! !

!Infinity methodsFor: 'errors'!

errorUndefinedResult: messageName
	self error: 'Undefined result in an Infinity ', messageName
! !

!Infinity methodsFor: 'private'!

setPositive: aBoolean
	positive := aBoolean
! !

!Infinity class methodsFor: 'class initialization'!

initialize
	"Infinity initialize"

	PositiveInfinity := self basicNew setPositive: true.
	NegativeInfinity := self basicNew setPositive: false
! !

!Infinity class methodsFor: 'instance creation'!

negative
	"Return the unique instance of negative infinity"

	^NegativeInfinity
!

new
	self shouldNotImplement
!

positive
	"Return the unique instance of positive infinity"

	^PositiveInfinity
! !

Infinity initialize!