TimeDuration.st
author Claus Gittinger <cg@exept.de>
Tue, 09 Jul 2019 20:55:17 +0200
changeset 24417 03b083548da2
parent 24365 b0e21078359c
child 24523 758ae1a35ecb
permissions -rw-r--r--
#REFACTORING by exept class: Smalltalk class changed: #recursiveInstallAutoloadedClassesFrom:rememberIn:maxLevels:noAutoload:packageTop:showSplashInLevels: Transcript showCR:(... bindWith:...) -> Transcript showCR:... with:...

"{ Encoding: utf8 }"

"
 COPYRIGHT (c) 1989 by Claus Gittinger
	      All Rights Reserved

 This software is furnished under a license and may be used
 only in accordance with the terms of that license and with the
 inclusion of the above copyright notice.   This software may not
 be provided or otherwise made available to, or used by, any
 other person.  No title to or ownership of the software is
 hereby transferred.
"
"{ Package: 'stx:libbasic' }"

"{ NameSpace: Smalltalk }"

Time subclass:#TimeDuration
	instanceVariableNames:'additionalPicoseconds'
	classVariableNames:'DefaultFormatForPrinting TimeDurationZero'
	poolDictionaries:''
	category:'Magnitude-Time'
!

!TimeDuration class methodsFor:'documentation'!

copyright
"
 COPYRIGHT (c) 1989 by Claus Gittinger
	      All Rights Reserved

 This software is furnished under a license and may be used
 only in accordance with the terms of that license and with the
 inclusion of the above copyright notice.   This software may not
 be provided or otherwise made available to, or used by, any
 other person.  No title to or ownership of the software is
 hereby transferred.
"
!

documentation
"
    Represents a time/timestamp difference.

    The resolution is 1 ps.
    However, such small timedurations are usually only created by physical computations
    (see goodies/physic).
    The typical OS-time resolution is in the milli- or microsecond range.
    External logging hardware may generate timestamps in the micro- or nanosecond range.
    Picosecond resolution should be good enough for almost any application (at least for the near future).

    Most timedurations only require/have millisecond resolution,
    so the pico instvar is nil/0 and does not require an aditional largeInteger operation.

    DefaultFormatForPrinting    if non-nil, allows for the variable printFormat to be overwritten
"
! !

!TimeDuration class methodsFor:'instance creation'!

days:d 
    "return a new TimeDuration representing a duration of d days."

    d == 0 ifTrue:[^ TimeDurationZero].
    ^ self hours:(d*24) minutes:0

    "
     TimeDuration days:1  
    "
!

days:d hours:h minutes:m seconds:s 
    "return a new TimeDuration representing a duration of d days, h hours, m minutes and s seconds.
     See also Time now / Date today / Timestamp now."

    ^ self basicNew 
        setHours:(d*24)+h minutes:m seconds:s milliseconds:0

    "
     TimeDuration days:1  hours:2 minutes:33 seconds:0   
     TimeDuration days:4 hours:100 minutes:33 seconds:0   
    "
!

fromHours:hoursInterval
    "return a new TimeDuration representing a duration of n hours."

    ^ self new setSeconds:(hoursInterval * (60*60))

    "
     TimeDuration fromHours:8  
    "
!

fromMicroseconds:n
    "return a new TimeDuration representing a duration of n microseconds."

    ^ self new setMicroseconds:n

    "
     TimeDuration fromMicroseconds:500  
     500 microseconds  
    "

    "Created: / 18-07-2007 / 13:56:25 / cg"
!

fromMilliseconds:n
    "return a new TimeDuration representing a duration of n milliseconds."
    "redefined to disable wrapping at 24hours."

    ^ self new setMilliseconds:n

    "
     TimeDuration fromMilliseconds:500  
     500 milliseconds  
    "

    "Created: / 18-07-2007 / 13:56:25 / cg"
!

fromMinutes:minutesInterval
    "return a new TimeDuration representing a duration of n minutes."

    ^ self new setSeconds:(minutesInterval * 60)

    "
     TimeDuration fromMinutes:120  
    "
!

fromNanoseconds:n
    "return a new TimeDuration representing a duration of n nanoseconds."

    ^ self new setNanoseconds:n

    "
     TimeDuration fromNanoseconds:500  
     500 nanoseconds  
    "
!

fromPicoseconds:n
    "return a new TimeDuration representing a duration of n picoseconds."

    ^ self new setPicoseconds:n

    "
     TimeDuration fromPicoseconds:500  
     500 picoseconds  
    "
!

fromSeconds:secondsInterval
    "return a new TimeDuration representing a duration of n seconds."
    "redefined to disable wrapping at 24hours."

    ^ self new setSeconds:secondsInterval

    "
     TimeDuration fromSeconds:3600  
    "
!

hours:h
    "return a new TimeDuration representing a duration of h hours.
     See also Time now / Date today / Timestamp now."

    h == 0 ifTrue:[^ TimeDurationZero].
    ^ self basicNew setHours:h minutes:0 seconds:0 milliseconds:0

    "
     TimeDuration hours:2 
     TimeDuration hours:100  
    "

    "Created: / 14-07-2007 / 18:15:51 / cg"
!

hours:h minutes:m seconds:s millis:millis
    <resource: #obsolete>
    "return a new TimeDuration representing a duration of h hours, m minutes, s seconds and millis milliseconds.
     See also Time now / Date today / Timestamp now."

    self obsoleteMethodWarning:'use hours:minutes:seconds:milliseconds:'.
    ^ self hours:h minutes:m seconds:s milliseconds:millis

    "
     TimeDuration hours:2 minutes:33 seconds:0 milliseconds:123  
     TimeDuration hours:100 minutes:33 seconds:0 milliseconds:123  
    "
!

microseconds:microseconds
    "return a new TimeDuration representing a duration of microseconds microseconds.
     Now we support microseconds (even picoseconds) but we still round to milliseconds for backward
     compatibility with the historic interface."

    microseconds == 0 ifTrue:[^ TimeDurationZero].
    ^ self basicNew setMilliseconds:((microseconds / 1000) rounded).

    "
     TimeDuration microseconds:2499 
     TimeDuration microseconds:2500 
     TimeDuration microseconds:12345678900 
    "

    "Modified (comment): / 22-05-2018 / 16:54:17 / Stefan Vogel"
!

milliseconds:m
    "return a new TimeDuration representing a duration of m millis.
     See also Time now / Date today / Timestamp now."

    m == 0 ifTrue:[^ TimeDurationZero].
    ^ self basicNew setMilliseconds:m

    "
     TimeDuration milliseconds:2 
    "
!

minutes:m
    "return a new TimeDuration representing a duration of m minutes.
     See also Time now / Date today / Timestamp now."

    m == 0 ifTrue:[^ TimeDurationZero].
    ^ self basicNew setHours:0 minutes:m seconds:0 milliseconds:0

    "
     TimeDuration minutes:2 
    "

    "Created: / 06-08-2007 / 15:32:42 / cg"
!

