Time Formats

Previous Topic Next Topic
 
classic Classic list List threaded Threaded
11 messages Options
pax
Reply | Threaded
Open this post in threaded view
|

Time Formats

pax
Hello,

is there are way to change the Time format to Military time format? I
have been investigating this and have not found a solution. It should
be possible but I have not seen the appropriate behaviors in the image
that would be used to make such a change.

Any input would be appreciated.

Thanks,


PAX


Reply | Threaded
Open this post in threaded view
|

Re: Time Formats

Ian Bartholomew-21
Pax wrote:

> is there are way to change the Time format to Military time format? I
> have been investigating this and have not found a solution.

In what context, displaying times, inputting times or both. The Dolphin
image itself doesn't make a lot of use of Times so I would guess you are
asking about a deployed application.  In that case it would be
relatively easy to write a simple input/output converter to get exactly
the format you require.

And what is "Military time format".  The cynic in me immediately thought
of something like "the big hand is on the twelve and the little hand is
on the six" - but that's probably not right is it <vbg>

--
Ian

Use the Reply-To address to contact me.
Mail sent to the From address is ignored.


pax
Reply | Threaded
Open this post in threaded view
|

Re: Time Formats

pax
Ian,

in my runtime application, objects that are created will be tagged with
a Date and Time. The Time instance is of concern. Military format makes
use of a 24 hour clock. For example, an instance of Time after 12:59pm
will move to 13:00... This will continue until 23:59 where the next
instance of time goes back to 01:00...

The military establishment refers to these time values as "Thirteen
Hundred"... "Fourteen Hundred" or "O Three Hundred" etc... They don't
like to think like normal people... (grins).

I have been playing with a conversion method for class
Time>>asMilitaryTime. This would convert the time value to a military
time format for display purposes.

If possible, I would like it to be a valid instance of Time i.e,
MilitaryTime instance. I may have to create a subclass to accomplish
this.

At this time (no pun intended) I am browsing MSDN to see what
information MS has on the subject.


pax
Reply | Threaded
Open this post in threaded view
|

Re: Time Formats

pax
It appears this will be easier than anticipated... Locale default
timeFormats yields a collection of the following: an
OrderedCollection('h:mm:ss tt' 'hh:mm:ss tt' 'H:mm:ss' 'HH:mm:ss').

The last item 'HH:mm:ss' is the 24 hour or Military time format.

Class Time>>printOn: aStream format: aString would be used to pass in
the format which will render the Time instance in the supplied format.
If no format is provided, the Time instance will be rendered using the
currently configured default format of the host OS.

Thanks,

PAX


pax
Reply | Threaded
Open this post in threaded view
|

Re: Time Formats

pax
Here is a copy of the code I implemented to display Time instances in
24 hour (Military) format for anyone that is interested in such a
beasty...

Time>>asMilitaryTime

        "Return a string representation of the receiver in 24 hour format"
        | aFormat aStream |
        aFormat := 'HH:mm:ss'.
        aStream := String writeStream.
        self printOn: aStream format: aFormat .
        ^aStream contents


Reply | Threaded
Open this post in threaded view
|

Re: Time Formats

Esteban A. Maringolo-3
Pax escribió:

> Here is a copy of the code I implemented to display Time instances in
> 24 hour (Military) format for anyone that is interested in such a
> beasty...
>
> Time>>asMilitaryTime
>
> "Return a string representation of the receiver in 24 hour format"
> | aFormat aStream |
> aFormat := 'HH:mm:ss'.
> aStream := String writeStream.
> self printOn: aStream format: aFormat .
> ^aStream contents
>

Perhaps Time>>militaryDisplay would be a better name, considering
that you're not converting aTime to aMilitaryTime, and are returning
a string.

Just a bit of uniformity.

Regards,

--
Esteban.


Reply | Threaded
Open this post in threaded view
|

Re: Time Formats

Udo Schneider
In reply to this post by pax
Pax,

do you "just" want to output 24h time format or do you have to take care
of local to Z time conversion as well?

AFAIK military are allways expressed as Z-Time which is in fact the same
as UTC. So you should know the timezone each Time instance is in or
allways use normalized (accodring to UTC/Z) Times.

