Float>>raisedTo and Float>>ln

Hamish (DP) Harvey dh4180 at bristol.ac.uk
Tue Feb 3 15:18:21 UTC 1998


Content-Type: TEXT/PLAIN; CHARSET=US-ASCII
Content-ID: <Pine.LNX.3.96.980203151806.17332B at foldy>


There are problems in the above methods, which stem from the
implementation of the Interpreter>>primitiveLogN method. Taking the
natural log of a negative number does not cause the primitive to fail.
Instead the C value NaN is returned. When Squeak tries to print this, it
goes into infinite recursion of the Float>>floorLog: method.

The problem goes into raisedTo, as raisedTo is defined in terms of ln:

raisedTo: aNumber
	^ (aNumber * self ln) exp

So if the receiver is -ve, NaN comes back and the result cannot be
converted to a string.

Changing Interpreter>>primitiveLogN such that a -ve receiver will cause
failure is a step in the right direction (see new method in attached file
PFImprv1.st) as then an error will be thrown rather than the infinite
recursion filling up all the available memory until Squeak complains,
however, this will throw an error for the perfectly valid case

-2.0 raisedTo: 6

Trying to do this was how I discovered the problem in the first place.

So, Attached are two fileIns. The first (PFImprv1.st) contains the updated
Interpreter>>primitiveLogN which fails if the result is NaN and a new
method Interpreter>>primitiveFloatRaisedTo which is defined in terms of
the C math library pow() function. This primitive fails if the receiver or
argument are not floats, or if the result is NaN.

The second contains replacement Number>>raisedTo: and Float>>raisedTo:
methods which make use of the new primitive and allow raisedTo: to be used
on -ve receivers.

There are some comments at the top of PFImprv1.st.

Any comments would be of interest. Is there any reason not to do this?
Does it reduce portability? Is there another way to define raisedTo: such
and ln such that they either work or throw and error, rather then
surreptitiously returning garbage?

Cheers,
Hamish


Content-Type: TEXT/PLAIN; CHARSET=US-ASCII; NAME="PFImprv1.st"
Content-ID: <Pine.LNX.3.96.980203151647.17295B at foldy>
Content-Description: PFImprv1.st

"This file and PFImprv2.st provide the following improvements to the
Float primitives:

 Interpreter>>primitiveLogN modified
    Now fails if receiver -ve. Previously returned C NaN, which caused
    infinite recursion when printOn: was called for the result.
 Interpreter>>primitiveFloatRaisedTo is added.
    Float>>raisedTo: was previously defined in terms of ln. Now uses a new
    primitive defined in terms of C libm's pow() function. Before taking
    (a raisedTo: b) would produce NaN if a -ve. This would not result in
    an error, but would cause infinite recursion in printOn: (see above).
    The above change would have resulted in a error being signalled, but
    since powers of -ve numbers exist, this was also not perfect. Now an
    error is thrown in the result is not real, otherwise the correct answer
    is returned (I think!).

Any comments would be of interest. dh4180 at bris.ac.uk

Procedure:
File in this file (PFImprv1.st), which adds the modified primitives and
primitive table. Do

Interpreter initialize; translate: 'interpFileName.c' doInlining: true.

save image and exit.

compile new VM.

Start saved image with new VM and file in PFImrv2.st, which includes
the Number and Float methods to use the new primitive.
"

!Interpreter class methodsFor: 'initialization'!
initializePrimitiveTable
	"Interpreter initializePrimitiveTable"
	"This table generates a C switch statement."

	"NOTE: The real limit here is 2047, but our C compiler currently barfs over 700"
	MaxPrimitiveIndex _ 700.
	PrimitiveTable _ Array new: MaxPrimitiveIndex+1.
	self table: PrimitiveTable from: 
	#(
		"Integer Primitives (0-19)"
		(0 primitiveFail)
		(1 primitiveAdd)
		(2 primitiveSubtract)
		(3 primitiveLessThan)
		(4 primitiveGreaterThan)
		(5 primitiveLessOrEqual)
		(6 primitiveGreaterOrEqual)
		(7 primitiveEqual)
		(8 primitiveNotEqual)
		(9 primitiveMultiply)
		(10 primitiveDivide)
		(11 primitiveMod)
		(12 primitiveDiv)
		(13 primitiveQuo)
		(14 primitiveBitAnd)
		(15 primitiveBitOr)
		(16 primitiveBitXor)
		(17 primitiveBitShift)
		(18 primitiveMakePoint)
		(19 primitiveFail)

		"LargeInteger Primitives (20-39)"
		"32-bit logic is aliased to Integer prims above"
		(20 38 primitiveFail)

		"Float Primitives (40-59)"
	
