home *** CD-ROM | disk | FTP | other *** search
-
- Object subclass: #Appointment
- instanceVariableNames: 'alarm description date '
- classVariableNames: ''
- poolDictionaries: ''
- category: 'ClockWorks'!
-
- !Appointment methodsFor: 'appointment alarms' stamp: 'mjg 9/27/1998 14:34'!
- on
- "The appointment is today, so turn on alarm."
- alarm alarmBlock: [3 timesRepeat: [Smalltalk beep.].
- Transcript show: 'Appointment: ',description.
- alarm stop.].
- alarm setTime: (Time now printString).
- alarm start.
- ! !
-
-
- !Appointment methodsFor: 'accessing' stamp: 'mjg 9/27/1998 14:18'!
- alarm
- ^alarm
- ! !
-
- !Appointment methodsFor: 'accessing' stamp: 'mjg 9/27/1998 14:32'!
- alarm: someTime
- alarm _ AlarmClock new.
- alarm setTime: Time now printString.
- alarm setAlarmTime: someTime.
- ! !
-
- !Appointment methodsFor: 'accessing' stamp: 'mjg 9/27/1998 14:19'!
- date
- ^date! !
-
- !Appointment methodsFor: 'accessing' stamp: 'mjg 9/27/1998 14:19'!
- date: aDate
- "Set date of appointment."
- date _ aDate! !
-
- !Appointment methodsFor: 'accessing' stamp: 'mjg 9/27/1998 14:19'!
- description
- ^description! !
-
- !Appointment methodsFor: 'accessing' stamp: 'mjg 9/27/1998 14:19'!
- description: aDescription
- description := aDescription.! !
-
-
-
- Object subclass: #AppointmentBook
- instanceVariableNames: 'appointments '
- classVariableNames: ''
- poolDictionaries: ''
- category: 'ClockWorks'!
-
- !AppointmentBook methodsFor: 'appointment alarms' stamp: 'mjg 9/27/1998 14:36'!
- allOff
- appointments do: [:appointment | appointment alarm stop].! !
-
- !AppointmentBook methodsFor: 'appointment alarms' stamp: 'mjg 9/27/1998 14:31'!
- onToday
- (appointments select: [:each | each date = Date today]) do: [:each | each on].
- ! !
-
-
- !AppointmentBook methodsFor: 'appointments' stamp: 'mjg 9/27/1998 14:33'!
- appointments
- ^appointments! !
-
- !AppointmentBook methodsFor: 'appointments' stamp: 'mjg 9/27/1998 14:29'!
- makeAppointment: aDescription for: aDate at: aTime
- | a |
- a _ Appointment new.
- a description: aDescription.
- a date: (Date readFrom: (ReadStream on: aDate)).
- a alarm: aTime.
- appointments add: a.
- ! !
-
-
- !AppointmentBook methodsFor: 'initialization' stamp: 'mjg 9/27/1998 14:07'!
- initialize
- appointments _ OrderedCollection new.! !
-
-
-
- Object subclass: #Clock
- instanceVariableNames: 'time timer displayFormat '
- classVariableNames: ''
- poolDictionaries: ''
- category: 'ClockWorks'!
-
- !Clock methodsFor: 'time management' stamp: 'mjg 9/26/1998 17:22'!
- display
- "Display the time in a given format"
- | hours minutes seconds |
- hours _ time hours printString.
- minutes _ time minutes printString.
- (minutes size < 2) ifTrue: [minutes _ '0',minutes]. "Must be two digits"
- seconds _ time seconds printString.
- (seconds size < 2) ifTrue: [seconds _ '0',seconds].
- (displayFormat = '12')
- ifTrue: [(hours asNumber > 12)
- ifTrue: [^((hours asNumber - 12) printString),':',minutes,':',
- seconds,' pm'].
- (hours asNumber < 12)
- ifTrue: [^hours,':',minutes,':',seconds,' am']
- ifFalse: ["Exactly 12 must be printed as pm"
- ^hours,':',minutes ,':',seconds,' pm']]
- ifFalse: ["24-hour time is the default if no displayFormat is set"
- ^hours,':',minutes,':',seconds].! !
-
- !Clock methodsFor: 'time management' stamp: 'mjg 9/26/1998 16:57'!
- displayFormat: aType
- "aType should be '24' or '12'"
- displayFormat _ aType
- ! !
-
- !Clock methodsFor: 'time management' stamp: 'mjg 9/27/1998 14:10'!
- nextSecond
- time _ time addTime: (Time fromSeconds: 1)
- ! !
-
- !Clock methodsFor: 'time management' stamp: 'mjg 9/26/1998 16:56'!
- setTime: aString
- time _ Time readFrom: (ReadStream on: aString).
- ! !
-
- !Clock methodsFor: 'time management' stamp: 'mjg 9/27/1998 14:21'!
- start
- timer isNil ifFalse: [timer stopTicking. "Stop one if already existing."].
- timer _ SecondsTimer new.
- timer clock: self.
- timer startTicking.
- ! !
-
- !Clock methodsFor: 'time management' stamp: 'mjg 9/27/1998 14:37'!
- stop
- timer isNil ifFalse: [timer stopTicking].
- timer _ nil.
- ! !
-
-
- !Clock methodsFor: 'accessing' stamp: 'mjg 9/26/1998 17:02'!
- hours
- ^time hours! !
-
- !Clock methodsFor: 'accessing' stamp: 'mjg 9/26/1998 16:56'!
- time
- ^time! !
-
- !Clock methodsFor: 'accessing' stamp: 'mjg 9/27/1998 14:20'!
- timer
- ^timer
- ! !
-
-
-
- Clock subclass: #AlarmClock
- instanceVariableNames: 'alarmTime alarmBlock '
- classVariableNames: ''
- poolDictionaries: ''
- category: 'ClockWorks'!
-
- !AlarmClock methodsFor: 'time management' stamp: 'mjg 9/27/1998 14:02'!
- alarmBlock: aBlock
- alarmBlock _ aBlock.
- ! !
-
- !AlarmClock methodsFor: 'time management' stamp: 'mjg 9/27/1998 13:57'!
- alarmTime
- ^alarmTime
- ! !
-
- !AlarmClock methodsFor: 'time management' stamp: 'mjg 9/27/1998 13:58'!
- nextSecond
- super nextSecond.
- (time = alarmTime) ifTrue: [alarmBlock value].
- ! !
-
- !AlarmClock methodsFor: 'time management' stamp: 'mjg 9/27/1998 13:58'!
- setAlarmTime: aString
- alarmTime _ Time readFrom: (ReadStream on: aString).
- ! !
-
-
-
- Object subclass: #SecondsTimer
- instanceVariableNames: 'clock process '
- classVariableNames: ''
- poolDictionaries: ''
- category: 'ClockWorks'!
-
- !SecondsTimer methodsFor: 'access' stamp: 'mjg 9/26/1998 17:05'!
- clock
- ^clock! !
-
- !SecondsTimer methodsFor: 'access' stamp: 'mjg 9/26/1998 17:05'!
- clock: aClock
- clock _ aClock.! !
-
-
- !SecondsTimer methodsFor: 'time management' stamp: 'mjg 9/27/1998 14:12'!
- startTicking
- process := [[true] whileTrue: [(Delay forSeconds: 1) wait. clock nextSecond.]] newProcess.
- process priority: (Processor userBackgroundPriority).
- process resume.! !
-
- !SecondsTimer methodsFor: 'time management' stamp: 'mjg 9/26/1998 17:04'!
- stopTicking
- process terminate.! !
-
-
-
- Object subclass: #VCR
- instanceVariableNames: 'channel recorder '
- classVariableNames: ''
- poolDictionaries: ''
- category: 'ClockWorks'!
-
- !VCR methodsFor: 'accessing' stamp: 'mjg 9/27/1998 14:02'!
- channel: aChannel
- channel _ aChannel.
- ! !
-
- !VCR methodsFor: 'accessing' stamp: 'mjg 9/27/1998 13:56'!
- clock
- ^recorder clock! !
-
-
- !VCR methodsFor: 'vcr functions' stamp: 'mjg 9/27/1998 13:56'!
- fastforward
- ^'FastForwarding'! !
-
- !VCR methodsFor: 'vcr functions' stamp: 'mjg 9/27/1998 13:55'!
- play
- ^'Playing'! !
-
- !VCR methodsFor: 'vcr functions' stamp: 'mjg 9/27/1998 13:56'!
- record
- ^'Recording'! !
-
- !VCR methodsFor: 'vcr functions' stamp: 'mjg 9/27/1998 13:55'!
- rewind
- ^'Rewinding'! !
-
- !VCR methodsFor: 'vcr functions' stamp: 'mjg 9/27/1998 14:04'!
- stop
- ^'Stopping'! !
-
-
-
- Object subclass: #VCRRecorder
- instanceVariableNames: 'startTime endTime channel vcr '
- classVariableNames: ''
- poolDictionaries: ''
- category: 'ClockWorks'!
-
- !VCRRecorder methodsFor: 'timer functions' stamp: 'mjg 9/27/1998 14:23'!
- setEndTime: aTime
- endTime _ AlarmClock new.
- endTime setAlarmTime: aTime.
- endTime alarmBlock: [vcr channel: channel. vcr stop.].
- endTime start.
- ! !
-
- !VCRRecorder methodsFor: 'timer functions' stamp: 'mjg 9/27/1998 14:23'!
- setStartTime: aTime
- startTime _ AlarmClock new.
- startTime setAlarmTime: aTime.
- startTime alarmBlock: [vcr channel: channel. vcr record.].
- startTime start.
- ! !
-
-