I attached two apckages which implement RFC3399 Times. This migh give
you the methods to convert from and to UTC (for RFC3339) and might as
well contain some hints how to output custom time formats.

Regards,

Udo


Pax wrote:

> Here is a copy of the code I implemented to display Time instances in
> 24 hour (Military) format for anyone that is interested in such a
> beasty...
>
> Time>>asMilitaryTime
>
> "Return a string representation of the receiver in 24 hour format"
> | aFormat aStream |
> aFormat := 'HH:mm:ss'.
> aStream := String writeStream.
> self printOn: aStream format: aFormat .
> ^aStream contents
>

| package |
package := Package name: 'US RFC3339'.
package paxVersion: 0;
        basicComment: ''.


package methodNames
        add: #Date -> #rfc3339String;
        add: #Locale -> #bias;
        add: #Time -> #asUTC;
        add: #Time -> #rfc3339String;
        add: #TimeStamp -> #rfc3339String;
        add: 'Date class' -> #fromRfc3339String:;
        add: 'Time class' -> #fromHours:minutes:seconds:milliseconds:;
        add: 'Time class' -> #fromHours:minutes:seconds:millisecondsFraction:;
        add: 'Time class' -> #fromRfc3339String:;
        add: 'Time class' -> #fromUtcHours:minutes:seconds:milliseconds:;
        add: 'Time class' -> #fromUtcHours:minutes:seconds:millisecondsFraction:;
        add: 'Time class' -> #fromUtcTime:;
        add: 'TimeStamp class' -> #fromRfc3339String:;
        yourself.

package binaryGlobalNames: (Set new
        yourself).

package globalAliases: (Set new
        yourself).

package allResourceNames: (Set new
        yourself).

package setPrerequisites: (IdentitySet new
        add: '..\Object Arts\Dolphin\Base\Dolphin';
        yourself).

package!

"Class Definitions"!


"Global Aliases"!


"Loose Methods"!

!Date methodsFor!

rfc3339String
        | stream |
        stream := ReadWriteStream on: String new.
        self printOn: stream format: 'yyyy-MM-dd'.
        ^stream contents! !
!Date categoriesFor: #rfc3339String!public! !

!Date class methodsFor!

fromRfc3339String: aString
^self fromString: aString format: 'YYYY-MM-DD'! !
!Date class categoriesFor: #fromRfc3339String:!public! !

!Locale methodsFor!

bias
        ^(self timeZoneInformation at: 2) bias! !
!Locale categoriesFor: #bias!public! !

!Time methodsFor!

asUTC

        ^self addTime: (Time fromSeconds: (Locale userDefault bias) * 60)!

rfc3339String
        | stream bias |
        stream := ReadWriteStream on: String new.
        self printOn: stream format: 'HH:mm'.
        bias := Locale userDefault bias.
        bias isNull ifTrue: [stream nextPut: $Z].
        bias positive ifTrue: [stream nextPut: $+].
        bias negative ifTrue: [stream nextPut: $-].
        (Time fromSeconds: bias abs * 60) printOn: stream format: 'HH.mm'.
        ^stream contents! !
!Time categoriesFor: #asUTC!public! !
!Time categoriesFor: #rfc3339String!public! !

!Time class methodsFor!

fromHours: hours minutes: minutes seconds: seconds milliseconds: milliseconds
        ^Time
                fromMilliseconds: (((hours * 60 + minutes) * 60 + seconds) * 1000 + milliseconds) asInteger!

fromHours: hours minutes: minutes seconds: seconds millisecondsFraction: millisecondsFraction
        ^self
                fromHours: hours
                minutes: minutes
                seconds: seconds
                milliseconds: (millisecondsFraction notNull
                                ifTrue: [millisecondsFraction / (10 raisedTo: millisecondsFraction log ceiling)]
                                ifFalse: [0]) * 1000!