readFrom:aStringOrStream defaultUnit:defaultUnitOrNilArg onError:exceptionBlock
    "return a new TimeDuration, reading a printed representation from aStream.
     The format is either:
        [n 'yr'] [n 'mon'] [n 'w'] [n 'd'] [n 'h'] [n 'm'] [n 's'] 
                 ([n 'ms'] | [n 'us'] | [n 'ns'] | [n 'ps'])
        where 
            yr -> year
            mon -> month
            w -> week
            d -> day
            h -> hour
            m -> minutes
            s -> seconds
            ms -> milliseconds (only one of ms,us,ns or ps can follow)
            us -> microseconds
            ns -> nanoseconds
            ps -> picoseconds
     or:
        h:m:s.<ms2>
        h:m:s.<fract>

     The yr and mon specifiers stand for 365d and 30d respectively.
     If defaultUnitOrNil is non-nil, a plain number is treated as that;
     otherwise, a plain number raises an error.
     Individual components may be negative, as in '1h -10m', which gives 50m
     or the whole duration may be negative, as in '-(1h 10m)'
    "

    ^ [
        |seconds millis picos restMillis 
         t1 str val fraction mantissa uIdx unit unitChar1 negative defaultUnitOrNil|

        defaultUnitOrNil := defaultUnitOrNilArg.
        str := aStringOrStream readStream.
        seconds := 0.
        millis := 0.
        picos := 0.

        negative := false.
        str peek == $- ifTrue:[
            str next.
            str peek == $( ifTrue:[
                |t|
                str next.
                t := self readFrom:str defaultUnit:defaultUnitOrNil onError:[^ exceptionBlock value].
                str skipSeparators.
                str peek == $) ifTrue:[
                    str next.
                    ^ t negated.
                ].
                ^ exceptionBlock value.
            ].                
            negative := true.
        ].
        
        [
            |nextCh|

            val := Integer readFrom:str onError:nil.
            val isNil ifTrue:[^ exceptionBlock value].
            negative ifTrue:[ val := val negated. negative := false. ].
            str peek == $: ifTrue:[
                "/ hour:minutes format
                str next.
                seconds := val*3600.
                val := Integer readFrom:str onError:nil.
                val isNil ifTrue:[^ exceptionBlock value].
                seconds := seconds + (val*60).
                str peek == $: ifTrue:[
                    "/ hour:minutes:seconds format
                    str next.
                    val := Integer readFrom:str onError:nil.
                    val isNil ifTrue:[^ exceptionBlock value].
                    seconds := seconds + val.
                    (str peek == $. or:[str peek == $,]) ifTrue:[
                        "/ hour:minutes:seconds.millis format
                        str next.
                        "/ the old code here was wrong in assuming that exactly 3 digits
                        "/ are coming; thus hh:mm:ss.1 was interpreted as 1ms (instead of 100)
                        "/ thus: count the zeros...
                        str peek isDigit ifTrue:[
                            "/ fraction := Number readMantissaFrom:str radix:10.
                            "/ fraction isNil ifTrue:[^ exceptionBlock value].
                            "/ ignore the float value; take the fraction

                            mantissa := Number readMantissaAndScaleFrom:str radix:10.
                            fraction := (mantissa at:2) / (10 raisedTo:(mantissa at:3)).
                            (mantissa at:3) > 3 ifTrue:[
                                picos := fraction * (1000 * 1000 * 1000 * 1000).
                                millis := picos // (1000 * 1000 * 1000).
                                picos := picos \\ (1000 * 1000 * 1000).
                            ] ifFalse:[
                                millis := fraction * 1000.
                            ].
                        ] ifFalse:[
                            millis := 0
                        ].
                    ]
                ].
                t1 := self fromMilliseconds:(seconds*1000+millis).
                picos notNil ifTrue:[
                    t1 additionalPicoseconds:picos
                ].
                ^ t1
            ].
            ((str peek == $.) or:[(str peek == $,)]) ifTrue:[
                str next.
                "/ fraction := Number readMantissaFrom:str radix:10.
                "/ ignore the float value; take the fraction
                mantissa := Number readMantissaAndScaleFrom:str radix:10.
                fraction := (mantissa at:2) / (10 raisedTo:(mantissa at:3)).
                val := val + fraction.
            ].
            str skipSeparators.
            str atEnd ifTrue:[
                defaultUnitOrNil isNil ifTrue:[
                    ^ exceptionBlock value
                ].
                "/ no unit given - assume defaultUnit
                unitChar1 := defaultUnitOrNil.
                "/ can be only used for one number
                defaultUnitOrNil := nil.
            ] ifFalse:[
                unitChar1 := str next.
            ].

            str atEnd ifFalse:[ 
                nextCh := str peek
            ].

            "/ milli, micro, nano and pico
            unitChar1 == $µ ifTrue:[ unitChar1 := $u].
            uIdx := 'munp' indexOf:unitChar1.
            ((uIdx ~~ 0) and:[nextCh == $s]) ifTrue:[
                unitChar1 == $m ifTrue:[
                    millis := millis + val.
                ] ifFalse:[
                    unit := #(
                          1000000       "us" 
                          1000          "ns" 
                          1             "ps" 
                          ) at:uIdx-1.
                    picos := (unit * val).
                    millis := picos // (1000 * 1000 * 1000).
                    picos := picos \\ (1000 * 1000 * 1000).
                ].
            ] ifFalse:[
                uIdx := 'ywdhms' indexOf:unitChar1.
                uIdx == 0 ifTrue:[^ exceptionBlock value].

                (unitChar1 == $m and:[nextCh == $s]) ifTrue:[
                    millis := millis + val.
                ] ifFalse:[
                    (unitChar1 == $m and:[nextCh == $o]) ifTrue:[
                        unit := 2592000 "24*60*60*30"     "mon"
                    ] ifFalse:[
                        unit := #(
                                  31536000 "24*60*60*365" "yr"
                                  604800 "24*60*60*7"     "w"
                                  86400  "24*60*60"       "d"
                                  3600                    "h"
                                  60                      "m"
                                  1 ) at:uIdx.
                    ].
                    seconds := seconds + (unit * val).
                ].
            ].
            [str atEnd not and:[str peek isSeparator not and:[str peek ~~ $)]]] whileTrue:[ str next].
            str skipSeparators.
            "/ done when at the end or a $) is to be read
            str atEnd or:[aStringOrStream isString not and:[str peek == $)]]
        ] whileFalse.
        millis := (seconds*1000) + millis.
        restMillis := millis - millis truncated.
        millis := millis truncated.
        picos := picos + (restMillis * 1000 * 1000 * 1000) truncated. 
        millis := millis + (picos // (1000*1000*1000)).
        picos := picos \\ (1000*1000*1000).
        t1 := self fromMilliseconds:millis asInteger.
        t1 additionalPicoseconds:picos.
        t1
    ] on:Error do:[:ex |
        |t|

        "/ retry, using inherited readFrom (Object-storeString)
        t := Object readFrom:aStringOrStream onError:[^ exceptionBlock value].
        (t isTimeDuration) ifFalse:[
            ^ exceptionBlock value
        ].
        t
    ]

    "
     TimeDuration readFrom:'2' defaultUnit:$h onError:nil -> 2h
     TimeDuration readFrom:'100' defaultUnit:$m onError:nil -> 1h 40m
     TimeDuration readFrom:'100' defaultUnit:$s onError:nil -> 1m 40s
     TimeDuration readFrom:'0200' defaultUnit:$h onError:nil -> 1w 1d 8h

     TimeDuration readFrom:'1h'      
     TimeDuration readFrom:'1h 35m'     
     TimeDuration readFrom:'25h'     
     TimeDuration readFrom:'3d'     
     TimeDuration readFrom:'1w'     
     TimeDuration readFrom:'120s'     
     TimeDuration readFrom:'1500ms'    
     TimeDuration readFrom:'3ms'     
     TimeDuration readFrom:'1yr 5d'     
     TimeDuration readFrom:'1mon'     
     TimeDuration readFrom:'05:10'     
     TimeDuration readFrom:'05:10:5'     
     TimeDuration readFrom:'05:10:5.150'  

     TimeDuration readFrom:'-1h'
     TimeDuration readFrom:'-1h 10m'
     TimeDuration readFrom:'1h -10m'
     TimeDuration readFrom:'-(1h 10m)' 

     TimeDuration readFrom:'1ms' -> 1ms 
     TimeDuration readFrom:'5us' 
     TimeDuration readFrom:'5µs' 
     TimeDuration readFrom:'5ns' 
     TimeDuration readFrom:'5ps' 
     TimeDuration readFrom:'5005 ps' 
     TimeDuration readFrom:'1.01 s' -> 1.010s 
     TimeDuration readFrom:'1.001 s' -> 1.001s 
     TimeDuration readFrom:'1.0001 s' -> 1.0001s 
     TimeDuration readFrom:'1s 5ns' -> 1.000000005s
     (TimeDuration readFrom:'1s 5ns') = (TimeDuration fromNanoseconds:(5+1000000000))

     TimeDuration readFrom:(TimeDuration new storeString)
    "

    "Modified: / 08-10-2007 / 16:41:48 / cg"
    "Modified: / 27-07-2018 / 11:51:42 / Stefan Vogel"
!

readFrom:aStringOrStream onError:exceptionBlock
    "return a new TimeDuration, reading a printed representation from aStream.
     The format is [n 'yr'] [n 'mon'] [n 'w'] [n 'd'] [n 'h'] [n 'm'] [n 's'] [n 'ms']
     where 
            yr -> year
            mon -> month
            w -> week
            d -> day
            h -> hour
            m -> minutes
            s -> seconds
            ms -> milliseconds
     The yr and mon specifiers stand for 365d and 30d respectively.
     If no unit is given (i.e. a plain number string is given), assume seconds.
    "

    ^ self readFrom:aStringOrStream defaultUnit:$s onError:exceptionBlock

    "
     TimeDuration readFrom:'100' onError:nil      
     TimeDuration readFrom:'100' defaultUnit:$m onError:nil 

     TimeDuration readFrom:'1h'      
     TimeDuration readFrom:'1h 35m'     
     TimeDuration readFrom:'25h'     
     TimeDuration readFrom:'3d'     
     TimeDuration readFrom:'1w'     
     TimeDuration readFrom:'120s'     
     TimeDuration readFrom:'1500ms    
     TimeDuration readFrom:'3ms'     
     TimeDuration readFrom:'1yr 5d'     
     TimeDuration readFrom:'1mon'     
    "

    "Modified: / 08-10-2007 / 16:41:48 / cg"
!

seconds:s
    "return a new TimeDuration representing a duration of s seconds.
     See also Time now / Date today / Timestamp now."

    s == 0 ifTrue:[^ TimeDurationZero].

    ^ self basicNew setMilliseconds:(s * 1000)

    "
     TimeDuration seconds:2 
    "

    "Created: / 06-08-2007 / 15:32:21 / cg"
!

weeks:w 
    "return a new TimeDuration representing a duration of w weeks."

    ^ self days:(w * 7)

    "
     TimeDuration weeks:1  
    "

    "Created: / 05-09-2011 / 11:18:27 / cg"
!

years:y 
    "return a new TimeDuration representing a duration of y years."

    ^ self days:(y * 365)

    "
     TimeDuration years:1  
    "

    "Created: / 08-05-2019 / 12:42:16 / Claus Gittinger"
! !

!TimeDuration class methodsFor:'class initialization'!

initialize
    TimeDurationZero isNil ifTrue:[
        TimeDurationZero := self basicNew setHours:0 minutes:0 seconds:0 milliseconds:0.
    ]

    "Modified: / 10-05-2011 / 10:31:35 / cg"
! !

!TimeDuration class methodsFor:'constants'!

zero
    "return the neutral element for addition (0s)"

    ^ TimeDurationZero

    "Modified: 18.7.1996 / 12:26:12 / cg"
! !

!TimeDuration class methodsFor:'format strings'!

defaultFormatForPrinting
    ^  DefaultFormatForPrinting
!

defaultFormatForPrinting:aString
    DefaultFormatForPrinting := aString
!

formatString12us
    "return the format string used to format US times (and other areas)"

    ^ '%h:%m:%s.%i'
!

formatString24
    "return the format string used to format european times (and other areas)"

    ^ '%h:%m:%s.%i'
! !

!TimeDuration class methodsFor:'timing evaluation'!

toRun:aBlock
    "return the TimeDuration it takes to execute aBlock.                          
     A modern variant of Time millisecondsToRun: (which prints itself nicely)"

    ^ self microseconds:(Time microsecondsToRun:aBlock).

    "
     TimeDuration toRun:[ 20000 factorial ]     
     TimeDuration toRun:[ 2000 factorial ]     
     TimeDuration toRun:[ 900 factorial ]     
    "
! !

!TimeDuration methodsFor:'Compatibility-Squeak'!

wait
    "wait the receiver's timeDuration"
    
    Delay waitFor:self

    "
     5 seconds wait
    "

    "Modified (comment): / 26-06-2019 / 11:35:02 / Claus Gittinger"
! !

!TimeDuration methodsFor:'accessing'!

days
    "get the (truncated) total number of days.
     Use this only for printing.
     Sigh: this is inconsistent: hours, minutes, seconds etc. 
     return the fraction, not the total"

    ^ self 
        possiblyNegatedValueFromTimeEncodingInto:[:t |
            t // 1000 // 3600 // 24
        ].    

    "
     (Duration fromString:'1mon 1d 4h 3m 5s 10ms') days

     (Duration days:9 hours:1 minutes:2 seconds:3) days   
     (Duration days:-9 hours:-1 minutes:-2 seconds:-3) days 
    "
!

