AbstractTime.st
author Claus Gittinger <cg@exept.de>
Thu, 31 Aug 2000 16:26:21 +0200
changeset 5573 efd0dc6578ac
parent 5548 eead51e4752e
child 5730 b377ec6357e7
permissions -rw-r--r--
#-, #< and #> moved from AbsoluteTime

"
 COPYRIGHT (c) 1995 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' }"

Magnitude subclass:#AbstractTime
	instanceVariableNames:''
	classVariableNames:''
	poolDictionaries:''
	category:'Magnitude-General'
!

!AbstractTime class methodsFor:'documentation'!

copyright
"
 COPYRIGHT (c) 1995 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
"
    This is an abstract class providing common protocol for Time (time in day)
    and AbsoluteTime (time plus day).
    There are no instances of this class in the system.
    It is meant as a home for methods common to time handling classes.

    [author:]
        Claus Gittinger

    [See also:]
        Time Date AbsoluteTime
        Delay ProcessorScheduler
"
! !

!AbstractTime class methodsFor:'instance creation'!

dateAndTimeNow
    "return an array filled with the current date and time.
     See also: Date today / Time now / AbsoluteTime now."

    ^ Array with:(Date today) with:(Time now)

    "
     Time dateAndTimeNow
    "

    "Modified: 19.4.1996 / 15:23:37 / cg"
!

now
    "return an instance of myself representing this moment."

    ^ self basicNew fromOSTime:(OperatingSystem getOSTime)

    "
     AbsoluteTime now   
     Time now   
    "

    "Modified: 1.7.1996 / 15:20:10 / cg"
! !

!AbstractTime class methodsFor:'Compatibility - ST80'!

totalSeconds
    "returns an internal second clock. Dont interpret the returned
     value - if at all, use it to compute time deltas, by subtracting
     returned values."

    ^ self secondClock
! !

!AbstractTime class methodsFor:'private instance creation'!

fromOSTime:osTime
    "return a time, representing the time given by the operatingSystem time.
     Not meant for public use."

    ^ self basicNew fromOSTime:osTime.

    "Modified: 1.7.1996 / 15:09:54 / cg"
!

fromSeconds:seconds
    "return an instance that is constructed from seconds.
     This method is only allowed for second values as returned by
     getSeconds, possibly adding/subtracting to that. 
     Never depend on any specific interpretation of the seconds,
     since it depends on how the OperatingSystem counts time
     (some start at 1900, others with 1970 ...)"

   ^ self basicNew setSeconds:seconds

    "
     Time fromSeconds:0             should return midnight
     AbsoluteTime fromSeconds:0     on UNIX: returns 1st. Jan 1970
                                    on others: dont know
     (AbsoluteTime day:1 month:1 year:1970 hour:1 minutes:0 seconds:0)
        getSeconds                  on UNIX: returns 0
                                    on others: dont know
    "

    "Modified: 1.7.1996 / 13:39:30 / cg"
! !

!AbstractTime class methodsFor:'queries'!

millisecondClockValue
    "return the millisecond clock - since this one overruns
     regularly, use the value only for short timing deltas.
     Also remember that it wraps when compares these values."

    ^ OperatingSystem getMillisecondTime.

    "
     Time millisecondClockValue 
    "
!

secondClock
    "return seconds of now - for GNU-ST compatibility"

    ^ OperatingSystem getOSTime // 1000

    "
     AbstractTime secondClock    
    "

    "Modified: 1.7.1996 / 15:20:14 / cg"
! !

!AbstractTime class methodsFor:'timing evaluations'!

millisecondsToRun:aBlock
    "evaluate the argument, aBlock; return the number of milliseconds it took"

    |startTime endTime|

    startTime := OperatingSystem getMillisecondTime.
    aBlock value.
    endTime := OperatingSystem getMillisecondTime.
    ^ endTime - startTime

    "
     Time millisecondsToRun:[100 factorial]  
    "

    "Modified: 17.6.1996 / 16:57:37 / cg"
!

secondsToRun:aBlock
    "evaluate the argument, aBlock; return the number of seconds it took"

    |startTime endTime|

    startTime := self secondClock.
    aBlock value.
    endTime := self secondClock.
    ^ endTime - startTime

    "
     Time secondsToRun:[1000 factorial]  
    "