fromRfc3339String: aString
        | time offset |
        (aString includes: $-)
                ifTrue:
                        [time := aString copyFrom: 1 to: (aString indexOf: $-) - 1.
                        offset := aString copyFrom: (aString indexOf: $-) + 1.
                        time := Time fromUtcTime: (Time fromString: time).
                        time := time addTime: (Time fromString: offset).
                        ^time].
        (aString includes: $+)
                ifTrue:
                        [time := aString copyFrom: 1 to: (aString indexOf: $+) - 1.
                        offset := aString copyFrom: (aString indexOf: $+) + 1.
                        time := Time fromUtcTime: (Time fromString: time).
                        time := time subtractTime: (Time fromString: offset).
                        ^time].
        time := aString copyFrom: 1 to: aString size - 1.
        offset := '00:00'.
        ^Time fromUtcTime: (Time fromString: time)!

fromUtcHours: hours minutes: minutes seconds: seconds milliseconds: milliseconds
        ^Time fromUtcTime: (Time
                                fromMilliseconds: (((hours * 60 + minutes) * 60 + seconds) * 1000 + milliseconds )asInteger)!

fromUtcHours: hours minutes: minutes seconds: seconds millisecondsFraction: millisecondsFraction
        ^self
                fromUtcHours: hours
                minutes: minutes
                seconds: seconds
                milliseconds: (millisecondsFraction notNull
                                ifTrue: [millisecondsFraction / (10 raisedTo: millisecondsFraction log ceiling)]
                                ifFalse: [0]) * 1000!

fromUtcTime: aTime
        ^aTime subtractTime: (Time fromSeconds: Locale userDefault bias * 60)! !
!Time class categoriesFor: #fromHours:minutes:seconds:milliseconds:!public! !
!Time class categoriesFor: #fromHours:minutes:seconds:millisecondsFraction:!public! !
!Time class categoriesFor: #fromRfc3339String:!public! !
!Time class categoriesFor: #fromUtcHours:minutes:seconds:milliseconds:!public! !
!Time class categoriesFor: #fromUtcHours:minutes:seconds:millisecondsFraction:!public! !
!Time class categoriesFor: #fromUtcTime:!public! !

!TimeStamp methodsFor!

rfc3339String
         ^self date rfc3339String , 'T' , self time rfc3339String! !
!TimeStamp categoriesFor: #rfc3339String!public! !

!TimeStamp class methodsFor!

fromRfc3339String: aString

|tokens|
tokens := aString subStrings: 'T'.
^TimeStamp date: (Date fromRfc3339String: (tokens at: 1)) time: (Time fromRfc3339String: (tokens at: 2))! !
!TimeStamp class categoriesFor: #fromRfc3339String:!public! !

"End of package definition"!

"Source Globals"!

"Classes"!

"Binary Globals"!

"Resources"!


| package |
package := Package name: 'US RFC3339 Tests'.
package paxVersion: 0;
        basicComment: ''.


package classNames
        add: #MillisecondsFractionTest;
        add: #RFC3339Test;
        yourself.

package binaryGlobalNames: (Set new
        yourself).

package globalAliases: (Set new
        yourself).

package allResourceNames: (Set new
        yourself).

package setPrerequisites: (IdentitySet new
        add: '..\Object Arts\Dolphin\Base\Dolphin';
        add: '..\Camp Smalltalk\SUnit\SUnit';
        add: 'US RFC3339';
        yourself).

package setManualPrerequisites: #(
        'US RFC3339').

package!

"Class Definitions"!

TestCase subclass: #MillisecondsFractionTest
        instanceVariableNames: ''
        classVariableNames: ''
        poolDictionaries: ''
        classInstanceVariableNames: ''!
TestCase subclass: #RFC3339Test
        instanceVariableNames: ''
        classVariableNames: ''
        poolDictionaries: ''
        classInstanceVariableNames: ''!

"Global Aliases"!


"Loose Methods"!

"End of package definition"!

"Source Globals"!

"Classes"!

MillisecondsFractionTest guid: (GUID fromString: '{8D6C42B2-9AB8-4DE5-9CA2-31E160FA9573}')!
MillisecondsFractionTest comment: ''!
!MillisecondsFractionTest categoriesForClass!Unclassified! !
!MillisecondsFractionTest methodsFor!

