AbstractTime.st
author Stefan Vogel <sv@exept.de>
Wed, 22 Sep 2004 16:42:22 +0200
changeset 8586 a38e882affa5
parent 8450 312e775936dc
child 9429 173bcd493d7c
permissions -rw-r--r--
take care of time-wrap in #millisecondsToRun:

"
 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-Time'
!

!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 Timestamp (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 Timestamp
        Delay ProcessorScheduler
"
!

iso8601Format
"
  Abstract

    This document defines a profile of ISO 8601, the International Standard for the representation of dates and times. ISO
    8601 describes a large number of date/time formats. To reduce the scope for error and the complexity of software, it is
    useful to restrict the supported formats to a small number. This profile defines a few date/time formats, likely to satisfy
    most requirements. 


  Formats

    Different standards may need different levels of granularity in the date and time, so this profile defines six levels.
    Standards that reference this profile should specify one or more of these granularities. If a given standard allows more
    than one granularity, it should specify the meaning of the dates and times with reduced precision, for example, the result
    of comparing two dates with different precisions.

    The formats are as follows. Exactly the components shown here must be present, with exactly this punctuation. Note
    that the 'T' appears literally in the string, to indicate the beginning of the time element, as specified in ISO 8601. 

       Year:
          YYYY (eg 1997)
       Year and month:
          YYYY-MM (eg 1997-07)
       Complete date:
          YYYY-MM-DD (eg 1997-07-16)
       Complete date plus hours and minutes:
          YYYY-MM-DDThh:mmTZD (eg 1997-07-16T19:20+01:00)
       Complete date plus hours, minutes and seconds:
          YYYY-MM-DDThh:mm:ssTZD (eg 1997-07-16T19:20:30+01:00)
       Complete date plus hours, minutes, seconds and a decimal fraction of a
    second
          YYYY-MM-DDThh:mm:ss.sTZD (eg 1997-07-16T19:20:30.45+01:00)

    where:

         YYYY = four-digit year
         MM   = two-digit month (01=January, etc.)
         DD   = two-digit day of month (01 through 31)
         hh   = two digits of hour (00 through 23) (am/pm NOT allowed)
         mm   = two digits of minute (00 through 59)
         ss   = two digits of second (00 through 59)
         s    = one or more digits representing a decimal fraction of a second
         TZD  = time zone designator (Z or +hh:mm or -hh:mm)

    This profile does not specify how many digits may be used to represent the decimal fraction of a second. An adopting
    standard that permits fractions of a second must specify both the minimum number of digits (a number greater than or
    equal to one) and the maximum number of digits (the maximum may be stated to be 'unlimited').

    This profile defines two ways of handling time zone offsets:

       1.Times are expressed in UTC (Coordinated Universal Time), with a special UTC designator ('Z'). 
       2.Times are expressed in local time, together with a time zone offset in hours and minutes. A time zone offset of
         '+hh:mm' indicates that the date/time uses a local time zone which is 'hh' hours and 'mm' minutes ahead of
         UTC. A time zone offset of '-hh:mm' indicates that the date/time uses a local time zone which is 'hh' hours and
         'mm' minutes behind UTC. 

    A standard referencing this profile should permit one or both of these ways of handling time zone offsets.

  The ISO8601 printString are generated with:

       Year:
          YYYY (eg 1997)
                Date today printStringFormat:'%(year)'
                Timestamp now printStringFormat:'%(year)'  

       Year and month:
          YYYY-MM (eg 1997-07)
                Date today printStringFormat:'%(year)-%(month)'  
                Timestamp now printStringFormat:'%(year)-%(month)'  

       Complete date:
          YYYY-MM-DD (eg 1997-07-16)
                Date today printStringFormat:'%(year)-%(month)-%(day)'    
                Timestamp now printStringFormat:'%(year)-%(month)-%(day)'  

       Complete date plus hours and minutes:
          YYYY-MM-DDThh:mmTZD (eg 1997-07-16T19:20+01:00)
                Timestamp now printStringFormat:'%(year)-%(month)-%(day)T%h:%m%(TZD)'  

       Complete date plus hours, minutes and seconds:
          YYYY-MM-DDThh:mm:ssTZD (eg 1997-07-16T19:20:30+01:00)
                Timestamp now printStringFormat:'%(year)-%(month)-%(day)T%h:%m:%s%(TZD)'  

       Complete date plus hours, minutes, seconds and a decimal fraction of a second
          YYYY-MM-DDThh:mm:ss.sTZD (eg 1997-07-16T19:20:30.45+01:00)
                Timestamp now printStringFormat:'%(year)-%(month)-%(day)T%h:%m:%s.%(milli2)%(TZD)'  
"
! !

!AbstractTime class methodsFor:'instance creation'!

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

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

    "
     Time dateAndTimeNow
     Date dateAndTimeNow
    "

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

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

    ^ self basicNew fromOSTime:(OperatingSystem getOSTime)

    "
     Timestamp now   
     Time now   
    "

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

!AbstractTime class methodsFor:'Compatibility-Squeak'!

dateAndTimeFromSeconds: secondCount
    ^ Array
        with: (Date fromSeconds: secondCount)
        with: (Time fromSeconds: secondCount \\ 86400)

    "
     Time dateAndTimeFromSeconds: (Time totalSeconds) 
     Date dateAndTimeFromSeconds: (Time totalSeconds)
    "
!

primSecondsClock
    "returns the number of seconds since 1.1.1901"

    ^ self totalSeconds
! !

!AbstractTime class methodsFor:'Compatibility-VW'!

totalSeconds
    "returns the number of seconds since 1.1.1901"

    ^ Timestamp now utcSecondsSince1901
! !

!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
     Timestamp fromSeconds:0     on UNIX: returns 1st. Jan 1970
                                    on others: dont know
     (Timestamp 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 comparing these values."

    ^ OperatingSystem getMillisecondTime.

    "
     Time millisecondClockValue 
    "
!

milliseconds:msTime1 since:msTime2
    "return the number of milliseconds between two
     millisecond time values, compensating for roll-over.
     The same as millisecondsBetween:and: for Squeak compatibility."

    ^ OperatingSystem millisecondTimeDeltaBetween:msTime1 and:msTime2
!

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.
    ^ self milliseconds:endTime since:startTime

    "
     Time millisecondsToRun:[1000 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:'Compatibility-ANSI'!

hour12
    "return the hour (1..12)."

    ^ self hours - 1 \\ 12 + 1.

    "
     Time now hour12   
     Time now hour24   
     (Time hours:0 minutes:0 seconds:0) hour24   
     (Time hours:0 minutes:0 seconds:0) hour12   
     (Time hours:1 minutes:0 seconds:0) hour24   
     (Time hours:1 minutes:0 seconds:0) hour12   
     (Time hours:12 minutes:0 seconds:0) hour24 
     (Time hours:12 minutes:0 seconds:0) hour12   
     (Time hours:13 minutes:0 seconds:0) hour24 
     (Time hours:13 minutes:0 seconds:0) hour12   
     (Time hours:23 minutes:0 seconds:0) hour24 
     (Time hours:23 minutes:0 seconds:0) hour12   
     (Time hours:24 minutes:0 seconds:0) hour24 
     (Time hours:24 minutes:0 seconds:0) hour12   
    "
!

hour24
    "return the hour (0..23)."

    ^ self hours

    "
     Time now hour12   
     Time now hour24   
     (Time hours:0 minutes:0 seconds:0) hour24 
     (Time hours:0 minutes:0 seconds:0) hour12 
     (Time hours:1 minutes:0 seconds:0) hour24 
     (Time hours:1 minutes:0 seconds:0) hour12 
     (Time hours:12 minutes:0 seconds:0) hour24 
     (Time hours:12 minutes:0 seconds:0) hour12 
     (Time hours:13 minutes:0 seconds:0) hour24 
     (Time hours:13 minutes:0 seconds:0) hour12 
     (Time hours:23 minutes:0 seconds:0) hour24 
     (Time hours:23 minutes:0 seconds:0) hour12 
     (Time hours:24 minutes:0 seconds:0) hour24 
     (Time hours:24 minutes:0 seconds:0) hour12 
    "
!

meridianAbbreviation
    "am/pm"

    self hours // 12 == 0 ifTrue:[
        ^ 'am'.
    ] ifFalse:[
        (self hours == 12 and:[self minutes == 0 and:[self seconds == 0]]) ifTrue:[
            ^ 'noon'
        ].
        ^ 'pm'.
    ].

    "
     Time now meridianAbbreviation   
     (Time hours:0 minutes:0 seconds:0) meridianAbbreviation  
     (Time hours:11 minutes:59 seconds:59) meridianAbbreviation  
     (Time hours:12 minutes:0 seconds:0) meridianAbbreviation    
     (Time hours:12 minutes:0 seconds:1) meridianAbbreviation  
    "
! !

!AbstractTime methodsFor:'abstract'!

hours
    "return the hour of time (0..23)"

    ^ self subclassResponsibility

    "
     Timestamp now hours 
     Time now hours 
    "
!

milliseconds
    "return the milliseconds since the start of the second (0..999)"

    ^ self subclassResponsibility

    "
     Timestamp now milliseconds 
     Time now milliseconds 
    "
!

minutes
    "return the minutes since the start of the hour (0..59)"

    ^ self subclassResponsibility.

    "
     Timestamp now minutes 
     Time now minutes 
    "
!

seconds
    "return the seconds since the start of the minute (0..59)"

    ^ self subclassResponsibility

    "
     Timestamp now seconds. 
     Time now seconds 
    "
! !

!AbstractTime methodsFor:'accessing'!

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

    ^ self hours

    "
     Timestamp now hourInDay 
     Time now hourInDay 
    "
!

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

    ^ self minutes.

    "
     Timestamp now minuteInDay 
     Time now minuteInDay 
    "
!

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

    ^ self seconds

    "
     Timestamp now secondInDay 
     Time now seconds 
    "

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

timeZoneDeltaInMinutes
    ^ 0
!

timeZoneName
    ^ 'utc'
!

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

    ^ Date weekInYearOf:self

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

!AbstractTime methodsFor:'arithmetic'!

+ aNumber
    "Add aNumber numberOfSeconds"

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

    "
     Timestamp now to:(Timestamp now + 30) by:2 do:[:time|
        Transcript showCR:time.
     ].

     (Timestamp now + 20)  -  Timestamp now 
     (Timestamp now + 0.5)  -  Timestamp now 
    "
!

- aTimeOrNumberOfSeconds
    "return the delta in seconds between 2 times or subtract a number of seconds."

    aTimeOrNumberOfSeconds isNumber ifTrue:[
        ^ self species basicNew 
            setMilliseconds:(self getMilliseconds - (aTimeOrNumberOfSeconds * 1000) asInteger)
    ].
    ^ self getSeconds - aTimeOrNumberOfSeconds getSeconds



    "
     Timestamp now - 3600.

     |t1 t2|

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

addDays:numberOfDays
    "return a new instance of myself, numberOfDays afterwards."

    ^ self addSeconds:(numberOfDays * (60 * 60 * 24))

    "
     |t|

     t := Timestamp now.
     Transcript showCR:t.
     Transcript showCR:(t addDays:7)
    "
!

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

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

    "
     |t|

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

    "
     |t|

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

addMilliseconds:numberOfMilliSeconds
    "return a new instance of myself, numberOfMilliSeconds afterwards."

    ^ self species basicNew 
        setMilliseconds:(self getMilliseconds + numberOfMilliSeconds)

    "
     |t|

     t := Timestamp now.
     Transcript showCR:t.
     Transcript showCR:(t addMilliseconds:100).
    "

    "
     |t|

     t := Time now.
     Transcript showCR:t.
     Transcript showCR:(t addMilliseconds:1000).
    "
!

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

    ^ self addSeconds:(numberOfMinutes * 60)

    "
     |t|

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

    "
     |t|

     t := Time now.
     Transcript showCR:t.
     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 := Timestamp now.
     Transcript showCR:t.
     Transcript showCR:(t addSeconds:60).
    "

    "
     |t|

     t := Time now.
     Transcript showCR:t.
     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"

    timeAmount isNumber ifFalse:[
        ^ self addSeconds:(timeAmount asSeconds).
    ].
    ^ self addSeconds:timeAmount
!

subtractDays:numberOfDays
    "return a new instance of myself, numberOfDays before."

    ^ self subtractSeconds:(numberOfDays * (60 * 60 * 24))

    "
     |t|

     t := Timestamp now.
     Transcript showCR:t.
     Transcript showCR:(t subtractDays:50)
    "
!

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

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

    "
     |t|

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

    "
     |t|

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

subtractMilliseconds:numberOfMilliSeconds
    "return a new instance of myself, numberOfMilliSeconds before."

    ^ self species basicNew 
        setMilliseconds:(self getMilliseconds - numberOfMilliSeconds)

    "
     |t|

     t := Timestamp now.
     Transcript showCR:t.
     Transcript showCR:(t subtractMilliseconds:100).
    "

    "
     |t|

     t := Time now.
     Transcript showCR:t.
     Transcript showCR:(t subtractMilliseconds:1000).
    "
!

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

    ^ self subtractSeconds:(numberOfMinutes * 60)

    "
     |t|

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

    "
     |t|

     t := Time now.
     Transcript showCR:t.
     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 := Timestamp now.
     Transcript showCR:t.
     Transcript showCR:(t subtractSeconds:60).
    "

    "
     |t|

     t := Time now.
     Transcript showCR:t.
     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"

    timeAmount isNumber ifFalse:[
        ^ self subtractSeconds:(timeAmount asSeconds).
    ].
    ^ 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:'converting'!

asAbsoluteTime
    "deprecated, use #asTimestamp"
    <resource:#obsolete>

    ^ self asTimestamp
!

asTimestamp
    ^ self subclassResponsibility
! !

!AbstractTime methodsFor:'printing & storing'!

addPrintBindingsTo:aDictionary
    "private print support: add bindings for printing to aDictionary."

    self addPrintBindingsTo:aDictionary language:nil
!

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

    |hours minutes seconds millis usHours ampm s zone tzDelta|

    hours := self hours.
    minutes := self minutes.
    seconds := self seconds.
    millis := self milliseconds.
    zone := self timeZoneName.
    tzDelta := self timeZoneDeltaInMinutes.

    ampm := self meridianAbbreviation.
    usHours := self hour12.

    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.
    aDictionary at:$z put:zone.
    aDictionary at:$Z put:zone asUppercase.

    s := tzDelta >= 0 ifTrue:[ '+' ] ifFalse:[ '-' ].
    tzDelta := tzDelta abs.
    s := s , ((tzDelta // 60) printStringLeftPaddedTo:2 with:$0).
    s := s , ':'.
    s := s , ((tzDelta \\ 60) printStringLeftPaddedTo:2 with:$0).
    aDictionary at:#TZD put:s
!

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

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

        %nth           - counting day-in-month (1->'st'; 2->'nd'; 3->'rd'; 4...->'th')      
        %weekDayNth    - counting day-in-week (1->'st'; 2->'nd'; 3->'rd'; 4...->'th')      
        %weekNth       - counting week-in-year (1->'st'; 2->'nd'; 3->'rd'; 4...->'th')      

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

    aStream nextPutAll:(self printStringFormat:aFormatString)

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

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

        %(TZD)  timeZone delta from UTC in the format +/-hh:mm  

        %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        

        %nth           - counting day-in-month (1->'st'; 2->'nd'; 3->'rd'; 4...->'th')      
        %weekDayNth    - counting day-in-week (1->'st'; 2->'nd'; 3->'rd'; 4...->'th')      
        %weekNth       - counting week-in-year (1->'st'; 2->'nd'; 3->'rd'; 4...->'th')      

     Timestamp only:
        %Day    day - unpadded                    
        %Month  month - unpadded                    
        %(yearOrTime)  year or time 5 digits    as in unix-ls:
                                                year if it is not the current year;
                                                time otherwise


     The ISO8601 printString are generated with:

       Year:
          YYYY (eg 1997)
                Date today printStringFormat:'%(year)'
                Timestamp now printStringFormat:'%(year)'  

       Year and month:
          YYYY-MM (eg 1997-07)
                Date today printStringFormat:'%(year)-%(month)'  
                Timestamp now printStringFormat:'%(year)-%(month)'  

       Complete date:
          YYYY-MM-DD (eg 1997-07-16)
                Date today printStringFormat:'%(year)-%(month)-%(day)'    
                Timestamp now printStringFormat:'%(year)-%(month)-%(day)'  

       Complete date plus hours and minutes:
          YYYY-MM-DDThh:mmTZD (eg 1997-07-16T19:20+01:00)
                Timestamp now printStringFormat:'%(year)-%(month)-%(day)T%h:%m%(TZD)'  

       Complete date plus hours, minutes and seconds:
          YYYY-MM-DDThh:mm:ssTZD (eg 1997-07-16T19:20:30+01:00)
                Timestamp now printStringFormat:'%(year)-%(month)-%(day)T%h:%m:%s%(TZD)'  

       Complete date plus hours, minutes, seconds and a decimal fraction of a second
          YYYY-MM-DDThh:mm:ss.sTZD (eg 1997-07-16T19:20:30.45+01:00)
                Timestamp now printStringFormat:'%(year)-%(month)-%(day)T%h:%m:%s.%(milli2)%(TZD)'  

    "

    |dict|

    dict := IdentityDictionary new.
    self addPrintBindingsTo:dict.

    ^ (aFormatString expandPlaceholdersWith:dict)

    "
     Timestamp 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'           
     Timestamp now printStringFormat:'%H:%m:%s.%i'   
     Timestamp now printStringFormat:'%H:%m:%s.%(milli1)'   
     Timestamp now printStringFormat:'%H:%m:%s.%(milli2)'     
     Timestamp now printStringFormat:'%(day)-%(month)-%(year) :%m:%s'       
     Timestamp now printStringFormat:'%(day)-%(monthName)-%(year) :%m:%s'       
     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 some point of time in the past.
     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 some point of time in the past.
     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 some point of time in the past.
     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 some point of time in the past.
     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.50 2004-09-22 14:42:22 stefan Exp $'
! !