Date.st
author james
Wed, 09 Apr 2003 14:29:15 +0200
changeset 7182 42dce0ee1b98
parent 7023 6092f474bbba
child 7258 9ccdbee7d1ad
permissions -rw-r--r--
james' package changes

"
 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' }"

Magnitude subclass:#Date
	instanceVariableNames:'dateEncoding'
	classVariableNames:'DayNames MonthNames DayAbbrevs MonthAbbrevs EnvironmentChange'
	poolDictionaries:''
	category:'Magnitude-General'
!

!Date 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
"
    Instances of Date represent dates as year, month and day encoded in the 
    (private & hidden) instance dateEncoding. The value found there is 
    year*100*100 + month*100 + day (which makes magnitude-like comparison of 
    dates easy, but is not guaranteed for future versions).
    Do not depend on the internal representation.

    The old representation used days since 1st Jan. 1901 internally - 
    with the new implementation, it is possible to reasonably represent almost 
    any Date.  (which insurance companies will like, since they can now 
    represent even very old peoples birthday :-)
    Notice: no correction for pre-Julian dates is done.

    The printed representation of dates is controlled by resource definitions -
    thus national variants are already supported (see file 'resources/Date.rs').

    Compatibility notice:
        due to some historic reasons, there are some methods found twice
        with different names in this class. The old ST/X methods will vanish in
        one of the next releases, and kept for a while to support existing
        applications (the info on how these methods should be named came 
        somewhat late from the testers ..).

        Please do not use methods marked as obsolete in their comment.

    Most useful methods:

        Date today
        (Date today) addDays:
        (Date today) subtractDays:

    [author:]
        Claus Gittinger

    [see also:]
        Time AbstractTime
        Filename
        OperatingSystem
"
! !

!Date class methodsFor:'instance creation'!

