[Seaside] Help understanding WATableReport

LK s002 at landr.net
Sun Aug 29 08:44:57 CEST 2004


Avi Bryant wrote:

>
> On Aug 27, 2004, at 2:29 PM, LK wrote:
>
>> Kamil Kukura wrote:
>>
>>>
>>>>> Date today yyyymmdd
>>>>>
>>>>> (you should really learn how to find such answers yourself. Is it 
>>>>> that
>>>>> hard to open browser on class Date and look what methods are there?)
>>>>
>>>>
>>>>
>>>> No, it's not. And that is precisely what I spent several hours 
>>>> doing. The only method that I could get to work through seaside was 
>>>> #asString. So, I thought that there must be some magic that only 
>>>> the experts know about. Clicking on the Sort link above my date or 
>>>> time columns returns a ' Dates are not indexable' error. I inferred 
>>>> from this, that dates could not be sorted. Converting them to 
>>>> strings removed the error, which re-inforced my belief.
>>>
>>>
>>>
>>> From your question it was not clear as for what purpose you want to 
>>> convert date to string. If you get an error, try to examine walkback 
>>> and post it here or to squeak-dev mailing list if it is more general 
>>> thing.
>>>
>> For some reason, when I retrieve my dates from GOODS storage, I must 
>> explicitly convert it to a Date to get it to behave the way is should.
>
>
> What class does it start out being?  What happens when you send 
> #yyyymmdd to it directly? 

PMLogItem is of the #Object class.  When I open a workspace, and enter this:
Transcript clear.
a := PMLogItem new.
a entryDate: Date today.
Transcript cr; show: a entryDate yyyymmdd.

db _ KKDatabase onHost: 'localhost' port: 6100.
logs _ db root at: 'logs'.
b _ logs first.
Transcript cr; cr; show: b entryDate yyyymmdd.
--
It shows what I expect:
2004-08-28

2004-08-20
--
But, within seaside I must  use:

WAReportColumn new valueBlock: [:ea| (ea entryDate asDate) yyyymmdd]; 
title: 'Date').
Otherwise, I get the attached error messages. I have also attached are 
the class files I have built.
.

--Larry


>
> _______________________________________________
> Seaside mailing list
> Seaside at lists.squeakfoundation.org
> http://lists.squeakfoundation.org/listinfo/seaside
>
>