hours
    "get the (truncated) number of hours.
     notice: that is NOT the total number of hours,
     but the fractional part only. 
     Use this only for printing"

    ^ self 
        possiblyNegatedValueFromTimeEncodingInto:[:t |
            (t // 1000 // 3600 \\ 24)
        ]
    "
     (Duration fromString:'1d 4h 3m 5s 10ms') hours
     (Duration fromString:'1d 4h 3m 1s 10ms') getHours

     (Duration days: 9 hours: 1 minutes: 2 seconds: 3) hours
     (Duration days: -9 hours: -1 minutes: -2 seconds: -3) hours
    "

    "Modified (comment): / 21-09-2017 / 18:53:32 / cg"
!

milliseconds
    "get the milliseconds part 
     notice: that is NOT the total number of millis,
     but the fractional part (within the second) only. 
     Use this only for printing.
     asMilliseconds is probably what you want"

    ^ self 
        possiblyNegatedValueFromTimeEncodingInto:[:t |
            t \\ 1000
        ].    
    "
     (Duration milliseconds:10) milliseconds
     (Duration milliseconds:-10) milliseconds

     (Duration fromString:'1s 10ms') milliseconds
     (Duration fromString:'1s 10ms') getMilliseconds
    "

    "Modified: / 05-05-2010 / 14:22:04 / cg"
    "Modified (comment): / 21-09-2017 / 18:53:26 / cg"
!

minutes
    "get the number of minutes.
     notice: that is NOT the total number of minutes,
     but the fractional part only. 
     Use this only for printing"

    ^ self 
        possiblyNegatedValueFromTimeEncodingInto:[:t |
            t // 1000 // 60 \\ 60
        ]
        
    "
     (Duration fromString:'1h 3m 5s 10ms') minutes
     (Duration fromString:'1h 3m 1s 10ms') getMinutes

     (Duration days: 9 hours: 1 minutes: 2 seconds: 3) minutes
     (Duration days: -9 hours: -1 minutes: -2 seconds: -3) minutes
    "

    "Modified (comment): / 21-09-2017 / 18:53:22 / cg"
!

picoseconds
    "get the optional additional picoseconds (0..999999999)
     notice: that is NOT the total number of picoseconds,
     but the fractional part (within the second) only. 
     Use this only for printing."

    ^ (self milliseconds * 1000 * 1000 * 1000) + (additionalPicoseconds ? 0)
!

seconds
    "get the number of seconds.
     notice: that is NOT the total number of seconds,
     but the fractional part only. 
     Use this only for printing.
     asSeconds is probably what you want"

    ^ self 
        possiblyNegatedValueFromTimeEncodingInto:[:t |
            t // 1000 \\ 60
        ]
        
    "
     (Duration fromString:'1m 5s 10ms') seconds
     (Duration fromString:'1m 1s 10ms') getSeconds

     (Duration days: 9 hours: 1 minutes: 2 seconds: 3) seconds
     (Duration days: -9 hours: -1 minutes: -2 seconds: -3) seconds
    "

    "Modified (comment): / 21-09-2017 / 18:53:13 / cg"
! !

!TimeDuration methodsFor:'arithmetic'!

* aNumber
    "return a new scaled timeDuration"

    aNumber isNumber ifTrue:[
        ^ self species basicNew 
            setMilliseconds:(timeEncoding * aNumber)
            additionalPicoseconds:(additionalPicoseconds ? 0) * aNumber.
    ].

    "/ notice: although noone seems to implement it (currently),
    "/ there are additional packages which add support (i.e. goodies/physic),
    "/ so do not remove the call below.
    ^ aNumber productFromTimeDuration:self
    
    "
     5 c* (TimeDuration fromString:'10s')

     (TimeDuration fromString:'10s') * 5
     (TimeDuration fromString:'10s') * 10
     (TimeDuration fromString:'10s') * 100
     (TimeDuration fromString:'10s') * 1000
     (TimeDuration fromString:'-10s') * 1000
     (TimeDuration fromString:'10s') * (TimeDuration fromString:'10s')

     (TimeDuration fromString:'10ms') * 5
     (TimeDuration fromString:'10us') * 5
    "

    "Modified: / 27-07-2018 / 10:32:02 / Stefan Vogel"
!

+ aTimeDurationOrNumberOfSeconds
    "return a new timeDuration.
     The argument may be a timeDuration or
     a number, which is interpreted as seconds."

    |newMillis newPicos|

    aTimeDurationOrNumberOfSeconds isNumber ifTrue:[
        newMillis := timeEncoding + (aTimeDurationOrNumberOfSeconds * 1000) asInteger.
        newPicos := additionalPicoseconds ? 0.
        ^ self species basicNew
            setMilliseconds:newMillis additionalPicoseconds:newPicos
    ].
    ^ aTimeDurationOrNumberOfSeconds sumFromTimeDuration:self.

    "
     (TimeDuration fromString:'1m') + (TimeDuration fromString:'10s') 
     1 minutes - 10 seconds
    "

    "Created: / 25-07-2018 / 20:58:17 / Stefan Vogel"
    "Modified: / 27-07-2018 / 10:32:21 / Stefan Vogel"
!

- aTimeDurationOrNumberOfSeconds
    "return a new timeDuration.
     The argument may be a timeDuration or
     a number, which is interpreted as seconds."

    |newMillis newPicos|

    aTimeDurationOrNumberOfSeconds isNumber ifTrue:[
        newMillis := timeEncoding - (aTimeDurationOrNumberOfSeconds * 1000) asInteger.
        newPicos := additionalPicoseconds ? 0.
        ^ self species basicNew
            setMilliseconds:newMillis additionalPicoseconds:newPicos
    ].
    ^ aTimeDurationOrNumberOfSeconds differenceFromTimeDuration:self.

    "
     (TimeDuration fromString:'1m') - (TimeDuration fromString:'10s') 
     1 minutes - 10 seconds
    "

    "Modified: / 27-07-2018 / 10:32:29 / Stefan Vogel"
!

/ aTimeDurationOrNumberOfSeconds
    "if the argument is a number, return a new timeDuration.
     Otherwise, return the quotient as a number."

    aTimeDurationOrNumberOfSeconds isNumber ifTrue:[
        ^ self species basicNew 
            setMilliseconds:(timeEncoding / aTimeDurationOrNumberOfSeconds)
            additionalPicoseconds:((additionalPicoseconds?0) / aTimeDurationOrNumberOfSeconds).
    ].
    aTimeDurationOrNumberOfSeconds isTimeDuration ifTrue:[
        ^ self getPicoseconds / aTimeDurationOrNumberOfSeconds getPicoseconds.
    ].

    "/ notice: although noone seems to implement it (currently),
    "/ there are additional packages which add support (i.e. goodies/physic),
    "/ so do not remove the call below.
    ^ aTimeDurationOrNumberOfSeconds quotientFromTimeDuration:self
    
    "
     (TimeDuration fromString:'10s') / (TimeDuration fromString:'5s')
     (TimeDuration fromString:'10s') / 5
    "

    "Modified (format): / 27-07-2018 / 10:38:07 / Stefan Vogel"
!

// aTimeDurationOrNumberOfSeconds
    "if the argument is a number, return a new timeDuration.
     Otherwise, return the quotient as a number."

    aTimeDurationOrNumberOfSeconds isNumber ifTrue:[
        ^ self species basicNew 
            setSeconds:(self getSeconds // aTimeDurationOrNumberOfSeconds)
    ].
    aTimeDurationOrNumberOfSeconds isTimeDuration ifTrue:[
        ^ (self getSeconds // aTimeDurationOrNumberOfSeconds getSeconds)
    ].

    "/ notice: although noone seems to implement it (currently),
    "/ there are additional packages which add support (i.e. goodies/physic),
    "/ so do not remove the call below.
    ^ (aTimeDurationOrNumberOfSeconds quotientFromTimeDuration:self) truncated
    
    "
     (TimeDuration fromString:'10s') // (TimeDuration fromString:'3')
     (TimeDuration fromString:'10s') // 3

     (TimeDuration fromString:'10s') / (TimeDuration fromString:'3')
     (TimeDuration fromString:'10s') / 3
    "
!

abs
    ^ self class new setMilliseconds:(self asExactMilliseconds abs)

    "
     (TimeDuration fromSeconds:3600) abs
     (TimeDuration fromSeconds:-3600) abs

     (TimeDuration fromSeconds:20000) abs
     (TimeDuration fromSeconds:-20000) abs
    "
!

negated
    ^ self class new setMilliseconds:(self asExactMilliseconds) negated

    "
     50 nanoseconds negated asNanoseconds
     1 seconds negated asSeconds
    "
!

squared
    "answer a  float representing my value in seconds - squared.
     Used to compute e.g. variance and standard deviation."

    ^ self secondsAsFloat squared

    "
     50 nanoseconds squared 
     1 seconds squared
    "

    "Created: / 15-03-2019 / 17:57:50 / Stefan Vogel"
! !

!TimeDuration methodsFor:'comparing'!

< something
    |otherTimeEncoding|
    
    something class == self class ifTrue:[
        otherTimeEncoding :=something timeEncoding.
        timeEncoding = otherTimeEncoding ifTrue:[
            ^ (additionalPicoseconds ? 0) < something additionalPicoseconds
        ].    
        ^ timeEncoding < otherTimeEncoding
    ].    
    ^ super < something

    "Created: / 26-05-2019 / 10:02:59 / Claus Gittinger"
!

= something
    something class == self class ifTrue:[
        ^ timeEncoding = something timeEncoding
        and:[(additionalPicoseconds ? 0) = something additionalPicoseconds]
    ].    
    ^ super = something

    "Created: / 26-05-2019 / 09:40:44 / Claus Gittinger"
!

hash
    ^ timeEncoding bitXor:(additionalPicoseconds ? 0)

    "Created: / 26-05-2019 / 09:45:19 / Claus Gittinger"
! !

!TimeDuration methodsFor:'converting'!

asExactHours
    "answer the duration as hours.
     In contrast to asTruncatedHours, which returns them truncated,
     this may return a non-integer value."

    ^ self asExactSeconds / (3600)

    "
     (2 hours + 10 minutes + 30 seconds) asExactHours
     (2 hours + 10 minutes + 30 seconds) asExactHours asFloat
     (2 hours + 10 minutes + 30 seconds) asTruncatedHours
     (2 hours + 10 minutes) asExactHours asFloat
     (2 hours + 10 minutes) asTruncatedHours
     10 milliseconds asExactHours 
     10 milliseconds asExactHours asFloat 
    "
!

asExactMicroseconds
    "return the exact number of mcroseconds.
     In contrast to asMicroSeconds, which returns them truncated,
     this may return a non-integer value."

    additionalPicoseconds isNil ifTrue:[
        ^ (timeEncoding * 1000) "/ millis as micros
    ].
    ^ (timeEncoding * 1000)                    "/ millis as micros 
    + (additionalPicoseconds / (1000 * 1000))  "/ picos as microseconds.

    "
     40 milliseconds asExactMicroseconds
     40 microseconds asExactMicroseconds
     40 nanoseconds asExactMicroseconds
     40 picoseconds asExactMicroseconds
    "

    "Created: / 21-09-2017 / 18:52:26 / cg"
!

asExactMilliseconds
    "return the exact number of milliseconds.
     In contrast to asMilliSeconds, which returns them truncated,
     this may return a non-integer value."

    additionalPicoseconds isNil ifTrue:[
        ^ timeEncoding "/ millis
    ].
    ^ timeEncoding                         "/ millis 
      + (additionalPicoseconds / (1000 * 1000 * 1000))  "/ picos as milliseconds.

    "
     40 milliseconds asExactMilliseconds
     40 microseconds asExactMilliseconds
     40 nanoseconds asExactMilliseconds
     40 picoseconds asExactMilliseconds
    "

    "Created: / 21-09-2017 / 18:52:26 / cg"
    "Modified (format): / 24-07-2018 / 16:27:10 / Stefan Vogel"
!

asExactMinutes
    "answer the duration as minutes.
     In contrast to asTruncatedMinutes, which returns them truncated,
     this may return a non-integer value."

    ^ self asExactSeconds / 60

    "
     (2 hours + 10 minutes + 30 seconds) asExactMinutes
     (2 hours + 10 minutes + 30 seconds) asExactMinutes asFloat
     (2 hours + 10 minutes + 30 seconds) asTruncatedMinutes
     (2 hours + 10 minutes) asExactMinutes
     (2 hours + 10 minutes) asTruncatedMinutes
     10 milliseconds asExactMinutes 
     10 milliseconds asExactMinutes asFloat 
    "
!

asExactNanoseconds
    "return the exact number of nanoseconds.
     In contrast to asNanoSeconds, which returns them truncated,
     this may return a non-integer value."

    additionalPicoseconds isNil ifTrue:[
        ^ (timeEncoding * 1000 * 1000) "/ millis as nanos
    ].
    ^ (timeEncoding * 1000 * 1000)          "/ millis as nanos 
    + (additionalPicoseconds / (1000))      "/ picos as nanoseconds.

    "
     40 milliseconds asExactNanoseconds
     40 microseconds asExactNanoseconds
     40 nanoseconds asExactNanoseconds
     40 picoseconds asExactNanoseconds
    "

    "Created: / 21-09-2017 / 18:52:26 / cg"
!

asExactSeconds
    "return the exact number of seconds.
     In contrast to asSeconds, which returns them truncated,
     this may return a non-integer value."

    additionalPicoseconds isNil ifTrue:[
        ^ (timeEncoding / 1000) "/ millis as seconds
    ].
    ^ (timeEncoding / 1000)                         "/ millis as seconds
    + (additionalPicoseconds / (1000 * 1000 * 1000 * 1000))  "/ picos as seconds.

    "
     1.5 seconds asExactSeconds
     40 seconds asExactSeconds
     40 milliseconds asExactSeconds
     40 microseconds asExactSeconds
     40 nanoseconds asExactSeconds
    "

    "Created: / 21-09-2017 / 18:52:26 / cg"
!

asFixedPoint
    <resource: #obsolete>
    "answer the duration in seconds as a fixedPoint number.
     This method has a bad name (a historic leftover);
     Please change any sender to use secondsAsFixedPoint"

    ^ self secondsAsFixedPoint 

    "
     (10 milliseconds) asFixedPoint
     (10 milliseconds) asFixedPoint asFixedPoint:3 
    "

    "Modified (comment): / 14-09-2017 / 15:15:24 / stefan"
!

asFixedPoint:scale
    <resource: #obsolete>
    "answer the duration in seconds as a fixedPoint number with given scale.
     This method has a bad name (a historic leftover);
     Please change any sender to use secondsAsFixedPoint"

    ^ self secondsAsFixedPoint:scale

    "
     (1000 milliseconds) secondsAsFixedPoint
     (10 milliseconds) secondsAsFixedPoint
     (10 microseconds) secondsAsFixedPoint scale:8
     (10 nanoseconds) secondsAsFixedPoint scale:8   
     (1000001 microseconds) secondsAsFixedPoint scale:8
    "

    "Modified (comment): / 14-09-2017 / 15:15:24 / stefan"
!

asFloat
    <resource: #obsolete>
    "answer the duration in seconds as a float.
     This method has a bad name (a historic leftover);
     Please change any sender to use secondsAsFloat"

    ^ self secondsAsFloat

    "
     (1000 milliseconds) asFloat
     (10 milliseconds) asFloat
     (10 microseconds) asFloat
     (10 nanoseconds) asFloat
     (1000001 microseconds) asFloat
    "

    "Modified (comment): / 14-09-2017 / 15:15:18 / stefan"
!

asFraction
    <resource: #obsolete>
    "answer the duration in seconds as a fraction
     (might return an integer, if the duration is an exact multiple
      of millis).
     This method has a bad name (a historic leftover);
     Please change any sender to use secondsAsFraction"

    ^ self secondsAsFraction

    "
     (1000 milliseconds) asFraction
     (10 milliseconds) asFraction
     (10 microseconds) asFraction
     (10 nanoseconds) asFraction
     (1000001 microseconds) asFraction asFloat
    "

    "Modified (comment): / 19-01-2018 / 17:29:24 / stefan"
!

asInteger
    <resource: #obsolete>
    "answer the duration as (truncated) integer seconds.
     Better use the explicit asTruncatedSeconds"

    ^ self asTruncatedSeconds

    "
     10 milliseconds asInteger
    "

    "Modified (comment): / 14-09-2017 / 15:14:49 / stefan"
    "Modified (comment): / 21-09-2017 / 18:57:43 / cg"
!

asLongFloat
    <resource: #obsolete>
    "answer the duration as longfloat seconds.
     This method has a bad name (a historic leftover);
     Please change any sender to use secondsAsFloat"

    ^ self secondsAsLongFloat

    "
     (10 milliseconds) asLongFloat
     (10 microseconds) asLongFloat
     (10 nanoseconds) asLongFloat
     (1000001 microseconds) asLongFloat
    "
!

asMicroseconds
    "answer the duration as microseconds (truncated).
     Values smaller than 1 us will be returned as 0"

    ^ self asTruncatedMicroseconds

    "
     100 nanoseconds asTruncatedMicroseconds
     100 nanoseconds asExactMicroseconds

     10 milliseconds asMicroseconds
     1.5 milliseconds asMicroseconds
     10 seconds asMicroseconds
    "
!

asMilliseconds
    "answer the duration as milliseconds (truncated).
     Values smaller than 1 ms will be returned as 0"

    ^ self asTruncatedMilliseconds

    "
     10 microseconds asTruncatedMilliseconds
     10 microseconds asExactMilliseconds
     10 microseconds asMilliseconds

     10 milliseconds asMilliseconds
     10 seconds asMilliseconds
    "
!

asNanoseconds
    "answer the duration as nanoseconds (truncated).
     Values smaller than 1 ns will be returned as 0"

    ^ self asTruncatedNanoseconds

    "
     10 picoseconds asTruncatedNanoseconds
     10 picoseconds asExactNanoseconds
    "
!

asNumber
    <resource: #obsolete>
    "answer the duration as seconds.
     This method has a bad name (a historic leftover);
     Please change any sender to use asTruncatedSeconds or
     asExactSeconds, depending on what is wanted."

    ^ self asExactSeconds

    "Modified (comment): / 14-09-2017 / 15:15:00 / stefan"
    "Modified: / 21-09-2017 / 18:57:57 / cg"
!

asPicoseconds
    "answer the duration as picoseconds (truncated).
     Because the smallest representable timeDuration is 1ps,
     there is no distinction between truncated and exact picos."

    ^ (timeEncoding * 1000000000) + ((additionalPicoseconds ? 0))

    "
     10 milliseconds asPicoeconds
     10 seconds asPicoeconds
    "
!

asSeconds
    "answer the duration as seconds (truncated).
     Values smaller than 1 s will be returned as 0.

     To get the exact number, use asExactSeconds.
     Please change senders to use asTruncatedSeconds 
     to make this truncation explicit (and obvious when reading code).
     For compatibility (both backward and with other smalltalks),
     asSeconds returns the TRUNCATED integer value
     (many senders assume that an integer is returned)"

    ^ self asTruncatedSeconds

    "
     10 milliseconds asSeconds
     10 nanoseconds asSeconds
     10 milliseconds asExactSeconds
     10 nanoseconds asExactSeconds
     2 minutes asSeconds
    "
!

asTimeDuration
    "return a TimeDuration object from the receiver - that's the receiver."

    ^ self
!

asTruncatedHours
    "answer the duration as hours (truncated).
     Values smaller than 1 h will be returned as 0.

     To get the exact number, use asExactHours."

    ^ self asTruncatedSeconds // (3600)

    "
     (2 hours + 10 minutes) asTruncatedHours
     (2 hours + 10 minutes + 30 seconds) asTruncatedHours
     2 minutes asTruncatedHours
     10 milliseconds asTruncatedHours
    "
!

asTruncatedMicroseconds
    "answer the duration as microseconds (truncated).
     Values smaller than 1 us will be returned as 0.
     This is the total number of microseconds - not just the fractional part"

    ^ (timeEncoding * 1000) + ((additionalPicoseconds ? 0) // (1000 * 1000))

    "
     100 nanoseconds asTruncatedMicroseconds
     100 nanoseconds asExactMicroseconds

     10 milliseconds asTruncatedMicroseconds
     10 seconds asTruncatedMicroseconds
    "
!

asTruncatedMilliseconds
    "answer the duration as milliseconds (truncated).
     Values smaller than 1 ms will be returned as 0.
     This is the total number of milliseconds - not just the fractional part"

    ^ timeEncoding

    "
     0.1 milliseconds asTruncatedMilliseconds
     0.1 milliseconds asExactMilliseconds

     10 milliseconds asMilliseconds
     10 seconds asMilliseconds
    "
!

asTruncatedMinutes
    "answer the duration as minutes (truncated).
     Values smaller than 1 m will be returned as 0.

     To get the exact number, use asExactMinutes."

    ^ self asTruncatedSeconds // 60

    "
     (2 hours + 10 minutes) asTruncatedMinutes
     (2 hours + 10 minutes + 30 seconds) asTruncatedMinutes
     2 minutes asTruncatedMinutes
     10 milliseconds asTruncatedMinutes
    "
!

asTruncatedNanoseconds
    "answer the duration as nanoseconds (truncated).
     Values smaller than 1 ns will be returned as 0.
     This is the total number of nanoseconds - not just the fractional part"

    ^ (timeEncoding * 1000000) + ((additionalPicoseconds ? 0) // (1000))

    "
     10 picoseconds asTruncatedNanoseconds
     10 picoseconds asExactNanoseconds

     10 milliseconds asTruncatedNanoseconds
     10 seconds asTruncatedNanoseconds
    "
!

asTruncatedSeconds
    "answer the duration as seconds (truncated).
     Values smaller than 1 s will be returned as 0.
     This is the total number of seconds - not just the fractional part.
     To get the exact number, use asExactSeconds."

    ^ timeEncoding // 1000

    "
     10 milliseconds asTruncatedSeconds
     10 milliseconds asExactSeconds
     2 minutes asTruncatedSeconds
    "
!

secondsAsFixedPoint
    "answer the duration in seconds as a fixedPoint number."

    ^ self secondsAsFixedPoint:4 

    "
     (10 milliseconds) secondsAsFixedPoint
     (10 milliseconds) secondsAsFixedPoint asFixedPoint:3 
    "

    "Modified (comment): / 14-09-2017 / 15:15:24 / stefan"
!

secondsAsFixedPoint:scale
    "answer the duration in seconds as a fixedPoint number with given scale."

    |t|

    t := FixedPoint numerator:timeEncoding denominator:1000 scale:scale.
    additionalPicoseconds notNil ifTrue:[
        t := t + (FixedPoint numerator:additionalPicoseconds denominator:((1000*1000)*(1000*1000)) scale:scale)
    ].
    ^ t

    "
     (1000 milliseconds) secondsAsFixedPoint
     (10 milliseconds) secondsAsFixedPoint
     (10 microseconds) secondsAsFixedPoint scale:8
     (10 nanoseconds) secondsAsFixedPoint scale:8   
     (1000001 microseconds) secondsAsFixedPoint scale:8
    "

    "Modified (comment): / 14-09-2017 / 15:15:24 / stefan"
!

secondsAsFloat
    "answer the duration in seconds as a float."

    |t|

    t := timeEncoding / 1000.0.
    additionalPicoseconds notNil ifTrue:[
        t := t + (additionalPicoseconds / ((1000.0*1000.0) * (1000.0*1000.0))).
    ].
    ^ t

    "
     (1000 milliseconds) secondsAsFloat
     (10 milliseconds) secondsAsFloat
     (10 microseconds) secondsAsFloat
     (10 nanoseconds) secondsAsFloat
     (1000001 microseconds) secondsAsFloat
    "

    "Modified (comment): / 14-09-2017 / 15:15:18 / stefan"
!

secondsAsFraction
    "answer the duration in seconds as a fraction
     (might return an integer, if the duration is an exact multiple
      of millis)."

    |t|

    t := timeEncoding / 1000.
    additionalPicoseconds notNil ifTrue:[
        t := t + (additionalPicoseconds / ((1000*1000)*(1000*1000))).
    ].
    ^ t

    "
     (1000 milliseconds) secondsAsFraction
     (10 milliseconds) secondsAsFraction
     (10 microseconds) secondsAsFraction
     (10 nanoseconds) secondsAsFraction
     (1000001 microseconds) secondsAsFraction asFloat
    "

    "Modified (comment): / 19-01-2018 / 17:29:24 / stefan"
!

secondsAsLongFloat
    "answer the duration as longfloat seconds."

    |t|

    t := timeEncoding / 1000 asLongFloat.
    additionalPicoseconds notNil ifTrue:[
        t := t + (additionalPicoseconds / (((1000*1000) asLongFloat) * (1000*1000) asLongFloat)).
    ].
    ^ t

    "
     (10 milliseconds) secondsAsLongFloat
     (10 microseconds) secondsAsLongFloat
     (10 nanoseconds) secondsAsLongFloat
     (1000001 microseconds) secondsAsLongFloat
    "
! !

!TimeDuration methodsFor:'double dispatching'!

differenceFromInteger:anInteger
    "treat the integer as a number of seconds.
     Might be questionable, but adding integers to timeDurations is also allowed,
     and addition is kommutative...
     ...maybe mixing should be forbidden."

    ^ (self species seconds:anInteger) - self

    "
     10 seconds - 5 seconds
     10 - 5 seconds
     10 seconds - 5 

     10 seconds * 2 
     2 * 10 seconds
    "

    "Created: / 16-09-2017 / 12:49:33 / cg"
!

differenceFromTimeDuration:aTimeDuration
    "return a new timeDuration"

    |newMillis newPicos|

    newMillis := aTimeDuration getMilliseconds - timeEncoding.
    newPicos := (aTimeDuration additionalPicoseconds) - (additionalPicoseconds ? 0).

    ^ aTimeDuration species basicNew
        setMilliseconds:newMillis additionalPicoseconds:newPicos

    "
     (TimeDuration fromString:'1m') - (TimeDuration fromString:'10s') 
     1 minutes - 10 seconds
     10 - 1 minutes
    "

    "Created: / 25-07-2018 / 21:17:50 / Stefan Vogel"
    "Modified: / 27-07-2018 / 10:32:53 / Stefan Vogel"
!

differenceFromTimestamp:aTimestamp
    "return the timestamp this timeDuration before aTimestamp"

    |newMillis newPicos|

    newMillis := aTimestamp getMilliseconds - timeEncoding.
    newPicos := (aTimestamp additionalPicoseconds) - (additionalPicoseconds ? 0).

    ^ aTimestamp species basicNew
        setMilliseconds:newMillis additionalPicoseconds:newPicos.

    "
     Timestamp now - 100 seconds
     Time now - 100 seconds
     Timestamp now - 100
    "

    "Modified (comment): / 16-09-2017 / 12:51:38 / cg"
    "Modified (format): / 27-07-2018 / 10:50:13 / Stefan Vogel"
!

productFromFloat:aFloat
    "sent when aFloat does not know how to multiply the receiver.
     Return a new timeDuration"

    ^ self productFromNumber:aFloat

    "
     5.1 * (TimeDuration fromString:'10s') 
    "

    "Modified (comment): / 12-06-2017 / 20:51:38 / cg"
!

productFromFraction:aFraction
    "sent when aFraction does not know how to multiply the receiver.
     Return a new timeDuration"

    ^ self productFromNumber:aFraction

    "
     (TimeDuration fromString:'10s') * 5
    "

    "Modified (comment): / 12-06-2017 / 20:51:25 / cg"
!

productFromInteger:anInteger
    "sent when an integer does not know how to multiply the receiver"

    ^ self productFromNumber:anInteger

    "
     5 * (TimeDuration fromString:'10s') 
    "

    "Modified (comment): / 12-06-2017 / 20:50:56 / cg"
!

productFromNumber:aNumber
    "sent when an integer does not know how to multiply the receiver.
     Return a new timeDuration"

    ^ self species basicNew 
        setMilliseconds:(timeEncoding * aNumber) additionalPicoseconds:(additionalPicoseconds ? 0) * aNumber.

    "
     5.1 * (TimeDuration fromString:'10s') 
     (TimeDuration fromString:'10s') * 5
    "

    "Modified (comment): / 16-09-2017 / 12:52:16 / cg"
    "Modified: / 27-07-2018 / 10:33:21 / Stefan Vogel"
!

productFromTimeDuration:aTimeDuration
    "return a new timeDuration"

    |newMillis newPicos|

    newMillis := timeEncoding * aTimeDuration getMilliseconds.
    newPicos := (additionalPicoseconds ? 0) * (aTimeDuration additionalPicoseconds).

    ^ aTimeDuration species basicNew
        setMilliseconds:newMillis additionalPicoseconds:newPicos

    "
     (TimeDuration fromString:'1m') * (TimeDuration fromString:'10s') 
     1 minutes * 10 seconds
     10 * 1 minutes
    "

    "Created: / 25-07-2018 / 21:11:40 / Stefan Vogel"
    "Modified: / 27-07-2018 / 10:33:29 / Stefan Vogel"
!

sumFromInteger:anInteger
    "treat the integer as a number of seconds.
     Might be questionable, but adding integers to timeDurations is also allowed,
     and addition is kommutative...
     ...maybe mixing should be forbidden."

    ^ self addSeconds:anInteger

    "
     10 + 5 seconds
     10 seconds + 5 
    "

    "Created: / 16-09-2017 / 12:46:20 / cg"
!

sumFromTimeDuration:aTimeDuration
    "return a new timeDuration"

    |newMillis newPicos|

    newMillis := timeEncoding + aTimeDuration getMilliseconds.
    newPicos := (additionalPicoseconds ? 0) + (aTimeDuration additionalPicoseconds).

    ^ aTimeDuration species basicNew
        setMilliseconds:newMillis additionalPicoseconds:newPicos

    "
     (TimeDuration fromString:'1m') + (TimeDuration fromString:'10s') 
     1 minutes + 10 seconds
     10 + 1 minutes
    "

    "Created: / 16-09-2017 / 12:43:28 / cg"
    "Modified: / 27-07-2018 / 10:33:47 / Stefan Vogel"
!

sumFromTimestamp:aTimestamp
    "return the timestamp this timeDuration after aTimestamp"

    |newMillis newPicos|

    newMillis := timeEncoding + aTimestamp getMilliseconds.
    newPicos := (additionalPicoseconds ? 0) + (aTimestamp additionalPicoseconds).

    ^ aTimestamp species basicNew
        setMilliseconds:newMillis additionalPicoseconds:newPicos

    "
     Timestamp now + 100 seconds
    "

    "Modified (comment): / 16-09-2017 / 12:53:14 / cg"
    "Modified: / 27-07-2018 / 10:30:13 / Stefan Vogel"
! !



!TimeDuration methodsFor:'printing'!

addPrintBindingsTo:aDictionary language:languageOrNil
    "private print support: add bindings for printing to aDictionary.
     languageOrNil can only be #en or nil for the current language.

     Additional formats available here (for timeDuration) are:
        %(Hd)       hours in day (i.e. 0..23)
        %(hd)       hours in day padded to 2 chars (i.e. 00..23)

        %(yrR)      years rounded (i.e. for 730 days, we get 2 asFixedPoint:1 )
        %(monR)     month rounded (i.e. for 45 days, we get 1.5 asFixedPoint:1 )
        %(w)        weeks 
        %(wR)       weeks rounded (i.e. for 45 days, we get 6.xxx asFixedPoint:1 )
        %(dR)       days rounded (i.e. for 36 hours, we get 1.5 asFixedPoint:1 )
        %(dw)       days in week (rest days after taking out the weeks)
        %(hR)       hours rounded (i.e. for 3h 30m, we get 3.5 asFixedPoint:1 )
        %(mR)       minutes rounded (i.e. for 2m 30s, we get 2.5 asFixedPoint:1 )
        %(sR)       seconds rounded to 1 postDecimal (i.e. for 2s 100ms, we get 2.1 asFixedPoint:1 )
    "

    |hoursInDay s yearsRounded monthsRounded weeksRounded daysRounded hoursRounded minutesRounded secondsRounded|

    self addBasicPrintBindingsTo:aDictionary language:languageOrNil.
    aDictionary at:$d put:self days.

    hoursInDay := self hours \\ 24.
    aDictionary at:#Hd put:(s := hoursInDay printString).
    aDictionary at:#hd put:(s leftPaddedTo:2 with:$0).

    aDictionary at:#dw put:(self days \\ 7).

    yearsRounded := (self hours / 24 / 365).
    yearsRounded isInteger ifFalse:[
        yearsRounded := yearsRounded asFixedPoint:1.
    ].
    aDictionary at:#yrR put:yearsRounded.

    monthsRounded := self days / 30.
    monthsRounded isInteger ifFalse:[
        monthsRounded := monthsRounded asFixedPoint:1.
        monthsRounded roundedToScale = monthsRounded asInteger ifTrue:[
            monthsRounded := monthsRounded truncated
        ].
    ].
    aDictionary at:#monR put:monthsRounded.

    aDictionary at:#w put:(self days // 7).
    weeksRounded := self days / 7.
    weeksRounded isInteger ifFalse:[
        weeksRounded := weeksRounded asFixedPoint:1.
        weeksRounded roundedToScale = weeksRounded asInteger ifTrue:[
            weeksRounded := weeksRounded truncated
        ].
    ].
    aDictionary at:#wR put:weeksRounded.

    daysRounded := (self hours / 24).
    daysRounded isInteger ifFalse:[
        daysRounded := daysRounded asFixedPoint:1.
        daysRounded roundedToScale = daysRounded asInteger ifTrue:[
            daysRounded := daysRounded truncated
        ].
    ].
    aDictionary at:#dR put:daysRounded.

    hoursRounded := self hours + (self minutes / 60).
    hoursRounded isInteger ifFalse:[
        hoursRounded := hoursRounded asFixedPoint:1.
        hoursRounded roundedToScale = hoursRounded asInteger ifTrue:[
            hoursRounded := hoursRounded truncated
        ].
    ].
    aDictionary at:#hR put:hoursRounded.

    minutesRounded := self minutes + (self seconds / 60).
    minutesRounded isInteger ifFalse:[
        minutesRounded := minutesRounded asFixedPoint:1.
        minutesRounded roundedToScale = minutesRounded asInteger ifTrue:[
            minutesRounded := minutesRounded truncated
        ].
    ].
    aDictionary at:#mR put:minutesRounded.

    secondsRounded := self seconds + (self milliseconds / 1000).
    secondsRounded isInteger ifFalse:[
        secondsRounded := secondsRounded asFixedPoint:1.
        secondsRounded roundedToScale = secondsRounded asInteger ifTrue:[
            secondsRounded := secondsRounded truncated
        ].
    ].
    aDictionary at:#sR put:secondsRounded.

    "Modified: / 22-02-2011 / 15:55:38 / cg"
!

formatForApproximatePrinting
    "Return a format which is suitable for a human - not meant to be read back.
     In contrast to the regular format, this one only gives a rounded approximation
     of the time duration as useful in information-dialogs or other user-hint-GUI elements.
     For example, in a timeDuration of more than 2hours, the user might not be interested in
     individual seconds or even milliseconds.
     The way this hidding/rounding is done is pure magic heuristics."

    |hours mins secs millis|

    hours := self hours.

    hours >= (24*365*2) ifTrue:[
        ^ '%(yrR)yr'. 
    ].
    hours >= (24*40) ifTrue:[
        ^ '%(monR)mon'. 
    ].
    hours >= 48 ifTrue:[
        ^ '%(dR)d'. 
    ].
    hours >= 24 ifTrue:[
        ^ '%dd %(Hd)h'. 
    ].
    hours >= 2 ifTrue:[
        ^ '%(hR)h'.
    ].
    hours >= 1 ifTrue:[
        ^ '%Hh %Mm'.
    ].

    "/ no hours
    mins := self minutes.
    mins >= 5 ifTrue:[
        ^ '%(mR)m'.
    ].
    mins >= 1 ifTrue:[
        ^ '%Mm %Ss'.
    ].

    "/ no mins
    secs := self seconds.
    secs >= 1 ifTrue:[
        secs >= 30 ifTrue:[
            ^ '%(S)s'.
        ].
        ^ '%(sR)s'.
    ].

    "/ no secs
    millis := self milliseconds.
    millis > 500 ifTrue:[
        ^ '%(sR)s'
    ].

    ^ self formatForPrinting

    "
     (TimeDuration hours:0 minutes:0 seconds:0 millis:12) printStringForApproximation       

     (TimeDuration hours:0 minutes:0 seconds:10 millis:123) printStringForApproximation        
     (TimeDuration hours:0 minutes:1 seconds:10 millis:123) printStringForApproximation        
     (TimeDuration hours:0 minutes:2 seconds:10 millis:123) printStringForApproximation        
     (TimeDuration hours:0 minutes:33 seconds:0 millis:123) printStringForApproximation        
     (TimeDuration hours:2 minutes:0 seconds:0 millis:123) printStringForApproximation         
     (TimeDuration hours:2 minutes:33 seconds:0 millis:123) printStringForApproximation        
     (TimeDuration hours:100 minutes:33 seconds:0 millis:123) printStringForApproximation      
     (TimeDuration hours:10000 minutes:33 seconds:0 millis:123) printStringForApproximation    
     (TimeDuration hours:1000000 minutes:33 seconds:0 millis:123) printStringForApproximation    

     (TimeDuration hours:2 minutes:33 seconds:0 millis:0) printStringForApproximation         
     (TimeDuration hours:2 minutes:0 seconds:0 millis:0) printStringForApproximation          
     (TimeDuration hours:24 minutes:0 seconds:0 millis:0) printStringForApproximation          

     (TimeDuration fromMicroseconds:20) printStringForApproximation          
    "

    "Modified: / 21-09-2017 / 22:19:53 / cg"
!

formatForPrinting
    "Return the format for printing"

    DefaultFormatForPrinting notNil ifTrue:[
        ^ DefaultFormatForPrinting
    ].
    ^ self formatForPrinting:false

    "
     (TimeDuration readFrom:'10h 3s') formatForPrinting  
     (TimeDuration readFrom:'3s') formatForPrinting      
     (TimeDuration readFrom:'1d 2ms') formatForPrinting      
     (TimeDuration readFrom:'1 week') formatForPrinting      
    "
!

formatForShortPrinting
    "Return the short format for printing (without ms)"

    ^ self formatForPrinting:true
!

printAsApproximationOn:aStream
    "append a human readable printed representation of the receiver to aStream.
     The format is meant for a human and does not give all information;
     especially, useless detail is hidden.
     This means, that seconds are rounded or hidden, if the dT is more than a few minutes;
     minutes rounded into the hour or hidden, if it's more than a few hours etc.
     The way this is done is pure magic heuristics - let me know, if you have a better algorithm."

    ^ self
        printOn:aStream 
        format:(self formatForApproximatePrinting).

    "
     (TimeDuration hours:0 minutes:0 seconds:0 milliseconds:123) printAsApproximationOn:Transcript
     (TimeDuration hours:0 minutes:0 seconds:10 milliseconds:123) printAsApproximationOn:Transcript
     (TimeDuration hours:0 minutes:33 seconds:0 milliseconds:123) printAsApproximationOn:Transcript
     (TimeDuration hours:2 minutes:0 seconds:0 milliseconds:123) printAsApproximationOn:Transcript
     (TimeDuration hours:2 minutes:33 seconds:0 milliseconds:123) printAsApproximationOn:Transcript
     (TimeDuration hours:100 minutes:33 seconds:0 milliseconds:123) printAsApproximationOn:Transcript
     (TimeDuration hours:10000 minutes:33 seconds:0 milliseconds:123) printAsApproximationOn:Transcript
     (TimeDuration hours:1000000 minutes:33 seconds:0 milliseconds:123) printAsApproximationOn:Transcript

     (TimeDuration hours:2 minutes:33 seconds:0) printAsApproximationOn:Transcript
     (TimeDuration hours:2 minutes:0 seconds:0) printAsApproximationOn:Transcript
     (TimeDuration hours:24 minutes:0 seconds:0) printAsApproximationOn:Transcript
    "

    "Modified: / 18-07-2007 / 14:06:17 / cg"
    "Modified (comment): / 13-02-2017 / 20:32:54 / cg"
!

printOn:aStream
    "append a human readable printed representation of the receiver to aStream.
     The format is suitable for a human - not meant to be read back."

    timeEncoding negative ifTrue:[
        aStream nextPutAll:'-('.
        (self class basicNew timeEncoding:timeEncoding negated) printOn:aStream.
        aStream nextPutAll:')'.
        ^  self
    ].
    ^ self
        printOn:aStream 
        format:(self formatForPrinting).

    "
     TimeDuration hours:0 minutes:0 seconds:0 millis:12       

     TimeDuration hours:0 minutes:0 seconds:0 millis:123       
     TimeDuration hours:0 minutes:0 seconds:10 millis:123       
     TimeDuration hours:0 minutes:33 seconds:0 millis:123       
     TimeDuration hours:2 minutes:0 seconds:0 millis:123       
     TimeDuration hours:2 minutes:33 seconds:0 millis:123       
     TimeDuration hours:100 minutes:33 seconds:0 millis:123    
     TimeDuration hours:10000 minutes:33 seconds:0 millis:123    
     TimeDuration hours:1000000 minutes:33 seconds:0 millis:123    

     TimeDuration hours:2 minutes:33 seconds:0 millis:0         
     TimeDuration hours:2 minutes:0 seconds:0 millis:0          
     TimeDuration hours:24 minutes:0 seconds:0 millis:0          

     (TimeDuration hours:0 minutes:0 seconds:0 millis:123) printStringFormat:'%h:%m:%s'       
     (TimeDuration hours:0 minutes:0 seconds:10 millis:123) printStringFormat:'%h:%m:%s'         
     (TimeDuration hours:0 minutes:33 seconds:0 millis:123) printStringFormat:'%h:%m:%s'         
     (TimeDuration hours:2 minutes:33 seconds:0 millis:123) printStringFormat:'%h:%m:%s'         
     (TimeDuration hours:100 minutes:33 seconds:0 millis:123) printStringFormat:'%h:%m:%s'      
     (TimeDuration hours:10000 minutes:33 seconds:0 millis:123) printStringFormat:'%h:%m:%s'      
     (TimeDuration hours:1000000 minutes:33 seconds:0 millis:123) printStringFormat:'%h:%m:%s'      
    "

    "Modified: / 18-07-2007 / 14:06:17 / cg"
!

printShortOn:aStream
    "append a human readable printed representation  
     of the receiver to aStream (without milliseconds)"

    ^ self
        printOn:aStream 
        format:(self formatForShortPrinting).

    "
     TimeDuration hours:0 minutes:0 seconds:0 millis:12       

     TimeDuration hours:0 minutes:0 seconds:0 millis:123       
     TimeDuration hours:0 minutes:0 seconds:10 millis:123       
     TimeDuration hours:0 minutes:33 seconds:0 millis:123       
     TimeDuration hours:2 minutes:0 seconds:0 millis:123       
     TimeDuration hours:2 minutes:33 seconds:0 millis:123       
     TimeDuration hours:100 minutes:33 seconds:0 millis:123    
     TimeDuration hours:10000 minutes:33 seconds:0 millis:123    
     TimeDuration hours:1000000 minutes:33 seconds:0 millis:123    

     TimeDuration hours:2 minutes:33 seconds:0 millis:0         
     TimeDuration hours:2 minutes:0 seconds:0 millis:0          
     TimeDuration hours:24 minutes:0 seconds:0 millis:0          

     (TimeDuration hours:0 minutes:0 seconds:0 millis:123) printStringFormat:'%h:%m:%s'       
     (TimeDuration hours:0 minutes:0 seconds:10 millis:123) printStringFormat:'%h:%m:%s'         
     (TimeDuration hours:0 minutes:33 seconds:0 millis:123) printStringFormat:'%h:%m:%s'         
     (TimeDuration hours:2 minutes:33 seconds:0 millis:123) printStringFormat:'%h:%m:%s'         
     (TimeDuration hours:100 minutes:33 seconds:0 millis:123) printStringFormat:'%h:%m:%s'      
     (TimeDuration hours:10000 minutes:33 seconds:0 millis:123) printStringFormat:'%h:%m:%s'      
     (TimeDuration hours:1000000 minutes:33 seconds:0 millis:123) printStringFormat:'%h:%m:%s'      
    "

    "Modified: / 18-07-2007 / 14:06:17 / cg"
!

printStringForApproximation
    "return a human readable printed representation of the receiver to aStream.
     The format is meant for a human and does not give all information;
     especially, useless detail is hidden.
     This means, that seconds are rounded or hidden, if the dT is more than a few minutes;
     minutes rounded into the hour or hidden, if it's more than a few hours etc.
     The way this is done is pure magic heuristics - let me know, if you have a better algorithm."

    ^ self printStringFormat:(self formatForApproximatePrinting).

    "
     (TimeDuration hours:0 minutes:0 seconds:0 milliseconds:123) printStringForApproximation
     (TimeDuration hours:0 minutes:0 seconds:10 milliseconds:123) printStringForApproximation
     (TimeDuration hours:0 minutes:33 seconds:0 milliseconds:123) printStringForApproximation
     (TimeDuration hours:2 minutes:0 seconds:0 milliseconds:123) printStringForApproximation
     (TimeDuration hours:2 minutes:33 seconds:0 milliseconds:123) printStringForApproximation
     (TimeDuration hours:100 minutes:33 seconds:0 milliseconds:123) printStringForApproximation
     (TimeDuration hours:10000 minutes:33 seconds:0 milliseconds:123) printStringForApproximation
     (TimeDuration hours:1000000 minutes:33 seconds:0 milliseconds:123) printStringForApproximation

     (TimeDuration hours:2 minutes:33 seconds:0) printStringForApproximation
     (TimeDuration hours:2 minutes:0 seconds:0) printStringForApproximation
     (TimeDuration hours:24 minutes:0 seconds:0) printStringForApproximation
    "

    "Modified (comment): / 13-02-2017 / 20:32:59 / cg"
! !

!TimeDuration methodsFor:'private'!

additionalPicoseconds
    "get the optional additional picoseconds (0..999999999)
     notice: that is NOT the total number of picoseconds,
     but the fractional part only. 
     Use this only for printing."

    ^ additionalPicoseconds ? 0
!

additionalPicoseconds:picosecondPart
    "set the optional additional picoseconds (0..999999999)"

    self assert:(picosecondPart isInteger).
    self assert:(picosecondPart < (1000*1000*1000)).
    additionalPicoseconds := picosecondPart
!

formatForPrinting:shortFlag
    "Return a format which is suitable for a human (i.e. not ISO8601) 
     (not meant to be read back because it will not print tiny fractions,
      but instead round it heuristically.
     However, the reader can read that format, but you'll loose some precision if you do).
     If shortFlag is true, some millisecond-info is omitted for longer times.
     For timeDurations to be read back exactly, use iso8601 format."

    |fmt days weeks hours mins secs 
     overAllSeconds overAllMicros overAllNanos millis|

    days := self days.  "/ that's the total
    weeks := days // 7.
    hours := self hours.
    mins := self minutes.
    secs := self seconds.
    millis := self milliseconds.

    "/ q: for up to 2 weeks, whould we better generate: "10d" instead of "1w 3d" ??
    weeks > 0 ifTrue:[
        "/ notice: dw here, which prints the remaining days, after taking out the weeks
        fmt := '%(w)w %(dw)d %(Hd)h %Mm'.
        secs = 0 ifTrue:[
            fmt := '%(w)w %(dw)d %(Hd)h %Mm'.
            mins = 0 ifTrue:[
                fmt := '%(w)w %(dw)d %(Hd)h'.
                (hours \\ 24) = 0 ifTrue:[
                    fmt := '%(w)w %(dw)d'.
                    (days \\ 7) = 0 ifTrue:[
                        fmt := '%(w)w'.
                    ].
                ].
            ].
        ].
    ] ifFalse:[days > 0 ifTrue:[
        "/ notice: d here, which prints the total number of days
        fmt := '%dd %(Hd)h %Mm'.
        secs = 0 ifTrue:[
            fmt := '%dd %(Hd)h %Mm'.
            mins = 0 ifTrue:[
                fmt := '%dd %(Hd)h'.
                (hours \\ 24) = 0 ifTrue:[
                    fmt := '%dd'.
                ].
            ].
        ].
    ] ifFalse:[
        hours > 0 ifTrue:[
            fmt := '%Hh %Mm'.
            secs = 0 ifTrue:[
                fmt := '%Hh %Mm'.
                mins = 0 ifTrue:[
                    fmt := '%Hh'.
                ].
            ].
        ] ifFalse:[
            mins > 0 ifTrue:[
                fmt := '%Mm'.
                secs = 0 ifTrue:[
                    fmt := '%Mm'
                ].
            ] ifFalse:[
                fmt := ''
            ].
        ].
    ]].
    ((secs ~= 0) or:[millis ~= 0 or:[(additionalPicoseconds?0) ~= 0]]) ifTrue:[
        fmt size ~~ 0 ifTrue:[
            fmt := fmt , ' '
        ].
        ((millis = 0) and:[(additionalPicoseconds?0) = 0]) ifTrue:[
            fmt := fmt , '%Ss'
        ] ifFalse:[
            (secs = 0 and:[(additionalPicoseconds?0) = 0]) ifTrue:[
                fmt := fmt , '%Ims'
            ] ifFalse:[
                shortFlag ifFalse:[
                    "/ show millis
                    (millis ~= 0) ifTrue:[
                        fmt := fmt , '%S.%is'
                    ] ifFalse:[
                        overAllMicros := self microseconds.
                        overAllMicros > 2 ifTrue:[
                            fmt := fmt , '%(micro)µs'.
                        ] ifFalse:[
                            overAllNanos := self nanoseconds.
                            overAllNanos > 2 ifTrue:[
                                fmt := fmt , '%(nano)ns'.
                            ] ifFalse:[
                                fmt := fmt , '%(pico)ps'.
                            ].
                        ].
                    ].
                ] ifTrue:[
                    "/ only show millis if the number of seconds is small
                    overAllSeconds := self asSeconds.
                    overAllSeconds > 2 ifTrue:[
                        overAllSeconds > 10 ifTrue:[
                            overAllSeconds > 300 ifTrue:[
                               "/ no decimal above 300 seconds
                                fmt := fmt , '%Ss'
                            ] ifFalse:[
                               "/ 1 decimals up to 300 seconds
                                fmt := fmt , '%S.%(milli1)s'
                            ]
                        ] ifFalse:[
                           "/ 2 decimals up to 10seconds
                            fmt := fmt , '%S.%(milli2)s'
                        ]
                    ] ifFalse:[
                        "/ millis up to 2seconds
                        fmt := fmt , '%S.%is'.
                    ]
                ]
            ]
        ].
    ] ifFalse:[
        fmt isEmpty ifTrue:[
            fmt := '%Ss'
        ].
    ].

    ^ fmt.

    "
     3001 seconds formatForPrinting:false
     3001 seconds formatForPrinting:true

     (TimeDuration fromString:'1w 3d') formatForPrinting
     (TimeDuration fromString:'1w 3d') printString
     (TimeDuration fromString:'7d') printString
     (TimeDuration fromString:'6d') printString

     (TimeDuration fromMilliseconds:0.5) printString
     (TimeDuration fromMilliseconds:0.05) printString
     (TimeDuration fromMilliseconds:0.005) printString
     (TimeDuration fromMilliseconds:0.0005) printString
     (TimeDuration fromMilliseconds:0.00005) printString
     (TimeDuration fromMilliseconds:0.000005) printString
     (TimeDuration fromMilliseconds:0.0000005) printString
     (TimeDuration fromMilliseconds:0.00000005) printString
     (TimeDuration fromMilliseconds:0.000000005) printString

     (TimeDuration hours:0 minutes:0 seconds:0 milliseconds:12) formatForPrinting
     (TimeDuration hours:0 minutes:0 seconds:2 milliseconds:12) formatForPrinting 
     (TimeDuration hours:0 minutes:0 seconds:8 milliseconds:12) formatForPrinting  
     (TimeDuration hours:0 minutes:0 seconds:10 milliseconds:12) formatForPrinting  

     (TimeDuration hours:0 minutes:0 seconds:0 milliseconds:123) formatForPrinting
     (TimeDuration hours:0 minutes:0 seconds:10 milliseconds:123) formatForPrinting
     (TimeDuration hours:0 minutes:33 seconds:0 milliseconds:123) formatForPrinting
     (TimeDuration hours:2 minutes:0 seconds:0 milliseconds:123) formatForPrinting
     (TimeDuration hours:2 minutes:33 seconds:0 milliseconds:123) formatForPrinting
     (TimeDuration hours:100 minutes:33 seconds:0 milliseconds:123) formatForPrinting
     (TimeDuration hours:10000 minutes:33 seconds:0 milliseconds:123) formatForPrinting
     (TimeDuration hours:1000000 minutes:33 seconds:0 milliseconds:123) formatForPrinting

     (TimeDuration hours:0 minutes:38 seconds:22 milliseconds:123) formatForPrinting:true

     (TimeDuration hours:2 minutes:33 seconds:0 milliseconds:0) formatForPrinting
     (TimeDuration hours:2 minutes:0 seconds:0 milliseconds:0) formatForPrinting
     (TimeDuration hours:24 minutes:0 seconds:0 milliseconds:0) formatForPrinting

     (TimeDuration hours:0 minutes:0 seconds:0 milliseconds:123) printStringFormat:'%h:%m:%s'
     (TimeDuration hours:0 minutes:0 seconds:10 milliseconds:123) printStringFormat:'%h:%m:%s'
     (TimeDuration hours:0 minutes:33 seconds:0 milliseconds:123) printStringFormat:'%h:%m:%s'
     (TimeDuration hours:2 minutes:33 seconds:0 milliseconds:123) printStringFormat:'%h:%m:%s'
     (TimeDuration hours:100 minutes:33 seconds:0 milliseconds:123) printStringFormat:'%h:%m:%s'
     (TimeDuration hours:10000 minutes:33 seconds:0 milliseconds:123) printStringFormat:'%h:%m:%s'
     (TimeDuration hours:1000000 minutes:33 seconds:0 milliseconds:123) printStringFormat:'%h:%m:%s'
    "

    "Modified: / 18-07-2007 / 14:06:17 / cg"
    "Modified (comment): / 17-05-2017 / 16:35:56 / mawalch"
    "Modified: / 23-05-2018 / 10:36:21 / Claus Gittinger"
!

getHours
    "return the number of hours (truncated).
     This is the total number of hours - not just the fractional part"

    ^ self getSeconds // 60 // 60
!

getMicroseconds
    "return the number of microseconds (truncated).
     This is the total number of microseconds - not just the fractional part"

    ^ (timeEncoding * 1000) + ((additionalPicoseconds ? 0) // (1000 * 1000))
!

getMilliseconds
    "return the number of milliseconds (truncated).
     This is the total number of milliseconds - not just the fractional part"

    ^ timeEncoding

    "Modified: / 18-07-2007 / 13:44:33 / cg"
!

getMinutes
    "return the number of minutes (truncated).
     This is the total number of minutes - not just the fractional part"

    ^ self getSeconds // 60
!

getPicoseconds
    "return the number of picoseconds (truncated).
     This is the total number of picoseconds - not just the fractional part"

    ^ (timeEncoding * 1000000000) + ((additionalPicoseconds ? 0))
!

getSeconds
    "return the number of seconds (truncated).
     This is the total number of seconds - not just the fractional part"

    ^ timeEncoding // 1000

    "Modified: / 18-07-2007 / 13:44:37 / cg"
    "Modified (comment): / 21-09-2017 / 18:50:03 / cg"
!

possiblyNegatedValueFromTimeEncodingInto:aBlock
    timeEncoding < 0 ifTrue:[
        ^ (aBlock value:(timeEncoding negated)) negated
    ].    
    ^ aBlock value:timeEncoding
!

setHours:h minutes:m seconds:s millis:millis
    <resource: #obsolete>
    "set my time given individual values"

    self obsoleteMethodWarning:'use setHours:minutes:seconds:milliseconds:'.
    self setHours:h minutes:m seconds:s milliseconds:millis.
!

setHours:h minutes:m seconds:s milliseconds:millis
    "set my time given individual values"

    self setMilliseconds:((h * 60 * 60 ) + (m * 60) + s) * 1000 + millis.
!

setMicroseconds:micros
    "set my duration given microseconds."

    |restMicros|

    timeEncoding := micros // 1000.
    micros isInteger ifTrue:[
        additionalPicoseconds := (micros \\ 1000) * 1000000
    ] ifFalse:[
        restMicros := micros - (timeEncoding * 1000).
        additionalPicoseconds := (restMicros * 1000000) truncated.
    ].

    "
     self new setMicroseconds:100
     self new setMicroseconds:2
     self new setMicroseconds:1.5
     self new setMicroseconds:0.1
    "

    "Modified: / 18-07-2007 / 13:44:16 / cg"
    "Modified: / 27-07-2018 / 11:53:05 / Stefan Vogel"
!

setMilliseconds:millis
    "set my duration given milliseconds.
     Duration can be longer than a day"

    millis isInteger ifTrue:[
        timeEncoding := millis.
    ] ifFalse:[
        timeEncoding := millis // 1.
        additionalPicoseconds := ((millis \\ 1) * 1000000000) truncated.
    ]

    "Modified: / 18-07-2007 / 13:44:16 / cg"
    "Modified: / 22-05-2018 / 16:51:30 / Stefan Vogel"
!

setMilliseconds:millis additionalPicoseconds:picos
    "set my duration given milliseconds and addon picos.
     Duration can be longer than a day; 
     values may be negative (eg. if resulting from a subtraction)"

    |rest newMillis newPicos|

    millis isInteger ifTrue:[
        newMillis := millis.
        newPicos := 0.
    ] ifFalse:[
        newMillis := millis truncated.
        rest := millis - newMillis.
        newPicos := (rest * 1000000000) truncated.
    ].

    picos ~= 0 ifTrue:[
        newPicos := (newPicos + picos) truncated.
        newMillis := newMillis + (newPicos // 1000000000).
        newPicos := newPicos \\ 1000000000.
    ].
    timeEncoding := newMillis.
    additionalPicoseconds := newPicos.

    "Modified: / 18-07-2007 / 13:44:16 / cg"
    "Modified: / 22-05-2018 / 16:55:53 / Stefan Vogel"
!

setNanoseconds:nanos
    "set my duration given nanoseconds."

    |millis restNanos|

    millis := nanos // (1000*1000).
    timeEncoding := millis.
    nanos isInteger ifTrue:[
        restNanos := nanos \\ (1000*1000).
        additionalPicoseconds := restNanos * 1000 
    ] ifFalse:[
        restNanos := nanos - (millis * 1000000).
        additionalPicoseconds := (restNanos * 1000) truncated.
    ].

    "
     self new setMicroseconds:4
     self new setNanoseconds:4
     self new setNanoseconds:4000
     self new setNanoseconds:4000000
     self new setNanoseconds:40000000
     self new setNanoseconds:0.1
    "

    "Modified: / 18-07-2007 / 13:44:16 / cg"
    "Modified: / 27-07-2018 / 11:53:41 / Stefan Vogel"
!

setPicoseconds:picos
    "set my duration given picoseconds."

    timeEncoding := picos // 1000000000.
    additionalPicoseconds := (picos \\ 1000000000) truncated.

    "
     self new setMicroseconds:4
     self new setNanoseconds:4
     self new setPicoseconds:4
     self new setPicoseconds:4.5

     self assert: (self new setPicoseconds:4000) = (self new setNanoseconds:4) .
     self assert: (self new setPicoseconds:4000000) = (self new setNanoseconds:4000) .
     self assert: (self new setPicoseconds:4000000) = (self new setMicroseconds:4) .
     self assert: (self new setPicoseconds:4000000000) = (self new setNanoseconds:4000000) .
     self assert: (self new setPicoseconds:4000000000) = (self new setMicroseconds:4000) .
     self assert: (self new setPicoseconds:4000000000) = (self new setMilliseconds:4) .
     self assert: (self new setPicoseconds:4000000000000) = (self new setMilliseconds:4000) .
     self assert: (self new setPicoseconds:4000000000000) = (self new setMicroseconds:4000000) .
     self assert: (self new setPicoseconds:4000000000000) = (self new setNanoseconds:4000000000) .
     self assert: (self new setPicoseconds:4000000000000) = (self new setSeconds:4) .
    "

    "Modified: / 18-07-2007 / 13:44:16 / cg"
    "Modified: / 22-05-2018 / 16:51:45 / Stefan Vogel"
!

setSeconds:secs
    "set my timeduration given seconds.
     Notice that (in contrast to Time), there is no modulu operation here.
     Duration can be longer than a day, and (much) smaller than a second"

    self setMilliseconds:(secs * 1000).

    "Modified: / 18-07-2007 / 13:44:24 / cg"
! !

!TimeDuration methodsFor:'testing'!

isTimeDuration
    ^ true
!

isZero
    ^ self = self class zero
!

negative
    ^ timeEncoding < 0
! !

!TimeDuration class methodsFor:'documentation'!

version
    ^ '$Header$'
!

version_CVS
    ^ '$Header$'
! !


TimeDuration initialize!