testMillisecondsFraction
        self
                assert: ((Time
                                fromHours: 0
                                minutes: 0
                                seconds: 0
                                milliseconds: 500) addTime: (Time
                                                        fromHours: 0
                                                        minutes: 0
                                                        seconds: 0
                                                        milliseconds: 500))
                                = (Time
                                                fromHours: 0
                                                minutes: 0
                                                seconds: 1
                                                milliseconds: 0).
        self
                assert: ((Time
                                fromHours: 0
                                minutes: 0
                                seconds: 0
                                millisecondsFraction: 5) addTime: (Time
                                                        fromHours: 0
                                                        minutes: 0
                                                        seconds: 0
                                                        millisecondsFraction: 5))
                                = (Time
                                                fromHours: 0
                                                minutes: 0
                                                seconds: 1
                                                milliseconds: 0)! !
!MillisecondsFractionTest categoriesFor: #testMillisecondsFraction!public! !

RFC3339Test guid: (GUID fromString: '{43591C45-0787-4B62-A2ED-984751060562}')!
RFC3339Test comment: ''!
!RFC3339Test categoriesForClass!Unclassified! !
!RFC3339Test methodsFor!

assertHour: hour minute: minute second: second millisecondFraction: millisecondFraction equalsRfc3339String: aString
        self
                assert: (Time
                                fromUtcHours: hour
                                minutes: minute
                                seconds: second
                                millisecondsFraction: millisecondFraction) rfc3339String
                                = (Time fromRfc3339String: aString) rfc3339String!

assertHour: hour minute: minute second: second millisecondFraction: millisecondFraction offsetAdd: anOffset equalsRfc3339String: aString
        self
                assert: ((Time
                                fromUtcHours: hour
                                minutes: minute
                                seconds: second
                                millisecondsFraction: millisecondFraction) subtractTime: (Time fromString: anOffset))
                                rfc3339String = (Time fromRfc3339String: aString) rfc3339String!

assertHour: hour minute: minute second: second millisecondFraction: millisecondFraction offsetSubtract: anOffset equalsRfc3339String: aString
        self
                assert: ((Time
                                fromUtcHours: hour
                                minutes: minute
                                seconds: second
                                millisecondsFraction: millisecondFraction) addTime: (Time fromString: anOffset))
                                rfc3339String = (Time fromRfc3339String: aString) rfc3339String!

assertRfc3339String: aString equalsHour: hour minute: minute second: second millisecondFraction: millisecondFraction
        self
                assert: (Time fromRfc3339String: aString) = (Time
                                                fromUtcHours: hour
                                                minutes: minute
                                                seconds: second
                                                millisecondsFraction: millisecondFraction)!

assertRfc3339String: aString equalsHour: hour minute: minute second: second millisecondFraction: millisecondFraction offsetAdd: offset
        self assert: (Time fromRfc3339String: aString)
                                = ((Time
                                                fromUtcHours: hour
                                                minutes: minute
                                                seconds: second
                                                millisecondsFraction: millisecondFraction) subtractTime: (Time fromString: offset))!

assertRfc3339String: aString equalsHour: hour minute: minute second: second millisecondFraction: millisecondFraction offsetSubtract: offset
        self assert: (Time fromRfc3339String: aString)
                                = ((Time
                                                fromUtcHours: hour
                                                minutes: minute
                                                seconds: second
                                                millisecondsFraction: millisecondFraction) addTime: (Time fromString: offset))!

assertRfc3339String: aString equalsYear: year month: month day: day
        self
                assert: (Date fromRfc3339String: aString) = (Date
                                                newDay: day
                                                monthIndex: month
                                                year: year)!

assertRfc3339String: aString equalsYear: year month: month day: day hour: hour minute: minute second: second millisecondFraction: millisecondFraction self assert: (TimeStamp fromRfc3339String: aString)
                                = (TimeStamp date: (Date
                                                                newDay: day
                                                                monthIndex: month
                                                                year: year)
                                                time: ((Time
                                                                fromUtcHours: hour
                                                                minutes: minute
                                                                seconds: second
                                                                millisecondsFraction: millisecondFraction) ))!

assertRfc3339String: aString equalsYear: year month: month day: day hour: hour minute: minute second: second millisecondFraction: millisecondFraction offsetAdd: offset
        self assert: (TimeStamp fromRfc3339String: aString)
                                = (TimeStamp date: (Date
                                                                newDay: day
                                                                monthIndex: month
                                                                year: year)
                                                time: ((Time
                                                                fromUtcHours: hour
                                                                minutes: minute
                                                                seconds: second
                                                                millisecondsFraction: millisecondFraction) subtractTime: (Time fromString: offset)))!