! !

!AbstractTime methodsFor:'accessing'!

hourInDay
    "return the hours (0..23)"

    ^ self hours

    "
     AbsoluteTime now hourInDay 
     Time now hourInDay 
    "
!

minuteInDay
    "return the minutes (0..59)"

    ^ self minutes.

    "
     AbsoluteTime now minuteInDay 
     Time now minuteInDay 
    "
!

secondInDay
    "return the seconds (0..59)"

    ^ self seconds

    "
     AbsoluteTime now secondInDay 
     Time now seconds 
    "

    "Created: 22.10.1996 / 09:27:47 / stefan"
!

weekInYear
    "return the week number of the receiver - 1 for Jan, 1st."

    ^ Date weekInYearOf:self

    "
     (AbsoluteTime newDay:1 year:2000) weekInYear    
     (AbsoluteTime newDay:2 year:2000) weekInYear    
     (AbsoluteTime newDay:3 year:2000) weekInYear    
    "
! !

!AbstractTime methodsFor:'arithmetic'!

- aTime
    "return the delta in seconds between 2 times."

    ^ self getSeconds - (aTime getSeconds)

    "
     |t1 t2|

     t1 := AbsoluteTime now.
     (Delay forSeconds:5) wait.
     t2 := AbsoluteTime now.
     Transcript showCR:('seconds passed: ' , (t2 - t1) printString).
    "
!

addHours:numberOfHours
    "return a new instance of myself, numberOfHours afterwards."

    ^ self addSeconds:(numberOfHours * (60 * 60))

    "
     |t|

     t := AbsoluteTime now.
     Transcript showCR:t.
     t printNL.
     Transcript showCR:(t addHours:12).
    "

    "
     |t|

     t := Time now.
     Transcript showCR:t.
     t printNL.
     Transcript showCR:(t addHours:12).
    "

!

addMinutes:numberOfMinutes
    "return a new instance of myself, numberOfMinutes afterwards."

    ^ self addSeconds:(numberOfMinutes * 60)

    "
     |t|

     t := AbsoluteTime now.
     Transcript showCR:t.
     t printNL.
     Transcript showCR:(t addMinutes:60).
    "

    "
     |t|

     t := Time now.
     Transcript showCR:t.
     t printNL.
     Transcript showCR:(t addMinutes:60).
    "
!

addSeconds:numberOfSeconds
    "return a new instance of myself, numberOfSeconds afterwards."

    ^ self species basicNew 
        setMilliseconds:(self getMilliseconds + (numberOfSeconds * 1000))

    "
     |t|

     t := AbsoluteTime now.
     Transcript showCR:t.
     t printNL.
     Transcript showCR:(t addSeconds:60).
    "

    "
     |t|

     t := Time now.
     Transcript showCR:t.
     t printNL.
     Transcript showCR:(t addSeconds:60).
    "

!

addTime:timeAmount
    "return a new instance of myself, timeAmount seconds afterwards.
     Provided for ST-80 compatibility.
     WARNING:
        AddTime is a bad name - it does not add a time, but expects
        a numberOfSeconds as argument. 
        Use any of addSeconds/addHours etc. to make things clear"

    ^ self addSeconds:timeAmount
!

subtractHours:numberOfHours
    "return a new instance of myself, numberOfHours before."

    ^ self subtractSeconds:(numberOfHours * (60 * 60))

    "
     |t|

     t := AbsoluteTime now.
     Transcript showCR:t.
     t printNL.
     Transcript showCR:(t subtractHours:12).
    "

    "
     |t|

     t := Time now.
     Transcript showCR:t.
     t printNL.
     Transcript showCR:(t subtractHours:12).
    "
!

subtractMinutes:numberOfMinutes
    "return a new instance of myself, numberOfMinutes before."

    ^ self subtractSeconds:(numberOfMinutes * 60)

    "
     |t|

     t := AbsoluteTime now.
     Transcript showCR:t.
     t printNL.
     Transcript showCR:(t subtractMinutes:60).
    "

    "
     |t|

     t := Time now.
     Transcript showCR:t.
     t printNL.
     Transcript showCR:(t subtractMinutes:60).
    "
!

