[Vm-dev] Microsecond clock primitives in Cog and SqueakVM

David T. Lewis lewis at mail.msen.com
Thu Aug 16 03:07:32 UTC 2012


We currently have incompatible implementations of microsecond clock primitives
in SqueakVM and Cog. Opinions may vary as the the preferred approach, but the
inconsistencies need to be reconciled.

I have implemented the Cog primitives on SqueakVM, and the SqueakVM primitive
on Cog. The platform source support for these is different on Cog and trunk, but it
turned out to be straightforward to do equivalent implementations in the two VMMaker
branches. I would like to suggest that we adopt a common set of three primitives in
both Cog and SqueakVM trunk. We can worry about reconciling the platform sources
in the future, meanwhile there is value in providing a common api for the primitives.

The three primitives of interest are these:

primitiveUtcWithOffset
        "Answer an array with UTC microseconds since the Posix epoch and
        the current seconds offset from GMT in the local time zone.
        This is a named (not numbered) primitive in the null module (ie the VM)"

primitiveUTCMicrosecondClock
        "Answer the UTC microseconds since the Smalltalk epoch. The value is
        derived from the Posix epoch with a constant offset corresponding to
        elapsed microseconds between the two epochs according to RFC 868."

primitiveLocalMicrosecondClock
        "Answer the local microseconds since the Smalltalk epoch. The value is
        derived from the Posix epoch with a constant offset corresponding to
        elapsed microseconds between the two epochs according to RFC 868, and
        with an offset duration corresponding to the current offset of local
        time from UTC."

I am attaching two change sets for consideration. Cog-primitiveUtcWithOffset-dtl.cs
is for inclusion in oscog to provide an implementation of the SqueakVM primitiveUtcWithOffset.
SqueakVM-cogMicrosecondPrimitives-dtl.cs is for inclusion in the interpreter VM to
provide implementions of primitiveUTCMicrosecondClock and primitiveLocalMicrosecondClock
and add them to the numbered primitives table.

Does this sound like a reasonable solution? If so, I will commit primitiveUTCMicrosecondClock
and primitiveLocalMicrosecondClock to VMMaker trunk, and request that the
primitiveUtcWithOffset change be added to Cog.

Thanks,
Dave

-------------- next part --------------
'From Squeak4.3 of 16 May 2012 [latest update: #12046] on 13 August 2012 at 9:24:08 pm'!
"Change Set:		Cog-primitiveUtcWithOffset-dtl
Date:			13 August 2012
Author:			David T. Lewis

Provide an implementation of InterpreterPrimitives>>primitiveUtcWithOffset for the oscog platform source branch. The primitive is compatible with that of trunk VMMaker and trunk sources, but implemented with the ioUTCMicroseconds ioLocalMicroseconds support functions from oscog. Strictly speaking this does not provide an atomic call to UTC clock and offset, but the likelihood of problems is vanishingly small. No modification of platform sources is required."!


!InterpreterPrimitives methodsFor: 'system control primitives' stamp: 'dtl 8/13/2012 08:31'!
primitiveUtcWithOffset
	"Answer an array with UTC microseconds since the Posix epoch and
	the current seconds offset from GMT in the local time zone.
	This is a named (not numbered) primitive in the null module (ie the VM)"
	| offset resultArray |

	<export: true>
	<var: #clock type: 'sqLong'>
	offset := self ioUTCMicroseconds - self ioLocalMicroseconds.
	objectMemory pushRemappableOop: (self positive64BitIntegerFor: self ioUTCMicroseconds).
	resultArray := objectMemory instantiateClass: objectMemory classArray indexableSize: 2.
	self stObject: resultArray at: 1 put: objectMemory popRemappableOop.
	self stObject: resultArray at: 2 put: (objectMemory integerObjectOf: offset).
	self pop: 1 thenPush: resultArray
! !

