[squeak-dev] The Inbox: Chronology-Core-cmm.46.mcz

Chris Muller asqueaker at gmail.com
Sat May 18 21:33:11 UTC 2019


Would someone please double check this Duration class>>microSeconds:?

There are only a few methods left in Kernel which depend on
Chronology, but their responsibilities are very Kernel'ish, so I left
them.

On Sat, May 18, 2019 at 4:29 PM <commits at source.squeak.org> wrote:
>
> Chris Muller uploaded a new version of Chronology-Core to project The Inbox:
> http://source.squeak.org/inbox/Chronology-Core-cmm.46.mcz
>
> ==================== Summary ====================
>
> Name: Chronology-Core-cmm.46
> Author: cmm
> Time: 18 May 2019, 4:29:08.749118 pm
> UUID: 174774f6-20e5-4476-8f42-7a9eb71c6b5a
> Ancestors: Chronology-Core-nice.44
>
> - Make #utcOffset: match the prior behavior.
> - Move Duration convenience constructors, String-to-date converting methods, and benching API to this package.
>
> =============== Diff against Chronology-Core-nice.44 ===============
>
> Item was added:
> + ----- Method: BlockClosure>>bench (in category '*chronology-core') -----
> + bench
> +       "See how many times I can value in 5 seconds.  I'll answer a meaningful description."
> +
> +       ^self benchFor: 5 seconds!
>
> Item was added:
> + ----- Method: BlockClosure>>benchFor: (in category '*chronology-core') -----
> + benchFor: aDuration
> +       "See how many times I can value within the given duration.  I'll answer a meaningful description."
> +
> +       | startTime shouldRun count elapsedTime  roundTo3Digits delay |
> +       roundTo3Digits := [:num |
> +               | rounded lowDigit |
> +               rounded := (num * 1000) rounded. "round to 1/1000"
> +               lowDigit := (rounded numberOfDigitsInBase: 10) - 3. "keep only first 3 digits"
> +               rounded := rounded roundTo:(10 raisedTo: lowDigit).
> +               (lowDigit >= 3 or: [rounded \\ 1000 = 0]) "display fractional part only when needed"
> +                       ifTrue: [(rounded // 1000) asStringWithCommas]
> +                       ifFalse: [(rounded / 1000.0) printString]].
> +       delay := aDuration asDelay.
> +       count := 0.
> +       shouldRun := true.
> +       [ delay wait. shouldRun := false ] forkAt: Processor timingPriority - 1.
> +       startTime := Time millisecondClockValue.
> +       [ shouldRun ] whileTrue: [
> +               self value.
> +               count := count + 1 ].
> +       elapsedTime := Time millisecondsSince: startTime.
> +       ^(roundTo3Digits value: count * 1000 / elapsedTime) , ' per second.', ((
> +               #(
> +                       (1e-3 'seconds')
> +                       (1 'milliseconds')
> +                       (1e3 'microseconds')
> +                       (1e6 'nanoseconds')
> +               )
> +                       detect: [ :pair | elapsedTime * pair first >= count ]
> +                       ifNone: [ #(1e9 'picoseconds') ])
> +               in: [ :pair |
> +                       ' {1} {2} per run.' format: {
> +                               (roundTo3Digits value: elapsedTime * pair first / count).
> +                               pair second } ])!
>
> Item was added:
> + ----- Method: BlockClosure>>durationToRun (in category '*chronology-core') -----
> + durationToRun
> +       "Answer the duration taken before this block returns."
> +
> +       ^ Time durationToRun: self
> + !
>
> Item was added:
> + ----- Method: BlockClosure>>timeToRun (in category '*chronology-core') -----
> + timeToRun
> +       "Answer the number of milliseconds taken to execute this block."
> +
> +       ^ Time millisecondsToRun: self
> + !
>
> Item was added:
> + ----- Method: BlockClosure>>timeToRunWithoutGC (in category '*chronology-core') -----
> + timeToRunWithoutGC
> +       "Answer the number of milliseconds taken to execute this block without GC time."
> +
> +       ^(Smalltalk vmParameterAt: 8) +
> +               (Smalltalk vmParameterAt: 10) +
> +               self timeToRun -
> +               (Smalltalk vmParameterAt: 8) -
> +               (Smalltalk vmParameterAt: 10)
> + !
>
> Item was added:
> + ----- Method: BlockClosure>>valueWithin:onTimeout: (in category '*chronology-core') -----
> + valueWithin: aDuration onTimeout: timeoutBlock
> +       "Evaluate the receiver.
> +       If the evaluation does not complete in less than aDuration evaluate the timeoutBlock instead"
> +
> +       | theProcess delay watchdog tag |
> +
> +       aDuration <= Duration zero ifTrue: [^ timeoutBlock value ].
> +
> +       "the block will be executed in the current process"
> +       theProcess := Processor activeProcess.
> +       delay := aDuration asDelay.
> +       tag := self.
> +
> +       "make a watchdog process"
> +       watchdog := [
> +               delay wait.     "wait for timeout or completion"
> +               theProcess ifNotNil:[ theProcess signalException: (TimedOut new tag: tag)]
> +       ] newProcess.
> +
> +       "Watchdog needs to run at high priority to do its job (but not at timing priority)"
> +       watchdog priority: Processor timingPriority-1.
> +
> +       "catch the timeout signal"
> +       ^ [     watchdog resume.                                "start up the watchdog"
> +               self ensure:[                                           "evaluate the receiver"
> +                       theProcess := nil.                              "it has completed, so ..."
> +                       delay delaySemaphore signal.    "arrange for the watchdog to exit"
> +               ]] on: TimedOut do: [ :e |
> +                       e tag == tag
> +                               ifTrue:[ timeoutBlock value ]
> +                               ifFalse:[ e pass]].!
>
> Item was changed:
>   ----- Method: DateAndTime>>utcOffset: (in category 'squeak protocol') -----
> + utcOffset: anOffset
> +       "Answer a DateAndTime equivalent to the receiver but offset from UTC by anOffset"
> +       ^ self class
> +               utcMicroseconds: utcMicroseconds
> +               offset: anOffset asDuration asSeconds!
> - utcOffset: anOffset
> -
> -       "Answer a <DateAndTime> equivalent to the receiver but offset from UTC by anOffset"
> -
> -       self flag: #FIXME. "check the definition of this and of #offset:"
> -       ^self utcMicroseconds: utcMicroseconds offset: anOffset asDuration asSeconds
> - !
>
> Item was added:
> + ----- Method: Duration class>>microSeconds: (in category 'squeak protocol') -----
> + microSeconds: anInteger
> +       ^ self
> +               seconds: (anInteger quo: 1e6)
> +               nanoSeconds: (anInteger rem: 1000) * 1000!
>
> Item was added:
> + ----- Method: Integer>>asYear (in category '*chronology-core') -----
> + asYear
> +
> +       ^ Year year: self
> + !
>
> Item was added:
> + ----- Method: Number>>asDuration (in category '*chronology-core') -----
> + asDuration
> +
> +       ^ Duration nanoSeconds: self asInteger
> + !
>
> Item was added:
> + ----- Method: Number>>day (in category '*chronology-core') -----
> + day
> +
> +       ^ self sign days!
>
> Item was added:
> + ----- Method: Number>>days (in category '*chronology-core') -----
> + days
> +
> +       ^ Duration days: self!
>
> Item was added:
> + ----- Method: Number>>hour (in category '*chronology-core') -----
> + hour
> +
> +       ^ self sign hours
> + !
>
> Item was added:
> + ----- Method: Number>>hours (in category '*chronology-core') -----
> + hours
> +
> +       ^ Duration hours: self!
>
> Item was added:
> + ----- Method: Number>>microSecond (in category '*chronology-core') -----
> + microSecond
> +       ^ self sign microSeconds!
>
> Item was added:
> + ----- Method: Number>>microSeconds (in category '*chronology-core') -----
> + microSeconds
> +       ^ Duration microSeconds: self!
>
> Item was added:
> + ----- Method: Number>>milliSecond (in category '*chronology-core') -----
> + milliSecond
> +
> +       ^ self sign milliSeconds
> + !
>
> Item was added:
> + ----- Method: Number>>milliSeconds (in category '*chronology-core') -----
> + milliSeconds
> +
> +       ^ Duration milliSeconds: self
> + !
>
> Item was added:
> + ----- Method: Number>>minute (in category '*chronology-core') -----
> + minute
> +
> +       ^ self sign minutes
> + !
>
> Item was added:
> + ----- Method: Number>>minutes (in category '*chronology-core') -----
> + minutes
> +
> +       ^ Duration minutes: self!
>
> Item was added:
> + ----- Method: Number>>nanoSecond (in category '*chronology-core') -----
> + nanoSecond
> +
> +       ^ self sign nanoSeconds
> + !
>
> Item was added:
> + ----- Method: Number>>nanoSeconds (in category '*chronology-core') -----
> + nanoSeconds
> +
> +       ^ Duration nanoSeconds: self.!
>
> Item was added:
> + ----- Method: Number>>second (in category '*chronology-core') -----
> + second
> +
> +       ^ self sign seconds
> + !
>
> Item was added:
> + ----- Method: Number>>seconds (in category '*chronology-core') -----
> + seconds
> +
> +       ^ Duration seconds: self!
>
> Item was added:
> + ----- Method: Number>>week (in category '*chronology-core') -----
> + week
> +
> +       ^ self sign weeks
> + !
>
> Item was added:
> + ----- Method: Number>>weeks (in category '*chronology-core') -----
> + weeks
> +
> +       ^ Duration weeks: self!
>
> Item was added:
> + ----- Method: String>>asDate (in category '*chronology-core') -----
> + asDate
> +       "Many allowed forms, see Date>>#readFrom:"
> +
> +       ^ Date fromString: self!
>
> Item was added:
> + ----- Method: String>>asDateAndTime (in category '*chronology-core') -----
> + asDateAndTime
> +
> +       "Convert from UTC format"       ^ DateAndTime fromString: self!
>
> Item was added:
> + ----- Method: String>>asDuration (in category '*chronology-core') -----
> + asDuration
> +       "convert from [nnnd]hh:mm:ss[.nanos] format. [] implies optional elements"
> +
> +       ^ Duration fromString: self
> + !
>
>


More information about the Squeak-dev mailing list