assertRfc3339String: aString equalsYear: year month: month day: day hour: hour minute: minute second: second millisecondFraction: millisecondFraction offsetSubtract: offset
        self assert: (TimeStamp fromRfc3339String: aString)
                                = (TimeStamp date: (Date
                                                                newDay: day
                                                                monthIndex: month
                                                                year: year)
                                                time: ((Time
                                                                fromUtcHours: hour
                                                                minutes: minute
                                                                seconds: second
                                                                millisecondsFraction: millisecondFraction) addTime: (Time fromString: offset)))!

assertYear: year month: month day: day equalsRfc3339String: aString
        self
                assert: (Date
                                newDay: day
                                monthIndex: month
                                year: year) rfc3339String
                                = aString!

assertYear: year month: month day: day hour: hour minute: minute second: second millisecondFraction: millisecondFraction  equalsRfc3339String: string
        self
                assert: (TimeStamp date: (Date
                                                newDay: day
                                                monthIndex: month
                                                year: year)
                                time: ((Time
                                                fromUtcHours: hour
                                                minutes: minute
                                                seconds: second
                                                millisecondsFraction: millisecondFraction) ))
                                        rfc3339String = (TimeStamp fromRfc3339String: string) rfc3339String!

assertYear: year month: month day: day hour: hour minute: minute second: second millisecondFraction: millisecondFraction offsetAdd: offset equalsRfc3339String: string
        self
                assert: (TimeStamp date: (Date
                                                newDay: day
                                                monthIndex: month
                                                year: year)
                                time: ((Time
                                                fromUtcHours: hour
                                                minutes: minute
                                                seconds: second
                                                millisecondsFraction: millisecondFraction) subtractTime: (Time fromString: offset)))
                                        rfc3339String = (TimeStamp fromRfc3339String: string) rfc3339String!

assertYear: year month: month day: day hour: hour minute: minute second: second millisecondFraction: millisecondFraction offsetSubtract: offset equalsRfc3339String: string
        self
                assert: (TimeStamp date: (Date
                                                newDay: day
                                                monthIndex: month
                                                year: year)
                                time: ((Time
                                                fromUtcHours: hour
                                                minutes: minute
                                                seconds: second
                                                millisecondsFraction: millisecondFraction) addTime: (Time fromString: offset)))
                                        rfc3339String = (TimeStamp fromRfc3339String: string) rfc3339String!

testFromRfc3339Date
        self
                assertRfc3339String: '1985-04-12'
                        equalsYear: 1985
                        month: 4
                        day: 12;
                assertRfc3339String: '1996-12-19'
                        equalsYear: 1996
                        month: 12
                        day: 19;
                assertRfc3339String: '1990-12-31'
                        equalsYear: 1990
                        month: 12
                        day: 31;
                assertRfc3339String: '1937-01-01'
                        equalsYear: 1937
                        month: 1
                        day: 1!

testFromRfc3339Time
        self
                assertRfc3339String: '23:20:50.52Z'
                        equalsHour: 23
                        minute: 20
                        second: 50
                        millisecondFraction: 52;
                assertRfc3339String: '16:39:57-08:00'
                        equalsHour: 16
                        minute: 39
                        second: 57
                        millisecondFraction: 0
                        offsetSubtract: '08:00';
                assertRfc3339String: '12:00:27.87+00:20'
                        equalsHour: 12
                        minute: 0
                        second: 27
                        millisecondFraction: 87
                        offsetAdd: '00:20'!

testFromRfc3339TimeStamp
        self
                assertRfc3339String: '1985-04-12T23:20:50.52Z'
                        equalsYear: 1985
                        month: 4
                        day: 12
                        hour: 23
                        minute: 20
                        second: 50
                        millisecondFraction: 52;
                assertRfc3339String: '1996-12-19T16:39:57-08:00'
                        equalsYear: 1996
                        month: 12
                        day: 19
                        hour: 16
                        minute: 39
                        second: 57
                        millisecondFraction: 0
                        offsetSubtract: '08:00';
                assertRfc3339String: '1937-01-01T12:00:27.87+00:20'
                        equalsYear: 1937
                        month: 1
                        day: 1
                        hour: 12
                        minute: 0
                        second: 27
                        millisecondFraction: 87
                        offsetAdd: '00:20'!