fromDays:dayCount
    "return a new Date, given the day-number starting with 0 at 1.Jan 1901;
     (i.e. 'Date fromDays:0' returns 1st Jan. 1901).
     Date asDays is the reverse operation.
     Added for GNU/ST-80 compatibility"

    |yr rest d|

    "approx. year"
    yr := (dayCount // 366) + 1901.
    rest := dayCount - (self yearAsDays:yr) + 1. "+1 for ST-80 compatibility"
    d := self daysInYear:yr.
    (rest > d) ifTrue:[
        "adjust"
        yr := yr + 1.
        rest := rest - d.
    ].

    ^ self newDay:rest year:yr

    "
     Date fromDays:0     -> 1 jan 1901
     Date fromDays:365   -> 1 jan 1902
     Date fromDays:730   -> 1 jan 1903
     Date fromDays:1095  -> 1 jan 1903
     Date fromDays:1460  ->31 dec 1904 since 1904 was a leap year
    "

    "Modified: 1.7.1996 / 14:24:25 / cg"
!

newDay:day month:month year:year
    "return a new Date, given the day, month and year.
     For your convenience, month may be either an integer 
     or the months name as a string. 

     WARNING: semantics changed: 0..99 is no longer treated as 1900..1999,
              but as 0..99 now.
              Any such adjustments must be made by the caller of this method now
              (see those, for example readFrom:onError:)"

    |monthIndex ok|

    year < 100 ifTrue:[
        'Date [warning]: year in [0..99] no longer converted to [1900..1999]' infoPrintCR.
    ].
    month isInteger ifTrue:[
        monthIndex := month
    ] ifFalse:[
        monthIndex := self indexOfMonth:month
    ].
    (monthIndex == 2 and:[day == 29]) ifTrue:[
        ok := self leapYear:year
    ] ifFalse:[
        ok := day <= (self daysInMonth:month forYear:year)
    ].
    ((day > 0) and:[ok]) ifTrue:[
        ^ self basicNew dateEncoding:(((year * 100) + monthIndex) * 100) + day
    ].

    "this error is triggered if you try to create a date from an
     invalid year/month/day combination;
     Such as 29-feb-year, where year is no leap year
    "
    self error:'invalid date'

    "
     Date newDay:8  month:'may' year:1993
     Date newDay:8  month:5     year:1994
     Date newDay:29 month:'feb' year:1994
     Date newDay:29 month:'feb' year:1993
     Date newDay:28 month:'feb' year:5   
     Date newDay:28 month:'feb' year:95  
    "

    "Modified: 19.4.1996 / 15:28:15 / cg"
!

newDay:dayInYear year:year
    "return a new Date, given the year and the day-in-year (starting at 1).
     See also: Date today / Time now / AbsoluteTime now.
     ST-80 compatibility"

    |monthAndDay|

    (dayInYear between:1 and:365) ifFalse:[
        ((dayInYear == 366) and:[self leapYear:year]) ifFalse:[
            "
             this error is triggered, when you try to create a
             day from an invalid day-in-year; 
             for example, 366 in a non-leap year.
             I dont know, if ST-80 wraps to the next year(s) in this case.
            "
            ^ self error:'invalid date'
        ]
    ].
    monthAndDay := self monthAndDayFromDayInYear:dayInYear forYear:year.
    ^ self newDay:(monthAndDay at:2) month:(monthAndDay at:1) year:year

    "
     Date newDay:150 year:1994
     Date newDay:1 year:1994
     Date newDay:1 year:1901
     Date newDay:1 year:1902
     Date newDay:365 year:1992
     Date newDay:366 year:1992
     Date newDay:365 year:1994
     Date newDay:366 year:1994
    "

    "Modified: 1.7.1996 / 14:22:24 / cg"
!

readFrom:aStringOrStream onError:exceptionBlock
    "return a new Date, reading a printed representation from aStream.
     Notice, that this is not the storeString format and 
     is different from the format expected by readFrom:.
     BUG:
       This method assumes american format (i.e. month-day-year) instead
       of the german/french and other day-month-year.
       There ought to be a internationalized variant of this."

    ^ [
        |str month day year|
        str := aStringOrStream readStream.

        [str peek isLetterOrDigit] whileFalse:[str next].
        (str peek isDigit) ifTrue:[
            day := Integer readFrom:str
        ].
        [str peek isLetterOrDigit] whileFalse:[str next].
        (str peek isLetter) ifTrue:[
            month := str nextAlphaNumericWord.
            day isNil ifTrue:[
                [str peek isLetterOrDigit] whileFalse:[str next].
                day := Integer readFrom:str.
            ]
        ] ifFalse:[
            month := self nameOfMonth:day.
            day := Integer readFrom:str
        ].
        [str peek isLetterOrDigit] whileFalse:[str next].
        year := Integer readFrom:str.
        (year between:0 and:99) ifTrue:[
            year := UserPreferences current twoDigitDateHandler value:year.
        ].
        self newDay:day month:month year:year
    ] on:Error do:exceptionBlock.

    "
     Date readFromString:'31 December 1992'  
     Date readFrom:'19:11:1999'  
     Date readFromString:'December, 5 1992'  
     Date readFromString:'12/31/1992'        
     Date readFromString:'3-jan-95'           
     Date readFromString:'3-jan-01'           
     Date readFromString:'12/31/01'        
     Date readFromString:'15.4.1992'         -> german; leads to an error
     Date readFromString:'10.4.1992'         -> german; leads to a wrong date
     Date readFromString:'10.4.1992' onError:['wrong date']
     Date readFromString:'32.4.1992' onError:['wrong date']
     Date readFromString:'fooBar' onError:['wrong date']
     Date readFromString:'10.4' onError:['wrong date']
     Date readFromString:'10041999' onError:['wrong date']  
    "

    "Created: 16.11.1995 / 22:50:17 / cg"
    "Modified: 8.10.1996 / 19:25:39 / cg"
!

readFrom:aStringOrStream printFormat:aFormatArray
    "return a new Date, reading a printed representation from aStream.
     1   day position (1, 2 or 3)
     2   month position (1..3)
     3   year position (1..3)
    "
    ^ self readFrom:aStringOrStream
        printFormat:aFormatArray 
            onError:[self error:'expected: ' , self name]

    "
     Date readFrom:'19:11:1999' printFormat:#( 1 2 3 )
     Date readFrom:'19-nov-1999' printFormat:#( 1 2 3 )
     Date readFrom:'19:11:1999' printFormat:#( 2 1 3 )  -> exception: wrong month
     Date readFrom:'5:12:1999' printFormat:#( 2 1 3 )  
     Date readFrom:'may-12-1999' printFormat:#( 2 1 3 )  
     Date readFrom:'1999 may 12' printFormat:#( 3 2 1 )  
    "

    "Created: 16.11.1995 / 22:50:17 / cg"
    "Modified: 8.10.1996 / 19:25:39 / cg"
!

readFrom:aStringOrStream printFormat:aFormatArray onError:exceptionBlock
    "return a new Date, reading a printed representation from aStream.
     1   day position (1, 2 or 3)
     2   month position (1..3)
     3   year position (1..3)
    "

    ^ [
        |str arg year|

        str := aStringOrStream readStream.
        arg := Array new:3.

        1 to:3 do:[:i||v|
            [str peek isLetterOrDigit] whileFalse:[str next].

            v := (str peek isDigit) ifTrue:[Integer readFrom:str]
                                   ifFalse:[str nextAlphaNumericWord].
            arg at:i put:v
        ].
        year := (arg at:(aFormatArray at:3)).
        (year between:0 and:99) ifTrue:[
            year := UserPreferences current twoDigitDateHandler value:year.
        ].
        self newDay:(arg at:(aFormatArray at:1))
              month:(arg at:(aFormatArray at:2))
               year:year
    ] on:Error do:exceptionBlock.

    "
     Date readFrom:'31 December 1992' printFormat:#(1 2 3) onError:'fail' 
     Date readFrom:'19:11:1999' printFormat:#(1 2 3) onError:'fail'  
     Date readFrom:'December, 5 1992' printFormat:#(1 2 3) onError:'fail' 
     Date readFrom:'3-jan-95' printFormat:#(1 2 3) onError:'fail'          
     Date readFrom:'12/31/1992' printFormat:#(1 2 3) onError:'fail'       
     Date readFrom:'15.4.1992' printFormat:#(1 2 3) onError:'wrong date'  -> german
     Date readFrom:'10.4.1992' printFormat:#(1 2 3) onError:'fail'        -> german
     Date readFrom:'10.4.1992' printFormat:#(1 2 3) onError:['wrong date']
     Date readFrom:'32.4.1992' printFormat:#(1 2 3) onError:['wrong date']
     Date readFrom:'fooBar' printFormat:#(1 2 3) onError:['wrong date']
     Date readFrom:'10.4' printFormat:#(1 2 3) onError:['wrong date']
     Date readFrom:'10041999' printFormat:#(1 2 3) onError:['wrong date']  

     Date readFrom:'31/12/92' printFormat:#(1 2 3) onError:'fail'       
     Date readFrom:'31/12/01' printFormat:#(1 2 3) onError:'fail'       
    "

    "Created: 16.11.1995 / 22:50:17 / cg"
    "Modified: 8.10.1996 / 19:25:39 / cg"
!

readMMDDYYYYFrom:aStringOrStream onError:exceptionBlock
    "return a new Date, reading a printed representation from aStream.
     Notice, that this is not the storeString format and 
     is different from the format expected by readFrom:"

    ^ [
        |str month day year|

        str := aStringOrStream readStream.
        month := str next:2.
        month := Integer readFrom:month.
        day := str next:2.
        day := Integer readFrom:day.
        year := str next:4.
        year := Integer readFrom:year.

        self newDay:day month:month year:year
    ] on:Error do:exceptionBlock

    "
     Date readMMDDYYYYFrom:'10041999' onError:['wrong date']  
     Date readMMDDYYYYFrom:'100419' onError:['wrong date']  

     Date readMMDDYYYYFrom:'10040001' onError:['wrong date']  
    "

    "Created: 16.11.1995 / 22:50:17 / cg"
    "Modified: 8.10.1996 / 19:25:39 / cg"
!

today
    "return a date, representing today.
     See also: Time now / AbsoluteTime now."

    ^ self fromOSTime:(OperatingSystem getOSTime)

    "
     Date today
    "

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

tomorrow
    "return a date, representing tomorrow.
     See also: Time now / AbsoluteTime now."

    ^ Date today addDays:1

    "
     Date tomorrow 
     Date tomorrow dayInWeek
    "
!

yesterday
    "return a date, representing yesterday.
     See also: Time now / AbsoluteTime now."

    ^ Date today subtractDays:1

    "
     Date yesterday 
     Date yesterday dayInWeek
    "
! !

!Date class methodsFor:'Compatibility - Dolphin'!

newDay:day monthIndex:month year:year
    ^ self newDay:day month:month year:year

    "
     Date newDay:8 monthIndex:5 year:1993
    "

    "Modified: 19.4.1996 / 15:28:15 / cg"
! !

!Date class methodsFor:'Compatibility - Squeak'!

fromSeconds:seconds
    "Answer an instance of me which is 'seconds' seconds after January 1, 1901."

    | secondsInDay |

    secondsInDay := 24 * 60 * 60.
    ^self fromDays: seconds // secondsInDay

    "
     Date fromSeconds:0
     Date fromSeconds:(24 * 60 * 60 * 365)
    "
! !

!Date class methodsFor:'general queries'!

abbreviatedNameOfDay:dayIndex
    "given a day index (1..7), return the abbreviated name
     of the day"

    (DayAbbrevs isNil or:[EnvironmentChange]) ifTrue:[
        self initNames
    ].
    ^ DayAbbrevs at:dayIndex

    "
     Date abbreviatedNameOfDay:4
    "
!

abbreviatedNameOfMonth:monthIndex
    "given a month index (1..12), return the abbreviated name
     of the month"

    (MonthAbbrevs isNil or:[EnvironmentChange]) ifTrue:[
        self initNames
    ].
    ^ MonthAbbrevs at:monthIndex

    "
     Date abbreviatedNameOfMonth:11
     Date abbreviatedNameOfMonth:12
    "
!

dateAndTimeNow
    "return an array containing the date and time of now"

    ^ Time dateAndTimeNow

    "
     Date dateAndTimeNow
    "
!

dayOfFirstWeekInYear:aYear
    "for a given year, return the day corresponding to that years monday of week-01.
     The 1st week is the one, in which the first thursday is found;
     and the 1st day of that week is the preceeding monday 
     (that means: that the returned day might be a day of the previous year)"

    |day dayInWeekOf1stJan firstThursday firstDayInWeek|

    "/ find the first thursday ...
    day := AbsoluteTime newDay:1 year:aYear.
    dayInWeekOf1stJan := day dayInWeek.
    dayInWeekOf1stJan > 4 ifTrue:[
        firstThursday := day addDays:(4 - dayInWeekOf1stJan + 7).
    ] ifFalse:[
        firstThursday := day addDays:(4 - dayInWeekOf1stJan).
    ].
    "/ back to the preceeding monday
    firstDayInWeek := firstThursday subtractDays:3.
    ^ firstDayInWeek

    "
     Date dayOfFirstWeekInYear:1998   
     Date dayOfFirstWeekInYear:1999    
     Date dayOfFirstWeekInYear:2000  
     Date dayOfFirstWeekInYear:2001   
    "
!

dayOfWeek:dayName
    "given the name of a day (either string or symbol),
     return the day-index (1 for monday; 7 for sunday).
     Return 0 for invalid day name"

    |idx|

    (DayNames isNil or:[EnvironmentChange]) ifTrue:[
        self initNames
    ].
    idx := DayNames indexOf:dayName.
    idx == 0 ifTrue:[
        idx := DayNames indexOf:dayName asLowercase.
    ].
    ^ idx

    "
     Date dayOfWeek:'wednesday' 
     Date dayOfWeek:'Wednesday' 
    "
!

daysInMonth:month forYear:yearInteger
    "given the name of a month and a year, return the number 
     of days this month has (modified GNU).
     return 0 if the month name was invalid.
     For your convenience, month maybe an integer or name-string."

    |monthIndex "{ Class: SmallInteger }"|

    month isInteger ifTrue:[
	monthIndex := month
    ] ifFalse:[
	monthIndex := self indexOfMonth:month
    ].

    ^ self daysInMonthIndex:monthIndex forYear:yearInteger

    "
     Date daysInMonth:2 forYear:1980
     Date daysInMonth:2 forYear:1981
     Date daysInMonth:'feb' forYear:1981
    "
!

daysInYear:yearInteger
    "return the number of days in a year"

    (self leapYear:yearInteger) ifTrue:[^ 366].
    ^ 365

    "
     Date daysInYear:1900  
     Date daysInYear:1901 
     Date daysInYear:1904 
     Date daysInYear:1980 
     Date daysInYear:1981
    "
!

daysUntilMonth:month forYear:yearInteger
    "given the name of a month and a year, return the number 
     of days from 1st january to last of prev month of that year.
     Return 0 if the month name/index is invalid or is january.
     For your convenience, month maybe an integer or name-string."

    |monthIndex "{ Class: SmallInteger }"
     sumDays    "{ Class: SmallInteger }" |

    month isInteger ifTrue:[
	monthIndex := month
    ] ifFalse:[
	monthIndex := self indexOfMonth:month
    ].
    (monthIndex between:1 and:12) ifFalse:[^ 0].

    sumDays := 0.
    1 to:monthIndex-1 do:[:m |
	sumDays := sumDays + (self daysInMonthIndex:m forYear:yearInteger)
    ].
    ^ sumDays

    "
     Date daysUntilMonth:'feb' forYear:1993
     Date daysUntilMonth:'jan' forYear:1993
    "
!

firstDayOfYear:inYear
    "return the weekDay-index of the 1st-january of the given year.
     1->monday, 2->tuesday, ... 7->sunday"

    | t d |

    ((inYear < 1) or:[ inYear > 9999]) ifTrue:[
        ^ 0.
    ].

    "/ normal Gregorian calendar: one extra day per four years 
    t := 4 + inYear + ((inYear + 3) // 4).

    inYear > 1800 ifTrue:[
        "/ Julian calendar: regular Gregorian less 3 days per 400
        t := t - ((inYear - 1701) // 100) + ((inYear - 1601) // 400).
    ].
    inYear > 1752 ifTrue:[
        "/ calendar changeover
        t := t + 3.
    ].
    d := t \\ 7.
    "/ convert from 0 (sunday) .. 6 (saturday)
    "/ to 1 (munday) .. 7 (sunday)
    d == 0 ifTrue:[^ 7].
    ^ d

    "
     self firstDayOfYear:2000           
     (Date newDay:1 year:2000) dayInWeek 
     self firstDayOfYear:1999      
     (Date newDay:1 year:1999) dayInWeek
     self firstDayOfYear:1998      
     (Date newDay:1 year:1998) dayInWeek    
     self firstDayOfYear:2001           
     (Date newDay:1 year:2001) dayInWeek    
     self firstDayOfYear:2002           
     (Date newDay:1 year:2002) dayInWeek    
     self firstDayOfYear:2006           
     (Date newDay:1 year:2006) dayInWeek    

     self firstDayOfYear:1800           
     (Date newDay:1 year:1800) dayInWeek    
    "
!

indexOfMonth:aMonthString
    "given the name of a month (either string or symbol),
     return the month-index (1 for jan; 12 for december).
     The given string may be a full or abbreviated name,
     case is ignored.
     Return 0 for invalid month name."

    |idx name|

    EnvironmentChange ifTrue:[
	self initNames
    ].
    name := aMonthString asLowercase.
    idx := MonthAbbrevs indexOf:name.
    idx ~~ 0 ifTrue:[^ idx].
    idx := MonthNames indexOf:name.
    idx ~~ 0 ifTrue:[^ idx].

    name at:1 put:(name at:1) asUppercase.
    idx := MonthAbbrevs indexOf:name.
    idx ~~ 0 ifTrue:[^ idx].
    idx := MonthNames indexOf:name.
    idx ~~ 0 ifTrue:[^ idx].

    ^ idx

    "
     Date indexOfMonth:'jan'
     Date indexOfMonth:'Jan'
     Date indexOfMonth:'December'
    "
!

isLeapYear:yearInteger
    "Return true, if a year is a leap year.
     Obsolete:
	 Please use the ST-80 compatible #leapYear for new programs, 
	 since this method will vanish."

    ^ self leapYear:yearInteger
!

leapYear:yearInteger
    "return true, if yearInteger is a leap year."

    |y "{ Class: SmallInteger }"|

    y := yearInteger.
    (y \\ 4 == 0) ifTrue:[
	(y \\ 100 ~~ 0) ifTrue:[^ true].
	(y \\ 400 == 0) ifTrue:[^ true]
    ].
    ^ false

    "
     Date leapYear:1992
     Date leapYear:1994
     Date leapYear:1900
     Date leapYear:2000
    "
!

monthAndDayFromDayInYear:aDayInYear forYear:yearInteger
    "given a day-in-year (1..365) return an Array containing the
     month index and the day-in-month. Return nil if the argument is invalid."

    |restDays daysInMonth|

    restDays := aDayInYear.
    restDays < 1 ifTrue:[^ nil].

    1 to:12 do:[:m |
	daysInMonth := self daysInMonthIndex:m forYear:yearInteger.
	restDays <= daysInMonth ifTrue:[
	    ^ Array with:m with:restDays
	].
	restDays := restDays - daysInMonth 
    ].
    restDays > daysInMonth ifTrue:[^ nil].
    ^ Array with:12 with:restDays

    "
     Date monthAndDayFromDayInYear:66 forYear:1980
     Date monthAndDayFromDayInYear:66 forYear:1981
    "
!

nameOfDay:dayIndex
    "given a day index (1..7), return the name of the day" 

    (DayNames isNil or:[EnvironmentChange]) ifTrue:[
        self initNames
    ].
    ^ DayNames at:dayIndex

    "
     Date nameOfDay:4
    "
!

nameOfMonth:monthIndex
    "given a month index (1..12), return the name of the month"

    (MonthNames isNil or:[EnvironmentChange]) ifTrue:[
        self initNames
    ].
    ^ MonthNames at:monthIndex

    "
     Date nameOfMonth:11
     Date nameOfMonth:12
     Date nameOfMonth:4
    "
!

weekInYearOf:aDateOrTimestamp
    "for a given date or timeStamp, return the week-number.
     the returned week number starts with 1 for the first week which has a thursday in it.
     The above definition can lead to the 1st week starting in the old year!!"

    |dayInYear numDays dayOfFirstWeekInYear dayOfFirstWeekInNextYear week|

    dayInYear := aDateOrTimestamp dayInYear.
    dayOfFirstWeekInYear := self dayOfFirstWeekInYear:aDateOrTimestamp year.

    numDays := aDateOrTimestamp asDate subtractDate:dayOfFirstWeekInYear asDate.
    "/ careful with the first days - could be W52/W53 of the previous year ...
    numDays < 0 ifTrue:[
        "/ not in a week here ...
        "/ can be either 52 or 53, depending on the previous year.
        ^ self weekInYearOf:(Date day:31 month:12 year:aDateOrTimestamp year - 1)
    ].

    "/ compute the week 
    week := numDays // 7 + 1.

    "/ careful with the last days - could be W01 of the next year ...
    week == 53 ifTrue:[
        dayOfFirstWeekInNextYear := self dayOfFirstWeekInYear:aDateOrTimestamp year + 1.
        aDateOrTimestamp asDate >= dayOfFirstWeekInNextYear asDate ifTrue:[
            ^ 1
        ].
    ].
    ^ week

    "
     AbsoluteTime now weekInYear    
     Date weekInYearOf:(Date day:31 month:12 year:1999)     was a friday; 
     Date weekInYearOf:(AbsoluteTime newDay:1 year:2000)    was a saturday; therefore last week of 1999
     Date weekInYearOf:(AbsoluteTime newDay:2 year:2000)    was a sunday; therefore last week of 1999
     Date weekInYearOf:(AbsoluteTime newDay:3 year:2000)    was a monday -> W01
     Date weekInYearOf:(AbsoluteTime newDay:4 year:2000)    was a tuesday -> W01
     Date weekInYearOf:(AbsoluteTime newDay:5 year:2000)    was a wed    -> W01
     Date weekInYearOf:(AbsoluteTime newDay:6 year:2000)    was a thursday -> W01
     Date weekInYearOf:(AbsoluteTime newDay:7 year:2000)    was a fri    -> W01
     Date weekInYearOf:(AbsoluteTime newDay:8 year:2000)    was a sat   -> W01
     Date weekInYearOf:(AbsoluteTime newDay:9 year:2000)    was a sun   -> W01
     Date weekInYearOf:(AbsoluteTime newDay:10 year:2000)   was a monday -> W02
     Date weekInYearOf:(AbsoluteTime newDay:16 year:2000)   was a sunday -> W02
     Date weekInYearOf:(AbsoluteTime newDay:17 year:2000)   was a monday -> W03
     Date weekInYearOf:(Date day:1 month:1 year:2001)     
     Date weekInYearOf:(Date day:2 month:1 year:2001)     
     Date weekInYearOf:(Date day:3 month:1 year:2001)     
     Date weekInYearOf:(Date day:24 month:12 year:2001)   -> W52
     Date weekInYearOf:(Date day:30 month:12 year:2001)   -> W52
     Date weekInYearOf:(Date day:31 month:12 year:2001)   -> W01
     Date weekInYearOf:(Date day:1 month:1 year:2002)    
     Date weekInYearOf:(Date day:2 month:1 year:2002)      
     Date weekInYearOf:(Date day:7 month:1 year:2002)      
    "
!

yearAsDays: yearInteger
    "Returns the number of days since Jan 1, 1901. (GNU)
     to the first Jan of the year, yearInteger.
     For 1901 this is zero, for 1902 its 365.
     Defined for years >= 1901"

    |y "{ Class: SmallInteger }"|

    y := yearInteger - 1900.
    y := y - 1.
    ^ (y * 365)
	+ (y // 4)
	- (y // 100)
	+ ((y + 300) // 400)

    "
     Date yearAsDays:1901 
     Date yearAsDays:1902   
     Date yearAsDays:1903   
     Date yearAsDays:1904    
     Date yearAsDays:1905     
     Date yearAsDays:1994   
     (Date yearAsDays:2001) - (Date yearAsDays:2000)   
    "
! !

!Date class methodsFor:'handling language changes'!

initialize
    "check for case where Resource-classes are absent"
    ResourcePack isNil ifTrue:[
	self initNames
    ] ifFalse:[
	Smalltalk addDependent:self.
	EnvironmentChange := true
    ]
!

update:something with:aParameter from:changedObject
    ((something == #Language) or:[something == #LanguageTerritory]) ifTrue:[
        "just remember change for next access"
        EnvironmentChange := true
    ]

    "Created: 15.6.1996 / 15:19:25 / cg"
! !

!Date class methodsFor:'obsolete instance creation'!

day:day month:month year:year
    "return a new Date, given the day, month and year.
     Obsolete:
	use newDay:month:year: for ST-80 compatibility"

    ^ self newDay:day month:month year:year
!

day:dayInYear year:year
    "return a new Date, given the year and the day-in-year (starting at 1).
     Obsolete:
	use newDay:year: for ST-80 compatibility"

    ^ self newDay:dayInYear year:year
! !

!Date class methodsFor:'private'!

daysInMonthIndex: monthIndex forYear: yearInteger
    "return the number of days in month monthIndex of
     year yearInteger (modified GNU).
     Return 0 for invalid month index.
     This is the internal version of daysInMonth:forYear:"

    |days|

    (monthIndex between:1 and:12) ifFalse:[^ 0].

    days := #(31 28 31           "Jan Feb Mar"
	      30 31 30           "Apr May Jun"
	      31 31 30           "Jul Aug Sep"
	      31 30 31           "Oct Nov Dec"
	     ) at: monthIndex.

    (monthIndex == 2) ifTrue:[
	(self leapYear:yearInteger) ifTrue:[
	    ^ days + 1
	]
    ].
    ^ days

    "
     Date daysInMonthIndex:2 forYear:1994
     Date daysInMonthIndex:2 forYear:1980
     Date daysInMonthIndex:2 forYear:1981
    "
!

initNames
    "read the language specific names"

    |resources|

    DayNames := #('monday'
		  'tuesday'
		  'wednesday'
		  'thursday'
		  'friday'
		  'saturday'
		  'sunday').

    DayAbbrevs := #('mon' 
		    'tue' 
		    'wed'
		    'thu' 
		    'fri' 
		    'sat' 
		    'sun').

    MonthNames := #('january'
		    'february'
		    'march'
		    'april'
		    'may'
		    'june'
		    'july'
		    'august'
		    'september'
		    'october'
		    'november'
		    'december').

    MonthAbbrevs := #('jan'
		      'feb'
		      'mar'
		      'apr'
		      'may'
		      'jun'
		      'jul'
		      'aug'
		      'sep'
		      'oct'
		      'nov'
		      'dec').

    "check for case where Resource-classes are absent"
    ResourcePack notNil ifTrue:[
	resources := ResourcePack for:self.

	DayNames := resources array:DayNames.
	DayAbbrevs := resources array:DayAbbrevs.
	MonthNames := resources array:MonthNames.
	MonthAbbrevs := resources array:MonthAbbrevs.
    ].

    EnvironmentChange := false

    "Date initNames"
! !

!Date class methodsFor:'private encoding'!

encodeYear:y month:m day:d
    "the internal encoding is stricktly private, 
     and should not be used outside."

    ^ (((y * 100) + m) * 100) + d
! !

!Date class methodsFor:'private instance creation'!

fromOSTime:osTime
    "return a date, representing the date given by the operatingSystem time.
     This somewhat clumsy implementation hides the OS's date representation
     (i.e. makes this class independent of what the OS starts its time values with).
     Dont use this method, the osTime representation is totally unportable."

    ^ self basicNew fromOSTime:osTime

    "
     Date fromOSTime:#(0 0)      -> on UNIX: this should return 1st Jan 1970
				    thats where Unix time starts
				    On other systems, it may be something different.

     Date fromOSTime:#(86400 0)  -> on UNIX: the day after
    "
! !

!Date methodsFor:'Compatibility - ANSI'!

dayOfWeek
    "return the week-day of the receiver - 1 is sunday, 7 for saturday.
     WARNING: different from dayInWeek (which returns 1 for monday, ... 7 for sunday).  
    "

    |d|

    d := self dayInWeek.
    d == 7 ifTrue:[
        ^ 1
    ].
    ^ d + 1

    "
     Date today dayOfWeek
     Date today dayInWeek
    "
!

dayOfWeekAbbreviation
    "return the short week-day of the receiver as a string.
     The returned string depends on the language setting.
     Expect things like 'mon', 'tue' ..."

    ^ self abbreviatedDayName

    "
     Date today dayOfWeekAbbreviation
    "
!

dayOfWeekName
    "return the week-day of the receiver as a string.
     The returned string depends on the language setting.
     Expect things like 'monday', 'tuesday' ..."

    ^ self weekday

    "
     Date today dayOfWeekName
     Date today dayOfWeekAbbreviation 
    "
!

dayOfYear
    "return the day-nr within the year of the receiver - 1..365/366"

    ^ self dayInYear

    "
     Date today dayOfYear 
    "
!

isLeapYear
    "return true, if the receivers year is a leap year"

    ^ self leap

    "
     Date today isLeapYear
     (Date day:1 month:1 year:1992) isLeapYear
    "
!

monthAbbreviation
    "return the month of the receiver as a string.
     The returned string depends on the language setting.
     Expect things like 'jan', 'feb' ..."

    ^ self abbreviatedMonthName

    "
     Date today monthAbbreviation  
    "
! !

!Date methodsFor:'Compatibility - ST80'!

previous:dayName 
    "Return the previous date whose weekday name is dayName.
     Caveat; dayName is expected to be in the current language"

    ^ self subtractDays:(self weekdayIndex - (self class dayOfWeek:dayName) - 1 \\ 7 + 1)

    "
     Date today                 
     Date today previous:#Monday 
     Date today previous:#Friday 
    "
!

printFormat:aFormatArray
    "Obsolete, backward ST-80 compatible formatted printing - see printStringFormat:
     Return a string containing a printed representation of the receiver.
     The formatArray argument consists of 6 or 7 integers which control
     the resulting string. The entries are:
     1   day position (1, 2 or 3)
     2   month position (1..3)
     3   year position (1..3)
     4   asciiValue of separator character or separator character
         or collection of 2 separator characters
     5   month format (1: numeric; 2: abbreviated name; 3: fullname
         4: abbreviated uppercase 5: full uppercase)
     6   year format (1 include century; 2 exclude century)
     7  (optional) true/false.
         if true, print numbers in 2-digit format
         (i.e. with leading zeros); 
         Taken as false, if ommited

     Day and monthnames are in the currently active language.

     This method supports more options than the ST-80 version; month formats 
     4 and 5, non-numeric separators and the optional 7th parameter are not 
     supported by ST-80. Be aware of this for compatibility reasons.

     Notice that not all formats can be scanned (correctly) by #readFrom:
     This is an ST-80 compatibility method - I would have choosen another
     (less cryptic) formatString ...
    "

    |mf upperCase day month year components sep1 sep2 leadingZeros|

    aFormatArray size > 6 ifTrue:[
        leadingZeros := aFormatArray at:7
    ] ifFalse:[
        leadingZeros := false.
    ].

    components := Array new:3.
    day := self day.
    leadingZeros ifTrue:[
        day := day printStringLeftPaddedTo:2 with:$0 
    ] ifFalse:[
        day := day printString
    ].
    components at:(aFormatArray at:1) put:day.

    upperCase := false.
    mf := aFormatArray at:5.
    (mf between:4 and:5) ifTrue:[mf := mf - 2. upperCase := true].

    mf == 1 ifTrue:[
        month := self month.
        leadingZeros ifTrue:[
            month := month printStringLeftPaddedTo:2 with:$0 
        ] ifFalse:[
            month := month printString
        ]
    ] ifFalse:[
        mf == 2 ifTrue:[
            month := self abbreviatedMonthName
        ] ifFalse:[
            month := self monthName
        ]
    ].
    upperCase ifTrue:[month := month asUppercase].
    components at:(aFormatArray at:2) put:month.

    year := self year.
    (aFormatArray at:6) == 2 ifTrue:[
        year := year \\ 100.
        year := year printStringLeftPaddedTo:2 with:$0 
    ].
    year := year printString.
    components at:(aFormatArray at:3) put:year.

    sep1 := sep2 := (aFormatArray at:4).
    sep1 isString ifFalse:[
        sep1 isCollection ifTrue:[
            sep2 := (sep1 at:2).
            sep1 := (sep1 at:1).
        ] ifFalse:[
            sep1 := sep2 := sep1 asCharacter
        ]
    ].

    ^ (components at:1)
      , sep1 asString
      , (components at:2)
      , sep2 asString
      , (components at:3)

    "
     Date today printFormat:#(1 2 3 '' 1 2)          
     Date today printFormat:#(1 2 3 $- 1 2)          
     Date today printFormat:#(1 2 3 $. 1 2 true)     
     Date today printFormat:#(2 1 3 32 3 1)          
     Date today printFormat:#(2 1 3 #(' ' ', ') 3 1)  
     Date today printFormat:#(1 2 3 $- 2 1)          
     Date today printFormat:#(1 2 3 $- 4 1)          
    "
!

printFormat:aFormatArray on:aStream
    "Obsolete, backward ST-80 compatible formatted printing - see comment
     in printFormat:.
     Append a printed representation of the receiver to aStream.
     The argument, aFormatString controls the format, as described
     in the #printFormat: method.
     Notice that not all formats can be scanned (correctly) by #readFrom:"

    aStream nextPutAll:(self printFormat:aFormatArray)


    "european formats:

     Date today printFormat:#(1 2 3 $- 1 2) on:Transcript. Transcript cr.
     Date today printFormat:#(1 2 3 $- 2 2) on:Transcript. Transcript cr.
     Date today printFormat:#(1 2 3 $- 2 1) on:Transcript. Transcript cr.
     Date today printFormat:#(1 2 3 $- 3 2) on:Transcript. Transcript cr.
     Date today printFormat:#(1 2 3 $. 1 2) on:Transcript. Transcript cr.
     Date today printFormat:#(1 2 3 $. 1 2 true) on:Transcript. Transcript cr.

     US formats:

     Date today printFormat:#(2 1 3 32 3 1) on:Transcript. Transcript cr.
     Date today printFormat:#(2 1 3 32 2 2) on:Transcript. Transcript cr.
     Date today printFormat:#(2 1 3 $/ 1 2) on:Transcript. Transcript cr.
     Date today printFormat:#(2 1 3 $- 2 1) on:Transcript. Transcript cr.
     Date today printFormat:#(2 1 3 #(' ' ', ') 2 1) on:Transcript. Transcript cr.
     Date today printFormat:#(1 2 3 $- 2 1) on:Transcript. Transcript cr.
     Date today printFormat:#(1 2 3 $- 4 1) on:Transcript. Transcript cr.
    "
!

shortPrintString
    "dummy - for now"

    ^ self printString

    "Created: 20.6.1997 / 17:16:48 / cg"
!

weekdayIndex
    "Return the day index; Monday=1, ... , Sunday=7"

    ^ (self asDays + 1) \\ 7 + 1  "1 January 1901 was a Tuesday"

    "
     Date today dayName
     Date today weekdayIndex      
    "
! !

!Date methodsFor:'Compatibility - Squeak'!

mmddyyyy
    "return a printed representation of the receiver in the
     form mmddyyyy.
     The receiver can be reconstructed with: 
        Date readMMDDYYYYFrom:aStringOrStream onError:[...]"

    ^ (self month printStringLeftPaddedTo:2 with:$0)
       , (self day printStringLeftPaddedTo:2 with:$0) 
       , (self year printStringLeftPaddedTo:4 with:$0)

    "
     Date today mmddyyyy
    "
! !

!Date methodsFor:'accessing'!

abbreviatedDayName
    "return the short week-day of the receiver as a string.
     The returned string depends on the language setting.
     Expect things like 'mon', 'tue' ..."

    ^ self class abbreviatedNameOfDay:(self dayInWeek)

    "
     Date today abbreviatedDayName
     (Date day:15 month:4 year:1959) abbreviatedDayName
    "
!

abbreviatedMonthName
    "return the month of the receiver as a string.
     The returned string depends on the language setting.
     Expect things like 'jan', 'feb' ..."

    ^ self class abbreviatedNameOfMonth:(self month)

    "
     Date today abbreviatedMonthName
     (Date day:15 month:4 year:1959) abbreviatedMonthName
    "
!

asDays
    "return the number of days elapsed since 01-Jan-1901
     and the receiver's day; starts with 0 for 1-1-1901.
     Date>>fromDays: is the reverse operation.
     For ST-80 compatibility."

    |yr|

    yr := self year.
    ^ (self class yearAsDays:yr)
      + (self class daysUntilMonth:self month forYear:yr)
      + self day
      - 1

    "
     (Date day: 5 month: 8 year: 1962) asDays  -> should be 22496
     (Date day: 1 month: 1 year: 1901) asDays  -> 0
     Date today asDays
     Date fromDays:(Date today asDays + 7)
    "
!

asSeconds
    "return the seconds between 1.jan.1901 and the same time in the receivers 
     day. (i.e. midnight to midnight).
     This does not include any leapSeconds ... strictly speaking, this is incorrect.
     ST-80 compatibility."

    ^ 60*60*24 * self asDays

    "
     (Date day: 5 month: 8 year: 1962) asSeconds
     (Date day: 1 month: 1 year: 1901) asSeconds
     (Date today addDays:7) asSeconds - Date today asSeconds
    "

    "Modified: 1.7.1996 / 14:19:17 / cg"
!

day
    "return the day (1..31) of the receiver"

    ^ dateEncoding \\ 100

    "
     Date today day
    "
!

dayCount
    "return the number of days since 1st. Jan. 1901;
     starting with 0 for this date.
     Date>>fromDays: is the reverse operation.
     Obsolete:
	 please use asDays for ST-80 compatibility"

    ^ self asDays.

    "
     (Date day:1 month:1 year:1901) dayCount
     Date fromDays:(Date day:1 month:1 year:1994) dayCount
     Date today dayCount
    "
!

dayInWeek
    "return the week-day of the receiver - 1 for monday, 7 for sunday.
     WARNING: different from ANSIs dayOfWeek (which returns 1 for sunday, ... 7 for saturday).  
     WARNING: does not care for pre-julian dates 
        (i.e. do not use this for dates before 1752)
    "

    |wday|

    wday := (1 "knowing, that 1st Jan 1901 was a tuesday"
            + self asDays) \\ 7 + 1.
    wday < 1 ifTrue:[
        wday := wday + 7
    ].
    ^ wday

    "
     Date today dayInWeek      
     Date tomorrow dayInWeek 
     Date yesterday dayInWeek 
     (Date today subtractDays:2) dayInWeek 
     Date today weekday 
     Date tomorrow weekday 
     Date yesterday weekday 
     (Date day:15 month:4 year:1959) dayInWeek 
     (Date day:1 month:1 year:1901) dayInWeek 
     (Date day:31 month:12 year:1899) dayInWeek 
    "

    "Modified: / 1.2.1998 / 14:10:27 / cg"
!

dayInYear
    "return the day-nr within the year of the receiver - 1 .. 365/366"

    ^ self asAbsoluteTime dayInYear

    "
     Date today dayInYear 
     (Date newDay:1 year:1999) dayInYear
     (Date newDay:1 year:2000) dayInYear
     (Date newDay:2 year:2000) dayInYear
    "
!

dayName
    "return the week-day of the receiver as a string.
     The returned string depends on the language setting.
     Expect things like 'monday', 'tuesday' ...
     Obsolete:
	use #weekday for ST-80 compatibility"

    ^ self weekday
!

dayOfMonth
    "Answer the day of the month represented by me.
     Same as day; for ST-80 compatibility."

    ^ self day

    "
     Date today dayOfMonth
    "
!

daysInMonth
    "return the number of days in the month of the receiver"

    ^ Date daysInMonth:(self month) forYear:(self year)

    "
     Date today daysInMonth
    "
!

daysInYear
    "return the number of days in the year of the receiver"

    ^ Date daysInYear:(self year)

    "
     Date today daysInYear
    "
!

daysLeftInMonth
    "return the number of days left in the month of the receiver"

    ^ self daysInMonth - self day

    "
     Date today daysLeftInMonth             
    "
!

daysLeftInYear
    "return the number of days left in the year of the receiver"

    ^ (Date daysInYear:(self year)) - self day

    "
     Date today daysLeftInYear             
    "
!

leap
    "return true, if the receivers year is a leap year"

    ^ Date leapYear:(self year)

    "
     Date today leap
     (Date day:1 month:1 year:1992) leap
    "
!

month
    "return the month (1..12) of the receiver"

    ^ (dateEncoding // 100) \\ 100

    "
     Date today month
    "
!

monthIndex
    "return the index of the month (e.g. Feb.=2).
     Same as month; for ST-80 compatibility."

    ^ self month  
!

monthName
    "return the month of the receiver as a string.
     The returned string depends on the language setting.
     Expect things like 'january', 'february' ..."

    ^ self class nameOfMonth:(self month)

    "
     Date today monthName
     (Date day:15 month:4 year:1959) monthName
    "
!

weekInYear
    "return the week number of the receiver - 1 for Jan, 1st.
     each week is Mon .. Sun (i.e. Sunday belongs to the previous week)"

    ^ self class weekInYearOf:self

    "
     Date today weekInYear    
     (Date newDay:1 year:2000) weekInYear   was a saturday
     (Date newDay:2 year:2000) weekInYear   was a sunday
     (Date newDay:3 year:2000) weekInYear   was a monday
     (Date newDay:4 year:2000) weekInYear   was a tuesday
     (Date newDay:5 year:2000) weekInYear   was a wed
     (Date newDay:6 year:2000) weekInYear   was a thursday
     (Date newDay:7 year:2000) weekInYear   was a fri
     (Date newDay:8 year:2000) weekInYear   was a sat
     (Date newDay:9 year:2000) weekInYear   was a sun
     (Date newDay:10 year:2000) weekInYear  was a monday
     (Date day:3 month:1 year:2001) weekInYear 
    "
!

weekday
    "return the week-day of the receiver as a string.
     The returned string depends on the language setting.
     Expect things like 'monday', 'tuesday' ...
     For ST-80 compatibility"

    ^ self class nameOfDay:(self dayInWeek)

    "
     Date today weekday
     (Date day:15 month:4 year:1959) weekday
    "
!

year
    "return the year (1..12) of the receiver"

    ^ dateEncoding // (100*100)

    "
     Date today year
    "
! !

!Date methodsFor:'arithmetic'!

addDays:days
    "return a new date representing 'days' after the receiver.
     The argument should be some kind of integer.
     For ST-80 compatibility."

    ^ self class fromDays:(self asDays + days)

    "
     Date today addDays:7
    "
!

daysUntil:aDate
    "return the number of days between the receiver and the argument,
     aDate, whuch should be some kind of date"

    ^ aDate asDays - self asDays

    "
     (Date day:24 month:12 year:1994) daysUntil:(Date day:1 month:1 year:1995)
     (Date day:1 month:2 year:1992) daysUntil:(Date day:1 month:3 year:1992)
     (Date day:1 month:2 year:1994) daysUntil:(Date day:1 month:3 year:1994)
    
     |delta|
     delta := Date today
		daysUntil:(Date day:25 month:12 year:Date today year).
     Transcript show:'still ';
		show:delta ;
		showCR:' days till xmas'
    "
!

minusDays:days
    "return a new date representing 'days' before the receiver.
     The argument should be some kind of integer.
     Obsolete:
	 Please dont use this method since it will vanish.
	 Use #subtractDays: instead for ST-80 compatibility."

    ^ self subtractDays:days
!

plusDays:days
    "return a new date representing 'days' after the receiver.
     The argument should be some kind of integer.
     Obsolete:
	 Please dont use this method since it will vanish.
	 Use #addDays: instead for ST-80 compatibility."

    ^ self addDays:days
!

subtractDate:aDate
    "return the number of days between the receiver and aDate"

    ^ self asDays - aDate asDays

    "
    (Date day:1 month:1 year:1995) subtractDate:(Date day:24 month:12 year:1994)
    (Date day:1 month:3 year:1992) subtractDate:(Date day:1 month:2 year:1992)
    (Date day:1 month:3 year:1994) subtractDate:(Date day:1 month:2 year:1994)
    "
!

subtractDays:days
    "return a new date representing 'days' before the receiver.
     The argument should be some kind of integer.
     For ST-80 compatibility"

    ^ self class fromDays:(self asDays - days)

    "
     Date today subtractDays:7
    "
! !

!Date methodsFor:'comparing'!

< aDate
    "return true, if the date represented by the receiver
     is before the argument, aDate"

    (aDate isMemberOf:Date) ifTrue:[
	^ dateEncoding < aDate dateEncoding
    ].

    "the argument must understand year, month and day to be
     comparable, whatever it is"

    ^ dateEncoding < (Date encodeYear:aDate year
				month:aDate month
				  day:aDate day)

    "Date today < (Date day:24 month:12 year:2000)"
    "Date today < (Date day:24 month:12 year:1900)"
!

= aDate
    "return true, if the date represented by the receiver
     is the same as the one represented by argument, aDate"

    (aDate isMemberOf:Date) ifFalse:[^ false].

    ^ dateEncoding = aDate dateEncoding

    "the argument must understand year, month and day to be
     comparable, whatever it is"

"
    ^ dateEncoding = (Date encodeYear:aDate year
				month:aDate month
				  day:aDate day)
"
    "Date today = ((Date today plusDays:7) minusDays:7)"
!

> aDate
    "return true, if the date represented by the receiver
     is after the argument, aDate"

    (aDate isMemberOf:Date) ifTrue:[
	^ dateEncoding > aDate dateEncoding
    ].

    "the argument must understand year, month and day to be
     comparable, whatever it is"

    ^ dateEncoding > (Date encodeYear:aDate year
				month:aDate month
				  day:aDate day)

    "Date today > (Date day:24 month:12 year:2000)"
    "Date today > (Date day:24 month:12 year:1900)"
!

hash
    "return an integer useful for hashing on dates"

    ^ dateEncoding
! !

!Date methodsFor:'converting'!

asAbsoluteTime
    "return an absoluteTime instance, representing midnight of last night"

    ^ AbsoluteTime year:(self year) month:(self month) day:(self day)  
                   hour:0 minute:0 second:0 millisecond:0

    "
     Date today asAbsoluteTime
    "

    "Modified: / 1.7.1996 / 14:53:32 / cg"
    "Modified: / 13.7.1999 / 12:31:47 / stefan"
!

asDate
    "return the receiver"

    ^ self
!

asTimestamp
    "return an absoluteTime instance, representing midnight of last night"

    ^ self asAbsoluteTime

    "
     Date today asTimestamp
    "
! !

!Date methodsFor:'printing & storing'!

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

    |d ds ds0 dsB m ms ms0 msB y w mn dn ws ws0 dw|

    d := self day.
    ds := d printString.
    dsB := d printStringLeftPaddedTo:2.
    ds0 := d printStringLeftPaddedTo:2 with:$0.

    m := self month.
    ms := m printString.
    msB := m printStringLeftPaddedTo:2.
    ms0 := m printStringLeftPaddedTo:2 with:$0.

    y := self year.
    w := self weekInYear.
    ws := w printString.
    ws0 := w printStringLeftPaddedTo:2 with:$0.
    mn := self monthName.
    dn := self dayName.

    aDictionary at:#day put:ds0.        "/ 0-padded
    aDictionary at:#dayPadded put:dsB.  "/ Blank-padded
    aDictionary at:#Day put:ds.         "/ unpadded

    aDictionary at:#month put:ms0.  "/ 0-padded
    aDictionary at:#monthPadded put:ms0.  "/ Blank-padded
    aDictionary at:#Month put:ms.   "/ unpadded
    aDictionary at:#mon put:ms0.    "/ 0-padded - for backward compatibility only
    aDictionary at:#Mon put:ms.     "/ unpadded - for backward compatibility only

    aDictionary at:#year put:y.     "/ padded
    aDictionary at:#week put:ws0.
    aDictionary at:#Week put:ws.

    y ~~ Date today year ifTrue:[
        aDictionary at:#yearOrTime put:(' ' , y printString).
    ].

    aDictionary at:$d put:ds0.
    aDictionary at:$D put:ds.
    aDictionary at:$m put:ms0.
    aDictionary at:$M put:ms.
    aDictionary at:$y put:y.
    aDictionary at:$Y put:((y \\ 100)printStringLeftPaddedTo:2 with:$0).
    aDictionary at:$w put:ws0.
    aDictionary at:$W put:ws.

    aDictionary at:#monthName put:mn.
    aDictionary at:#MonthName put:mn asUppercaseFirst.
    aDictionary at:#MONTHNAME put:mn asUppercase.

    aDictionary at:#dayName put:dn.
    aDictionary at:#DayName put:dn asUppercaseFirst.
    aDictionary at:#DAYNAME put:dn asUppercase.

    aDictionary at:#weekDay put:(dw := self dayInWeek).
    aDictionary at:#weekDayUS put:(dw := self dayOfWeek).

    aDictionary at:#dayInWeek put:dw.     "/ for backward compatibility only
    aDictionary at:#shortDayName put:(dn := self abbreviatedDayName).
    aDictionary at:#ShortDayName put:dn asUppercaseFirst.
    aDictionary at:#SHORTDAYNAME put:dn asUppercase.

    aDictionary at:#shortMonthName put:(mn := self abbreviatedMonthName).
    aDictionary at:#ShortMonthName put:mn asUppercaseFirst.
    aDictionary at:#SHORTMONTHNAME put:mn asUppercase.

    aDictionary at:#nth put:(#('th' 'st' 'nd' 'rd' 'th' 'th' 'th' 'th' 'th' 'th') at:d \\ 10 + 1).
                              "/ 0   1    2    3    4    5    6    7    8    9
!

printOn:aStream
    "append a printed representation of the receiver to aStream"

    self printFormat:#(1 2 3 $- 2 1) on:aStream

    "
     Date today printOn:Transcript
     Date today printNL
    "

    "Modified: 27.8.1995 / 01:01:49 / claus"
!

printOn:aStream format:aFormatStringOrSqueakFormatArray
    "print using a format string;
     valid format items are:
        %d      day, 01..31                    0-padded to length 2
        %m      month, 01..12                  0-padded to length 2
        %w      week in year, 00..53           0-padded to length 2
        %y      year, full                     

     special:
        %D      day - unpadded
        %M      month - unpadded
        %W      week in year - unpadded
        %Y      year, last 2 digits only (danger)                     

        %weekDay        - day in week (1->monday, 2->tuesday, ... ,7->sunday)

        %dayName        - full day name     
        %DayName        - full day name, first character uppercase      
        %DAYNAME        - full day name, all uppercase       

        %monthName      - full month name     
        %MonthName      - full month name, first character uppercase      
        %MONTHNAME      - full month name, all uppercase       

        %shortDayName   - short (abbreviated) day name     
        %ShortDayName   - short (abbreviated) day name, first character uppercase      
        %SHORTDAYNAME   - short (abbreviated) day name, all uppercase       

        %shortMonthName - short (abbreviated) month name     
        %ShortMonthName - short (abbreviated) month name, first character uppercase      
        %SHORTMONTHNAME - short (abbreviated) month name, all uppercase       

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

     for ST80/squeak compatibility (which expects a format-array), the following is also supported:
        #(item item item sep monthfmt yearfmt twoDigits)
            items:  1=day  2=month  3=year  will appear in the order given,
            separated by sep which is eaither an ascii code or character.
            monthFmt:  1=09  2=Sep  3=September
            yearFmt:  1=1996  2=96
            digits:  (missing or)1=9  2=09.
    "

    aFormatStringOrSqueakFormatArray isArray ifTrue:[
        "/ a squeak format array
        ^ self printFormat:aFormatStringOrSqueakFormatArray on:aStream
    ].

    aStream nextPutAll:(self printStringFormat:aFormatStringOrSqueakFormatArray)

    "
     Date today printOn:Transcript format:'%y%m%d'                                      (iso format)
     Date today printOn:Transcript format:'%y-%m-%d'                                    (iso format)
     Date today printOn:Transcript format:'%y-W%w'                                      (iso format - working week)
     Date today printOn:Transcript format:'%d-%m-%y'                                    (european trivia format)
     Date today printOn:Transcript format:'%m/%d/%y'                                    (us trivia format)
     Date today printOn:Transcript format:'%D-%(monthName)-%y'                          (us trivia format)
     Date today printOn:Transcript format:'%D-%(MonthName)-%y'                          (us trivia format)
     Date today printOn:Transcript format:'%D-%(MONTHNAME)-%y'                          (us trivia format)
     Date today printOn:Transcript format:'%(DayName), %D%(nth) of %(MonthName), %y'   
     Date today printOn:Transcript format:'%(ShortDayName), %D-%(ShortMonthName)-%y'   
     Date today printOn:Transcript format:'%d%m%Y'                                      (millenium bug format - danger)
     Date today printOn:Transcript format:'Today is the %(weekDay) day of the week'     
    "
    "
     String streamContents:[:s |
        Date today printOn:s format:#(1 2 3 $/ 1 2)
     ]   
    "
!

printStringFormat:aFormatStringOrArray
    "print using a format string;
     valid format items are:
        %d      day, 01..31                    0-padded to length 2
        %m      month, 01..12                  0-padded to length 2
        %w      week in year, 00..53           0-padded to length 2
        %y      year, full                     

     special:
        %D      day - unpadded
        %M      month - unpadded
        %W      week in year - unpadded
        %Y      year, last 2 digits only (danger)                     

        %weekDay        - day in week (1->monday, 2->tuesday, ... ,7->sunday)
        %weekDayUS      - day in week (1->sunday, 2->monday, ... ,7->saturday)

        %dayName        - full day name     
        %DayName        - full day name, first character uppercase      
        %DAYNAME        - full day name, all uppercase       

        %monthName      - full month name     
        %MonthName      - full month name, first character uppercase      
        %MONTHNAME      - full month name, all uppercase       

        %shortDayName   - short (abbreviated) day name     
        %ShortDayName   - short (abbreviated) day name, first character uppercase      
        %SHORTDAYNAME   - short (abbreviated) day name, all uppercase       

        %shortMonthName - short (abbreviated) month name     
        %ShortMonthName - short (abbreviated) month name, first character uppercase      
        %SHORTMONTHNAME - short (abbreviated) month name, all uppercase       

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

    |dict|

    dict := IdentityDictionary new.
    self addPrintBindingsTo:dict.

    ^ (aFormatStringOrArray expandPlaceholdersWith:dict)

    "
     Date today printStringFormat:'%y%m%d'                                      (iso format)
     Date today printStringFormat:'%y-%m-%d'                                    (iso format)
     Date today printStringFormat:'%y-W%w'                                      (iso format - working week)
     Date today printStringFormat:'%d-%m-%y'                                    (european trivia format)
     Date today printStringFormat:'%m/%d/%y'                                    (us trivia format)
     Date today printStringFormat:'%D-%(monthName)-%y'                          (us trivia format)
     Date today printStringFormat:'%D-%(MonthName)-%y'                          (us trivia format)
     Date today printStringFormat:'%D-%(MONTHNAME)-%y'                          (us trivia format)
     Date today printStringFormat:'%(DayName), %D%(nth) of %(MonthName), %y'   
     Date today printStringFormat:'%(ShortDayName), %D-%(ShortMonthName)-%y'   
     Date today printStringFormat:'%d%m%Y'                                      (millenium bug format - danger)
     Date today printStringFormat:'Today is the %(weekDay) day of the week'     
    "
!

storeOn:aStream
    "append a representation to aStream, from which the receiver
     can be reconstructed"

    aStream nextPutAll:'('; nextPutAll:'Date day:'.
    self day printOn:aStream.
    aStream nextPutAll:' month:'.
    self month printOn:aStream.
    aStream nextPutAll:' year:'.
    self year printOn:aStream.
    aStream nextPutAll:')'

    "
     Date today storeOn:Transcript
     Date today storeString
    "
! !

!Date methodsFor:'private accessing'!

dateEncoding
    "the internal encoding is stricktly private, 
     and should not be used outside."

    ^ dateEncoding
!

dateEncoding:anInteger
    "the internal encoding is stricktly private, 
     and should not be used outside."

    dateEncoding := anInteger
!

fromOSTime:osTime
    "set my dateEncoding from an OS time.
     This somewhat clumsy implementation hides the OS's date representation
     (i.e. makes this class independent of what the OS starts its time values with).
     Dont use this method, the osTime representation is totally unportable."

    |v y m d|

    v := OperatingSystem computeTimeAndDateFrom:osTime.
    y := v at:1.
    m := v at:2.
    d := v at:3.
"/    OperatingSystem computeDatePartsOf:osTime 
"/                                   for:[:year :month :day |
"/        y := year.
"/        m := month.
"/        d := day.
"/    ].
    dateEncoding := (((y * 100) + m) * 100) + d

    "Modified: 1.7.1996 / 15:23:12 / cg"
! !

!Date class methodsFor:'documentation'!

version
    ^ '$Header: /cvs/stx/stx/libbasic/Date.st,v 1.69 2003-02-10 17:46:24 penk Exp $'
! !

Date initialize!