TimeDuration.st
branchjv
changeset 25423 bcfde4da086a
parent 20837 3e0095bef7e6
equal deleted inserted replaced
25422:3b02b0f1f647 25423:bcfde4da086a
    12 "{ Package: 'stx:libbasic' }"
    12 "{ Package: 'stx:libbasic' }"
    13 
    13 
    14 "{ NameSpace: Smalltalk }"
    14 "{ NameSpace: Smalltalk }"
    15 
    15 
    16 Time subclass:#TimeDuration
    16 Time subclass:#TimeDuration
    17 	instanceVariableNames:''
    17 	instanceVariableNames:'additionalPicoseconds'
    18 	classVariableNames:'DefaultFormatForPrinting TimeDurationZero'
    18 	classVariableNames:'DefaultFormatForPrinting TimeDurationZero'
    19 	poolDictionaries:''
    19 	poolDictionaries:''
    20 	category:'Magnitude-Time'
    20 	category:'Magnitude-Time'
    21 !
    21 !
    22 
    22 
    36 "
    36 "
    37 !
    37 !
    38 
    38 
    39 documentation
    39 documentation
    40 "
    40 "
    41     Represents a timestap difference.
    41     Represents a time/timestamp difference.
    42 
    42 
    43     DefaultFormatForPrinting    if non-nil, allows for the variable printFormat to be overwritten
    43     The resolution is 1 picosecond.
       
    44     However, such small timedurations are usually only created by physical computations (see goodies/physic),
       
    45     or when reading timestamps from external measurement equipment.
       
    46 
       
    47     The typical OS-time resolution is in the milli- or microsecond range.
       
    48     External logging hardware may generate timestamps in the micro- or nanosecond range,
       
    49     and picosecond resolution should be good enough for almost any application (at least for the near future).
       
    50 
       
    51     Most timedurations only require/have millisecond resolution,
       
    52     so the picoseconds are held in a separate instvar (which is often nil or zero) 
       
    53     and does on most cases not require aditional slow largeInteger operations.
       
    54 
       
    55     [class variables:]
       
    56         DefaultFormatForPrinting    if non-nil, allows for the variable printFormat to be overwritten
       
    57 
       
    58     [author:]
       
    59         Claus Gittinger
       
    60 
       
    61     [see also:]
       
    62         Date Time Timestamp AbstractTime OperatingSystem
    44 "
    63 "
    45 ! !
    64 ! !
    46 
    65 
    47 !TimeDuration class methodsFor:'instance creation'!
    66 !TimeDuration class methodsFor:'instance creation'!
    48 
    67 
    78     "
    97     "
    79      TimeDuration fromHours:8  
    98      TimeDuration fromHours:8  
    80     "
    99     "
    81 !
   100 !
    82 
   101 
       
   102 fromMicroseconds:n
       
   103     "return a new TimeDuration representing a duration of n microseconds."
       
   104 
       
   105     ^ self new setMicroseconds:n
       
   106 
       
   107     "
       
   108      TimeDuration fromMicroseconds:500  
       
   109      500 microseconds  
       
   110     "
       
   111 
       
   112     "Created: / 18-07-2007 / 13:56:25 / cg"
       
   113 !
       
   114 
    83 fromMilliseconds:n
   115 fromMilliseconds:n
    84     "return a new TimeDuration representing a duration of n milliseconds."
   116     "return a new TimeDuration representing a duration of n milliseconds."
    85     "redefined to disable wrapping at 24hours."
   117     "redefined to disable wrapping at 24hours."
    86 
   118 
    87     ^ self new setMilliseconds:n
   119     ^ self new setMilliseconds:n
   102     "
   134     "
   103      TimeDuration fromMinutes:120  
   135      TimeDuration fromMinutes:120  
   104     "
   136     "
   105 !
   137 !
   106 
   138 
       
   139 fromNanoseconds:n
       
   140     "return a new TimeDuration representing a duration of n nanoseconds."
       
   141 
       
   142     ^ self new setNanoseconds:n
       
   143 
       
   144     "
       
   145      TimeDuration fromNanoseconds:500  
       
   146      500 nanoseconds  
       
   147     "
       
   148 !
       
   149 
       
   150 fromPicoseconds:n
       
   151     "return a new TimeDuration representing a duration of n picoseconds."
       
   152 
       
   153     ^ self new setPicoseconds:n
       
   154 
       
   155     "
       
   156      TimeDuration fromPicoseconds:500  
       
   157      500 picoseconds  
       
   158     "
       
   159 !
       
   160 
   107 fromSeconds:secondsInterval
   161 fromSeconds:secondsInterval
   108     "return a new TimeDuration representing a duration of n seconds."
   162     "return a new TimeDuration representing a duration of n seconds."
   109     "redefined to disable wrapping at 24hours."
   163     "redefined to disable wrapping at 24hours."
   110 
   164 
   111     ^ self new setSeconds:secondsInterval
   165     ^ self new setSeconds:secondsInterval
   126      TimeDuration hours:2 
   180      TimeDuration hours:2 
   127      TimeDuration hours:100  
   181      TimeDuration hours:100  
   128     "
   182     "
   129 
   183 
   130     "Created: / 14-07-2007 / 18:15:51 / cg"
   184     "Created: / 14-07-2007 / 18:15:51 / cg"
   131 !
       
   132 
       
   133 hours:h minutes:m
       
   134     "return a new TimeDuration representing a duration of h hours and m minutes.
       
   135      See also Time now / Date today / Timestamp now."
       
   136 
       
   137     ^ self basicNew setHours:h minutes:m seconds:0 milliseconds:0
       
   138 
       
   139     "
       
   140      TimeDuration hours:2 minutes:33 
       
   141      TimeDuration hours:100 minutes:33  
       
   142     "
       
   143 !
   185 !
   144 
   186 
   145 hours:h minutes:m seconds:s millis:millis
   187 hours:h minutes:m seconds:s millis:millis
   146     <resource: #obsolete>
   188     <resource: #obsolete>
   147     "return a new TimeDuration representing a duration of h hours, m minutes, s seconds and millis milliseconds.
   189     "return a new TimeDuration representing a duration of h hours, m minutes, s seconds and millis milliseconds.
   154      TimeDuration hours:2 minutes:33 seconds:0 milliseconds:123  
   196      TimeDuration hours:2 minutes:33 seconds:0 milliseconds:123  
   155      TimeDuration hours:100 minutes:33 seconds:0 milliseconds:123  
   197      TimeDuration hours:100 minutes:33 seconds:0 milliseconds:123  
   156     "
   198     "
   157 !
   199 !
   158 
   200 
   159 hours:h minutes:m seconds:s milliseconds:millis
       
   160     "return a new TimeDuration representing a duration of h hours, m minutes, s seconds and millis milliseconds.
       
   161      See also Time now / Date today / Timestamp now."
       
   162 
       
   163     ^ self basicNew 
       
   164         setHours:h minutes:m seconds:s milliseconds:millis
       
   165 
       
   166     "
       
   167      TimeDuration hours:2 minutes:33 seconds:0 milliseconds:123  
       
   168      TimeDuration hours:100 minutes:33 seconds:0 milliseconds:123  
       
   169     "
       
   170 !
       
   171 
       
   172 microseconds:microseconds
   201 microseconds:microseconds
   173     "return a new TimeDuration representing a duration of microseconds microseconds.
   202     "return a new TimeDuration representing a duration of microseconds microseconds.
   174      Currently we do not support this (we round to millis), but maybe later..."
   203      Now we support microseconds (even picoseconds) but we still round to milliseconds for backward
       
   204      compatibility with the historic interface."
   175 
   205 
   176     microseconds == 0 ifTrue:[^ TimeDurationZero].
   206     microseconds == 0 ifTrue:[^ TimeDurationZero].
   177     ^ self basicNew setMilliseconds:((microseconds / 1000) rounded).
   207     ^ self basicNew setMicroseconds:microseconds rounded.
   178 
   208 
   179     "
   209     "
   180      TimeDuration microseconds:2499 
   210      TimeDuration microseconds:2499 
   181      TimeDuration microseconds:2500 
   211      TimeDuration microseconds:2500 
   182      TimeDuration microseconds:12345678900 
   212      TimeDuration microseconds:12345678900 
   183     "
   213     "
       
   214 
       
   215     "Modified: / 02-03-2020 / 14:16:07 / Stefan Vogel"
   184 !
   216 !
   185 
   217 
   186 milliseconds:m
   218 milliseconds:m
   187     "return a new TimeDuration representing a duration of m millis.
   219     "return a new TimeDuration representing a duration of m millis.
   188      See also Time now / Date today / Timestamp now."
   220      See also Time now / Date today / Timestamp now."
   210 !
   242 !
   211 
   243 
   212 readFrom:aStringOrStream defaultUnit:defaultUnitOrNilArg onError:exceptionBlock
   244 readFrom:aStringOrStream defaultUnit:defaultUnitOrNilArg onError:exceptionBlock
   213     "return a new TimeDuration, reading a printed representation from aStream.
   245     "return a new TimeDuration, reading a printed representation from aStream.
   214      The format is either:
   246      The format is either:
   215         [n 'yr'] [n 'mon'] [n 'w'] [n 'd'] [n 'h'] [n 'm'] [n 's'] [n 'ms']
   247         [n 'yr'] [n 'mon'] [n 'w'] [n 'd'] [n 'h'] [n 'm'] [n 's'] 
       
   248                  ([n 'ms'] | [n 'us'] | [n 'ns'] | [n 'ps'])
   216         where 
   249         where 
   217             yr -> year
   250             yr -> year
   218             mon -> month
   251             mon -> month
   219             w -> week
   252             w -> week
   220             d -> day
   253             d -> day
   221             h -> hour
   254             h -> hour
   222             m -> minutes
   255             m -> minutes
   223             s -> seconds
   256             s -> seconds
   224             ms -> milliseconds
   257             ms -> milliseconds (only one of ms,us,ns or ps can follow)
       
   258             us -> microseconds
       
   259             ns -> nanoseconds
       
   260             ps -> picoseconds
   225      or:
   261      or:
   226         h:m:s.ms
   262         h:m:s.<ms2>
       
   263         h:m:s.<fract>
   227 
   264 
   228      The yr and mon specifiers stand for 365d and 30d respectively.
   265      The yr and mon specifiers stand for 365d and 30d respectively.
   229      If defaultUnitOrNil is non-nil, a plain number is treated as that;
   266      If defaultUnitOrNil is non-nil, a plain number is treated as that;
   230      otherwise, a plain number raises an error.
   267      otherwise, a plain number raises an error.
   231      Individual components may be negative, as in '1h -10m', which gives 50m
   268      Individual components may be negative, as in '1h -10m', which gives 50m
   232      or the whole duration may be negative, as in '-(1h 10m)'
   269      or the whole duration may be negative, as in '-(1h 10m)'
   233     "
   270     "
   234 
   271 
   235     ^ [
   272     ^ [
   236         |seconds millis str val fraction uIdx unit unitChar1 negative defaultUnitOrNil|
   273         |seconds millis picos restMillis 
       
   274          t1 str val fraction mantissa uIdx unit unitChar1 negative defaultUnitOrNil|
   237 
   275 
   238         defaultUnitOrNil := defaultUnitOrNilArg.
   276         defaultUnitOrNil := defaultUnitOrNilArg.
   239         str := aStringOrStream readStream.
   277         str := aStringOrStream readStream.
   240         seconds := 0.
   278         seconds := 0.
   241         millis := 0.
   279         millis := 0.
       
   280         picos := 0.
   242 
   281 
   243         negative := false.
   282         negative := false.
   244         str peek == $- ifTrue:[
   283         str peek == $- ifTrue:[
   245             str next.
   284             str next.
   246             str peek == $( ifTrue:[
   285             str peek == $( ifTrue:[
   247                 |t|
   286                 |t|
   248                 str next.
   287                 str next.
   249                 t := self readFrom:str defaultUnit:defaultUnitOrNil onError:[^ exceptionBlock value].
   288                 t := self readFrom:str defaultUnit:defaultUnitOrNil onError:[^ exceptionBlock value].
   250                 str skipSeparators.
   289                 str skipSeparators == $) ifTrue:[
   251                 str peek == $) ifTrue:[
       
   252                     str next.
   290                     str next.
   253                     ^ t negated.
   291                     ^ t negated.
   254                 ].
   292                 ].
   255                 ^ exceptionBlock value.
   293                 ^ exceptionBlock value.
   256             ].                
   294             ].                
   274                     "/ hour:minutes:seconds format
   312                     "/ hour:minutes:seconds format
   275                     str next.
   313                     str next.
   276                     val := Integer readFrom:str onError:nil.
   314                     val := Integer readFrom:str onError:nil.
   277                     val isNil ifTrue:[^ exceptionBlock value].
   315                     val isNil ifTrue:[^ exceptionBlock value].
   278                     seconds := seconds + val.
   316                     seconds := seconds + val.
   279                     str peek == $. ifTrue:[
   317                     (str peek == $. or:[str peek == $,]) ifTrue:[
   280                         "/ hour:minutes:seconds.millis format
   318                         "/ hour:minutes:seconds.millis format
   281                         str next.
   319                         str next.
   282                         val := Integer readFrom:str onError:nil.
   320                         "/ the old code here was wrong in assuming that exactly 3 digits
   283                         val isNil ifTrue:[^ exceptionBlock value].
   321                         "/ are coming; thus hh:mm:ss.1 was interpreted as 1ms (instead of 100)
   284                         millis := val.
   322                         "/ thus: count the zeros...
       
   323                         str peek isDigit ifTrue:[
       
   324                             "/ fraction := Number readMantissaFrom:str radix:10.
       
   325                             "/ fraction isNil ifTrue:[^ exceptionBlock value].
       
   326                             "/ ignore the float value; take the fraction
       
   327 
       
   328                             mantissa := Number readMantissaAndScaleFrom:str radix:10.
       
   329                             fraction := (mantissa at:2) / (10 raisedTo:(mantissa at:3)).
       
   330                             (mantissa at:3) > 3 ifTrue:[
       
   331                                 picos := fraction * (1000 * 1000 * 1000 * 1000).
       
   332                                 millis := picos // (1000 * 1000 * 1000).
       
   333                                 picos := picos \\ (1000 * 1000 * 1000).
       
   334                             ] ifFalse:[
       
   335                                 millis := fraction * 1000.
       
   336                             ].
       
   337                         ] ifFalse:[
       
   338                             millis := 0
       
   339                         ].
   285                     ]
   340                     ]
   286                 ].
   341                 ].
   287                 ^ self fromMilliseconds:(seconds*1000+millis) rounded asInteger.
   342                 t1 := self fromMilliseconds:(seconds*1000+millis).
       
   343                 picos notNil ifTrue:[
       
   344                     t1 additionalPicoseconds:picos
       
   345                 ].
       
   346                 ^ t1
   288             ].
   347             ].
   289             str peek == $. ifTrue:[
   348             ((str peek == $.) or:[(str peek == $,)]) ifTrue:[
   290                 str next.
   349                 str next.
   291                 fraction := Number readMantissaFrom:str radix:10.
   350                 "/ fraction := Number readMantissaFrom:str radix:10.
       
   351                 "/ ignore the float value; take the fraction
       
   352                 mantissa := Number readMantissaAndScaleFrom:str radix:10.
       
   353                 fraction := (mantissa at:2) / (10 raisedTo:(mantissa at:3)).
   292                 val := val + fraction.
   354                 val := val + fraction.
   293             ].
   355             ].
   294             str skipSeparators.
   356             str skipSeparators.
   295             str atEnd ifTrue:[
   357             str atEnd ifTrue:[
   296                 defaultUnitOrNil isNil ifTrue:[
   358                 defaultUnitOrNil isNil ifTrue:[
   301                 "/ can be only used for one number
   363                 "/ can be only used for one number
   302                 defaultUnitOrNil := nil.
   364                 defaultUnitOrNil := nil.
   303             ] ifFalse:[
   365             ] ifFalse:[
   304                 unitChar1 := str next.
   366                 unitChar1 := str next.
   305             ].
   367             ].
   306             uIdx := #($y $w $d $h $m $s) indexOf:unitChar1.
       
   307             uIdx == 0 ifTrue:[^ exceptionBlock value].
       
   308 
   368 
   309             str atEnd ifFalse:[ 
   369             str atEnd ifFalse:[ 
   310                 nextCh := str peek
   370                 nextCh := str peek
   311             ].
   371             ].
   312 
   372 
   313             (unitChar1 == $m and:[nextCh == $s]) ifTrue:[
   373             "/ milli, micro, nano and pico
   314                 millis := millis + val.
   374             unitChar1 == $µ ifTrue:[ unitChar1 := $u].
   315             ] ifFalse:[
   375             uIdx := 'munp' indexOf:unitChar1.
   316                 (unitChar1 == $m and:[nextCh == $o]) ifTrue:[
   376             ((uIdx ~~ 0) and:[nextCh == $s]) ifTrue:[
   317                     unit := 2592000 "24*60*60*30"     "mon"
   377                 unitChar1 == $m ifTrue:[
       
   378                     millis := millis + val.
   318                 ] ifFalse:[
   379                 ] ifFalse:[
   319                     unit := #(
   380                     unit := #(
   320                               31536000 "24*60*60*365" "yr"
   381                           1000000       "us" 
   321                               604800 "24*60*60*7"     "w"
   382                           1000          "ns" 
   322                               86400  "24*60*60"       "d"
   383                           1             "ps" 
   323                               3600                    "h"
   384                           ) at:uIdx-1.
   324                               60                      "m"
   385                     picos := (unit * val).
   325                               1 ) at:uIdx.
   386                     millis := picos // (1000 * 1000 * 1000).
       
   387                     picos := picos \\ (1000 * 1000 * 1000).
   326                 ].
   388                 ].
   327                 seconds := seconds + (unit * val).
   389             ] ifFalse:[
       
   390                 uIdx := 'ywdhms' indexOf:unitChar1.
       
   391                 uIdx == 0 ifTrue:[^ exceptionBlock value].
       
   392 
       
   393                 (unitChar1 == $m and:[nextCh == $s]) ifTrue:[
       
   394                     millis := millis + val.
       
   395                 ] ifFalse:[
       
   396                     (unitChar1 == $m and:[nextCh == $o]) ifTrue:[
       
   397                         unit := 2592000 "24*60*60*30"     "mon"
       
   398                     ] ifFalse:[
       
   399                         unit := #(
       
   400                                   31536000 "24*60*60*365" "yr"
       
   401                                   604800 "24*60*60*7"     "w"
       
   402                                   86400  "24*60*60"       "d"
       
   403                                   3600                    "h"
       
   404                                   60                      "m"
       
   405                                   1 ) at:uIdx.
       
   406                     ].
       
   407                     seconds := seconds + (unit * val).
       
   408                 ].
   328             ].
   409             ].
   329             [str atEnd not and:[str peek isSeparator not and:[str peek ~~ $)]]] whileTrue:[ str next].
   410             [str atEnd not and:[str peek isSeparator not and:[str peek ~~ $)]]] whileTrue:[ str next].
   330             str skipSeparators.
   411             str skipSeparators.
   331             "/ done when at the end or a $) is to be read
   412             "/ done when at the end or a $) is to be read
   332             str atEnd or:[aStringOrStream isString not and:[str peek == $)]]
   413             str atEnd or:[aStringOrStream isString not and:[str peek == $)]]
   333         ] whileFalse.
   414         ] whileFalse.
   334         self fromMilliseconds:(seconds*1000+millis) rounded asInteger.
   415         millis := (seconds*1000) + millis.
       
   416         restMillis := millis - millis truncated.
       
   417         millis := millis truncated.
       
   418         picos := picos + (restMillis * 1000 * 1000 * 1000) truncated. 
       
   419         millis := millis + (picos // (1000*1000*1000)).
       
   420         picos := picos \\ (1000*1000*1000).
       
   421         t1 := self fromMilliseconds:millis asInteger.
       
   422         t1 additionalPicoseconds:picos.
       
   423         t1
   335     ] on:Error do:[:ex |
   424     ] on:Error do:[:ex |
   336         |t|
   425         |t|
   337 
   426 
   338         "/ retry, using inherited readFrom (Object-storeString)
   427         "/ retry, using inherited readFrom (Object-storeString)
   339         t := Object readFrom:aStringOrStream onError:[^ exceptionBlock value].
   428         t := Object readFrom:aStringOrStream onError:[^ exceptionBlock value].
   340         (t isKindOf:TimeDuration) ifFalse:[
   429         (t isTimeDuration) ifFalse:[
   341             ^ exceptionBlock value
   430             ^ exceptionBlock value
   342         ].
   431         ].
   343         t
   432         t
   344     ]
   433     ]
   345 
   434 
   366      TimeDuration readFrom:'-1h'
   455      TimeDuration readFrom:'-1h'
   367      TimeDuration readFrom:'-1h 10m'
   456      TimeDuration readFrom:'-1h 10m'
   368      TimeDuration readFrom:'1h -10m'
   457      TimeDuration readFrom:'1h -10m'
   369      TimeDuration readFrom:'-(1h 10m)' 
   458      TimeDuration readFrom:'-(1h 10m)' 
   370 
   459 
       
   460      TimeDuration readFrom:'1ms' -> 1ms 
       
   461      TimeDuration readFrom:'5us' 
       
   462      TimeDuration readFrom:'5µs' 
       
   463      TimeDuration readFrom:'5ns' 
       
   464      TimeDuration readFrom:'5ps' 
       
   465      TimeDuration readFrom:'5005 ps' 
       
   466      TimeDuration readFrom:'1.01 s' -> 1.010s 
       
   467      TimeDuration readFrom:'1.001 s' -> 1.001s 
       
   468      TimeDuration readFrom:'1.0001 s' -> 1.0001s 
       
   469      TimeDuration readFrom:'1s 5ns' -> 1.000000005s
       
   470      (TimeDuration readFrom:'1s 5ns') = (TimeDuration fromNanoseconds:(5+1000000000))
       
   471 
   371      TimeDuration readFrom:(TimeDuration new storeString)
   472      TimeDuration readFrom:(TimeDuration new storeString)
   372     "
   473     "
   373 
   474 
   374     "Modified: / 08-10-2007 / 16:41:48 / cg"
   475     "Modified: / 08-10-2007 / 16:41:48 / cg"
       
   476     "Modified: / 28-09-2019 / 15:23:14 / Stefan Vogel"
   375 !
   477 !
   376 
   478 
   377 readFrom:aStringOrStream onError:exceptionBlock
   479 readFrom:aStringOrStream onError:exceptionBlock
   378     "return a new TimeDuration, reading a printed representation from aStream.
   480     "return a new TimeDuration, reading a printed representation from aStream.
   379      The format is [n 'yr'] [n 'mon'] [n 'w'] [n 'd'] [n 'h'] [n 'm'] [n 's'] [n 'ms']
   481      The format is [n 'yr'] [n 'mon'] [n 'w'] [n 'd'] [n 'h'] [n 'm'] [n 's'] [n 'ms']
   434     "
   536     "
   435      TimeDuration weeks:1  
   537      TimeDuration weeks:1  
   436     "
   538     "
   437 
   539 
   438     "Created: / 05-09-2011 / 11:18:27 / cg"
   540     "Created: / 05-09-2011 / 11:18:27 / cg"
       
   541 !
       
   542 
       
   543 years:y 
       
   544     "return a new TimeDuration representing a duration of y years."
       
   545 
       
   546     ^ self days:(y * 365)
       
   547 
       
   548     "
       
   549      TimeDuration years:1  
       
   550     "
       
   551 
       
   552     "Created: / 08-05-2019 / 12:42:16 / Claus Gittinger"
   439 ! !
   553 ! !
   440 
   554 
   441 !TimeDuration class methodsFor:'class initialization'!
   555 !TimeDuration class methodsFor:'class initialization'!
   442 
   556 
   443 initialize
   557 initialize
   490 
   604 
   491     "
   605     "
   492      TimeDuration toRun:[ 20000 factorial ]     
   606      TimeDuration toRun:[ 20000 factorial ]     
   493      TimeDuration toRun:[ 2000 factorial ]     
   607      TimeDuration toRun:[ 2000 factorial ]     
   494      TimeDuration toRun:[ 900 factorial ]     
   608      TimeDuration toRun:[ 900 factorial ]     
   495     "
   609      TimeDuration toRun:[ 10 factorial ]     
       
   610     "
       
   611 
       
   612     "Modified (comment): / 02-03-2020 / 14:15:09 / Stefan Vogel"
   496 ! !
   613 ! !
   497 
   614 
       
   615 !TimeDuration methodsFor:'Compatibility-Squeak'!
       
   616 
       
   617 wait
       
   618     "wait the receiver's timeDuration"
       
   619     
       
   620     Delay waitFor:self
       
   621 
       
   622     "
       
   623      5 seconds wait
       
   624     "
       
   625 
       
   626     "Modified (comment): / 26-06-2019 / 11:35:02 / Claus Gittinger"
       
   627 ! !
       
   628 
   498 !TimeDuration methodsFor:'accessing'!
   629 !TimeDuration methodsFor:'accessing'!
   499 
   630 
   500 days
   631 days
   501     "get the number of days"
   632     "get the (truncated) total number of days.
       
   633      Use this only for printing.
       
   634      Sigh: this is inconsistent: hours, minutes, seconds etc. 
       
   635      return the fraction, not the total"
   502 
   636 
   503     ^ self 
   637     ^ self 
   504         possiblyNegatedValueFromTimeEncodingInto:[:t |
   638         possiblyNegatedValueFromTimeEncodingInto:[:t |
   505             t // 1000 // 3600 // 24
   639             t // 1000 // 3600 // 24
   506         ].    
   640         ].    
   507 
   641 
   508     "
   642     "
   509      (Duration days: 9 hours: 1 minutes: 2 seconds: 3) days
   643      (Duration fromString:'1mon 1d 4h 3m 5s 10ms') days
   510      (Duration days: -9 hours: -1 minutes: -2 seconds: -3) days
   644 
       
   645      (Duration days:9 hours:1 minutes:2 seconds:3) days   
       
   646      (Duration days:-9 hours:-1 minutes:-2 seconds:-3) days 
   511     "
   647     "
   512 !
   648 !
   513 
   649 
   514 hours
   650 hours
   515     "get the number of hours.
   651     "get the (truncated) number of hours.
   516      (notice: that is NOT the total number of hours,
   652      notice: that is NOT the total number of hours,
   517      but the fractional part only. Use this only for printing"
   653      but the fractional part only. 
       
   654      Use this only for printing"
   518 
   655 
   519     ^ self 
   656     ^ self 
   520         possiblyNegatedValueFromTimeEncodingInto:[:t |
   657         possiblyNegatedValueFromTimeEncodingInto:[:t |
   521             (t // 1000 // 3600 \\ 24)
   658             (t // 1000 // 3600 \\ 24)
   522         ]
   659         ]
   523     "
   660     "
       
   661      (Duration fromString:'1d 4h 3m 5s 10ms') hours
       
   662      (Duration fromString:'1d 4h 3m 1s 10ms') getHours
       
   663 
   524      (Duration days: 9 hours: 1 minutes: 2 seconds: 3) hours
   664      (Duration days: 9 hours: 1 minutes: 2 seconds: 3) hours
   525      (Duration days: -9 hours: -1 minutes: -2 seconds: -3) hours
   665      (Duration days: -9 hours: -1 minutes: -2 seconds: -3) hours
   526     "
   666     "
       
   667 
       
   668     "Modified (comment): / 21-09-2017 / 18:53:32 / cg"
   527 !
   669 !
   528 
   670 
   529 milliseconds
   671 milliseconds
   530     "get the milliseconds part 
   672     "get the milliseconds part 
   531      (notice: that is NOT the total number of millis,
   673      notice: that is NOT the total number of millis,
   532      but the fractional part only. Use this only for printing.
   674      but the fractional part (within the second) only. 
   533      asMilliseconds or getMilliseconds is probably what you want"
   675      Use this only for printing.
       
   676      asMilliseconds is probably what you want"
   534 
   677 
   535     ^ self 
   678     ^ self 
   536         possiblyNegatedValueFromTimeEncodingInto:[:t |
   679         possiblyNegatedValueFromTimeEncodingInto:[:t |
   537             t \\ 1000
   680             t \\ 1000
   538         ].    
   681         ].    
   539     "
   682     "
   540      (Duration milliseconds:10) milliseconds
   683      (Duration milliseconds:10) milliseconds
   541      (Duration milliseconds:-10) milliseconds
   684      (Duration milliseconds:-10) milliseconds
       
   685 
       
   686      (Duration fromString:'1s 10ms') milliseconds
       
   687      (Duration fromString:'1s 10ms') getMilliseconds
   542     "
   688     "
   543 
   689 
   544     "Modified: / 05-05-2010 / 14:22:04 / cg"
   690     "Modified: / 05-05-2010 / 14:22:04 / cg"
       
   691     "Modified (comment): / 21-09-2017 / 18:53:26 / cg"
   545 !
   692 !
   546 
   693 
   547 minutes
   694 minutes
   548     "get the number of minutes.
   695     "get the number of minutes.
   549      (notice: that is NOT the total number of minutes,
   696      notice: that is NOT the total number of minutes,
   550      but the fractional part only. Use this only for printing"
   697      but the fractional part only. 
       
   698      Use this only for printing"
   551 
   699 
   552     ^ self 
   700     ^ self 
   553         possiblyNegatedValueFromTimeEncodingInto:[:t |
   701         possiblyNegatedValueFromTimeEncodingInto:[:t |
   554             t // 1000 // 60 \\ 60
   702             t // 1000 // 60 \\ 60
   555         ]
   703         ]
   556         
   704         
   557     "
   705     "
       
   706      (Duration fromString:'1h 3m 5s 10ms') minutes
       
   707      (Duration fromString:'1h 3m 1s 10ms') getMinutes
       
   708 
   558      (Duration days: 9 hours: 1 minutes: 2 seconds: 3) minutes
   709      (Duration days: 9 hours: 1 minutes: 2 seconds: 3) minutes
   559      (Duration days: -9 hours: -1 minutes: -2 seconds: -3) minutes
   710      (Duration days: -9 hours: -1 minutes: -2 seconds: -3) minutes
   560     "
   711     "
       
   712 
       
   713     "Modified (comment): / 21-09-2017 / 18:53:22 / cg"
       
   714 !
       
   715 
       
   716 picoseconds
       
   717     "get the optional additional picoseconds (0..999999999)
       
   718      notice: that is NOT the total number of picoseconds,
       
   719      but the fractional part (within the second) only. 
       
   720      Use this only for printing."
       
   721 
       
   722     ^ (self milliseconds * 1000 * 1000 * 1000) + (additionalPicoseconds ? 0)
   561 !
   723 !
   562 
   724 
   563 seconds
   725 seconds
   564     "get the number of seconds.
   726     "get the number of seconds.
   565      (notice: that is NOT the total number of seconds,
   727      notice: that is NOT the total number of seconds,
   566      but the fractional part only. Use this only for printing.
   728      but the fractional part only. 
   567      asSeconds or getSeconds is probably what you want"
   729      Use this only for printing.
       
   730      asSeconds is probably what you want"
   568 
   731 
   569     ^ self 
   732     ^ self 
   570         possiblyNegatedValueFromTimeEncodingInto:[:t |
   733         possiblyNegatedValueFromTimeEncodingInto:[:t |
   571             t // 1000 \\ 60
   734             t // 1000 \\ 60
   572         ]
   735         ]
   573         
   736         
   574     "
   737     "
   575      (Duration days: 9 hours: 1 minutes: 2 seconds: 3) seconds
   738      (TimeDuration fromString:'1m 5s 10ms') seconds
   576      (Duration days: -9 hours: -1 minutes: -2 seconds: -3) seconds
   739      (TimeDuration fromString:'1m 1s 10ms') getSeconds
   577     "
   740 
       
   741      (TimeDuration days: 9 hours: 1 minutes: 2 seconds: 3) seconds
       
   742      (TimeDuration days: -9 hours: -1 minutes: -2 seconds: -3) seconds
       
   743     "
       
   744 
       
   745     "Modified (comment): / 21-09-2017 / 18:53:13 / cg"
   578 ! !
   746 ! !
   579 
   747 
   580 !TimeDuration methodsFor:'arithmetic'!
   748 !TimeDuration methodsFor:'arithmetic'!
   581 
   749 
   582 * aNumber
   750 * aNumber
   583     "return a new scaled timeDuration"
   751     "return a new scaled timeDuration"
   584 
   752 
   585     aNumber isNumber ifTrue:[
   753     aNumber isNumber ifTrue:[
   586         ^ self species basicNew 
   754         ^ self species basicNew 
   587             setMilliseconds:(self getMilliseconds * aNumber) asInteger
   755             setMilliseconds:(timeEncoding * aNumber)
   588     ].
   756             additionalPicoseconds:(additionalPicoseconds ? 0) * aNumber.
       
   757     ].
       
   758 
       
   759     "/ notice: although noone seems to implement it (currently),
       
   760     "/ there are additional packages which add support (i.e. goodies/physic),
       
   761     "/ so do not remove the call below.
   589     ^ aNumber productFromTimeDuration:self
   762     ^ aNumber productFromTimeDuration:self
   590     
   763     
   591     "
   764     "
       
   765      5 c* (TimeDuration fromString:'10s')
       
   766 
   592      (TimeDuration fromString:'10s') * 5
   767      (TimeDuration fromString:'10s') * 5
   593      (TimeDuration fromString:'10s') * 10
   768      (TimeDuration fromString:'10s') * 10
   594      (TimeDuration fromString:'10s') * 100
   769      (TimeDuration fromString:'10s') * 100
   595      (TimeDuration fromString:'10s') * 1000
   770      (TimeDuration fromString:'10s') * 1000
   596      (TimeDuration fromString:'-10s') * 1000
   771      (TimeDuration fromString:'-10s') * 1000
   597     "
   772      (TimeDuration fromString:'10s') * (TimeDuration fromString:'10s')
       
   773 
       
   774      (TimeDuration fromString:'10ms') * 5
       
   775      (TimeDuration fromString:'10us') * 5
       
   776     "
       
   777 
       
   778     "Modified: / 27-07-2018 / 10:32:02 / Stefan Vogel"
   598 !
   779 !
   599 
   780 
   600 + aTimeDurationOrNumberOfSeconds
   781 + aTimeDurationOrNumberOfSeconds
   601     "return a new timeDuration"
   782     "return a new timeDuration.
       
   783      The argument may be a timeDuration or
       
   784      a number, which is interpreted as seconds."
       
   785 
       
   786     |newMillis newPicos|
   602 
   787 
   603     aTimeDurationOrNumberOfSeconds isNumber ifTrue:[
   788     aTimeDurationOrNumberOfSeconds isNumber ifTrue:[
   604         ^ self species basicNew 
   789         newMillis := timeEncoding + (aTimeDurationOrNumberOfSeconds * 1000) asInteger.
   605             setMilliseconds:(self getMilliseconds + (aTimeDurationOrNumberOfSeconds * 1000) asInteger)
   790         newPicos := additionalPicoseconds ? 0.
   606     ].
   791         ^ self species basicNew
   607     ^ self species basicNew
   792             setMilliseconds:newMillis additionalPicoseconds:newPicos
   608         setMilliseconds:(self getMilliseconds + aTimeDurationOrNumberOfSeconds getMilliseconds)
   793     ].
       
   794     ^ aTimeDurationOrNumberOfSeconds sumFromTimeDuration:self.
   609 
   795 
   610     "
   796     "
   611      (TimeDuration fromString:'1m') + (TimeDuration fromString:'10s') 
   797      (TimeDuration fromString:'1m') + (TimeDuration fromString:'10s') 
   612      1 minutes + 10 seconds
   798      1 minutes - 10 seconds
   613     "
   799     "
       
   800 
       
   801     "Created: / 25-07-2018 / 20:58:17 / Stefan Vogel"
       
   802     "Modified: / 27-07-2018 / 10:32:21 / Stefan Vogel"
       
   803 !
       
   804 
       
   805 - aTimeDurationOrNumberOfSeconds
       
   806     "return a new timeDuration.
       
   807      The argument may be a timeDuration or
       
   808      a number, which is interpreted as seconds."
       
   809 
       
   810     |newMillis newPicos|
       
   811 
       
   812     aTimeDurationOrNumberOfSeconds isNumber ifTrue:[
       
   813         newMillis := timeEncoding - (aTimeDurationOrNumberOfSeconds * 1000) asInteger.
       
   814         newPicos := additionalPicoseconds ? 0.
       
   815         ^ self species basicNew
       
   816             setMilliseconds:newMillis additionalPicoseconds:newPicos
       
   817     ].
       
   818     ^ aTimeDurationOrNumberOfSeconds differenceFromTimeDuration:self.
       
   819 
       
   820     "
       
   821      (TimeDuration fromString:'1m') - (TimeDuration fromString:'10s') 
       
   822      1 minutes - 10 seconds
       
   823     "
       
   824 
       
   825     "Modified: / 27-07-2018 / 10:32:29 / Stefan Vogel"
   614 !
   826 !
   615 
   827 
   616 / aTimeDurationOrNumberOfSeconds
   828 / aTimeDurationOrNumberOfSeconds
   617     "if the argument is a number, return a new timeDuration.
   829     "if the argument is a number, return a new timeDuration.
   618      Otherwise, return the quotient as a number."
   830      Otherwise, return the quotient as a number."
   619 
   831 
   620     aTimeDurationOrNumberOfSeconds isNumber ifTrue:[
   832     aTimeDurationOrNumberOfSeconds isNumber ifTrue:[
   621         ^ self species basicNew 
   833         ^ self species basicNew 
   622             setMilliseconds:(self getMilliseconds / aTimeDurationOrNumberOfSeconds) asInteger
   834             setMilliseconds:(timeEncoding / aTimeDurationOrNumberOfSeconds)
       
   835             additionalPicoseconds:((additionalPicoseconds?0) / aTimeDurationOrNumberOfSeconds).
   623     ].
   836     ].
   624     aTimeDurationOrNumberOfSeconds isTimeDuration ifTrue:[
   837     aTimeDurationOrNumberOfSeconds isTimeDuration ifTrue:[
   625         ^ (self getMilliseconds / aTimeDurationOrNumberOfSeconds getMilliseconds)
   838         ^ self getPicoseconds / aTimeDurationOrNumberOfSeconds getPicoseconds.
   626     ].
   839     ].
       
   840 
       
   841     "/ notice: although noone seems to implement it (currently),
       
   842     "/ there are additional packages which add support (i.e. goodies/physic),
       
   843     "/ so do not remove the call below.
   627     ^ aTimeDurationOrNumberOfSeconds quotientFromTimeDuration:self
   844     ^ aTimeDurationOrNumberOfSeconds quotientFromTimeDuration:self
   628     
   845     
   629     "
   846     "
   630      (TimeDuration fromString:'10s') / (TimeDuration fromString:'5s')
   847      (TimeDuration fromString:'10s') / (TimeDuration fromString:'5s')
   631      (TimeDuration fromString:'10s') / 5
   848      (TimeDuration fromString:'10s') / 5
   632     "
   849     "
       
   850 
       
   851     "Modified (format): / 27-07-2018 / 10:38:07 / Stefan Vogel"
       
   852 !
       
   853 
       
   854 // aTimeDurationOrNumberOfSeconds
       
   855     "if the argument is a number, return a new timeDuration.
       
   856      Otherwise, return the quotient as a number."
       
   857 
       
   858     aTimeDurationOrNumberOfSeconds isNumber ifTrue:[
       
   859         ^ self species basicNew 
       
   860             setSeconds:(self getSeconds // aTimeDurationOrNumberOfSeconds)
       
   861     ].
       
   862     aTimeDurationOrNumberOfSeconds isTimeDuration ifTrue:[
       
   863         ^ (self getSeconds // aTimeDurationOrNumberOfSeconds getSeconds)
       
   864     ].
       
   865 
       
   866     "/ notice: although noone seems to implement it (currently),
       
   867     "/ there are additional packages which add support (i.e. goodies/physic),
       
   868     "/ so do not remove the call below.
       
   869     ^ (aTimeDurationOrNumberOfSeconds quotientFromTimeDuration:self) truncated
       
   870     
       
   871     "
       
   872      (TimeDuration fromString:'10s') // (TimeDuration fromString:'3')
       
   873      (TimeDuration fromString:'10s') // 3
       
   874 
       
   875      (TimeDuration fromString:'10s') / (TimeDuration fromString:'3')
       
   876      (TimeDuration fromString:'10s') / 3
       
   877     "
   633 !
   878 !
   634 
   879 
   635 abs
   880 abs
   636     timeEncoding >= 0 ifTrue:[
   881     ^ self class new setMilliseconds:(self asExactMilliseconds abs)
   637         ^ self. 
   882 
   638     ].
   883     "
   639     ^ self class new timeEncoding:(timeEncoding negated)
   884      (TimeDuration fromSeconds:3600) abs
   640 
   885      (TimeDuration fromSeconds:-3600) abs
   641     "
   886 
   642         (TimeDuration fromSeconds:20000) abs
   887      (TimeDuration fromSeconds:20000) abs
   643         (TimeDuration fromSeconds:-20000) abs
   888      (TimeDuration fromSeconds:-20000) abs
   644     "
   889     "
   645 !
   890 !
   646 
   891 
   647 negated
   892 negated
   648     ^ self class new timeEncoding:(timeEncoding negated)
   893     ^ self class new setMilliseconds:(self asExactMilliseconds) negated
       
   894 
       
   895     "
       
   896      50 nanoseconds negated asNanoseconds
       
   897      1 seconds negated asSeconds
       
   898     "
   649 !
   899 !
   650 
   900 
   651 productFromFloat:aFloat
   901 productFromFloat:aFloat
   652     "return a new timeDuration"
   902     "sent when aFloat does not know how to multiply the receiver.
       
   903      Return a new timeDuration"
   653 
   904 
   654     ^ self productFromNumber:aFloat
   905     ^ self productFromNumber:aFloat
   655 
   906 
   656     "
   907     "
   657      5.1 * (TimeDuration fromString:'10s') 
   908      5.1 * (TimeDuration fromString:'10s') 
   658     "
   909     "
   659 !
   910 
   660 
   911     "Modified (comment): / 12-06-2017 / 20:51:38 / cg"
   661 productFromFraction:aNumber
   912 !
   662     "return a new timeDuration"
   913 
   663 
   914 productFromFraction:aFraction
   664     ^ self productFromNumber:aNumber
   915     "sent when aFraction does not know how to multiply the receiver.
       
   916      Return a new timeDuration"
       
   917 
       
   918     ^ self productFromNumber:aFraction
   665 
   919 
   666     "
   920     "
   667      (TimeDuration fromString:'10s') * 5
   921      (TimeDuration fromString:'10s') * 5
   668     "
   922     "
       
   923 
       
   924     "Modified (comment): / 12-06-2017 / 20:51:25 / cg"
   669 !
   925 !
   670 
   926 
   671 productFromInteger:anInteger
   927 productFromInteger:anInteger
   672     "return a new timeDuration"
   928     "sent when an integer does not know how to multiply the receiver"
   673 
   929 
   674     ^ self productFromNumber:anInteger
   930     ^ self productFromNumber:anInteger
   675 
   931 
   676     "
   932     "
   677      5 * (TimeDuration fromString:'10s') 
   933      5 * (TimeDuration fromString:'10s') 
   678     "
   934     "
       
   935 
       
   936     "Modified (comment): / 12-06-2017 / 20:50:56 / cg"
   679 !
   937 !
   680 
   938 
   681 productFromNumber:aNumber
   939 productFromNumber:aNumber
   682     "return a new timeDuration"
   940     "sent when an integer does not know how to multiply the receiver.
       
   941      Return a new timeDuration"
   683 
   942 
   684     ^ self species basicNew 
   943     ^ self species basicNew 
   685         setMilliseconds:(self getMilliseconds * aNumber) asInteger
   944         setMilliseconds:(timeEncoding * aNumber) additionalPicoseconds:(additionalPicoseconds ? 0) * aNumber.
   686 
   945 
   687     "
   946     "
   688      5.1 * (TimeDuration fromString:'10s') 
   947      5.1 * (TimeDuration fromString:'10s') 
   689     "
   948      (TimeDuration fromString:'10s') * 5
       
   949     "
       
   950 
       
   951     "Modified (comment): / 16-09-2017 / 12:52:16 / cg"
       
   952     "Modified: / 27-07-2018 / 10:33:21 / Stefan Vogel"
       
   953 !
       
   954 
       
   955 squared
       
   956     "answer a squared time (unit: s^2).
       
   957      Do NOT return a scalar here, because this breaks computations such as
       
   958         1 meter / 1 seconds squared
       
   959      (I hope, no one uses it yet )"
       
   960 
       
   961     "/ notice: although noone seems to implement it (currently),
       
   962     "/ there are additional packages which add support (i.e. goodies/physic),
       
   963     "/ so do not remove the call below.
       
   964     ^ self productFromTimeDuration:self
       
   965 
       
   966     "
       
   967      50 nanoseconds squared 
       
   968      1 seconds squared
       
   969      ObjectMemory traceSendsIn:[
       
   970         1 meter / 1 seconds squared
       
   971      ]
       
   972     "
       
   973 
       
   974     "Created: / 15-03-2019 / 17:57:50 / Stefan Vogel"
       
   975 !
       
   976 
       
   977 squaredSeconds
       
   978     "answer a float representing my value in seconds - squared.
       
   979      Used to compute e.g. variance and standard deviation."
       
   980 
       
   981     ^ self secondsAsFloat squared
       
   982 
       
   983     "
       
   984      50 nanoseconds squaredSeconds 
       
   985      1 seconds squaredSeconds
       
   986     "
       
   987 
       
   988     "Created: / 15-03-2019 / 17:57:50 / Stefan Vogel"
   690 ! !
   989 ! !
   691 
   990 
       
   991 !TimeDuration methodsFor:'comparing'!
       
   992 
       
   993 < something
       
   994     |otherTimeEncoding|
       
   995     
       
   996     something class == self class ifTrue:[
       
   997         otherTimeEncoding :=something timeEncoding.
       
   998         timeEncoding = otherTimeEncoding ifTrue:[
       
   999             ^ (additionalPicoseconds ? 0) < something additionalPicoseconds
       
  1000         ].    
       
  1001         ^ timeEncoding < otherTimeEncoding
       
  1002     ].    
       
  1003     ^ super < something
       
  1004 
       
  1005     "Created: / 26-05-2019 / 10:02:59 / Claus Gittinger"
       
  1006 !
       
  1007 
       
  1008 = something
       
  1009     something class == self class ifTrue:[
       
  1010         ^ timeEncoding = something timeEncoding
       
  1011         and:[(additionalPicoseconds ? 0) = something additionalPicoseconds]
       
  1012     ].    
       
  1013     ^ super = something
       
  1014 
       
  1015     "Created: / 26-05-2019 / 09:40:44 / Claus Gittinger"
       
  1016 !
       
  1017 
       
  1018 hash
       
  1019     ^ timeEncoding bitXor:(additionalPicoseconds ? 0)
       
  1020 
       
  1021     "Created: / 26-05-2019 / 09:45:19 / Claus Gittinger"
       
  1022 !
       
  1023 
       
  1024 negative
       
  1025     ^ timeEncoding < 0
       
  1026 !
       
  1027 
       
  1028 positive
       
  1029     ^ timeEncoding >= 0
       
  1030 ! !
       
  1031 
   692 !TimeDuration methodsFor:'converting'!
  1032 !TimeDuration methodsFor:'converting'!
   693 
  1033 
       
  1034 asExactHours
       
  1035     "answer the duration as hours.
       
  1036      In contrast to asTruncatedHours, which returns them truncated,
       
  1037      this may return a non-integer value."
       
  1038 
       
  1039     ^ self asExactSeconds / (3600)
       
  1040 
       
  1041     "
       
  1042      (2 hours + 10 minutes + 30 seconds) asExactHours
       
  1043      (2 hours + 10 minutes + 30 seconds) asExactHours asFloat
       
  1044      (2 hours + 10 minutes + 30 seconds) asTruncatedHours
       
  1045      (2 hours + 10 minutes) asExactHours asFloat
       
  1046      (2 hours + 10 minutes) asTruncatedHours
       
  1047      10 milliseconds asExactHours 
       
  1048      10 milliseconds asExactHours asFloat 
       
  1049     "
       
  1050 !
       
  1051 
       
  1052 asExactMicroseconds
       
  1053     "return the exact number of mcroseconds.
       
  1054      In contrast to asMicroSeconds, which returns them truncated,
       
  1055      this may return a non-integer value."
       
  1056 
       
  1057     additionalPicoseconds isNil ifTrue:[
       
  1058         ^ (timeEncoding * 1000) "/ millis as micros
       
  1059     ].
       
  1060     ^ (timeEncoding * 1000)                    "/ millis as micros 
       
  1061     + (additionalPicoseconds / (1000 * 1000))  "/ picos as microseconds.
       
  1062 
       
  1063     "
       
  1064      40 milliseconds asExactMicroseconds
       
  1065      40 microseconds asExactMicroseconds
       
  1066      40 nanoseconds asExactMicroseconds
       
  1067      40 picoseconds asExactMicroseconds
       
  1068     "
       
  1069 
       
  1070     "Created: / 21-09-2017 / 18:52:26 / cg"
       
  1071 !
       
  1072 
       
  1073 asExactMilliseconds
       
  1074     "return the exact number of milliseconds.
       
  1075      In contrast to asMilliSeconds, which returns them truncated,
       
  1076      this may return a non-integer value."
       
  1077 
       
  1078     additionalPicoseconds isNil ifTrue:[
       
  1079         ^ timeEncoding "/ millis
       
  1080     ].
       
  1081     ^ timeEncoding                         "/ millis 
       
  1082       + (additionalPicoseconds / (1000 * 1000 * 1000))  "/ picos as milliseconds.
       
  1083 
       
  1084     "
       
  1085      40 milliseconds asExactMilliseconds
       
  1086      40 microseconds asExactMilliseconds
       
  1087      40 nanoseconds asExactMilliseconds
       
  1088      40 picoseconds asExactMilliseconds
       
  1089     "
       
  1090 
       
  1091     "Created: / 21-09-2017 / 18:52:26 / cg"
       
  1092     "Modified (format): / 24-07-2018 / 16:27:10 / Stefan Vogel"
       
  1093 !
       
  1094 
       
  1095 asExactMinutes
       
  1096     "answer the duration as minutes.
       
  1097      In contrast to asTruncatedMinutes, which returns them truncated,
       
  1098      this may return a non-integer value."
       
  1099 
       
  1100     ^ self asExactSeconds / 60
       
  1101 
       
  1102     "
       
  1103      (2 hours + 10 minutes + 30 seconds) asExactMinutes
       
  1104      (2 hours + 10 minutes + 30 seconds) asExactMinutes asFloat
       
  1105      (2 hours + 10 minutes + 30 seconds) asTruncatedMinutes
       
  1106      (2 hours + 10 minutes) asExactMinutes
       
  1107      (2 hours + 10 minutes) asTruncatedMinutes
       
  1108      10 milliseconds asExactMinutes 
       
  1109      10 milliseconds asExactMinutes asFloat 
       
  1110     "
       
  1111 !
       
  1112 
       
  1113 asExactNanoseconds
       
  1114     "return the exact number of nanoseconds.
       
  1115      In contrast to asNanoSeconds, which returns them truncated,
       
  1116      this may return a non-integer value."
       
  1117 
       
  1118     additionalPicoseconds isNil ifTrue:[
       
  1119         ^ (timeEncoding * 1000 * 1000) "/ millis as nanos
       
  1120     ].
       
  1121     ^ (timeEncoding * 1000 * 1000)          "/ millis as nanos 
       
  1122     + (additionalPicoseconds / (1000))      "/ picos as nanoseconds.
       
  1123 
       
  1124     "
       
  1125      40 milliseconds asExactNanoseconds
       
  1126      40 microseconds asExactNanoseconds
       
  1127      40 nanoseconds asExactNanoseconds
       
  1128      40 picoseconds asExactNanoseconds
       
  1129     "
       
  1130 
       
  1131     "Created: / 21-09-2017 / 18:52:26 / cg"
       
  1132 !
       
  1133 
       
  1134 asExactSeconds
       
  1135     "return the exact number of seconds.
       
  1136      In contrast to asSeconds, which returns them truncated,
       
  1137      this may return a non-integer value."
       
  1138 
       
  1139     additionalPicoseconds isNil ifTrue:[
       
  1140         ^ (timeEncoding / 1000) "/ millis as seconds
       
  1141     ].
       
  1142     ^ (timeEncoding / 1000)                         "/ millis as seconds
       
  1143     + (additionalPicoseconds / (1000 * 1000 * 1000 * 1000))  "/ picos as seconds.
       
  1144 
       
  1145     "
       
  1146      1.5 milliSeconds asExactSeconds    
       
  1147      1.5 seconds asExactSeconds    
       
  1148      40 seconds asExactSeconds
       
  1149      40 milliseconds asExactSeconds
       
  1150      40 microseconds asExactSeconds
       
  1151      40 nanoseconds asExactSeconds 
       
  1152     "
       
  1153 
       
  1154     "Created: / 21-09-2017 / 18:52:26 / cg"
       
  1155 !
       
  1156 
   694 asFixedPoint
  1157 asFixedPoint
   695     "answer the duration is seconds"
  1158     <resource: #obsolete>
   696 
  1159     "answer the duration in seconds as a fixedPoint number.
   697     ^ FixedPoint numerator:timeEncoding denominator:1000 scale:4 
  1160      This method has a bad name (a historic leftover);
   698 
  1161      Please change any sender to use secondsAsFixedPoint"
   699     "
  1162 
   700         (10 milliseconds)  asFixedPoint
  1163     ^ self secondsAsFixedPoint 
   701     "
  1164 
       
  1165     "
       
  1166      (10 milliseconds) asFixedPoint
       
  1167      (10 milliseconds) asFixedPoint asFixedPoint:3 
       
  1168     "
       
  1169 
       
  1170     "Modified (comment): / 14-09-2017 / 15:15:24 / stefan"
       
  1171 !
       
  1172 
       
  1173 asFixedPoint:scale
       
  1174     <resource: #obsolete>
       
  1175     "answer the duration in seconds as a fixedPoint number with given scale.
       
  1176      This method has a bad name (a historic leftover);
       
  1177      Please change any sender to use secondsAsFixedPoint"
       
  1178 
       
  1179     ^ self secondsAsFixedPoint:scale
       
  1180 
       
  1181     "
       
  1182      (1000 milliseconds) secondsAsFixedPoint
       
  1183      (10 milliseconds) secondsAsFixedPoint
       
  1184      (10 microseconds) secondsAsFixedPoint scale:8
       
  1185      (10 nanoseconds) secondsAsFixedPoint scale:8   
       
  1186      (1000001 microseconds) secondsAsFixedPoint scale:8
       
  1187     "
       
  1188 
       
  1189     "Modified (comment): / 14-09-2017 / 15:15:24 / stefan"
   702 !
  1190 !
   703 
  1191 
   704 asFloat
  1192 asFloat
   705     "answer the duration is seconds"
  1193     <resource: #obsolete>
   706 
  1194     "answer the duration in seconds as a float.
   707     ^ timeEncoding / 1000.0
  1195      This method has a bad name (a historic leftover);
   708 
  1196      Please change any sender to use secondsAsFloat"
   709     "
  1197 
   710         (10 milliseconds)  asFloat
  1198     ^ self secondsAsFloat
   711     "
  1199 
       
  1200     "
       
  1201      (1000 milliseconds) asFloat
       
  1202      (10 milliseconds) asFloat
       
  1203      (10 microseconds) asFloat
       
  1204      (10 nanoseconds) asFloat
       
  1205      (1000001 microseconds) asFloat
       
  1206     "
       
  1207 
       
  1208     "Modified (comment): / 14-09-2017 / 15:15:18 / stefan"
   712 !
  1209 !
   713 
  1210 
   714 asFraction
  1211 asFraction
   715     "answer the duration is seconds"
  1212     <resource: #obsolete>
   716 
  1213     "answer the duration in seconds as a fraction
   717     ^ timeEncoding / 1000
  1214      (might return an integer, if the duration is an exact multiple
   718 
  1215       of millis).
   719     "
  1216      This method has a bad name (a historic leftover);
   720         (10 milliseconds)  asFraction
  1217      Please change any sender to use secondsAsFraction"
   721     "
  1218 
       
  1219     ^ self secondsAsFraction
       
  1220 
       
  1221     "
       
  1222      (1000 milliseconds) asFraction
       
  1223      (10 milliseconds) asFraction
       
  1224      (10 microseconds) asFraction
       
  1225      (10 nanoseconds) asFraction
       
  1226      (1000001 microseconds) asFraction asFloat
       
  1227     "
       
  1228 
       
  1229     "Modified (comment): / 19-01-2018 / 17:29:24 / stefan"
   722 !
  1230 !
   723 
  1231 
   724 asInteger
  1232 asInteger
   725     "answer the duration is seconds"
  1233     <resource: #obsolete>
   726 
  1234     "answer the duration as (truncated) integer seconds.
   727     ^ self getSeconds
  1235      Better use the explicit asTruncatedSeconds"
       
  1236 
       
  1237     ^ self asTruncatedSeconds
       
  1238 
       
  1239     "
       
  1240      10 milliseconds asInteger
       
  1241     "
       
  1242 
       
  1243     "Modified (comment): / 14-09-2017 / 15:14:49 / stefan"
       
  1244     "Modified (comment): / 21-09-2017 / 18:57:43 / cg"
   728 !
  1245 !
   729 
  1246 
   730 asLongFloat
  1247 asLongFloat
   731     "answer the duration is seconds"
  1248     <resource: #obsolete>
   732 
  1249     "answer the duration as longfloat seconds.
   733     ^ timeEncoding / 1000 asLongFloat
  1250      This method has a bad name (a historic leftover);
   734 
  1251      Please change any sender to use secondsAsFloat"
   735     "
  1252 
   736         (10 milliseconds)  asLongFloat
  1253     ^ self secondsAsLongFloat
       
  1254 
       
  1255     "
       
  1256      (10 milliseconds) asLongFloat
       
  1257      (10 microseconds) asLongFloat
       
  1258      (10 nanoseconds) asLongFloat
       
  1259      (1000001 microseconds) asLongFloat
       
  1260     "
       
  1261 !
       
  1262 
       
  1263 asMicroseconds
       
  1264     "answer the duration as microseconds (truncated).
       
  1265      Values smaller than 1 us will be returned as 0"
       
  1266 
       
  1267     ^ self asTruncatedMicroseconds
       
  1268 
       
  1269     "
       
  1270      100 nanoseconds asTruncatedMicroseconds
       
  1271      100 nanoseconds asExactMicroseconds
       
  1272 
       
  1273      10 milliseconds asMicroseconds
       
  1274      1.5 milliseconds asMicroseconds
       
  1275      10 seconds asMicroseconds
       
  1276     "
       
  1277 !
       
  1278 
       
  1279 asMilliseconds
       
  1280     "answer the duration as milliseconds (truncated).
       
  1281      Values smaller than 1 ms will be returned as 0"
       
  1282 
       
  1283     ^ self asTruncatedMilliseconds
       
  1284 
       
  1285     "
       
  1286      10 microseconds asTruncatedMilliseconds
       
  1287      10 microseconds asExactMilliseconds
       
  1288      10 microseconds asMilliseconds
       
  1289 
       
  1290      10 milliseconds asMilliseconds
       
  1291      10 seconds asMilliseconds
       
  1292     "
       
  1293 !
       
  1294 
       
  1295 asNanoseconds
       
  1296     "answer the duration as nanoseconds (truncated).
       
  1297      Values smaller than 1 ns will be returned as 0"
       
  1298 
       
  1299     ^ self asTruncatedNanoseconds
       
  1300 
       
  1301     "
       
  1302      10 picoseconds asTruncatedNanoseconds
       
  1303      10 picoseconds asExactNanoseconds
   737     "
  1304     "
   738 !
  1305 !
   739 
  1306 
   740 asNumber
  1307 asNumber
   741     "answer the duration is seconds.
  1308     <resource: #obsolete>
   742      Better use the explicit getSeconds"
  1309     "answer the duration as seconds.
   743 
  1310      This method has a bad name (a historic leftover);
   744     ^ self getSeconds
  1311      Please change any sender to use asTruncatedSeconds or
   745 !
  1312      asExactSeconds, depending on what is wanted."
   746 
  1313 
   747 asTime
  1314     ^ self asExactSeconds
   748     "return a Time object from the receiver."
  1315 
   749 
  1316     "Modified (comment): / 14-09-2017 / 15:15:00 / stefan"
   750     ^ Time hours:(self hours) minutes:(self minutes) seconds:(self seconds)
  1317     "Modified: / 21-09-2017 / 18:57:57 / cg"
       
  1318 !
       
  1319 
       
  1320 asPicoseconds
       
  1321     "answer the duration as picoseconds (truncated).
       
  1322      Because the smallest representable timeDuration is 1ps,
       
  1323      there is no distinction between truncated and exact picos."
       
  1324 
       
  1325     ^ (timeEncoding * 1000000000) + ((additionalPicoseconds ? 0))
       
  1326 
       
  1327     "
       
  1328      10 milliseconds asPicoeconds
       
  1329      10 seconds asPicoeconds
       
  1330     "
       
  1331 !
       
  1332 
       
  1333 asSeconds
       
  1334     "answer the duration as seconds (truncated).
       
  1335      Values smaller than 1 s will be returned as 0.
       
  1336 
       
  1337      To get the exact number, use asExactSeconds.
       
  1338      Please change senders to use asTruncatedSeconds 
       
  1339      to make this truncation explicit (and obvious when reading code).
       
  1340      For compatibility (both backward and with other smalltalks),
       
  1341      asSeconds returns the TRUNCATED integer value
       
  1342      (many senders assume that an integer is returned)"
       
  1343 
       
  1344     ^ self asTruncatedSeconds
       
  1345 
       
  1346     "
       
  1347      10 milliseconds asSeconds
       
  1348      10 nanoseconds asSeconds
       
  1349      10 milliseconds asExactSeconds
       
  1350      10 nanoseconds asExactSeconds
       
  1351      2 minutes asSeconds
       
  1352     "
   751 !
  1353 !
   752 
  1354 
   753 asTimeDuration
  1355 asTimeDuration
   754     "return a TimeDuration object from the receiver - that's the receiver."
  1356     "return a TimeDuration object from the receiver - that's the receiver."
   755 
  1357 
   756     ^ self
  1358     ^ self
       
  1359 !
       
  1360 
       
  1361 asTruncatedHours
       
  1362     "answer the duration as hours (truncated).
       
  1363      Values smaller than 1 h will be returned as 0.
       
  1364 
       
  1365      To get the exact number, use asExactHours."
       
  1366 
       
  1367     ^ self asTruncatedSeconds // (3600)
       
  1368 
       
  1369     "
       
  1370      (2 hours + 10 minutes) asTruncatedHours
       
  1371      (2 hours + 10 minutes + 30 seconds) asTruncatedHours
       
  1372      2 minutes asTruncatedHours
       
  1373      10 milliseconds asTruncatedHours
       
  1374     "
       
  1375 !
       
  1376 
       
  1377 asTruncatedMicroseconds
       
  1378     "answer the duration as microseconds (truncated).
       
  1379      Values smaller than 1 us will be returned as 0.
       
  1380      This is the total number of microseconds - not just the fractional part"
       
  1381 
       
  1382     ^ (timeEncoding * 1000) + ((additionalPicoseconds ? 0) // (1000 * 1000))
       
  1383 
       
  1384     "
       
  1385      100 nanoseconds asTruncatedMicroseconds
       
  1386      100 nanoseconds asExactMicroseconds
       
  1387 
       
  1388      10 milliseconds asTruncatedMicroseconds
       
  1389      10 seconds asTruncatedMicroseconds
       
  1390     "
       
  1391 !
       
  1392 
       
  1393 asTruncatedMilliseconds
       
  1394     "answer the duration as milliseconds (truncated).
       
  1395      Values smaller than 1 ms will be returned as 0.
       
  1396      This is the total number of milliseconds - not just the fractional part"
       
  1397 
       
  1398     ^ timeEncoding
       
  1399 
       
  1400     "
       
  1401      0.1 milliseconds asTruncatedMilliseconds
       
  1402      0.1 milliseconds asExactMilliseconds
       
  1403 
       
  1404      10 milliseconds asMilliseconds
       
  1405      10 seconds asMilliseconds
       
  1406     "
       
  1407 !
       
  1408 
       
  1409 asTruncatedMinutes
       
  1410     "answer the duration as minutes (truncated).
       
  1411      Values smaller than 1 m will be returned as 0.
       
  1412 
       
  1413      To get the exact number, use asExactMinutes."
       
  1414 
       
  1415     ^ self asTruncatedSeconds // 60
       
  1416 
       
  1417     "
       
  1418      (2 hours + 10 minutes) asTruncatedMinutes
       
  1419      (2 hours + 10 minutes + 30 seconds) asTruncatedMinutes
       
  1420      2 minutes asTruncatedMinutes
       
  1421      10 milliseconds asTruncatedMinutes
       
  1422     "
       
  1423 !
       
  1424 
       
  1425 asTruncatedNanoseconds
       
  1426     "answer the duration as nanoseconds (truncated).
       
  1427      Values smaller than 1 ns will be returned as 0.
       
  1428      This is the total number of nanoseconds - not just the fractional part"
       
  1429 
       
  1430     ^ (timeEncoding * 1000000) + ((additionalPicoseconds ? 0) // (1000))
       
  1431 
       
  1432     "
       
  1433      10 picoseconds asTruncatedNanoseconds
       
  1434      10 picoseconds asExactNanoseconds
       
  1435 
       
  1436      10 milliseconds asTruncatedNanoseconds
       
  1437      10 seconds asTruncatedNanoseconds
       
  1438     "
       
  1439 !
       
  1440 
       
  1441 asTruncatedSeconds
       
  1442     "answer the duration as seconds (truncated).
       
  1443      Values smaller than 1 s will be returned as 0.
       
  1444      This is the total number of seconds - not just the fractional part.
       
  1445      To get the exact number, use asExactSeconds."
       
  1446 
       
  1447     ^ timeEncoding // 1000
       
  1448 
       
  1449     "
       
  1450      10 milliseconds asTruncatedSeconds
       
  1451      10 milliseconds asExactSeconds
       
  1452      2 minutes asTruncatedSeconds
       
  1453     "
       
  1454 !
       
  1455 
       
  1456 secondsAsFixedPoint
       
  1457     "answer the duration in seconds as a fixedPoint number."
       
  1458 
       
  1459     ^ self secondsAsFixedPoint:4 
       
  1460 
       
  1461     "
       
  1462      (10 milliseconds) secondsAsFixedPoint
       
  1463      (10 milliseconds) secondsAsFixedPoint asFixedPoint:3 
       
  1464     "
       
  1465 
       
  1466     "Modified (comment): / 14-09-2017 / 15:15:24 / stefan"
       
  1467 !
       
  1468 
       
  1469 secondsAsFixedPoint:scale
       
  1470     "answer the duration in seconds as a fixedPoint number with given scale."
       
  1471 
       
  1472     |t|
       
  1473 
       
  1474     t := FixedPoint numerator:timeEncoding denominator:1000 scale:scale.
       
  1475     additionalPicoseconds notNil ifTrue:[
       
  1476         t := t + (FixedPoint numerator:additionalPicoseconds denominator:((1000*1000)*(1000*1000)) scale:scale)
       
  1477     ].
       
  1478     ^ t
       
  1479 
       
  1480     "
       
  1481      (1000 milliseconds) secondsAsFixedPoint
       
  1482      (10 milliseconds) secondsAsFixedPoint
       
  1483      (10 microseconds) secondsAsFixedPoint scale:8
       
  1484      (10 nanoseconds) secondsAsFixedPoint scale:8   
       
  1485      (1000001 microseconds) secondsAsFixedPoint scale:8
       
  1486     "
       
  1487 
       
  1488     "Modified (comment): / 14-09-2017 / 15:15:24 / stefan"
       
  1489 !
       
  1490 
       
  1491 secondsAsFloat
       
  1492     "answer the duration in seconds as a float."
       
  1493 
       
  1494     |t|
       
  1495 
       
  1496     t := timeEncoding / 1000.0.
       
  1497     additionalPicoseconds notNil ifTrue:[
       
  1498         t := t + (additionalPicoseconds / ((1000.0*1000.0) * (1000.0*1000.0))).
       
  1499     ].
       
  1500     ^ t
       
  1501 
       
  1502     "
       
  1503      (1000 milliseconds) secondsAsFloat
       
  1504      (10 milliseconds) secondsAsFloat
       
  1505      (10 microseconds) secondsAsFloat
       
  1506      (10 nanoseconds) secondsAsFloat
       
  1507      (1000001 microseconds) secondsAsFloat
       
  1508     "
       
  1509 
       
  1510     "Modified (comment): / 14-09-2017 / 15:15:18 / stefan"
       
  1511 !
       
  1512 
       
  1513 secondsAsFraction
       
  1514     "answer the duration in seconds as a fraction
       
  1515      (might return an integer, if the duration is an exact multiple
       
  1516       of millis)."
       
  1517 
       
  1518     |t|
       
  1519 
       
  1520     t := timeEncoding / 1000.
       
  1521     additionalPicoseconds notNil ifTrue:[
       
  1522         t := t + (additionalPicoseconds / ((1000*1000)*(1000*1000))).
       
  1523     ].
       
  1524     ^ t
       
  1525 
       
  1526     "
       
  1527      (1000 milliseconds) secondsAsFraction
       
  1528      (10 milliseconds) secondsAsFraction
       
  1529      (10 microseconds) secondsAsFraction
       
  1530      (10 nanoseconds) secondsAsFraction
       
  1531      (1000001 microseconds) secondsAsFraction asFloat
       
  1532     "
       
  1533 
       
  1534     "Modified (comment): / 19-01-2018 / 17:29:24 / stefan"
       
  1535 !
       
  1536 
       
  1537 secondsAsLongFloat
       
  1538     "answer the duration as longfloat seconds."
       
  1539 
       
  1540     |t|
       
  1541 
       
  1542     t := timeEncoding / 1000 asLongFloat.
       
  1543     additionalPicoseconds notNil ifTrue:[
       
  1544         t := t + (additionalPicoseconds / (((1000*1000) asLongFloat) * (1000*1000) asLongFloat)).
       
  1545     ].
       
  1546     ^ t
       
  1547 
       
  1548     "
       
  1549      (10 milliseconds) secondsAsLongFloat
       
  1550      (10 microseconds) secondsAsLongFloat
       
  1551      (10 nanoseconds) secondsAsLongFloat
       
  1552      (1000001 microseconds) secondsAsLongFloat
       
  1553     "
   757 ! !
  1554 ! !
   758 
  1555 
   759 !TimeDuration methodsFor:'double dispatching'!
  1556 !TimeDuration methodsFor:'double dispatching'!
       
  1557 
       
  1558 differenceFromFloat:aFloat
       
  1559     "treat the float as a number of seconds.
       
  1560      Might be questionable, but adding numbers to timeDurations is also allowed,
       
  1561      and addition is commutative...
       
  1562      ...maybe mixing should be forbidden."
       
  1563 
       
  1564     ^ (self species seconds:aFloat) - self
       
  1565 
       
  1566     "
       
  1567      10 seconds - 5 seconds
       
  1568      10 - 5 seconds
       
  1569      10.0 - 5 seconds
       
  1570      10 seconds - 5 
       
  1571      10 seconds - 5.0 
       
  1572 
       
  1573      10 seconds * 2 
       
  1574      10 seconds * 2.5 
       
  1575      2 * 10 seconds
       
  1576      2.5 * 10 seconds
       
  1577     "
       
  1578 
       
  1579     "Created: / 16-09-2017 / 12:49:33 / cg"
       
  1580 !
       
  1581 
       
  1582 differenceFromInteger:anInteger
       
  1583     "treat the integer as a number of seconds.
       
  1584      Might be questionable, but adding integers to timeDurations is also allowed,
       
  1585      and addition is commutative...
       
  1586      ...maybe mixing should be forbidden."
       
  1587 
       
  1588     ^ (self species seconds:anInteger) - self
       
  1589 
       
  1590     "
       
  1591      10 seconds - 5 seconds
       
  1592      10 - 5 seconds
       
  1593      10 seconds - 5 
       
  1594 
       
  1595      10 seconds * 2 
       
  1596      2 * 10 seconds
       
  1597     "
       
  1598 
       
  1599     "Created: / 16-09-2017 / 12:49:33 / cg"
       
  1600 !
       
  1601 
       
  1602 differenceFromTimeDuration:aTimeDuration
       
  1603     "return a new timeDuration"
       
  1604 
       
  1605     |newMillis newPicos|
       
  1606 
       
  1607     newMillis := aTimeDuration getMilliseconds - timeEncoding.
       
  1608     newPicos := (aTimeDuration additionalPicoseconds) - (additionalPicoseconds ? 0).
       
  1609 
       
  1610     ^ aTimeDuration species basicNew
       
  1611         setMilliseconds:newMillis additionalPicoseconds:newPicos
       
  1612 
       
  1613     "
       
  1614      (TimeDuration fromString:'1m') - (TimeDuration fromString:'10s') 
       
  1615      1 minutes - 10 seconds
       
  1616      10 - 1 minutes
       
  1617     "
       
  1618 
       
  1619     "Created: / 25-07-2018 / 21:17:50 / Stefan Vogel"
       
  1620     "Modified: / 27-07-2018 / 10:32:53 / Stefan Vogel"
       
  1621 !
   760 
  1622 
   761 differenceFromTimestamp:aTimestamp
  1623 differenceFromTimestamp:aTimestamp
   762     "return the timestamp this timeDuration before aTimestamp"
  1624     "return the timestamp this timeDuration before aTimestamp"
   763 
  1625 
   764     ^ aTimestamp subtractMilliseconds:(self getMilliseconds)
  1626     |newMillis newPicos|
       
  1627 
       
  1628     newMillis := aTimestamp getMilliseconds - timeEncoding.
       
  1629     newPicos := (aTimestamp additionalPicoseconds) - (additionalPicoseconds ? 0).
       
  1630 
       
  1631     ^ aTimestamp species basicNew
       
  1632         setMilliseconds:newMillis additionalPicoseconds:newPicos.
       
  1633 
       
  1634     "
       
  1635      Timestamp now - 100 seconds
       
  1636      Time now - 100 seconds
       
  1637      Timestamp now - 100
       
  1638     "
       
  1639 
       
  1640     "Modified (comment): / 16-09-2017 / 12:51:38 / cg"
       
  1641     "Modified (format): / 27-07-2018 / 10:50:13 / Stefan Vogel"
       
  1642 !
       
  1643 
       
  1644 productFromTimeDuration:aTimeDuration
       
  1645     "return a new timeDuration"
       
  1646 
       
  1647     |t newMillis newPicos|
       
  1648 
       
  1649     (t := Smalltalk at:#'Physic::Time') notNil ifTrue:[
       
  1650         ^ t dispatchProductFromAmount:(aTimeDuration asExactSeconds) 
       
  1651             into:t 
       
  1652             value:self asExactSeconds
       
  1653     ].
       
  1654 
       
  1655     "/ the code below is completely bogus.
       
  1656     "/ a square-second is NOT a second!!
       
  1657     newMillis := timeEncoding * aTimeDuration getMilliseconds.
       
  1658     newPicos := (additionalPicoseconds ? 0) * (aTimeDuration additionalPicoseconds).
       
  1659 
       
  1660     ^ aTimeDuration species basicNew
       
  1661         setMilliseconds:newMillis additionalPicoseconds:newPicos
       
  1662 
       
  1663     "
       
  1664      1 minutes * 10 seconds 
       
  1665      10 * 1 minutes         
       
  1666      1 minutes * 5        
       
  1667      (TimeDuration fromString:'10s') * (TimeDuration fromString:'10s')  
       
  1668      (TimeDuration fromString:'10s') / (TimeDuration fromString:'10s')  
       
  1669     "
       
  1670 
       
  1671     "Created: / 25-07-2018 / 21:11:40 / Stefan Vogel"
       
  1672     "Modified: / 27-07-2018 / 10:33:29 / Stefan Vogel"
       
  1673 !
       
  1674 
       
  1675 sumFromFloat:aFloat
       
  1676     "treat the float as a number of seconds.
       
  1677      Might be questionable, but adding floats to timeDurations is also allowed,
       
  1678      and addition is commutative...
       
  1679      ...maybe mixing should be forbidden."
       
  1680 
       
  1681     ^ self addSeconds:aFloat
       
  1682 
       
  1683     "
       
  1684      10 + 5 seconds
       
  1685      10.0 + 5 seconds
       
  1686      10 seconds + 5 
       
  1687      10 seconds + 5.0 
       
  1688     "
       
  1689 
       
  1690 
       
  1691 !
       
  1692 
       
  1693 sumFromInteger:anInteger
       
  1694     "treat the integer as a number of seconds.
       
  1695      Might be questionable, but adding integers to timeDurations is also allowed,
       
  1696      and addition is commutative...
       
  1697      ...maybe mixing should be forbidden."
       
  1698 
       
  1699     ^ self addSeconds:anInteger
       
  1700 
       
  1701     "
       
  1702      10 + 5 seconds
       
  1703      10 seconds + 5 
       
  1704     "
       
  1705 
       
  1706     "Created: / 16-09-2017 / 12:46:20 / cg"
       
  1707 !
       
  1708 
       
  1709 sumFromTimeDuration:aTimeDuration
       
  1710     "return a new timeDuration"
       
  1711 
       
  1712     |newMillis newPicos|
       
  1713 
       
  1714     newMillis := timeEncoding + aTimeDuration getMilliseconds.
       
  1715     newPicos := (additionalPicoseconds ? 0) + (aTimeDuration additionalPicoseconds).
       
  1716 
       
  1717     ^ aTimeDuration species basicNew
       
  1718         setMilliseconds:newMillis additionalPicoseconds:newPicos
       
  1719 
       
  1720     "
       
  1721      (TimeDuration fromString:'1m') + (TimeDuration fromString:'10s') 
       
  1722      1 minutes + 10 seconds
       
  1723      10 + 1 minutes
       
  1724     "
       
  1725 
       
  1726     "Created: / 16-09-2017 / 12:43:28 / cg"
       
  1727     "Modified: / 27-07-2018 / 10:33:47 / Stefan Vogel"
   765 !
  1728 !
   766 
  1729 
   767 sumFromTimestamp:aTimestamp
  1730 sumFromTimestamp:aTimestamp
   768     "return the timestamp this timeDuration after aTimestamp"
  1731     "return the timestamp this timeDuration after aTimestamp"
   769 
  1732 
   770     ^ aTimestamp addMilliseconds:(self getMilliseconds)
  1733     |newMillis newPicos|
       
  1734 
       
  1735     newMillis := timeEncoding + aTimestamp getMilliseconds.
       
  1736     newPicos := (additionalPicoseconds ? 0) + (aTimestamp additionalPicoseconds).
       
  1737 
       
  1738     ^ aTimestamp species basicNew
       
  1739         setMilliseconds:newMillis additionalPicoseconds:newPicos
       
  1740 
       
  1741     "
       
  1742      Timestamp now + 100 seconds
       
  1743     "
       
  1744 
       
  1745     "Modified (comment): / 16-09-2017 / 12:53:14 / cg"
       
  1746     "Modified: / 27-07-2018 / 10:30:13 / Stefan Vogel"
   771 ! !
  1747 ! !
   772 
  1748 
   773 !TimeDuration methodsFor:'printing'!
  1749 !TimeDuration methodsFor:'printing'!
   774 
  1750 
   775 addPrintBindingsTo:aDictionary language:languageOrNil
  1751 addPrintBindingsTo:aDictionary language:languageOrNil
   783         %(yrR)      years rounded (i.e. for 730 days, we get 2 asFixedPoint:1 )
  1759         %(yrR)      years rounded (i.e. for 730 days, we get 2 asFixedPoint:1 )
   784         %(monR)     month rounded (i.e. for 45 days, we get 1.5 asFixedPoint:1 )
  1760         %(monR)     month rounded (i.e. for 45 days, we get 1.5 asFixedPoint:1 )
   785         %(w)        weeks 
  1761         %(w)        weeks 
   786         %(wR)       weeks rounded (i.e. for 45 days, we get 6.xxx asFixedPoint:1 )
  1762         %(wR)       weeks rounded (i.e. for 45 days, we get 6.xxx asFixedPoint:1 )
   787         %(dR)       days rounded (i.e. for 36 hours, we get 1.5 asFixedPoint:1 )
  1763         %(dR)       days rounded (i.e. for 36 hours, we get 1.5 asFixedPoint:1 )
   788         %(dw)       days in week
  1764         %(dw)       days in week (rest days after taking out the weeks)
   789         %(hR)       hours rounded (i.e. for 3h 30m, we get 3.5 asFixedPoint:1 )
  1765         %(hR)       hours rounded (i.e. for 3h 30m, we get 3.5 asFixedPoint:1 )
   790         %(mR)       minutes rounded (i.e. for 2m 30s, we get 2.5 asFixedPoint:1 )
  1766         %(mR)       minutes rounded (i.e. for 2m 30s, we get 2.5 asFixedPoint:1 )
   791         %(sR)       seconds rounded to 1 postDecimal (i.e. for 2s 100ms, we get 2.1 asFixedPoint:1 )
  1767         %(sR)       seconds rounded to 1 postDecimal (i.e. for 2s 100ms, we get 2.1 asFixedPoint:1 )
   792     "
  1768     "
   793 
  1769 
   870     "Return a format which is suitable for a human - not meant to be read back.
  1846     "Return a format which is suitable for a human - not meant to be read back.
   871      In contrast to the regular format, this one only gives a rounded approximation
  1847      In contrast to the regular format, this one only gives a rounded approximation
   872      of the time duration as useful in information-dialogs or other user-hint-GUI elements.
  1848      of the time duration as useful in information-dialogs or other user-hint-GUI elements.
   873      For example, in a timeDuration of more than 2hours, the user might not be interested in
  1849      For example, in a timeDuration of more than 2hours, the user might not be interested in
   874      individual seconds or even milliseconds.
  1850      individual seconds or even milliseconds.
   875      The way this hidding/rounding is done is pure magic heuristics."
  1851      The way this is done is pure magic heuristics - let me know, if you have a better algorithm."
   876 
  1852 
   877     |hours mins secs ms|
  1853     |hours mins secs millis|
   878 
  1854 
   879     hours := self hours.
  1855     hours := self hours.
   880 
  1856 
   881     hours >= (24*356*2) ifTrue:[
  1857     hours >= (24*365*2) ifTrue:[
   882         ^ '%(yrR)yr'. 
  1858         ^ '%(yrR)yr'. 
   883     ].
  1859     ].
   884     hours >= (24*40) ifTrue:[
  1860     hours >= (24*40) ifTrue:[
   885         ^ '%(monR)mon'. 
  1861         ^ '%(monR)mon'. 
   886     ].
  1862     ].
   891         ^ '%dd %(Hd)h'. 
  1867         ^ '%dd %(Hd)h'. 
   892     ].
  1868     ].
   893     hours >= 2 ifTrue:[
  1869     hours >= 2 ifTrue:[
   894         ^ '%(hR)h'.
  1870         ^ '%(hR)h'.
   895     ].
  1871     ].
   896     hours >= 1 ifTrue:[
  1872     hours > 0 ifTrue:[
   897         ^ '%Hh %Mm'.
  1873         ^ '%Hh %Mm'.
   898     ].
  1874     ].
   899 
  1875 
   900     "/ no hours
  1876     "/ no hours
   901     mins := self minutes.
  1877     mins := self minutes.
   902     mins >= 5 ifTrue:[
  1878     mins >= 5 ifTrue:[
   903         ^ '%(mR)m'.
  1879         ^ '%(mR)m'.
   904     ].
  1880     ].
   905     mins >= 1 ifTrue:[
  1881     mins > 0 ifTrue:[
   906         ^ '%Mm %Ss'.
  1882         ^ '%Mm %Ss'.
   907     ].
  1883     ].
   908 
  1884 
   909     "/ no mins
  1885     "/ no mins
   910     secs := self seconds.
  1886     secs := self seconds.
   911     secs >= 1 ifTrue:[
  1887     secs > 0 ifTrue:[
   912         secs >= 30 ifTrue:[
  1888         secs >= 30 ifTrue:[
   913             ^ '%(S)s'.
  1889             ^ '%(S)s'.
   914         ].
  1890         ].
   915         ^ '%(sR)s'.
  1891         ^ '%(sR)s'.
   916     ].
  1892     ].
   917 
  1893 
   918     "/ no secs
  1894     "/ no secs
   919     ms := self milliseconds.
  1895     millis := self milliseconds.
   920     ms > 500 ifTrue:[
  1896     millis > 500 ifTrue:[
   921         ^ '%(sR)s'
  1897         ^ '%(sR)s'
   922     ].
  1898     ].
   923 
  1899 
   924     ^ self formatForPrinting
  1900     ^ self formatForPrinting
   925 
  1901 
   937      (TimeDuration hours:1000000 minutes:33 seconds:0 millis:123) printStringForApproximation    
  1913      (TimeDuration hours:1000000 minutes:33 seconds:0 millis:123) printStringForApproximation    
   938 
  1914 
   939      (TimeDuration hours:2 minutes:33 seconds:0 millis:0) printStringForApproximation         
  1915      (TimeDuration hours:2 minutes:33 seconds:0 millis:0) printStringForApproximation         
   940      (TimeDuration hours:2 minutes:0 seconds:0 millis:0) printStringForApproximation          
  1916      (TimeDuration hours:2 minutes:0 seconds:0 millis:0) printStringForApproximation          
   941      (TimeDuration hours:24 minutes:0 seconds:0 millis:0) printStringForApproximation          
  1917      (TimeDuration hours:24 minutes:0 seconds:0 millis:0) printStringForApproximation          
   942     "
  1918 
       
  1919      (TimeDuration fromMicroseconds:20) printStringForApproximation          
       
  1920     "
       
  1921 
       
  1922     "Modified: / 21-09-2017 / 22:19:53 / cg"
   943 !
  1923 !
   944 
  1924 
   945 formatForPrinting
  1925 formatForPrinting
   946     "Return the format for printing"
  1926     "Return the format for printing"
   947 
  1927 
   967 printAsApproximationOn:aStream
  1947 printAsApproximationOn:aStream
   968     "append a human readable printed representation of the receiver to aStream.
  1948     "append a human readable printed representation of the receiver to aStream.
   969      The format is meant for a human and does not give all information;
  1949      The format is meant for a human and does not give all information;
   970      especially, useless detail is hidden.
  1950      especially, useless detail is hidden.
   971      This means, that seconds are rounded or hidden, if the dT is more than a few minutes;
  1951      This means, that seconds are rounded or hidden, if the dT is more than a few minutes;
   972      minutes rounded into the hour or hidden, if its more than a few hours etc.
  1952      minutes rounded into the hour or hidden, if it's more than a few hours etc.
   973      The way this is done is pure magic heuristics - let me know, if you have a better algorithm."
  1953      The way this is done is pure magic heuristics - let me know, if you have a better algorithm."
   974 
  1954 
   975     ^ self
  1955     ^ self
   976         printOn:aStream 
  1956         printOn:aStream 
   977         format:(self formatForApproximatePrinting).
  1957         format:(self formatForApproximatePrinting).
   990      (TimeDuration hours:2 minutes:0 seconds:0) printAsApproximationOn:Transcript
  1970      (TimeDuration hours:2 minutes:0 seconds:0) printAsApproximationOn:Transcript
   991      (TimeDuration hours:24 minutes:0 seconds:0) printAsApproximationOn:Transcript
  1971      (TimeDuration hours:24 minutes:0 seconds:0) printAsApproximationOn:Transcript
   992     "
  1972     "
   993 
  1973 
   994     "Modified: / 18-07-2007 / 14:06:17 / cg"
  1974     "Modified: / 18-07-2007 / 14:06:17 / cg"
       
  1975     "Modified (comment): / 13-02-2017 / 20:32:54 / cg"
   995 !
  1976 !
   996 
  1977 
   997 printOn:aStream
  1978 printOn:aStream
   998     "append a human readable printed representation of the receiver to aStream.
  1979     "append a human readable printed representation of the receiver to aStream.
   999      The format is suitable for a human - not meant to be read back."
  1980      The format is suitable for a human - not meant to be read back."
  1075 printStringForApproximation
  2056 printStringForApproximation
  1076     "return a human readable printed representation of the receiver to aStream.
  2057     "return a human readable printed representation of the receiver to aStream.
  1077      The format is meant for a human and does not give all information;
  2058      The format is meant for a human and does not give all information;
  1078      especially, useless detail is hidden.
  2059      especially, useless detail is hidden.
  1079      This means, that seconds are rounded or hidden, if the dT is more than a few minutes;
  2060      This means, that seconds are rounded or hidden, if the dT is more than a few minutes;
  1080      minutes rounded into the hour or hidden, if its more than a few hours etc.
  2061      minutes rounded into the hour or hidden, if it's more than a few hours etc.
  1081      The way this is done is pure magic heuristics - let me know, if you have a better algorithm."
  2062      The way this is done is pure magic heuristics - let me know, if you have a better algorithm."
  1082 
  2063 
  1083     ^ self printStringFormat:(self formatForApproximatePrinting).
  2064     ^ self printStringFormat:(self formatForApproximatePrinting).
  1084 
  2065 
  1085     "
  2066     "
  1094 
  2075 
  1095      (TimeDuration hours:2 minutes:33 seconds:0) printStringForApproximation
  2076      (TimeDuration hours:2 minutes:33 seconds:0) printStringForApproximation
  1096      (TimeDuration hours:2 minutes:0 seconds:0) printStringForApproximation
  2077      (TimeDuration hours:2 minutes:0 seconds:0) printStringForApproximation
  1097      (TimeDuration hours:24 minutes:0 seconds:0) printStringForApproximation
  2078      (TimeDuration hours:24 minutes:0 seconds:0) printStringForApproximation
  1098     "
  2079     "
       
  2080 
       
  2081     "Modified (comment): / 13-02-2017 / 20:32:59 / cg"
  1099 ! !
  2082 ! !
  1100 
  2083 
  1101 !TimeDuration methodsFor:'private'!
  2084 !TimeDuration methodsFor:'private'!
  1102 
  2085 
       
  2086 additionalPicoseconds
       
  2087     "get the optional additional picoseconds (0..999999999)
       
  2088      notice: that is NOT the total number of picoseconds,
       
  2089      but the fractional part only. 
       
  2090      Use this only for printing."
       
  2091 
       
  2092     ^ additionalPicoseconds ? 0
       
  2093 !
       
  2094 
       
  2095 additionalPicoseconds:picosecondPart
       
  2096     "set the optional additional picoseconds (0..999999999)"
       
  2097 
       
  2098     self assert:(picosecondPart isInteger).
       
  2099     self assert:(picosecondPart < (1000*1000*1000)).
       
  2100     additionalPicoseconds := picosecondPart
       
  2101 !
       
  2102 
  1103 formatForPrinting:shortFlag
  2103 formatForPrinting:shortFlag
  1104     "Return a format which is suitable for a human - not meant to be read back.
  2104     "Return a format which is suitable for a human (i.e. not ISO8601) 
  1105      If shortFlag is true, some millisecond-info is ommitted for longer times."
  2105      (not meant to be read back because it will not print tiny fractions,
  1106 
  2106       but instead round it heuristically.
  1107     |fmt days weeks hours mins secs overAllSeconds millis|
  2107      However, the reader can read that format, but you'll loose some precision if you do).
  1108 
  2108      If shortFlag is true, some millisecond-info is omitted for longer times.
  1109     days := self days.
  2109      For timeDurations to be read back exactly, use iso8601 format."
       
  2110 
       
  2111     |fmt days weeks hours mins secs 
       
  2112      overAllSeconds overAllMicros overAllNanos millis|
       
  2113 
       
  2114     days := self days.  "/ that's the total
  1110     weeks := days // 7.
  2115     weeks := days // 7.
  1111     hours := self hours.
  2116     hours := self hours.
  1112     mins := self minutes.
  2117     mins := self minutes.
  1113     secs := self seconds.
  2118     secs := self seconds.
  1114     millis := self milliseconds.
  2119     millis := self milliseconds.
  1115 
  2120 
       
  2121     "/ q: for up to 2 weeks, whould we better generate: "10d" instead of "1w 3d" ??
  1116     weeks > 0 ifTrue:[
  2122     weeks > 0 ifTrue:[
       
  2123         "/ notice: dw here, which prints the remaining days, after taking out the weeks
  1117         fmt := '%(w)w %(dw)d %(Hd)h %Mm'.
  2124         fmt := '%(w)w %(dw)d %(Hd)h %Mm'.
  1118         secs = 0 ifTrue:[
  2125         secs = 0 ifTrue:[
  1119             fmt := '%(w)w %(dw)d %(Hd)h %Mm'.
  2126             fmt := '%(w)w %(dw)d %(Hd)h %Mm'.
  1120             mins = 0 ifTrue:[
  2127             mins = 0 ifTrue:[
  1121                 fmt := '%(w)w %(dw)d %(Hd)h'.
  2128                 fmt := '%(w)w %(dw)d %(Hd)h'.
  1126                     ].
  2133                     ].
  1127                 ].
  2134                 ].
  1128             ].
  2135             ].
  1129         ].
  2136         ].
  1130     ] ifFalse:[days > 0 ifTrue:[
  2137     ] ifFalse:[days > 0 ifTrue:[
       
  2138         "/ notice: d here, which prints the total number of days
  1131         fmt := '%dd %(Hd)h %Mm'.
  2139         fmt := '%dd %(Hd)h %Mm'.
  1132         secs = 0 ifTrue:[
  2140         secs = 0 ifTrue:[
  1133             fmt := '%dd %(Hd)h %Mm'.
  2141             fmt := '%dd %(Hd)h %Mm'.
  1134             mins = 0 ifTrue:[
  2142             mins = 0 ifTrue:[
  1135                 fmt := '%dd %(Hd)h'.
  2143                 fmt := '%dd %(Hd)h'.
  1156             ] ifFalse:[
  2164             ] ifFalse:[
  1157                 fmt := ''
  2165                 fmt := ''
  1158             ].
  2166             ].
  1159         ].
  2167         ].
  1160     ]].
  2168     ]].
  1161     ((secs ~= 0) or:[millis ~= 0])ifTrue:[
  2169     ((secs ~= 0) or:[millis ~= 0 or:[(additionalPicoseconds?0) ~= 0]]) ifTrue:[
  1162         fmt size ~~ 0 ifTrue:[
  2170         fmt size ~~ 0 ifTrue:[
  1163             fmt := fmt , ' '
  2171             fmt := fmt , ' '
  1164         ].
  2172         ].
  1165         (millis = 0) ifTrue:[
  2173         ((millis = 0) and:[(additionalPicoseconds?0) = 0]) ifTrue:[
  1166             fmt := fmt , '%Ss'
  2174             fmt := fmt , '%Ss'
  1167         ] ifFalse:[
  2175         ] ifFalse:[
  1168             secs = 0 ifTrue:[
  2176             (secs = 0 and:[(additionalPicoseconds?0) = 0]) ifTrue:[
  1169                 fmt := fmt , '%Ims'
  2177                 fmt := fmt , '%Ims'
  1170             ] ifFalse:[
  2178             ] ifFalse:[
  1171                 shortFlag ifFalse:[
  2179                 shortFlag ifFalse:[
  1172                     "/ show millis
  2180                     "/ show millis
  1173                     fmt := fmt , '%S.%is'
  2181                     (millis ~= 0) ifTrue:[
       
  2182                         fmt := fmt , '%S.%is'
       
  2183                     ] ifFalse:[
       
  2184                         overAllMicros := self microseconds.
       
  2185                         overAllMicros > 2 ifTrue:[
       
  2186                             fmt := fmt , '%(micro)µs'.
       
  2187                         ] ifFalse:[
       
  2188                             overAllNanos := self nanoseconds.
       
  2189                             overAllNanos > 2 ifTrue:[
       
  2190                                 fmt := fmt , '%(nano)ns'.
       
  2191                             ] ifFalse:[
       
  2192                                 fmt := fmt , '%(pico)ps'.
       
  2193                             ].
       
  2194                         ].
       
  2195                     ].
  1174                 ] ifTrue:[
  2196                 ] ifTrue:[
  1175                     "/ only show millis if the number of seconds is small
  2197                     "/ only show millis if the number of seconds is small
  1176                     overAllSeconds := self asSeconds.
  2198                     overAllSeconds := self asSeconds.
  1177                     overAllSeconds > 2 ifTrue:[
  2199                     overAllSeconds > 2 ifTrue:[
  1178                         overAllSeconds > 10 ifTrue:[
  2200                         overAllSeconds > 10 ifTrue:[
  1179                             overAllSeconds > 300 ifTrue:[
  2201                             overAllSeconds > 300 ifTrue:[
       
  2202                                "/ no decimal above 300 seconds
  1180                                 fmt := fmt , '%Ss'
  2203                                 fmt := fmt , '%Ss'
  1181                             ] ifFalse:[
  2204                             ] ifFalse:[
       
  2205                                "/ 1 decimals up to 300 seconds
  1182                                 fmt := fmt , '%S.%(milli1)s'
  2206                                 fmt := fmt , '%S.%(milli1)s'
  1183                             ]
  2207                             ]
  1184                         ] ifFalse:[
  2208                         ] ifFalse:[
       
  2209                            "/ 2 decimals up to 10seconds
  1185                             fmt := fmt , '%S.%(milli2)s'
  2210                             fmt := fmt , '%S.%(milli2)s'
  1186                         ]
  2211                         ]
  1187                     ] ifFalse:[
  2212                     ] ifFalse:[
  1188                         fmt := fmt , '%S.%is'
  2213                         "/ millis up to 2seconds
       
  2214                         fmt := fmt , '%S.%is'.
  1189                     ]
  2215                     ]
  1190                 ]
  2216                 ]
  1191             ]
  2217             ]
  1192         ].
  2218         ].
  1193     ] ifFalse:[
  2219     ] ifFalse:[
  1197     ].
  2223     ].
  1198 
  2224 
  1199     ^ fmt.
  2225     ^ fmt.
  1200 
  2226 
  1201     "
  2227     "
  1202      (TimeDuration hours:0 minutes:0 seconds:0 milliseconds:12) formatForPrinting       
  2228      3001 seconds formatForPrinting:false
  1203 
  2229      3001 seconds formatForPrinting:true
  1204      (TimeDuration hours:0 minutes:0 seconds:0 milliseconds:123) formatForPrinting       
  2230 
  1205      (TimeDuration hours:0 minutes:0 seconds:10 milliseconds:123) formatForPrinting       
  2231      (TimeDuration fromString:'1w 3d') formatForPrinting
  1206      (TimeDuration hours:0 minutes:33 seconds:0 milliseconds:123) formatForPrinting       
  2232      (TimeDuration fromString:'1w 3d') printString
  1207      (TimeDuration hours:2 minutes:0 seconds:0 milliseconds:123) formatForPrinting       
  2233      (TimeDuration fromString:'7d') printString
  1208      (TimeDuration hours:2 minutes:33 seconds:0 milliseconds:123) formatForPrinting       
  2234      (TimeDuration fromString:'6d') printString
  1209      (TimeDuration hours:100 minutes:33 seconds:0 milliseconds:123) formatForPrinting    
  2235 
  1210      (TimeDuration hours:10000 minutes:33 seconds:0 milliseconds:123) formatForPrinting    
  2236      10 microSeconds formatForPrinting:false
  1211      (TimeDuration hours:1000000 minutes:33 seconds:0 milliseconds:123) formatForPrinting    
  2237      1microSeconds formatForPrinting:false
  1212 
  2238      (TimeDuration fromMilliseconds:0.5) printString
  1213      (TimeDuration hours:0 minutes:38 seconds:22 milliseconds:123) formatForPrinting:true       
  2239      (TimeDuration fromMilliseconds:0.05) printString
  1214 
  2240      (TimeDuration fromMilliseconds:0.005) printString
  1215      (TimeDuration hours:2 minutes:33 seconds:0 milliseconds:0) formatForPrinting         
  2241      (TimeDuration fromMilliseconds:0.0005) printString
  1216      (TimeDuration hours:2 minutes:0 seconds:0 milliseconds:0) formatForPrinting          
  2242      (TimeDuration fromMilliseconds:0.00005) printString
  1217      (TimeDuration hours:24 minutes:0 seconds:0 milliseconds:0) formatForPrinting          
  2243      (TimeDuration fromMilliseconds:0.000005) printString
  1218 
  2244      (TimeDuration fromMilliseconds:0.0000005) printString
  1219      (TimeDuration hours:0 minutes:0 seconds:0 milliseconds:123) printStringFormat:'%h:%m:%s'       
  2245      (TimeDuration fromMilliseconds:0.00000005) printString
  1220      (TimeDuration hours:0 minutes:0 seconds:10 milliseconds:123) printStringFormat:'%h:%m:%s'         
  2246      (TimeDuration fromMilliseconds:0.000000005) printString
  1221      (TimeDuration hours:0 minutes:33 seconds:0 milliseconds:123) printStringFormat:'%h:%m:%s'         
  2247 
  1222      (TimeDuration hours:2 minutes:33 seconds:0 milliseconds:123) printStringFormat:'%h:%m:%s'         
  2248      (TimeDuration hours:0 minutes:0 seconds:0 milliseconds:12) formatForPrinting
  1223      (TimeDuration hours:100 minutes:33 seconds:0 milliseconds:123) printStringFormat:'%h:%m:%s'      
  2249      (TimeDuration hours:0 minutes:0 seconds:2 milliseconds:12) formatForPrinting 
  1224      (TimeDuration hours:10000 minutes:33 seconds:0 milliseconds:123) printStringFormat:'%h:%m:%s'      
  2250      (TimeDuration hours:0 minutes:0 seconds:8 milliseconds:12) formatForPrinting  
  1225      (TimeDuration hours:1000000 minutes:33 seconds:0 milliseconds:123) printStringFormat:'%h:%m:%s'      
  2251      (TimeDuration hours:0 minutes:0 seconds:10 milliseconds:12) formatForPrinting  
       
  2252 
       
  2253      (TimeDuration hours:0 minutes:0 seconds:0 milliseconds:123) formatForPrinting
       
  2254      (TimeDuration hours:0 minutes:0 seconds:10 milliseconds:123) formatForPrinting
       
  2255      (TimeDuration hours:0 minutes:33 seconds:0 milliseconds:123) formatForPrinting
       
  2256      (TimeDuration hours:2 minutes:0 seconds:0 milliseconds:123) formatForPrinting
       
  2257      (TimeDuration hours:2 minutes:33 seconds:0 milliseconds:123) formatForPrinting
       
  2258      (TimeDuration hours:100 minutes:33 seconds:0 milliseconds:123) formatForPrinting
       
  2259      (TimeDuration hours:10000 minutes:33 seconds:0 milliseconds:123) formatForPrinting
       
  2260      (TimeDuration hours:1000000 minutes:33 seconds:0 milliseconds:123) formatForPrinting
       
  2261 
       
  2262      (TimeDuration hours:0 minutes:38 seconds:22 milliseconds:123) formatForPrinting:true
       
  2263 
       
  2264      (TimeDuration hours:2 minutes:33 seconds:0 milliseconds:0) formatForPrinting
       
  2265      (TimeDuration hours:2 minutes:0 seconds:0 milliseconds:0) formatForPrinting
       
  2266      (TimeDuration hours:24 minutes:0 seconds:0 milliseconds:0) formatForPrinting
       
  2267 
       
  2268      (TimeDuration hours:0 minutes:0 seconds:0 milliseconds:123) printStringFormat:'%h:%m:%s'
       
  2269      (TimeDuration hours:0 minutes:0 seconds:10 milliseconds:123) printStringFormat:'%h:%m:%s'
       
  2270      (TimeDuration hours:0 minutes:33 seconds:0 milliseconds:123) printStringFormat:'%h:%m:%s'
       
  2271      (TimeDuration hours:2 minutes:33 seconds:0 milliseconds:123) printStringFormat:'%h:%m:%s'
       
  2272      (TimeDuration hours:100 minutes:33 seconds:0 milliseconds:123) printStringFormat:'%h:%m:%s'
       
  2273      (TimeDuration hours:10000 minutes:33 seconds:0 milliseconds:123) printStringFormat:'%h:%m:%s'
       
  2274      (TimeDuration hours:1000000 minutes:33 seconds:0 milliseconds:123) printStringFormat:'%h:%m:%s'
  1226     "
  2275     "
  1227 
  2276 
  1228     "Modified: / 18-07-2007 / 14:06:17 / cg"
  2277     "Modified: / 18-07-2007 / 14:06:17 / cg"
       
  2278     "Modified (comment): / 17-05-2017 / 16:35:56 / mawalch"
       
  2279     "Modified: / 23-05-2018 / 10:36:21 / Claus Gittinger"
       
  2280     "Modified (comment): / 02-03-2020 / 11:54:02 / Stefan Vogel"
       
  2281 !
       
  2282 
       
  2283 getHours
       
  2284     "return the number of hours (truncated).
       
  2285      This is the total number of hours - not just the fractional part"
       
  2286 
       
  2287     ^ self getSeconds // 60 // 60
       
  2288 !
       
  2289 
       
  2290 getMicroseconds
       
  2291     "return the number of microseconds (truncated).
       
  2292      This is the total number of microseconds - not just the fractional part"
       
  2293 
       
  2294     ^ (timeEncoding * 1000) + ((additionalPicoseconds ? 0) // (1000 * 1000))
  1229 !
  2295 !
  1230 
  2296 
  1231 getMilliseconds
  2297 getMilliseconds
  1232     "return the number of milliseconds"
  2298     "return the number of milliseconds (truncated).
       
  2299      This is the total number of milliseconds - not just the fractional part"
  1233 
  2300 
  1234     ^ timeEncoding
  2301     ^ timeEncoding
  1235 
  2302 
  1236     "Modified: / 18-07-2007 / 13:44:33 / cg"
  2303     "Modified: / 18-07-2007 / 13:44:33 / cg"
  1237 !
  2304 !
  1238 
  2305 
       
  2306 getMinutes
       
  2307     "return the number of minutes (truncated).
       
  2308      This is the total number of minutes - not just the fractional part"
       
  2309 
       
  2310     ^ self getSeconds // 60
       
  2311 !
       
  2312 
       
  2313 getPicoseconds
       
  2314     "return the number of picoseconds (truncated).
       
  2315      This is the total number of picoseconds - not just the fractional part"
       
  2316 
       
  2317     ^ (timeEncoding * 1000000000) + ((additionalPicoseconds ? 0))
       
  2318 !
       
  2319 
  1239 getSeconds
  2320 getSeconds
  1240     "return the number of seconds"
  2321     "return the number of seconds (truncated).
       
  2322      This is the total number of seconds - not just the fractional part"
  1241 
  2323 
  1242     ^ timeEncoding // 1000
  2324     ^ timeEncoding // 1000
  1243 
  2325 
  1244     "Modified: / 18-07-2007 / 13:44:37 / cg"
  2326     "Modified: / 18-07-2007 / 13:44:37 / cg"
       
  2327     "Modified (comment): / 21-09-2017 / 18:50:03 / cg"
  1245 !
  2328 !
  1246 
  2329 
  1247 possiblyNegatedValueFromTimeEncodingInto:aBlock
  2330 possiblyNegatedValueFromTimeEncodingInto:aBlock
  1248     timeEncoding < 0 ifTrue:[
  2331     timeEncoding < 0 ifTrue:[
  1249         ^ (aBlock value:(timeEncoding negated)) negated
  2332         ^ (aBlock value:(timeEncoding negated)) negated
  1263     "set my time given individual values"
  2346     "set my time given individual values"
  1264 
  2347 
  1265     self setMilliseconds:((h * 60 * 60 ) + (m * 60) + s) * 1000 + millis.
  2348     self setMilliseconds:((h * 60 * 60 ) + (m * 60) + s) * 1000 + millis.
  1266 !
  2349 !
  1267 
  2350 
       
  2351 setMicroseconds:micros
       
  2352     "set my duration given microseconds."
       
  2353 
       
  2354     |restMicros|
       
  2355 
       
  2356     timeEncoding := micros // 1000.
       
  2357     micros isInteger ifTrue:[
       
  2358         additionalPicoseconds := (micros \\ 1000) * 1000000
       
  2359     ] ifFalse:[
       
  2360         restMicros := micros - (timeEncoding * 1000).
       
  2361         additionalPicoseconds := (restMicros * 1000000) truncated.
       
  2362     ].
       
  2363 
       
  2364     "
       
  2365      self new setMicroseconds:100
       
  2366      self new setMicroseconds:2
       
  2367      self new setMicroseconds:1.5
       
  2368      self new setMicroseconds:0.1
       
  2369     "
       
  2370 
       
  2371     "Modified: / 18-07-2007 / 13:44:16 / cg"
       
  2372     "Modified: / 27-07-2018 / 11:53:05 / Stefan Vogel"
       
  2373 !
       
  2374 
  1268 setMilliseconds:millis
  2375 setMilliseconds:millis
  1269     "set my duration given milliseconds.
  2376     "set my duration given milliseconds.
  1270      Notice that (in contrast to Time), there is no modulo operation here.
       
  1271      Duration can be longer than a day"
  2377      Duration can be longer than a day"
  1272 
  2378 
  1273     "/ self assert:(millis isInteger).
  2379     millis isInteger ifTrue:[
  1274     timeEncoding := millis rounded
  2380         timeEncoding := millis.
       
  2381     ] ifFalse:[
       
  2382         timeEncoding := millis // 1.
       
  2383         additionalPicoseconds := ((millis \\ 1) * 1000000000) truncated.
       
  2384     ]
  1275 
  2385 
  1276     "Modified: / 18-07-2007 / 13:44:16 / cg"
  2386     "Modified: / 18-07-2007 / 13:44:16 / cg"
       
  2387     "Modified: / 22-05-2018 / 16:51:30 / Stefan Vogel"
       
  2388 !
       
  2389 
       
  2390 setMilliseconds:millis additionalPicoseconds:picos
       
  2391     "set my duration given milliseconds and addon picos.
       
  2392      Duration can be longer than a day; 
       
  2393      values may be negative (eg. if resulting from a subtraction)"
       
  2394 
       
  2395     |rest newMillis newPicos|
       
  2396 
       
  2397     millis isInteger ifTrue:[
       
  2398         newMillis := millis.
       
  2399         newPicos := 0.
       
  2400     ] ifFalse:[
       
  2401         newMillis := millis truncated.
       
  2402         rest := millis - newMillis.
       
  2403         newPicos := (rest * 1000000000) truncated.
       
  2404     ].
       
  2405 
       
  2406     picos ~= 0 ifTrue:[
       
  2407         newPicos := (newPicos + picos) truncated.
       
  2408         newMillis := newMillis + (newPicos // 1000000000).
       
  2409         newPicos := newPicos \\ 1000000000.
       
  2410     ].
       
  2411     timeEncoding := newMillis.
       
  2412     additionalPicoseconds := newPicos.
       
  2413 
       
  2414     "Modified: / 18-07-2007 / 13:44:16 / cg"
       
  2415     "Modified: / 22-05-2018 / 16:55:53 / Stefan Vogel"
       
  2416 !
       
  2417 
       
  2418 setNanoseconds:nanos
       
  2419     "set my duration given nanoseconds."
       
  2420 
       
  2421     |millis restNanos|
       
  2422 
       
  2423     millis := nanos // (1000*1000).
       
  2424     timeEncoding := millis.
       
  2425     nanos isInteger ifTrue:[
       
  2426         restNanos := nanos \\ (1000*1000).
       
  2427         additionalPicoseconds := restNanos * 1000 
       
  2428     ] ifFalse:[
       
  2429         restNanos := nanos - (millis * 1000000).
       
  2430         additionalPicoseconds := (restNanos * 1000) truncated.
       
  2431     ].
       
  2432 
       
  2433     "
       
  2434      self new setMicroseconds:4
       
  2435      self new setNanoseconds:4
       
  2436      self new setNanoseconds:4000
       
  2437      self new setNanoseconds:4000000
       
  2438      self new setNanoseconds:40000000
       
  2439      self new setNanoseconds:0.1
       
  2440     "
       
  2441 
       
  2442     "Modified: / 18-07-2007 / 13:44:16 / cg"
       
  2443     "Modified: / 27-07-2018 / 11:53:41 / Stefan Vogel"
       
  2444 !
       
  2445 
       
  2446 setPicoseconds:picos
       
  2447     "set my duration given picoseconds."
       
  2448 
       
  2449     timeEncoding := picos // 1000000000.
       
  2450     additionalPicoseconds := (picos \\ 1000000000) truncated.
       
  2451 
       
  2452     "
       
  2453      self new setMicroseconds:4
       
  2454      self new setNanoseconds:4
       
  2455      self new setPicoseconds:4
       
  2456      self new setPicoseconds:4.5
       
  2457 
       
  2458      self assert: (self new setPicoseconds:4000) = (self new setNanoseconds:4) .
       
  2459      self assert: (self new setPicoseconds:4000000) = (self new setNanoseconds:4000) .
       
  2460      self assert: (self new setPicoseconds:4000000) = (self new setMicroseconds:4) .
       
  2461      self assert: (self new setPicoseconds:4000000000) = (self new setNanoseconds:4000000) .
       
  2462      self assert: (self new setPicoseconds:4000000000) = (self new setMicroseconds:4000) .
       
  2463      self assert: (self new setPicoseconds:4000000000) = (self new setMilliseconds:4) .
       
  2464      self assert: (self new setPicoseconds:4000000000000) = (self new setMilliseconds:4000) .
       
  2465      self assert: (self new setPicoseconds:4000000000000) = (self new setMicroseconds:4000000) .
       
  2466      self assert: (self new setPicoseconds:4000000000000) = (self new setNanoseconds:4000000000) .
       
  2467      self assert: (self new setPicoseconds:4000000000000) = (self new setSeconds:4) .
       
  2468     "
       
  2469 
       
  2470     "Modified: / 18-07-2007 / 13:44:16 / cg"
       
  2471     "Modified: / 22-05-2018 / 16:51:45 / Stefan Vogel"
  1277 !
  2472 !
  1278 
  2473 
  1279 setSeconds:secs
  2474 setSeconds:secs
  1280     "set my timeduration given seconds.
  2475     "set my timeduration given seconds.
  1281      Notice that (in contrast to Time), there is no modulu operation here.
  2476      Notice that (in contrast to Time), there is no modulu operation here.
  1282      Duration can be longer than a day"
  2477      Duration can be longer than a day, and (much) smaller than a second"
  1283 
  2478 
  1284     self setMilliseconds:(secs * 1000).
  2479     self setMilliseconds:(secs * 1000).
  1285 
  2480 
  1286     "Modified: / 18-07-2007 / 13:44:24 / cg"
  2481     "Modified: / 18-07-2007 / 13:44:24 / cg"
  1287 ! !
  2482 ! !
  1292     ^ true
  2487     ^ true
  1293 !
  2488 !
  1294 
  2489 
  1295 isZero
  2490 isZero
  1296     ^ self = self class zero
  2491     ^ self = self class zero
  1297 !
       
  1298 
       
  1299 negative
       
  1300     ^ timeEncoding < 0
       
  1301 ! !
  2492 ! !
  1302 
  2493 
  1303 !TimeDuration class methodsFor:'documentation'!
  2494 !TimeDuration class methodsFor:'documentation'!
  1304 
  2495 
  1305 version
  2496 version