testToRfc3339Date
        self
                assertYear: 1985
                        month: 4
                        day: 12
                        equalsRfc3339String: '1985-04-12';
                assertYear: 1996
                        month: 12
                        day: 19
                        equalsRfc3339String: '1996-12-19';
                assertYear: 1990
                        month: 12
                        day: 31
                        equalsRfc3339String: '1990-12-31';
                assertYear: 1937
                        month: 1
                        day: 1
                        equalsRfc3339String: '1937-01-01'!

testToRfc3339Time
        self
                assertHour: 23
                        minute: 20
                        second: 50
                        millisecondFraction: 52
                        equalsRfc3339String: '23:20:50.52Z';
                assertHour: 16
                        minute: 39
                        second: 57
                        millisecondFraction: 0
                        offsetSubtract: '08:00'
                        equalsRfc3339String: '16:39:57-08:00';
                assertHour: 12
                        minute: 0
                        second: 27
                        millisecondFraction: 87
                        offsetAdd: '00:20'
                        equalsRfc3339String: '12:00:27.87+00:20'!

testToRfc3339TimeStamp
        self
                assertYear: 1985
                        month: 4
                        day: 12
                        hour: 23
                        minute: 20
                        second: 50
                        millisecondFraction: 52
                        equalsRfc3339String: '1985-04-12T23:20:50.52Z';
                assertYear: 1996
                        month: 12
                        day: 19
                        hour: 16
                        minute: 39
                        second: 57
                        millisecondFraction: 0
                        offsetSubtract: '08:00'
                        equalsRfc3339String: '1996-12-19T16:39:57-08:00';
                assertYear: 1937
                        month: 1
                        day: 1
                        hour: 12
                        minute: 0
                        second: 27
                        millisecondFraction: 87
                        offsetAdd: '00:20'
                        equalsRfc3339String: '1937-01-01T12:00:27.87+00:20'! !
!RFC3339Test categoriesFor: #assertHour:minute:second:millisecondFraction:equalsRfc3339String:!helpers!private! !
!RFC3339Test categoriesFor: #assertHour:minute:second:millisecondFraction:offsetAdd:equalsRfc3339String:!helpers!private! !
!RFC3339Test categoriesFor: #assertHour:minute:second:millisecondFraction:offsetSubtract:equalsRfc3339String:!helpers!private! !
!RFC3339Test categoriesFor: #assertRfc3339String:equalsHour:minute:second:millisecondFraction:!helpers!private! !
!RFC3339Test categoriesFor: #assertRfc3339String:equalsHour:minute:second:millisecondFraction:offsetAdd:!helpers!private! !
!RFC3339Test categoriesFor: #assertRfc3339String:equalsHour:minute:second:millisecondFraction:offsetSubtract:!helpers!private! !
!RFC3339Test categoriesFor: #assertRfc3339String:equalsYear:month:day:!helpers!private! !
!RFC3339Test categoriesFor: #assertRfc3339String:equalsYear:month:day:hour:minute:second:millisecondFraction:!helpers!private! !
!RFC3339Test categoriesFor: #assertRfc3339String:equalsYear:month:day:hour:minute:second:millisecondFraction:offsetAdd:!helpers!private! !
!RFC3339Test categoriesFor: #assertRfc3339String:equalsYear:month:day:hour:minute:second:millisecondFraction:offsetSubtract:!helpers!private! !
!RFC3339Test categoriesFor: #assertYear:month:day:equalsRfc3339String:!helpers!private! !
!RFC3339Test categoriesFor: #assertYear:month:day:hour:minute:second:millisecondFraction:equalsRfc3339String:!helpers!private! !
!RFC3339Test categoriesFor: #assertYear:month:day:hour:minute:second:millisecondFraction:offsetAdd:equalsRfc3339String:!helpers!private! !
!RFC3339Test categoriesFor: #assertYear:month:day:hour:minute:second:millisecondFraction:offsetSubtract:equalsRfc3339String:!helpers!private! !
!RFC3339Test categoriesFor: #testFromRfc3339Date!public!test! !
!RFC3339Test categoriesFor: #testFromRfc3339Time!public!test! !
!RFC3339Test categoriesFor: #testFromRfc3339TimeStamp!public!test! !
!RFC3339Test categoriesFor: #testToRfc3339Date!public!test! !
!RFC3339Test categoriesFor: #testToRfc3339Time!public!test! !
!RFC3339Test categoriesFor: #testToRfc3339TimeStamp!public!test! !