-------------- next part --------------
'From Squeak3.11alpha of 6 August 2012 [latest update: #12164] on 13 August 2012 at 10:22:33 pm'!
"Change Set:		SqueakVM-cogMicrosecondPrimitives-dtl
Date:			13 August 2012
Author:			David T. Lewis

For compatibility with Cog, add implementations of primitiveUTCMicrosecondClock and primitiveLocalMicrosecondClock derived from the existing primitiveUtcWithOffset and add these to the numbered primitives table."!


!InterpreterPrimitives methodsFor: 'system control primitives' stamp: 'dtl 8/13/2012 22:20'!
primitiveLocalMicrosecondClock
	"Answer the local microseconds since the Smalltalk epoch. The value is
	derived from the Posix epoch with a constant offset corresponding to
	elapsed microseconds between the two epochs according to RFC 868,
	and with an offset duration corresponding to the current offset of local
	time from UTC."
	
	| clock offset offsetMillis epochDelta uSecs |

	<export: true>
	<var: #clock type: 'usqLong'>
	<var: #offset type: 'int'>
	<var: #offsetMillis type: 'usqLong'>
	<var: #epochDelta declareC: 'static usqLong epochDelta= 2177452800000000ULL'>
	(self cCode: 'ioUtcWithOffset(&clock, &offset)' inSmalltalk: [-1]) = -1
		ifTrue: [^ self primitiveFail].
	clock := clock + epochDelta. "adjust for nominal Smalltalk epoch"
	offsetMillis := offset.
	offsetMillis := offsetMillis * 1000000.
	clock := clock + offsetMillis. "adjust for local time offset"
	uSecs := self positive64BitIntegerFor: clock.
	self pop: 1 thenPush: uSecs.
! !

!InterpreterPrimitives methodsFor: 'system control primitives' stamp: 'dtl 8/13/2012 22:19'!
primitiveUTCMicrosecondClock
	"Answer the UTC microseconds since the Smalltalk epoch. The value is
	derived from the Posix epoch with a constant offset corresponding to
	elapsed microseconds between the two epochs according to RFC 868."
	| clock epochDelta uSecs |

	<export: true>
	<var: #clock type: 'usqLong'>
	<var: #offset type: 'int'>
	<var: #epochDelta declareC: 'static usqLong epochDelta= 2177452800000000ULL'>
	(self cCode: 'ioUtcWithOffset(&clock, &offset)' inSmalltalk: [-1]) = -1
		ifTrue: [^ self primitiveFail].
	clock := clock + epochDelta.
	uSecs := self positive64BitIntegerFor: clock.
	self pop: 1 thenPush: uSecs.
! !