(39 primitiveFloatRaisedTo)	(40 primitiveAsFloat)
		(41 primitiveFloatAdd)
		(42 primitiveFloatSubtract)
		(43 primitiveFloatLessThan)
		(44 primitiveFloatGreaterThan)
		(45 primitiveFloatLessOrEqual)
		(46 primitiveFloatGreaterOrEqual)
		(47 primitiveFloatEqual)
		(48 primitiveFloatNotEqual)
		(49 primitiveFloatMultiply)
		(50 primitiveFloatDivide)
		(51 primitiveTruncated)
		(52 primitiveFractionalPart)
		(53 primitiveExponent)
		(54 primitiveTimesTwoPower)
		(55 primitiveSquareRoot)
		(56 primitiveSine)
		(57 primitiveArctan)
		(58 primitiveLogN)
		(59 primitiveExp)

		"Subscript and Stream Primitives (60-67)"
		(60 primitiveAt)
		(61 primitiveAtPut)
		(62 primitiveSize)
		(63 primitiveStringAt)
		(64 primitiveStringAtPut)
		(65 primitiveNext)
		(66 primitiveNextPut)
		(67 primitiveAtEnd)

		"StorageManagement Primitives (68-79)"
		(68 primitiveObjectAt)
		(69 primitiveObjectAtPut)
		(70 primitiveNew)
		(71 primitiveNewWithArg)
		(72 primitiveFail)					"Blue Book: primitiveBecome"
		(73 primitiveInstVarAt)
		(74 primitiveInstVarAtPut)
		(75 primitiveAsOop)
		(76 primitiveFail)					"Blue Book: primitiveAsObject"
		(77 primitiveSomeInstance)
		(78 primitiveNextInstance)
		(79 primitiveNewMethod)

		"Control Primitives (80-89)"
		(80 primitiveFail)   					"Blue Book:  primitiveBlockCopy"
		(81 primitiveValue)
		(82 primitiveValueWithArgs)
		(83 primitivePerform)
		(84 primitivePerformWithArgs)
		(85 primitiveSignal)
		(86 primitiveWait)
		(87 primitiveResume)
		(88 primitiveSuspend)
		(89 primitiveFlushCache)

		"Input/Output Primitives (90-109)"
		(90 primitiveMousePoint)
		(91 primitiveFail)					"Blue Book: primitiveCursorLocPut"
		(92 primitiveFail)					"Blue Book: primitiveCursorLink"
		(93 primitiveInputSemaphore)
		(94 primitiveFail)					"Blue Book: primitiveSampleInterval"
		(95 primitiveInputWord)
		(96 primitiveCopyBits)
		(97 primitiveSnapshot)
		(98 primitiveFail)					"Blue Book: primitiveTimeWordsInto"
		(99 primitiveFail)					"Blue Book: primitiveTickWordsInto"
		(100 primitiveFail)					"Blue Book: primitiveSignalAtTick"
		(101 primitiveBeCursor)
		(102 primitiveBeDisplay)
		(103 primitiveScanCharacters)
		(104 primitiveDrawLoop)
		(105 primitiveStringReplace)
		(106 primitiveScreenSize)
		(107 primitiveMouseButtons)
		(108 primitiveKbdNext)
		(109 primitiveKbdPeek)

		"System Primitives (110-119)"
		(110 primitiveEquivalent)
		(111 primitiveClass)
		(112 primitiveBytesLeft)
		(113 primitiveQuit)
		(114 primitiveExitToDebugger)
		(115 primitiveFail)					"Blue Book: primitiveOopsLeft"
		(116 primitiveFail)
		(117 primitiveFail)
		(118 primitiveDoPrimitiveWithArgs)
		(119 primitiveFlushCacheSelective)

		"Miscellaneous Primitives (120-127)"
		(120 primitiveFail)
		(121 primitiveImageName)
		(122 primitiveNoop)					"Blue Book: primitiveImageVolume"
		(123 primitiveFail)
		(124 primitiveLowSpaceSemaphore)
		(125 primitiveSignalAtBytesLeft)
		(126 primitiveFail)
		(127 primitiveFail)

		"Squeak Primitives Start Here"

		"Squeak Miscellaneous Primitives (128-149)"
		(128 primitiveArrayBecome)
		(129 primitiveSpecialObjectsOop)
		(130 primitiveFullGC)
		(131 primitiveIncrementalGC)
		(132 primitiveObjectPointsTo)
		(133 primitiveSetInterruptKey)
		(134 primitiveInterruptSemaphore)
		(135 primitiveMillisecondClock)
		(136 primitiveSignalAtMilliseconds)
		(137 primitiveSecondsClock)
		(138 primitiveSomeObject)
		(139 primitiveNextObject)
		(140 primitiveBeep)
		(141 primitiveClipboardText)
		(142 primitiveVMPath)
		(143 primitiveShortAt)
		(144 primitiveShortAtPut)
		(145 primitiveConstantFill)
		(146 primitiveReadJoystick)
		(147 primitiveWarpBits)
		(148 primitiveClone)
		(149 primitiveGetAttribute)

		"File Primitives (150-169)"
		(150 primitiveFileAtEnd)
		(151 primitiveFileClose)
		(152 primitiveFileGetPosition)
		(153 primitiveFileOpen)
		(154 primitiveFileRead)
		(155 primitiveFileSetPosition)
		(156 primitiveFileDelete)
		(157 primitiveFileSize)
		(158 primitiveFileWrite)
		(159 primitiveFileRename)
		(160 primitiveDirectoryCreate)
		(161 primitiveDirectoryDelimitor)
		(162 primitiveDirectoryLookup)
		(163 168 primitiveFail)
		(169 primitiveDirectorySetMacTypeAndCreator)

		"Sound Primitives (170-199)"
		(170 primitiveSoundStart)
		(171 primitiveSoundStartWithSemaphore)
		(172 primitiveSoundStop)
		(173 primitiveSoundAvailableSpace)
		(174 primitiveSoundPlaySamples)
		(175 primitiveSoundPlaySilence)		"obsolete; will be removed in the future"
		(176 primWaveTableSoundmixSampleCountintostartingAtpan)
		(177 primFMSoundmixSampleCountintostartingAtpan)
		(178 primPluckedSoundmixSampleCountintostartingAtpan)
		(179 primSampledSoundmixSampleCountintostartingAtpan)
		(180 primFMSoundmixSampleCountintostartingAtleftVolrightVol)
		(181 primPluckedSoundmixSampleCountintostartingAtleftVolrightVol)
		(182 primSampledSoundmixSampleCountintostartingAtleftVolrightVol)
		(183 188 primitiveFail)
		(189 primitiveSoundInsertSamples)
		(190 primitiveSoundStartRecording)
		(191 primitiveSoundStopRecording)
		(192 primitiveSoundGetRecordingSampleRate)
		(193 primitiveSoundRecordSamples)
		(194 primitiveSoundSetRecordLevel)
		(195 199 primitiveFail)

		"Networking Primitives (200-229)"
		(200 primitiveInitializeNetwork)
		(201 primitiveResolverStartNameLookup)
		(202 primitiveResolverNameLookupResult)
		(203 primitiveResolverStartAddressLookup)
		(204 primitiveResolverAddressLookupResult)
		(205 primitiveResolverAbortLookup)
		(206 primitiveResolverLocalAddress)
		(207 primitiveResolverStatus)
		(208 primitiveResolverError)
		(209 primitiveSocketCreate)
		(210 primitiveSocketDestroy)
		(211 primitiveSocketConnectionStatus)
		(212 primitiveSocketError)
		(213 primitiveSocketLocalAddress)
		(214 primitiveSocketLocalPort)
		(215 primitiveSocketRemoteAddress)
		(216 primitiveSocketRemotePort)
		(217 primitiveSocketConnectToPort)
		(218 primitiveSocketListenOnPort)
		(219 primitiveSocketCloseConnection)
		(220 primitiveSocketAbortConnection)
		(221 primitiveSocketReceiveDataBufCount)
		(222 primitiveSocketReceiveDataAvailable)
		(223 primitiveSocketSendDataBufCount)
		(224 primitiveSocketSendDone)
		(225 229 primitiveFail)

		"Other Primitives (230-249)"
		(230 primitiveRelinquishProcessor)
		(231 primitiveForceDisplayUpdate)
		(232 primitiveFormPrint)
		(233 249 primitiveFail)

		"VM Implementor Primitives (250-255)"
		(250 clearProfile)
		(251 dumpProfile)
		(252 startProfiling)
		(253 stopProfiling)
		(254 primitiveVMParameter)
		(255 primitiveFail)

		"Quick Push Const Methods"
		(256 primitivePushSelf)
		(257 primitivePushTrue)
		(258 primitivePushFalse)
		(259 primitivePushNil)
		(260 primitivePushMinusOne)
		(261 primitivePushZero)
		(262 primitivePushOne)
		(263 primitivePushTwo)

		"Quick Push Const Methods"
		(264 519 primitiveLoadInstVar)

		"Unassigned Primitives"
		(520 primitiveBeep) "test of new primitive indices"
		(521 700 primitiveFail)
	).! !