subtractSeconds:numberOfSeconds
    "return a new instance of myself, numberOfSeconds before."

    ^ self species basicNew 
        setMilliseconds:(self getMilliseconds - (numberOfSeconds * 1000))

    "
     |t|

     t := AbsoluteTime now.
     Transcript showCR:t.
     t printNL.
     Transcript showCR:(t subtractSeconds:60).
    "

    "
     |t|

     t := Time now.
     Transcript showCR:t.
     t printNL.
     Transcript showCR:(t subtractSeconds:60).
    "

!

subtractTime:timeAmount
    "return a new instance of myself, timeAmount seconds before myself.
     Provided for ST-80 compatibility.
     WARNING:
        SubtractTime is a bad name - it does not add a time, but expects
        a numberOfSeconds as argument. 
        Use any of addSeconds/addHours etc. to make things clear"

    ^ self subtractSeconds:timeAmount

! !

!AbstractTime methodsFor:'comparing'!

< aTime
    "return true if the receiver is before the argument"

    ^ self getMilliseconds < aTime getMilliseconds

    "Modified: 3.7.1996 / 13:10:17 / cg"
!

> aTime
    "return true if the receiver is after the argument"

    ^ self getMilliseconds > aTime getMilliseconds

    "Modified: 1.7.1996 / 15:24:38 / cg"
! !

!AbstractTime methodsFor:'printing & storing'!

addPrintBindingsTo:aDictionary
    "add bindings for printing to aDictionary."

    |hours minutes seconds millis usHours ampm s|

    hours := self hours.
    minutes := self minutes.
    seconds := self seconds.
    millis := self milliseconds.

    hours // 12 == 0 ifTrue:[
        ampm := 'am'.
    ] ifFalse:[
        ampm := 'pm'.
    ].
    usHours := hours.
    usHours ~~ 0 ifTrue:[
        usHours := usHours - 1 \\ 12 + 1.
    ].

    aDictionary at:$H put:(s := hours printString).
    aDictionary at:$h put:(s leftPaddedTo:2 with:$0).
    aDictionary at:$U put:(s := usHours printString).
    aDictionary at:$u put:(s leftPaddedTo:2 with:$0).
    aDictionary at:$M put:(s := minutes printString).
    aDictionary at:$m put:(s leftPaddedTo:2 with:$0).
    aDictionary at:$S put:(s := seconds printString).
    aDictionary at:$s put:(s leftPaddedTo:2 with:$0).
    aDictionary at:$I put:(s := millis printString).
    aDictionary at:$i put:(s leftPaddedTo:3 with:$0).
    aDictionary at:#milli1 put:((millis // 100) printString).
    aDictionary at:#milli2 put:((millis // 10) printStringLeftPaddedTo:2 with:$0).
    aDictionary at:$t put:(seconds * minutes) printString.
    aDictionary at:$T put:(seconds * minutes * hours) printString.
    aDictionary at:$a put:ampm.
    aDictionary at:$A put:ampm asUppercase.
!

printOn:aStream format:aFormatString
    "print using a format string;
     valid format items are:
        %h      hours, 00..23 (i.e. european)  0-padded to length 2
        %u      hours, 00..12 (i.e. us)        0-padded to length 2
        %m      minutes, 00..59                0-padded to length 2
        %s      seconds, 00..59                0-padded to length 2
        %i      milliseconds, 000..999         0-padded to length 3
        %a      am/pm

     AbsoluteTime only:
        %day     day, 00..31                    0-padded to length 2
        %mon     month, 00..12                  0-padded to length 2
        %yr      year, 4 digits                 0-padded to length 4

     special:
        %H      24-hours - unpadded
        %U      12-hours - unpadded
        %M      minutes - unpadded
        %S      seconds - unpadded
        %I      milliseconds - unpadded
        %A      AM/PM   - uppercase

        %t      seconds within hour  (unpadded)
        %T      seconds from midNight  (unpadded)

     AbsoluteTime only:
        %Day    day - unpadded                    
        %Mon    month - unpadded                    
    "

    aStream nextPutAll:(self printStringFormat:aFormatString)

    "
     AbsoluteTime now printOn:Transcript format:'%h:%m:%s'   . Transcript cr.      
     Time now printOn:Transcript format:'%h:%m:%s'   . Transcript cr.      
     Time now printOn:Transcript format:'%H:%m:%s'   . Transcript cr.      
     Time now printOn:Transcript format:'%u:%m:%s %a'. Transcript cr.   
     Time now printOn:Transcript format:'%h:%m'      . Transcript cr. 
     Time now printOn:Transcript format:'%H:%m %A'   . Transcript cr.
     Time now printOn:Transcript format:'minutes:%M seconds:%S'   . Transcript cr.
    "

    "Modified: 22.2.1996 / 16:58:30 / cg"