!Interpreter class methodsFor: 'initialization' stamp: 'dtl 8/9/2012 07:55'!
initializePrimitiveTable 
	"This table generates a C function address table use in primitiveResponse along with dispatchFunctionPointerOn:in:"

	"NOTE: The real limit here is 2047 because of the method header layout but there is no point in going over the needed size"
	MaxPrimitiveIndex := 575.
	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)					"Guard primitive for simulation -- *must* fail"

		"LargeInteger Primitives (20-39)"
		(20 primitiveFail)
		(21 primitiveAddLargeIntegers)
		(22 primitiveSubtractLargeIntegers)
		(23 primitiveLessThanLargeIntegers)
		(24 primitiveGreaterThanLargeIntegers)
		(25 primitiveLessOrEqualLargeIntegers)
		(26 primitiveGreaterOrEqualLargeIntegers)
		(27 primitiveEqualLargeIntegers)
		(28 primitiveNotEqualLargeIntegers)
		(29 primitiveMultiplyLargeIntegers)
		(30 primitiveDivideLargeIntegers)
		(31 primitiveModLargeIntegers)
		(32 primitiveDivLargeIntegers)
		(33 primitiveQuoLargeIntegers)
		(34 primitiveBitAndLargeIntegers)
		(35 primitiveBitOrLargeIntegers)
		(36 primitiveBitXorLargeIntegers)
		(37 primitiveBitShiftLargeIntegers)

		"Float Primitives (38-59)"
		(38 primitiveFloatAt)
		(39 primitiveFloatAtPut)
		(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 primitiveFail) "was primitiveNext which no longer pays its way (normal Smalltalk code is faster)"
		(66 primitiveFail) "was primitiveNextPut which no longer pays its way (normal Smalltalk code is faster)"
		(67 primitiveFail) "was primitiveAtEnd which no longer pays its way (normal Smalltalk code is faster)"

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

		"Control Primitives (80-89)"
		(80 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 primitiveTestDisplayDepth)			"Blue Book: primitiveCursorLocPut"
		(92 primitiveSetDisplayMode)				"Blue Book: primitiveCursorLink"
		(93 primitiveInputSemaphore)
		(94 primitiveGetNextEvent)				"Blue Book: primitiveSampleInterval"
		(95 primitiveInputWord)
		(96 primitiveFail)	"primitiveCopyBits"
		(97 primitiveSnapshot)
		(98 primitiveStoreImageSegment)
		(99 primitiveLoadImageSegment)
		(100 primitivePerformInSuperclass)		"Blue Book: primitiveSignalAtTick"
		(101 primitiveBeCursor)
		(102 primitiveBeDisplay)
		(103 primitiveScanCharacters)
		(104 primitiveFail)	"primitiveDrawLoop"
		(105 primitiveStringReplace)
		(106 primitiveScreenSize)
		(107 primitiveMouseButtons)
		(108 primitiveKbdNext)
		(109 primitiveKbdPeek)

		"System Primitives (110-119)"
		(110 primitiveIdentical)
		(111 primitiveClass)
		(112 primitiveBytesLeft)
		(113 primitiveQuit)
		(114 primitiveExitToDebugger)
		(115 primitiveChangeClass)					"Blue Book: primitiveOopsLeft"
		(116 primitiveFlushCacheByMethod)
		(117 primitiveExternalCall)
		(118 primitiveDoPrimitiveWithArgs)
		(119 primitiveFlushCacheSelective)
			"Squeak 2.2 and earlier use 119.  Squeak 2.3 and later use 116.
			Both are supported for backward compatibility."

		"Miscellaneous Primitives (120-127)"
		(120 primitiveCalloutToFFI)
		(121 primitiveImageName)
		(122 primitiveNoop)					"Blue Book: primitiveImageVolume"
		(123 primitiveValueUninterruptably)	"@@@: Remove this when all VMs have support"
		(124 primitiveLowSpaceSemaphore)
		(125 primitiveSignalAtBytesLeft)

		"Squeak Primitives Start Here"

		"Squeak Miscellaneous Primitives (128-149)"
		(126 primitiveDeferDisplayUpdates)
		(127 primitiveShowDisplayRect)
		(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)
		"NOTE: When removing the obsolete indexed primitives,
		the following two should go become #primitiveIntegerAt / atPut"
		(146 primitiveFail)	"primitiveReadJoystick"
		(147 primitiveFail)	"primitiveWarpBits"
		(148 primitiveClone)
		(149 primitiveGetAttribute)

		"File Primitives (150-169) - NO LONGER INDEXED"
		(150 159 primitiveFail)
		(160 primitiveAdoptInstance)
		(161 primitiveSetIdentityHash) "CogMemoryManager primitives"
		(162 164 primitiveFail)
		(165 primitiveIntegerAt)		"hacked in here for now"
		(166 primitiveIntegerAtPut)
		(167 primitiveYield)
		(168 primitiveCopyObject)
		(169 primitiveNotIdentical)

		"Sound Primitives (170-199) - NO LONGER INDEXED"
		(170 174 primitiveFail)

		"CogMemoryManager primitives"
		(175 primitiveBehaviorHash)
		(176 primitiveMaxIdentityHash)
		(177 185 primitiveFail)

		"Old closure primitives"
		(186 primitiveFail) "was primitiveClosureValue"
		(187 primitiveFail) "was primitiveClosureValueWithArgs"

		"Perform method directly"
		(188 primitiveExecuteMethodArgsArray)
		(189 primitiveExecuteMethod)

		"Sound Primitives (continued) - NO LONGER INDEXED"
		(190 194 primitiveFail)

		"Unwind primitives"
		(195 primitiveFindNextUnwindContext)
		(196 primitiveTerminateTo)
		(197 primitiveFindHandlerContext)
		(198 primitiveMarkUnwindMethod)
		(199 primitiveMarkHandlerMethod)

		"new closure primitives (were Networking primitives)"
		(200 primitiveClosureCopyWithCopiedValues)
		(201 primitiveClosureValue) "value"
		(202 primitiveClosureValue) "value:"
		(203 primitiveClosureValue) "value:value:"
		(204 primitiveClosureValue) "value:value:value:"
		(205 primitiveClosureValue) "value:value:value:value:"
		(206 primitiveClosureValueWithArgs) "valueWithArguments:"

		(207 209 primitiveFail) "reserved for Cog primitives"

		(210 primitiveAt)		"Compatibility with Cog StackInterpreter Context primitives"
		(211 primitiveAtPut)	"Compatibility with Cog StackInterpreter Context primitives"
		(212 primitiveSize)	"Compatibility with Cog StackInterpreter Context primitives"
		(213 219 primitiveFail) "reserved for Cog primitives"

		(220 primitiveFail)		"reserved for Cog primitives"

		(221 primitiveClosureValueNoContextSwitch) "valueNoContextSwitch"
		(222 primitiveClosureValueNoContextSwitch) "valueNoContextSwitch:"

		(223 229 primitiveFail)	"reserved for Cog primitives"

		(230 primitiveRelinquishProcessor)
		(231 primitiveForceDisplayUpdate)
		(232 primitiveFormPrint)
		(233 primitiveSetFullScreen)
		(234 primitiveFail) "primBitmapdecompressfromByteArrayat"
		(235 primitiveFail) "primStringcomparewithcollated"
		(236 primitiveFail) "primSampledSoundconvert8bitSignedFromto16Bit"
		(237 primitiveFail) "primBitmapcompresstoByteArray"
		(238 239 primitiveFail) "serial port primitives"
		(240 primitiveUTCMicrosecondClock)		"was serial port primitive"
		(241 primitiveLocalMicrosecondClock)		"was serial port primitive"
		(242 primitiveFail)
		(243 primitiveFail) "primStringtranslatefromtotable"
		(244 primitiveFail) "primStringfindFirstInStringinSetstartingAt"
		(245 primitiveFail) "primStringindexOfAsciiinStringstartingAt"
		(246 primitiveFail) "primStringfindSubstringinstartingAtmatchTable"
		(247 primitiveSnapshotEmbedded)
		(248 primitiveInvokeObjectAsMethod)
		(249 primitiveArrayBecomeOneWayCopyHash)

		"VM Implementor Primitives (250-255)"
		(250 clearProfile)
		(251 dumpProfile)
		(252 startProfiling)
		(253 stopProfiling)
		(254 primitiveVMParameter)
		(255 primitiveFail) "primitiveInstVarsPutFromStack. Never used except in Disney tests.  Remove after 2.3 release."

		"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)

		"These ranges used to be used by obsiolete indexed primitives."
		(520 529 primitiveFail)
		(530 539 primitiveFail)
		(540 549 primitiveFail)
		(550 559 primitiveFail)
		(560 569 primitiveFail)

		"External primitive support primitives"
		(570 primitiveFlushExternalPrimitives)
		(571 primitiveUnloadModule)
		(572 primitiveListBuiltinModule)
		(573 primitiveListExternalModule)
		(574 primitiveFail) "reserved for addl. external support prims"

		"Unassigned Primitives"
		(575 primitiveFail)).
! !



More information about the Vm-dev mailing list