Skip to content

Commit

Permalink
40297
Browse files Browse the repository at this point in the history
14210 Replace Announcer>>#on:send:to:s senders in Komitter
	https://pharo.fogbugz.com/f/cases/14210

14197 Little Morphic Package Reorganization
	https://pharo.fogbugz.com/f/cases/14197

14198 Time>>print24 prints nanos, though it claims not to
	https://pharo.fogbugz.com/f/cases/14198

14211 Replace Announcer>>#on:send:to:s senders in Manifest-CriticBrowser
	https://pharo.fogbugz.com/f/cases/14211

http://files.pharo.org/image/40/40297.zip
  • Loading branch information
Jenkins Build Server authored and ci committed Oct 10, 2014
1 parent b3267a7 commit b2faf4d
Show file tree
Hide file tree
Showing 38 changed files with 392 additions and 22 deletions.
20 changes: 18 additions & 2 deletions Kernel.package/Time.class/instance/printing/print24_on_.st
Original file line number Diff line number Diff line change
@@ -1,5 +1,21 @@
print24: hr24 on: aStream
"Format is 'hh:mm:ss' or 'h:mm:ss am' "

self print24: hr24 showSeconds: true on: aStream

| h m s |
h := self hour. m := self minute. s := self second.
hr24
ifTrue: [
h < 10 ifTrue: [ aStream nextPut: $0 ].
h printOn: aStream ]
ifFalse: [
h > 12
ifTrue: [ h - 12 printOn: aStream ]
ifFalse: [
h < 1
ifTrue: [ 12 printOn: aStream ]
ifFalse: [ h printOn: aStream ] ] ].
aStream nextPutAll: (m < 10 ifTrue: [ ':0' ] ifFalse: [ ':' ]).
m printOn: aStream.
aStream nextPutAll: (s < 10 ifTrue: [ ':0' ] ifFalse: [ ':' ]).
s printOn: aStream.
hr24 ifFalse: [ aStream nextPutAll: (h < 12 ifTrue: [ ' am' ] ifFalse: [ ' pm' ]) ]
Original file line number Diff line number Diff line change
@@ -1,5 +1,5 @@
print24: hr24 showSeconds: showSeconds on: aStream
"Format is 'hh:mm:ss' or 'h:mm:ss am' or, if showSeconds is false, 'hh:mm' or 'h:mm am'"
"Format is 'hh:mm:ss.nnnnnnnnn' or 'h:mm:ss.nnnnnnnnn am' or, if showSeconds is false, 'hh:mm' or 'h:mm am'"

| h m s |
h := self hour. m := self minute. s := self second.
Expand Down
Original file line number Diff line number Diff line change
@@ -0,0 +1,2 @@
testPrint24withNanos
self assert: '12:34:56.1' asTime print24 = '12:34:56'
Original file line number Diff line number Diff line change
@@ -1,10 +1,10 @@
registerToAnnouncements

SystemAnnouncer uniqueInstance weak
on: MCPackageModified send: #mcPackageModified: to: self;
on: ClassAdded, ClassModifiedClassDefinition, ClassRenamed, ClassCommented send: #classModified: to: self;
on: ClassRepackaged send: #classMoved: to: self;
on: ClassRemoved send: #classRemoved: to: self;
on: MethodAdded, MethodModified, MethodRecategorized send: #methodModified: to: self;
on: MethodRepackaged send: #methodMoved: to: self;
on: MethodRemoved send: #methodRemoved: to: self
when: MCPackageModified send: #mcPackageModified: to: self;
when: ClassAdded, ClassModifiedClassDefinition, ClassRenamed, ClassCommented send: #classModified: to: self;
when: ClassRepackaged send: #classMoved: to: self;
when: ClassRemoved send: #classRemoved: to: self;
when: MethodAdded, MethodModified, MethodRecategorized send: #methodModified: to: self;
when: MethodRepackaged send: #methodMoved: to: self;
when: MethodRemoved send: #methodRemoved: to: self
Original file line number Diff line number Diff line change
@@ -1,7 +1,7 @@
registerToAnnouncements

SystemAnnouncer uniqueInstance weak
on: ClassModifiedClassDefinition send: #classModified: to: self;
on: MethodModified send: #methodModified: to: self;
on: MethodRemoved send: #methodRemoved: to: self.
self window window announcer on: WindowClosed send: #onWindowClosed to: self.
when: ClassModifiedClassDefinition send: #classModified: to: self;
when: MethodModified send: #methodModified: to: self;
when: MethodRemoved send: #methodRemoved: to: self.
self window window announcer when: WindowClosed send: #onWindowClosed to: self.
Original file line number Diff line number Diff line change
Expand Up @@ -2,4 +2,4 @@ BracketSliderMorph subclass: #AColorSelectorMorph
instanceVariableNames: ''
classVariableNames: ''
poolDictionaries: ''
category: 'Morphic-Widgets-Scrolling'
category: 'Morphic-Widgets-ColorPicker'
Original file line number Diff line number Diff line change
Expand Up @@ -2,4 +2,4 @@ BracketSliderMorph subclass: #HColorSelectorMorph
instanceVariableNames: ''
classVariableNames: ''
poolDictionaries: ''
category: 'Morphic-Widgets-Scrolling'
category: 'Morphic-Widgets-ColorPicker'

0 comments on commit b2faf4d

Please sign in to comment.