-------------- next part --------------
MessageNotUnderstood: String>>yyyymmdd

    * String(Object)>>doesNotUnderstand: #yyyymmdd

          self	'15 August 2004'
          aMessage	a Message with selector: #yyyymmdd and arguments: #()

    * [] in PMLogsReport>>buildTable

          self	a PMLogsReport
          ea	a PMLogItem

    * WAReportColumn>>valueForRow:

          self	a WAReportColumn
          row	a PMLogItem

    * WAReportColumn>>textForRow:

          self	a WAReportColumn
          row	a PMLogItem

    * WATableReport>>renderColumn:row:on:

          self	a WATableReport
          aColumn	a WAReportColumn
          aRow	a PMLogItem
          html	a WAHtmlRenderer
          text	nil

    * [] in WATableReport>>renderRowNumber:item:on:

          self	a WATableReport
          index	26
          row	a PMLogItem
          html	a WAHtmlRenderer
          ea	a WAReportColumn

    * OrderedCollection>>do:

          self	an OrderedCollection(a WAReportColumn a WAReportColumn a WAReportColumn a WAReportColumn a WAReportC...etc...
          aBlock	[] in WATableReport>>renderRowNumber:item:on:
          index	4

    * [] in WATableReport>>renderRowNumber:item:on:

          self	a WATableReport
          index	26
          row	a PMLogItem
          html	a WAHtmlRenderer
          ea	a WAReportColumn

    * BlockContext>>renderOn:

          self	[] in WATableReport>>renderRowNumber:item:on:
          aRenderer	a WAHtmlRenderer

    * WAHtmlRenderer(WAAbstractHtmlBuilder)>>render:

          self	a WAHtmlRenderer
          anObject	[] in WATableReport>>renderRowNumber:item:on:

    * WAHtmlRenderer(WAAbstractHtmlBuilder)>>tag:do:

          self	a WAHtmlRenderer
          aString	'tr'
          anObject	[] in WATableReport>>renderRowNumber:item:on:

    * WAHtmlRenderer(WAAbstractHtmlBuilder)>>tableRow:

          self	a WAHtmlRenderer
          aBlock	[] in WATableReport>>renderRowNumber:item:on:

    * WATableReport>>renderRowNumber:item:on:

          self	a WATableReport
          index	26
          row	a PMLogItem
          html	a WAHtmlRenderer
          ea	a WAReportColumn

    * [] in WATableReport>>renderRowsOn:

          self	a WATableReport
          html	a WAHtmlRenderer
          row	a PMLogItem
          i	26

    * PMLogs(SequenceableCollection)>>withIndexDo:

          self	a PMLogs(a PMLogItem a PMLogItem a PMLogItem a PMLogItem a PMLogItem a PMLogItem a PMLogItem a PMLog...etc...
          elementAndIndexBlock	[] in WATableReport>>renderRowsOn:
          index	26
          indexLimiT	30

    * KKObjectProxy>>doesNotUnderstand: #withIndexDo:

          self	a PMLogs(a PMLogItem a PMLogItem a PMLogItem a PMLogItem a PMLogItem a PMLogItem a PMLogItem a PMLog...etc...
          aMessage	a Message with selector: #withIndexDo: and arguments: #([] in WATableReport>>renderRowsOn:)

    * WATableReport>>renderRowsOn:

          self	a WATableReport
          html	a WAHtmlRenderer
          row	a PMLogItem
          i	26

    * [] in WATableReport>>renderContentOn:

          self	a WATableReport
          html	a WAHtmlRenderer

    * BlockContext>>renderOn:

          self	[] in WATableReport>>renderContentOn:
          aRenderer	a WAHtmlRenderer

    * WAHtmlRenderer(WAAbstractHtmlBuilder)>>render:

          self	a WAHtmlRenderer
          anObject	[] in WATableReport>>renderContentOn:

    * WAHtmlRenderer(WAAbstractHtmlBuilder)>>tag:do:

          self	a WAHtmlRenderer
          aString	'table'
          anObject	[] in WATableReport>>renderContentOn:

    * WAHtmlRenderer(WAAbstractHtmlBuilder)>>table:

          self	a WAHtmlRenderer
          aBlock	[] in WATableReport>>renderContentOn:

    * WATableReport>>renderContentOn:

          self	a WATableReport
          html	a WAHtmlRenderer

    * WATableReport(WAPresenter)>>renderWithContext:

          self	a WATableReport
          aRenderingContext	a WARenderingContext
          html	a WAHtmlRenderer
          callbacks	a WACallbackRegistry

    * [] in WATableReport(WAComponent)>>renderOn:

          self	a WATableReport
          aRenderer	a WAHtmlRenderer
          ea	a WATableReport

    * WATableReport(WAComponent)>>decorationChainDo:

          self	a WATableReport
          aBlock	[] in WATableReport(WAComponent)>>renderOn:

    * WATableReport(WAComponent)>>renderOn:

          self	a WATableReport
          aRenderer	a WAHtmlRenderer
          ea	a WATableReport

    * WAHtmlRenderer(WAAbstractHtmlBuilder)>>render:

          self	a WAHtmlRenderer
          anObject	a WATableReport

    * PMLogsReport>>renderContentOn:

          self	a PMLogsReport
          html	a WAHtmlRenderer

    * PMLogsReport(WAPresenter)>>renderWithContext:

          self	a PMLogsReport
          aRenderingContext	a WARenderingContext
          html	a WAHtmlRenderer
          callbacks	a WACallbackRegistry

    * [] in PMLogsReport(WAComponent)>>renderOn:

          self	a PMLogsReport
          aRenderer	a WAHtmlRenderer
          ea	a PMLogsReport

    * PMLogsReport(WAComponent)>>decorationChainDo:

          self	a PMLogsReport
          aBlock	[] in PMLogsReport(WAComponent)>>renderOn:

    * PMLogsReport(WAComponent)>>renderOn:

          self	a PMLogsReport
          aRenderer	a WAHtmlRenderer
          ea	a PMLogsReport

    * WAHtmlRenderer(WAAbstractHtmlBuilder)>>render:

          self	a WAHtmlRenderer
          anObject	a PMLogsReport

    * PMLogsTask>>renderContentOn:

          self	a PMLogsTask
          html	a WAHtmlRenderer

    * PMLogsTask(WAPresenter)>>renderWithContext:

          self	a PMLogsTask
          aRenderingContext	a WARenderingContext
          html	a WAHtmlRenderer
          callbacks	a WACallbackRegistry

    * [] in PMLogsTask(WAComponent)>>renderOn:

          self	a PMLogsTask
          aRenderer	a WAHtmlRenderer
          ea	a PMLogsTask

    * PMLogsTask(WAComponent)>>decorationChainDo:

          self	a PMLogsTask
          aBlock	[] in PMLogsTask(WAComponent)>>renderOn:

    * PMLogsTask(WAComponent)>>renderOn:

          self	a PMLogsTask
          aRenderer	a WAHtmlRenderer
          ea	a PMLogsTask

    * WAHtmlRenderer(WAAbstractHtmlBuilder)>>render:

          self	a WAHtmlRenderer
          anObject	a PMLogsTask

    * WAToolFrame>>renderChildOn:

          self	a WAToolFrame
          html	a WAHtmlRenderer

    * [] in WAToolFrame>>renderContentOn:

          self	a WAToolFrame
          html	a WAHtmlRenderer

    * BlockContext>>renderOn:

          self	[] in WAToolFrame>>renderContentOn:
          aRenderer	a WAHtmlRenderer

    * WAHtmlRenderer(WAAbstractHtmlBuilder)>>render:

          self	a WAHtmlRenderer
          anObject	[] in WAToolFrame>>renderContentOn:

    * WAHtmlRenderer(WAAbstractHtmlBuilder)>>tag:do:

          self	a WAHtmlRenderer
          aString	'div'
          anObject	[] in WAToolFrame>>renderContentOn:

    * WAHtmlRenderer(WAAbstractHtmlBuilder)>>div:

          self	a WAHtmlRenderer
          aBlock	[] in WAToolFrame>>renderContentOn:

    * WAHtmlRenderer(WAAbstractHtmlBuilder)>>divNamed:with:

          self	a WAHtmlRenderer
          aString	'frameContent'
          anObject	[] in WAToolFrame>>renderContentOn:

    * WAToolFrame>>renderContentOn:

          self	a WAToolFrame
          html	a WAHtmlRenderer

    * WAToolFrame(WAPresenter)>>renderWithContext:

          self	a WAToolFrame
          aRenderingContext	a WARenderingContext
          html	a WAHtmlRenderer
          callbacks	a WACallbackRegistry

    * [] in WARenderLoop>>render

          self	a WARenderLoop
          request	nil
          context	a WARenderingContext
          document	a WAHtmlStreamDocument
          docRoot	a WARenderedHtmlRoot
          url	a WAUrl
          response	a WAResponse
          ea	a WAToolFrame

    * WAToolFrame(WAComponent)>>decorationChainDo:

          self	a WAToolFrame
          aBlock	[] in WARenderLoop>>render

    * [] in WARenderLoop>>render

          self	a WARenderLoop
          request	nil
          context	a WARenderingContext
          document	a WAHtmlStreamDocument
          docRoot	a WARenderedHtmlRoot
          url	a WAUrl
          response	a WAResponse
          ea	a WAToolFrame

    * [] in PMSession(WASession)>>respond:

          self	a PMSession(/seaside/logs?_s=veqUGXcDRzdjwnyF)
          responseBlock	[] in WARenderLoop>>render
          request	nil
          snapshotHolder	a ValueHolder
          response	nil
          oldEscape	a Continuation
          v	nil
          cc	a Continuation
          url	a WAUrl

    * Continuation class>>currentDo:

          self	Continuation
          aBlock	[] in PMSession(WASession)>>respond:

    * PMSession(WASession)>>respond:

          self	a PMSession(/seaside/logs?_s=veqUGXcDRzdjwnyF)
          responseBlock	[] in WARenderLoop>>render
          request	nil
          snapshotHolder	a ValueHolder
          response	nil
          oldEscape	a Continuation
          v	nil
          cc	a Continuation
          url	a WAUrl

    * WARenderLoop>>render

          self	a WARenderLoop
          request	nil
          context	a WARenderingContext
          document	a WAHtmlStreamDocument
          docRoot	a WARenderedHtmlRoot
          url	a WAUrl
          response	a WAResponse
          ea	a WAToolFrame

    * [] in WARenderLoop>>run

          self	a WARenderLoop
          notification	nil

    * BlockContext>>on:do:

          self	[] in WARenderLoop>>run
          exception	WARenderNotification
          handlerAction	[] in WARenderLoop>>withRenderNowHandler:
          handlerActive	true

    * WARenderLoop>>withRenderNowHandler:

          self	a WARenderLoop
          aBlock	[] in WARenderLoop>>run
          n	nil

    * [] in WARenderLoop>>run

          self	a WARenderLoop
          notification	nil

    * BlockContext>>on:do:

          self	[] in WARenderLoop>>run
          exception	WAPageExpired
          handlerAction	[] in WARenderLoop>>withPageExpiredHandler:
          handlerActive	true

    * WARenderLoop>>withPageExpiredHandler:

          self	a WARenderLoop
          aBlock	[] in WARenderLoop>>run
          n	nil

    * [] in WARenderLoop>>run

          self	a WARenderLoop
          notification	nil

    * BlockContext>>repeat

          self	[] in WARenderLoop>>run

    * WARenderLoop>>run

          self	a WARenderLoop
          notification	nil

    * WARenderLoopMain>>start:

          self	a WARenderLoopMain
          aRequest	a WARequest

    * PMSession(WASession)>>start:

          self	a PMSession(/seaside/logs?_s=veqUGXcDRzdjwnyF)
          aRequest	a WARequest

    * [] in PMSession(WASession)>>performRequest:

          self	a PMSession(/seaside/logs?_s=veqUGXcDRzdjwnyF)
          aRequest	a WARequest
          key	nil
          continuation	nil

    * Dictionary>>at:ifAbsent:

          self	a Dictionary()
          key	'_k'
          aBlock	[] in PMSession(WASession)>>performRequest:
          assoc	nil

    * PMSession(WASession)>>performRequest:

          self	a PMSession(/seaside/logs?_s=veqUGXcDRzdjwnyF)
          aRequest	a WARequest
          key	nil
          continuation	nil

    * [] in PMSession(WASession)>>responseForRequest:

          self	a PMSession(/seaside/logs?_s=veqUGXcDRzdjwnyF)
          aRequest	a WARequest

    * BlockContext>>on:do:

          self	[] in PMSession(WASession)>>responseForRequest:
          exception	Error
          handlerAction	[] in PMSession(WASession)>>withErrorHandler:
          handlerActive	false

    * [] in PMSession(WASession)>>withErrorHandler:

          self	a PMSession(/seaside/logs?_s=veqUGXcDRzdjwnyF)
          aBlock	[] in PMSession(WASession)>>responseForRequest:
          e	MessageNotUnderstood: String>>yyyymmdd
          w	nil

    * BlockContext>>on:do:

          self	[] in PMSession(WASession)>>withErrorHandler:
          exception	Warning
          handlerAction	[] in PMSession(WASession)>>withErrorHandler:
          handlerActive	true

    * PMSession(WASession)>>withErrorHandler:

          self	a PMSession(/seaside/logs?_s=veqUGXcDRzdjwnyF)
          aBlock	[] in PMSession(WASession)>>responseForRequest:
          e	MessageNotUnderstood: String>>yyyymmdd
          w	nil

    * [] in PMSession(WASession)>>responseForRequest:

          self	a PMSession(/seaside/logs?_s=veqUGXcDRzdjwnyF)
          aRequest	a WARequest

    * BlockContext>>on:do:

          self	[] in PMSession(WASession)>>responseForRequest:
          exception	WACurrentSession
          handlerAction	[] in WACurrentSession class(WADynamicVariable class)>>use:during:
          handlerActive	true

    * WACurrentSession class(WADynamicVariable class)>>use:during:

          self	WACurrentSession
          anObject	a PMSession(/seaside/logs?_s=veqUGXcDRzdjwnyF)
          aBlock	[] in PMSession(WASession)>>responseForRequest:
          n	WACurrentSession

    * [] in PMSession(WASession)>>responseForRequest:

          self	a PMSession(/seaside/logs?_s=veqUGXcDRzdjwnyF)
          aRequest	a WARequest

    * [] in PMSession(WASession)>>withEscapeContinuation:

          self	a PMSession(/seaside/logs?_s=veqUGXcDRzdjwnyF)
          aBlock	[] in PMSession(WASession)>>responseForRequest:
          cc	a Continuation

    * Continuation class>>currentDo:

          self	Continuation
          aBlock	[] in PMSession(WASession)>>withEscapeContinuation:

    * PMSession(WASession)>>withEscapeContinuation:

          self	a PMSession(/seaside/logs?_s=veqUGXcDRzdjwnyF)
          aBlock	[] in PMSession(WASession)>>responseForRequest:
          cc	a Continuation

    * [] in PMSession>>withEscapeContinuation:

          self	a PMSession(/seaside/logs?_s=veqUGXcDRzdjwnyF)
          aBlock	[] in PMSession(WASession)>>responseForRequest:

    * KKDatabase>>commitWithRetry:

          self	a KKDatabase
          aBlock	[] in PMSession>>withEscapeContinuation:
          val	nil

    * PMSession>>withEscapeContinuation:

          self	a PMSession(/seaside/logs?_s=veqUGXcDRzdjwnyF)
          aBlock	[] in PMSession(WASession)>>responseForRequest:

    * PMSession(WASession)>>responseForRequest:

          self	a PMSession(/seaside/logs?_s=veqUGXcDRzdjwnyF)
          aRequest	a WARequest

    * [] in PMSession(WASession)>>incomingRequest:

          self	a PMSession(/seaside/logs?_s=veqUGXcDRzdjwnyF)
          aRequest	a WARequest
          e	nil

    * BlockContext>>on:do:

          self	[] in PMSession(WASession)>>incomingRequest:
          exception	Error
          handlerAction	[] in PMSession(WASession)>>incomingRequest:
          handlerActive	true

    * [] in WAProcessMonitor>>critical:ifError:

          self	a WAProcessMonitor
          aBlock	[] in PMSession(WASession)>>incomingRequest:
          errorBlock	[] in PMSession(WASession)>>incomingRequest:
          value	nil

    * BlockContext>>ensure:

          self	[] in WAProcessMonitor>>critical:ifError:
          aBlock	[] in WAProcessMonitor>>critical:ifError:
          returnValue	nil

    * [] in WAProcessMonitor>>critical:ifError:

          self	a WAProcessMonitor
          aBlock	[] in PMSession(WASession)>>incomingRequest:
          errorBlock	[] in PMSession(WASession)>>incomingRequest:
          value	nil

    * [] in BlockContext>>newProcess

          self	[] in WAProcessMonitor>>critical:ifError:
-------------- next part --------------
'From Squeak3.6 of ''6 October 2003'' [latest update: #5429] on 28 August 2004 at 11:40:40 pm'!
Object subclass: #PMLogItem
	instanceVariableNames: 'type entryDate startTime endTime entryText '
	classVariableNames: ''
	poolDictionaries: ''
	category: 'Pim-Logs'!

!PMLogItem methodsFor: 'Initializing' stamp: 'ldk 5/24/2004 21:35'!
initialize
	self entryDate: Date today.
	self startTime: Time now.

! !


!PMLogItem methodsFor: 'accessing' stamp: 'ldk 5/24/2004 04:16'!
endTime
	^ endTime
! !

!PMLogItem methodsFor: 'accessing' stamp: 'ldk 5/24/2004 04:22'!
endTime: aTime
	endTime _ aTime! !

!PMLogItem methodsFor: 'accessing' stamp: 'ldk 5/24/2004 04:16'!
entryDate
	^ entryDate! !

!PMLogItem methodsFor: 'accessing' stamp: 'ldk 5/24/2004 04:23'!
entryDate: aDate
	entryDate _ aDate! !

!PMLogItem methodsFor: 'accessing' stamp: 'ldk 5/24/2004 04:17'!
entryText
	^ entryText
! !

!PMLogItem methodsFor: 'accessing' stamp: 'ldk 5/24/2004 04:23'!
entryText: aString
	entryText _ aString
! !

!PMLogItem methodsFor: 'accessing' stamp: 'ldk 8/20/2004 02:45'!
logTypes
	^ self session db root at: 'logTypes'! !

!PMLogItem methodsFor: 'accessing' stamp: 'ldk 5/24/2004 04:16'!
startTime
	^ startTime! !

!PMLogItem methodsFor: 'accessing' stamp: 'ldk 5/24/2004 04:24'!
startTime: aTime
	startTime _ aTime! !

!PMLogItem methodsFor: 'accessing' stamp: 'ldk 5/25/2004 21:27'!
type
	^type! !

!PMLogItem methodsFor: 'accessing' stamp: 'ldk 5/25/2004 21:27'!
type: aString
	type _ aString! !


!PMLogItem methodsFor: 'as yet unclassified' stamp: 'ldk 5/25/2004 21:42'!
showItem
	|anArray|
	anArray _ Array 
		with: type 
		with: (entryDate asString) 
		with: (startTime asString) 
		with: (endTime asString) 
		with: entryText.
	^ anArray
	
	! !


!PMLogItem methodsFor: 'math' stamp: 'ldk 5/25/2004 06:03'!
elapsedSeconds
	^ endTime asSeconds - startTime asSeconds! !

!PMLogItem methodsFor: 'math' stamp: 'ldk 5/24/2004 21:02'!
elapsedTime 
	|start end|
	start _ self startTime class totalSeconds.
	end _ self endTime class totalSeconds.
	^end - start! !


!PMLogItem methodsFor: 'rendering' stamp: 'ldk 8/20/2004 03:04'!
renderEndTimeOn: html 
	html
		tableRow: [html tableData: 'End Time'.
			html
				tableData: [html
						textInputWithValue: endTime
						callback: [:i | self endTime: i].
					html space; space.
					html
						submitButtonWithAction: [self endTime: Time now]
						text: 'End Now']]!
]style[(17 4 3 4 14 4 12 10 5 4 17 4 27 7 18 3 2 4 10 1 8 4 20 4 32 4 10 4 18 9 2)f1b,f1cblue;b,f1,f1cblue;i,f1,f1cblue;i,f1,f1c202202126,f1,f1cblue;i,f1,f1cblue;i,f1,f1cmagenta;,f1,f1cred;,f1,f1cmagenta;,f1,f1cblue;i,f1,f1cblue;i,f1,f1cblue;i,f1,f1cmagenta;,f1,f1cmagenta;,f1,f1c202202126,f1! !

!PMLogItem methodsFor: 'rendering' stamp: 'ldk 8/20/2004 02:20'!
renderEntryDateOn: html 
	html
		tableRow: [html tableData: 'Date'.
			html tableData: entryDate]!
]style[(19 4 3 4 14 4 12 6 5 4 12 9 1)f1b,f1cblue;b,f1,f1cblue;i,f1,f1cblue;i,f1,f1c202202126,f1,f1cblue;i,f1,f1cmagenta;,f1! !

!PMLogItem methodsFor: 'rendering' stamp: 'ldk 8/20/2004 02:56'!
renderEntryTextOn: html 
	html
		tableRow: [html tableData: 'Entry Text'.
			html
				tableData: [html attributeAt: 'cols' put: 50;
						 attributeAt: 'rows' put: 10.
					html
						textAreaWithValue: entryText
						callback: [:i | self entryText: i]]]!
]style[(19 4 3 4 14 4 12 12 5 4 17 4 14 6 6 2 22 6 6 2 7 4 26 9 18 3 2 4 12 1 3)f1b,f1cblue;b,f1,f1cblue;i,f1,f1cblue;i,f1,f1c202202126,f1,f1cblue;i,f1,f1cblue;i,f1,f1c202202126,f1,f1c202202126,f1,f1c202202126,f1,f1c202202126,f1,f1cblue;i,f1,f1cmagenta;,f1,f1cred;,f1,f1cmagenta;,f1,f1cblue;i,f1! !

!PMLogItem methodsFor: 'rendering' stamp: 'ldk 8/20/2004 02:35'!
renderStartTimeOn: html 
	html
		tableRow: [html tableData: 'Time'.
			html tableData: startTime]!
]style[(19 4 3 4 14 4 12 6 5 4 12 9 1)f1b,f1cblue;b,f1,f1cblue;i,f1,f1cblue;i,f1,f1c201201125,f1,f1cblue;i,f1,f1cmagenta;,f1! !

!PMLogItem methodsFor: 'rendering' stamp: 'ldk 8/20/2004 02:50'!
renderTypeOn: html 
	html
		tableRow: [html tableData: 'Type'.
			html
				tableData: [html
						selectFromList: #('DBA' 'DRE' 'KANDYBOUQUETS' 'LOGS' 'SA' 'TEST')
						selected: 'LOGS'
						callback: [:i | self type: i]]]!
]style[(14 4 3 4 14 4 12 6 5 4 17 4 89 6 18 3 2 4 7 1 3)f1b,f1cblue;b,f1,f1cblue;i,f1,f1cblue;i,f1,f1c201201125,f1,f1cblue;i,f1,f1cblue;i,f1,f1c201201125,f1,f1cred;,f1,f1cmagenta;,f1,f1cblue;i,f1! !

"-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "!

PMLogItem class
	instanceVariableNames: ''!

!PMLogItem class methodsFor: 'as yet unclassified' stamp: 'ldk 5/25/2004 21:19'!
types
	^ #('Personal' 'DRE' 'SA' 'DBA')! !
-------------- next part --------------
'From Squeak3.6 of ''6 October 2003'' [latest update: #5429] on 28 August 2004 at 11:40:15 pm'!
WAComponent subclass: #PMLogsReport
	instanceVariableNames: 'records table entryDate type startTime entryText endTime '
	classVariableNames: ''
	poolDictionaries: ''
	category: 'Pim-Logs'!

!PMLogsReport methodsFor: 'as yet unclassified' stamp: 'ldk 8/28/2004 23:36'!
buildTable
	^WATableReport new
		rowPeriod: 1;
		rowColors: #('white' 'lightbrown');
		rows: self session logs ;
		columns: (OrderedCollection new
			add: (WAReportColumn new valueBlock: [:ea| ea type ]; title: 'Type');
			add: (WAReportColumn new valueBlock: [:ea| (ea entryDate) yyyymmdd]; title: 'Date');
			add: (WAReportColumn new valueBlock: [:ea| ea startTime asString]; title: 'Start Time');
			add: (WAReportColumn new valueBlock: [:ea| ea entryText]; title: 'Entry');
			add: (WAReportColumn new valueBlock: [:ea| ea startTime]; title: 'End Time');
			yourself)! !

!PMLogsReport methodsFor: 'as yet unclassified' stamp: 'ldk 8/22/2004 10:53'!
children

	^ Array with: table.! !

!PMLogsReport methodsFor: 'as yet unclassified' stamp: 'ldk 8/14/2004 08:04'!
notes
	^ '
	When I initialize this the same way as PMLogsGrid, I get a ''cannot Understand'' canSort for the column name.
	Not sure this is a working widget.
	'! !

!PMLogsReport methodsFor: 'as yet unclassified' stamp: 'ldk 8/22/2004 10:54'!
renderContentOn: html

	html render: table.! !

!PMLogsReport methodsFor: 'as yet unclassified' stamp: 'ldk 8/22/2004 15:52'!
root: anObject

	records _ anObject.
	table _  self buildTable.! !
-------------- next part --------------
'From Squeak3.6 of ''6 October 2003'' [latest update: #5429] on 28 August 2004 at 11:40:07 pm'!
WAComponent subclass: #PMLogsTask
	instanceVariableNames: 'pmLogsView subtitle pages '
	classVariableNames: ''
	poolDictionaries: ''
	category: 'Pim-Logs'!

!PMLogsTask methodsFor: 'as yet unclassified' stamp: 'ldk 8/16/2004 02:33'!
children
	^ Array with: pmLogsView with: pages.! !

!PMLogsTask methodsFor: 'as yet unclassified' stamp: 'ldk 8/22/2004 16:03'!
initialize
	self session registerObjectForBacktracking: self.
	pmLogsView _ PMLogsReport new root: self session logs.
	"pages _ PMPagedList new."
	
	subtitle _ 'My Logs'! !

!PMLogsTask methodsFor: 'as yet unclassified' stamp: 'ldk 8/20/2004 22:06'!
renderContentOn: html 
	html cssId: 'banner'.
	html
		table: [html
				tableRowWith: [html divNamed: 'title' with: self title.
					html divNamed: 'subtitle' with: self subtitle]].
	"html render: pages. 
	self session filter: pages batch. 
	pmLogsView _ PMLogsGrid new ."
	html render: pmLogsView!
]style[(17 4 3 4 8 8 3 4 11 4 20 4 11 7 7 4 13 4 11 10 7 4 14 89 2 4 9 10)f1b,f1cblue;b,f1,f1cblue;i,f1,f1c202202126,f1,f1cblue;i,f1,f1cblue;i,f1,f1cblue;i,f1,f1c202202126,f1,f1cmagenta;,f1,f1cblue;i,f1,f1c202202126,f1,f1cmagenta;,f1,f1c152050000,f1,f1cblue;i,f1,f1cmagenta;! !

!PMLogsTask methodsFor: 'as yet unclassified' stamp: 'ldk 8/1/2004 11:19'!
style

	^ '
	body {margin: 0px; background-color: wheat; font-family: sans-serif}
	#banner {width: 100%}	
	#banner tr {background-color: lightgreen; text-align: right; padding: 10px; vertical-align: bottom}
	#title {font-size: 18pt; font-weight: bold}
	#subtitle {font-size: 12pt; font-style: italic}
	#body {padding: 5px}
	.validation-error {color: red; font-size: 9pt; padding: 5px}
	'! !

!PMLogsTask methodsFor: 'as yet unclassified' stamp: 'ldk 8/1/2004 11:08'!
subtitle
	^ subtitle
! !

!PMLogsTask methodsFor: 'as yet unclassified' stamp: 'ldk 8/1/2004 11:08'!
subtitle: aString
	subtitle _ aString! !

!PMLogsTask methodsFor: 'as yet unclassified' stamp: 'ldk 7/21/2004 07:00'!
title

	^ 'Logs'! !

!PMLogsTask methodsFor: 'as yet unclassified' stamp: 'ldk 7/24/2004 06:39'!
useDb: aDatabase during: aBlock
	| db |
   db := aDatabase.
   aBlock ensure: [db := nil] ! !

"-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "!

PMLogsTask class
	instanceVariableNames: ''!

!PMLogsTask class methodsFor: 'as yet unclassified' stamp: 'ldk 7/19/2004 23:21'!
canBeRoot
	^ true! !

!PMLogsTask class methodsFor: 'as yet unclassified' stamp: 'ldk 7/19/2004 23:11'!
initialize
	(self registerAsApplication: 'logs').! !


PMLogsTask initialize!
-------------- next part --------------
'From Squeak3.6 of ''6 October 2003'' [latest update: #5429] on 28 August 2004 at 11:39:55 pm'!
WASession subclass: #PMSession
	instanceVariableNames: 'filter logs db '
	classVariableNames: ''
	poolDictionaries: ''
	category: 'Pim-Seaside'!

!PMSession methodsFor: 'as yet unclassified' stamp: 'ldk 8/10/2004 07:47'!
db
      ^ db ifNil: [db := KKDatabase onHost: 'localhost' port: 6100].! !

!PMSession methodsFor: 'as yet unclassified' stamp: 'ldk 8/17/2004 05:05'!
filter
	^ filter! !

!PMSession methodsFor: 'as yet unclassified' stamp: 'ldk 8/17/2004 05:08'!
filter: aCollection
	filter _ aCollection! !

!PMSession methodsFor: 'as yet unclassified' stamp: 'ldk 8/14/2004 23:34'!
logs
	^( self db root at: 'logs')! !

!PMSession methodsFor: 'as yet unclassified' stamp: 'ldk 8/6/2004 02:41'!
user
   ^ user! !

!PMSession methodsFor: 'as yet unclassified' stamp: 'ldk 8/6/2004 02:40'!
user: aUser
   user := aUser! !

!PMSession methodsFor: 'as yet unclassified' stamp: 'ldk 8/12/2004 03:15'!
userForLogin: aLogin
    ^ self users detect: [:user | user login = aLogin]! !

!PMSession methodsFor: 'as yet unclassified' stamp: 'ldk 8/10/2004 07:48'!
users
   ^ self db root: 'users'! !

!PMSession methodsFor: 'as yet unclassified' stamp: 'ldk 8/6/2004 02:41'!
withEscapeContinuation: aBlock
   ^ (self db) commitWithRetry: [super withEscapeContinuation: aBlock]! !

"-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "!

PMSession class
	instanceVariableNames: ''!


More information about the Seaside mailing list