!Interpreter methodsFor: 'float primitives' stamp: 'dph 2/3/98 13:35'!
primitiveLogN
	"Natural log."

	| rcvr |
	self var: #rcvr declareC: 'double rcvr'.
	self var: #result declareC: 'double result'.
	rcvr _ self popFloat.
	self success: rcvr >= 0.0.
	successFlag
		ifTrue: [self pushFloat: rcvr]
		ifFalse: [self unPop: 1]! !

!Interpreter methodsFor: 'float primitives' stamp: 'dph 2/3/98 13:42'!
primitiveFloatRaisedTo

	| rcvr arg result |
	self var: #rcvr declareC: 'double rcvr'.
	self var: #arg declareC: 'double arg'.
	self var: #result declareC: 'double result'.

	arg _ self popFloat.
	rcvr _ self popFloat.
	result _ self cCode: 'pow(rcvr, arg)'.
	self success: (self cCode: '!!isnan(result)').
	successFlag
		ifTrue: [ self pushFloat: result ]
		ifFalse: [ self unPop: 2 ]
! !
Content-Type: TEXT/PLAIN; CHARSET=US-ASCII; NAME="PFImprv2.st"
Content-ID: <Pine.LNX.3.96.980203151647.17295C at foldy>
Content-Description: PFImprv2.st

"See comments at top of PFImprv1.st"

!Number methodsFor: 'mathematical functions'!
raisedTo: aNumber 
	"Answer the receiver raised to aNumber."
	(aNumber isInteger)
		ifTrue: ["Do the special case of integer power"
				^self raisedToInteger: aNumber].
	aNumber = 0 ifTrue: [^1].		"Special case of exponent=0"
	aNumber = 1 ifTrue: [^self].		"Special case of exponent=1"
	^ self asFloat raisedTo: aNumber "Otherwise raise using float primitive. This was the following:
	^(aNumber * self ln) exp		Otherwise raise it to the power using logarithms
but that fails for self < 0 (log of -ve)."! !

!Float methodsFor: 'mathematical functions' stamp: 'dph 2/3/98 00:14'!
raisedTo: power
	<primitive: 39>
	"If power is not a float, then coerce and retry."
	power isFloat not
		ifTrue: [^ (power adaptFloat: self) raisedTo: power adaptToFloat]
		ifFalse: [^ self error: 'No result (root(neg)?)']! !





More information about the Squeak-dev mailing list