!

printStringFormat:aFormatString
    "print using a format string;
     valid format items are:
        %h      hours, 00..23 (i.e. european)  0-padded to length 2
        %u      hours, 00..12 (i.e. us)        0-padded to length 2
        %m      minutes, 00..59                0-padded to length 2
        %s      seconds, 00..59                0-padded to length 2
        %i      milliseconds, 000..999         0-padded to length 3
        %a      am/pm

     AbsoluteTime only:
        %day     day, 00..31                    0-padded to length 2
        %month   month, 00..12                  0-padded to length 2
        %year    year, 4 digits                 0-padded to length 4

     special:
        %H      24-hours - unpadded
        %U      12-hours - unpadded
        %M      minutes - unpadded
        %S      seconds - unpadded
        %I      milliseconds, unpadded
        %A      AM/PM   - uppercase

        %t      seconds within hour  (unpadded)
        %T      seconds from midNight  (unpadded)

        %milli1 milliseconds, truncated to 1/10th of a second 0..9         
        %milli2 milliseconds, truncated to 1/100th of a second 00..99 0-padded to length 2        

     AbsoluteTime only:
        %Day    day - unpadded                    
        %Month  month - unpadded                    
    "

    |dict|

    dict := IdentityDictionary new.
    self addPrintBindingsTo:dict.

    ^ (aFormatString expandPlaceholdersWith:dict)

    "
     AbsoluteTime now printStringFormat:'%U:%m:%s %a'   
     Time now printStringFormat:'%U:%m:%s %a'   

     Time now printStringFormat:'%h:%m:%s'      
     Time now printStringFormat:'%H:%m:%s'      
     Time now printStringFormat:'%H:%m:%s.%i'           
     AbsoluteTime now printStringFormat:'%H:%m:%s.%i'   
     AbsoluteTime now printStringFormat:'%H:%m:%s.%(milli1)'   
     AbsoluteTime now printStringFormat:'%H:%m:%s.%(milli2)'     
     Time now printStringFormat:'%u:%m:%s %a'   
     Time now printStringFormat:'%h:%m'         
     Time now printStringFormat:'%h:%m'         
     Time now printStringFormat:'%H:%m %A'     
     Time now printStringFormat:'%m minutes after %U %a'     
     Time now printStringFormat:'%t seconds after %U %a'     
     Time now printStringFormat:'%T seconds from midNight'     
    "

    "Modified: 22.2.1996 / 16:58:30 / cg"
! !

!AbstractTime methodsFor:'private'!

fromOSTime:osTime
    "set my time, from operatingSystems time parts"

    ^ self subclassResponsibility

    "Modified: 1.7.1996 / 15:09:44 / cg"
!

getMilliseconds
    "get the milliseconds.
     Since I am abstract (not knowing how the time is actually
     represented), this must be done by a concrete class."

    ^ self subclassResponsibility

    "Created: 1.7.1996 / 14:16:49 / cg"
!

getSeconds
    "get the seconds.
     Since I am abstract (not knowing how the time is actually
     represented), this must be done by a concrete class."

    ^ self subclassResponsibility
!

setMilliseconds:millis
    "set the milliseconds.
     Since I am abstract (not knowing how the time is actually
     represented), this must be done by a concrete class."

    ^ self subclassResponsibility

    "Created: 1.7.1996 / 14:17:00 / cg"
!

setSeconds:secs
    "set the seconds.
     Since I am abstract (not knowing how the time is actually
     represented), this must be done by a concrete class."

    ^ self subclassResponsibility
! !

!AbstractTime class methodsFor:'documentation'!

version
    ^ '$Header: /cvs/stx/stx/libbasic/AbstractTime.st,v 1.27 2000-08-31 14:26:21 cg Exp $'
! !