"Binary Globals"!

"Resources"!

Reply | Threaded
Open this post in threaded view
|

Re: Time Formats

Chris Uppal-3
In reply to this post by pax
Pax wrote:

> Time>>asMilitaryTime
>
> "Return a string representation of the receiver in 24 hour format"
> > aFormat aStream |
> aFormat := 'HH:mm:ss'.
> aStream := String writeStream.
> self printOn: aStream format: aFormat .
> ^aStream contents

Or, in the spirit of Ian's remark:

=============
militaryDisplayString

 |
    numbers positions
    minutes hours
    bigHand bigNumber bigNext bigPosition
    littleHand littleNumber littleNext littlePosition
|

 numbers := #(
    'twelve' 'one' 'two' 'three'
    'four'  'five' 'six' 'seven'
    'eight'  'nine' 'ten' 'eleven'
    'twelve'
   ).
 positions := #(
   'on the %1'
   'just past the %1'
   'between the %1 and the %2'
   'between the %1 and the %2'
   'just before the %2'
   ).

 minutes := self seconds / 60.0 + self minutes.
 hours := minutes / 60.0 + self hours.
 hours >= 12.0 ifTrue: [hours := hours - 12].

 bigHand := hours.
 bigNumber := numbers at: bigHand truncated + 1.
 bigNext := numbers at: bigHand truncated + 2.
 bigPosition := positions at: (bigHand fractionPart * positions size) truncated
+ 1.

 littleHand := minutes / 5.0.
 littleNumber := numbers at: littleHand truncated + 1.
 littleNext := numbers at: littleHand truncated + 2.
 littlePosition := positions at: (littleHand fractionPart * positions size)
truncated + 1.

 ^ (String writeStream)
      nextPutAll: 'The big hand is ';
      nextPutAll: (bigPosition formatWith: bigNumber with: bigNext);
      nextPutAll: ', and the little hand is ';
      nextPutAll: (littlePosition formatWith: littleNumber with: littleNext);
      contents.
=============

;-)

    -- chris


Reply | Threaded
Open this post in threaded view
|

Re: Time Formats

Stefan Schmiedl
On Tue, 23 Aug 2005 14:51:36 +0100, Chris Uppal <[hidden email]> wrote:

>
> Or, in the spirit of Ian's remark:
>

which is only part of real life requirements according to

http://www.jumbojoke.com/000472.html

:-D

s.


pax
Reply | Threaded
Open this post in threaded view
|

Re: Time Formats

pax
In reply to this post by Udo Schneider
Udo,

I merely need to display the Time instance in 24 hour format. I also
needed the TIME_ZONE_INFORMATION (subclass of Win32Struct) information
which comes from Locale default timeZoneInformation. This is set at the
OS level and is easily read by Dolphin. But, I will have a look at the
package you uploaded.

Esteban, your suggestion is well received given that there is no
conversion of Time instance. Just displaying a different format. The
Big Hand/Little Hand proposals are not of interest and have no merit
for my project as a solution is in hand.

Pax


Reply | Threaded
Open this post in threaded view
|

Re: Time Formats

Udo Schneider
Pax wrote:
> I merely need to display the Time instance in 24 hour format. I also
> needed the TIME_ZONE_INFORMATION (subclass of Win32Struct) information
> which comes from Locale default timeZoneInformation. This is set at the
> OS level and is easily read by Dolphin. But, I will have a look at the
> package you uploaded.
The package I uploaded includes functionality to take care of the Time
Zone (using the approach you mentioned above). For the 24h time it
should be enough to strip time zone information from the RFC3339 String
(see approrpiate methods in Time) ... this of course only works if Times
are in UTC.

CU,

Udo