Component with multiples decorations

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

Component with multiples decorations

Julien Berthaud
Hello everyone,

First of all, I am using Seaside2.7a1-mb.215 within Squeak 3.9.
I have created a component by subclassing WAComponent.
Then I have added two decorations:
  - WAFormDecoration
  - WAValidationDecoration
So my component is wrapped into a form and a validator.
Here is my initialize method:
MyComponent>>initialize
  super initialize.
  form := WAFormDecoration new
                buttons: self buttons.
  self addDecoration: form.
  self validateWith: [...my validation constraints... ifTrue:
[WAValidationNotification raiseSignal: 'a custom message']].

MyComponent>>buttons
  ^ #(Ok Cancel)

I have two issues:
  1) The buttons Ok and Cancel are displayed two times, one time inside
the form and one time just outside the form (just after the </form> tag).
  2) When I hit the <Enter> key inside the form I encountered an issue
telling me that WAValidationDecoration does not understand the message
defaultButton.

For the first issue, I have used a trick inside my CSS stylesheet in
order to remove the display of the second set of buttons.
Here is the dedicated part inside my style function.
div.dialog-buttons {
  display:none;
}
form div.dialog-buttons {
  display:block;
}

For the second issue, I understand well that this message should be only
dedicated to the WAFormValidation component but why it is passed through
the other decoration (the validation one)?
After browsing the addDecoration method, I noticed that the decorations
are not collected through a list but they are chained. Here I guess that
form owner is MyComponent and that validation owner is form. I do not
know if I am right here? But anyway, I can't solve my problem.

Thank you in advance.
Any ideas?
Julien

_______________________________________________
Seaside mailing list
[hidden email]
http://lists.squeakfoundation.org/cgi-bin/mailman/listinfo/seaside
Reply | Threaded
Open this post in threaded view
|

Re: Component with multiples decorations

Lukas Renggli
>   1) The buttons Ok and Cancel are displayed two times, one time inside
> the form and one time just outside the form (just after the </form> tag).

I tried to reproduce this, but could not.

>   2) When I hit the <Enter> key inside the form I encountered an issue
> telling me that WAValidationDecoration does not understand the message
> defaultButton.

I cannot reproduce this either.

> For the first issue, I have used a trick inside my CSS stylesheet in
> order to remove the display of the second set of buttons.
> Here is the dedicated part inside my style function.

There is something wrong with your setup. The button definition #( Ok
Cancel ) looks odd, do you actually have methods #Ok and #Cancel in
your component?

> For the second issue, I understand well that this message should be only
> dedicated to the WAFormValidation component but why it is passed through
> the other decoration (the validation one)?
> After browsing the addDecoration method, I noticed that the decorations
> are not collected through a list but they are chained. Here I guess that
> form owner is MyComponent and that validation owner is form. I do not
> know if I am right here? But anyway, I can't solve my problem.

Can you provide a minimal file-out that shows the problem and that can
be loaded and browsed with a single click?

Lukas

--
Lukas Renggli
http://www.lukas-renggli.ch
_______________________________________________
Seaside mailing list
[hidden email]
http://lists.squeakfoundation.org/cgi-bin/mailman/listinfo/seaside
Reply | Threaded
Open this post in threaded view
|

Re: Component with multiples decorations

Roger Whitney
In reply to this post by Julien Berthaud

On Jun 5, 2007, at 2:14 AM, Julien Berthaud wrote:

> Hello everyone,
>
> First of all, I am using Seaside2.7a1-mb.215 within Squeak 3.9.
> I have created a component by subclassing WAComponent.
> Then I have added two decorations:
>  - WAFormDecoration
>  - WAValidationDecoration
> So my component is wrapped into a form and a validator.
> Here is my initialize method:
> MyComponent>>initialize
>  super initialize.
>  form := WAFormDecoration new
>                buttons: self buttons.
>  self addDecoration: form.
>  self validateWith: [...my validation constraints... ifTrue:  
> [WAValidationNotification raiseSignal: 'a custom message']].
>
> MyComponent>>buttons
>  ^ #(Ok Cancel)
>
> I have two issues:
>  1) The buttons Ok and Cancel are displayed two times, one time  
> inside the form and one time just outside the form (just after the  
> </form> tag).

I don't see this in Seaside 2.6b1.140 in VW. What happens if you  
create at form directly in your renderContentOn: method rather than  
use a decorator?

>  2) When I hit the <Enter> key inside the form I encountered an  
> issue telling me that WAValidationDecoration does not understand  
> the message defaultButton.
>
Are you sure that it is WAValidationDecoration that raises the DNU  
defaultButton? That message should be sent to your MyComponent class.

> For the first issue, I have used a trick inside my CSS stylesheet  
> in order to remove the display of the second set of buttons.
> Here is the dedicated part inside my style function.
> div.dialog-buttons {
>  display:none;
> }
> form div.dialog-buttons {
>  display:block;
> }
>
> For the second issue, I understand well that this message should be  
> only dedicated to the WAFormValidation component but why it is  
> passed through the other decoration (the validation one)?
> After browsing the addDecoration method, I noticed that the  
> decorations are not collected through a list but they are chained.  
> Here I guess that form owner is MyComponent and that validation  
> owner is form. I do not know if I am right here? But anyway, I  
> can't solve my problem.
>
> Thank you in advance.
> Any ideas?
> Julien
>
> _______________________________________________
> Seaside mailing list
> [hidden email]
> http://lists.squeakfoundation.org/cgi-bin/mailman/listinfo/seaside
>


----
Roger Whitney              Department of Computer Science
[hidden email]        San Diego State University
http://www.eli.sdsu.edu/   San Diego, CA 92182-7720
(619) 583-1978
(619) 594-3535 (office)
(619) 594-6746 (fax)

_______________________________________________
Seaside mailing list
[hidden email]
http://lists.squeakfoundation.org/cgi-bin/mailman/listinfo/seaside
Reply | Threaded
Open this post in threaded view
|

Re: Component with multiples decorations

Julien Berthaud
In reply to this post by Lukas Renggli
Hi Lukas,

I am trying to follow your tutorial on Seaside (I have found it on your
web site).
This tutorial is really great and let me address you a big THANK for
your impressive work.
This is the exercise 34 when editing a play.
>>   1) The buttons Ok and Cancel are displayed two times, one time inside
>> the form and one time just outside the form (just after the </form>
>> tag).
>
> I tried to reproduce this, but could not.
>
I cannot reproduce it either once I have isolated this component.
>>   2) When I hit the <Enter> key inside the form I encountered an issue
>> telling me that WAValidationDecoration does not understand the message
>> defaultButton.
>
> I cannot reproduce this either.
I cannot reproduce it either once I have isolated this component.

So this may mean that both issues are dealing with encapsulation (My
guess).
>
>> For the first issue, I have used a trick inside my CSS stylesheet in
>> order to remove the display of the second set of buttons.
>> Here is the dedicated part inside my style function.
>
> There is something wrong with your setup. The button definition #( Ok
> Cancel ) looks odd, do you actually have methods #Ok and #Cancel in
> your component?
I do. Here is the source code:
MyComponent>>Cancel
   ^ self answer: nil.

MyComponent>>Ok
   ^ self answer: play.

>
>> For the second issue, I understand well that this message should be only
>> dedicated to the WAFormValidation component but why it is passed through
>> the other decoration (the validation one)?
>> After browsing the addDecoration method, I noticed that the decorations
>> are not collected through a list but they are chained. Here I guess that
>> form owner is MyComponent and that validation owner is form. I do not
>> know if I am right here? But anyway, I can't solve my problem.
>
> Can you provide a minimal file-out that shows the problem and that can
> be loaded and browsed with a single click?
>
> Lukas
>
I have embedded a file-out of my work (try to minimize it but STEditPlay
is one my deepest component inside the application).
Sorry for the inconvenience.
I have set up an initialize class method inside STMainFrame component in
order to register my app under 'Theater'.

I have file-out the model just in case but I think you already have it.

STMainFrame is the main class of the app.
I use the following rendering method:
STMainFram>>renderContentOn: html
   (html div)
       class: 'page';
       with:
               [self renderHeaderOn: html.
               self renderMenuOn: html.
               (html div)
                   class: 'main-view';
                   with: [html render: currentTask]]

currentTask is holding the children component regarding the action
chosen by the user.
You can click on the 'Show Report' anchor.
In turn STShowReport may call STEditPlay when the user wants to edit a
play (just click on the name of a play).
I think my encapsulation is pretty bad.
It seems to me that I am replacing currentTask (STShowReport) with
STEditPlay but STMainFrame is not aware of STEditPlay (not declared in
children method neither in the initialize method for backtracking).

I do not know exactly what needs to be done in fact.

Thank you for your time.
Julien

WATask subclass: #STBuyTicketTask
        instanceVariableNames: 'play playChooser show showChooser ticketChooser tickets'
        classVariableNames: ''
        poolDictionaries: ''
        category: 'Tutorial-Theater-View'!

!STBuyTicketTask methodsFor: 'running' stamp: 'JB 5/9/2007 00:51'!
chooseAPlay

        playChooser :=  STPlayChooser new.
        ^ self call: playChooser.! !

!STBuyTicketTask methodsFor: 'running' stamp: 'JB 5/9/2007 00:52'!
chooseAShow: aCollectionOfShows

        showChooser := STShowChooser withShows: aCollectionOfShows.
        ^ self call: showChooser.
        ! !

!STBuyTicketTask methodsFor: 'running' stamp: 'JB 5/9/2007 00:53'!
chooseATicket: aShow
       
        ticketChooser := STTicketChooser withShow: aShow.
        ^ self call: ticketChooser.! !

!STBuyTicketTask methodsFor: 'running' stamp: 'JB 5/9/2007 00:47'!
go

        "self inform: 'Here is the start of my supa app... !!'."
       
        tickets := nil.
       
        self isolate: [
        "Choisir un spectacle"
        play := self chooseAPlay.
       
        "self inform: 'You choose the play named [', play title, ']'."
       
        [tickets = nil] whileTrue: [
                "Choisir ensuite un horaire pour le spectacle choisi précédemment."
                show := self chooseAShow: play shows.
       
                "elf inform: 'You choose the show named [', show printString, ']'."
       
                "Choisir plusieurs billets pour le show courant"
                tickets := self chooseATicket: show.
        ].
        ].
" self inform: 'Liste des tickets commandés: ', tickets printString."
        "self inform: 'You choose ', nbTicket printString, ' tickets'."
       
        self call: (STTicketPrinter withTickets: tickets).
       
       
        ! !


!STBuyTicketTask methodsFor: 'initialization' stamp: 'JB 5/9/2007 00:49'!
initialize

        play := nil.
        tickets := nil.
        show := nil.! !


!STBuyTicketTask methodsFor: 'accessing' stamp: 'JB 5/10/2007 00:25'!
playChooser
        ^ playChooser! !

!STBuyTicketTask methodsFor: 'accessing' stamp: 'JB 5/10/2007 00:25'!
playChooser: anObject
        playChooser := anObject! !

!STBuyTicketTask methodsFor: 'accessing' stamp: 'JB 5/10/2007 00:25'!
showChooser
        ^ showChooser! !

!STBuyTicketTask methodsFor: 'accessing' stamp: 'JB 5/10/2007 00:25'!
showChooser: anObject
        showChooser := anObject! !

!STBuyTicketTask methodsFor: 'accessing' stamp: 'JB 5/10/2007 00:25'!
ticketChooser
        ^ ticketChooser! !

!STBuyTicketTask methodsFor: 'accessing' stamp: 'JB 5/10/2007 00:25'!
ticketChooser: anObject
        ticketChooser := anObject! !

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

STBuyTicketTask class
        instanceVariableNames: ''!

!STBuyTicketTask class methodsFor: 'testing' stamp: 'JB 5/1/2007 00:13'!
canBeRoot
        "Point d'entrée de l'application"
        ^ true! !


WAComponent subclass: #STEditPlay
        instanceVariableNames: 'form play validationError'
        classVariableNames: ''
        poolDictionaries: ''
        category: 'Tutorial-Theater-View'!

!STEditPlay methodsFor: 'processing' stamp: 'JB 5/29/2007 10:35'!
Cancel

        ^ self answer: nil.! !

!STEditPlay methodsFor: 'processing' stamp: 'JB 5/29/2007 10:35'!
Ok

        ^ self answer: play.! !

!STEditPlay methodsFor: 'processing' stamp: 'JB 6/1/2007 12:38'!
addForm
        form := WAFormDecoration new
                                buttons: self buttons.
        self addDecoration: form! !

!STEditPlay methodsFor: 'processing' stamp: 'JB 5/29/2007 10:54'!
addFormByDefault

        ^ true! !

!STEditPlay methodsFor: 'processing' stamp: 'JB 5/31/2007 15:07'!
addNewError: aNewMsg toExistingError: aMsg

^ (aMsg isEmptyOrNil
        ifFalse: [aMsg, ' <br /> ']
        ifTrue: [aMsg]),
        aNewMsg.! !

!STEditPlay methodsFor: 'processing' stamp: 'JB 6/1/2007 12:37'!
addValidation

        "validationError := WAValidationDecoration new
                                                validateWith: [ :aPlay | | msg |
                                                        aPlay isNil ifFalse: [
                                                                msg := ''.
                                                                aPlay title isEmptyOrNil ifTrue: [
                                                                        msg := self addNewError: 'Vous devez renseigner le titre du spectacle.' toExistingError: msg.].
                                                                aPlay kind isEmptyOrNil ifTrue: [
                                                                        msg := self addNewError: 'Vous devez renseigner le type du spectacle.' toExistingError: msg.].
                                                                aPlay author isEmptyOrNil ifTrue: [
                                                                        msg := self addNewError: 'Vous devez renseigner l''auteur du spectacle.' toExistingError: msg.].
                                                                aPlay description isEmptyOrNil ifTrue: [
                                                                        msg := msg := self addNewError: 'Vous devez renseigner la description du spectacle.' toExistingError: msg.].
                                                                msg isEmptyOrNil ifFalse: [
                                                                        WAValidationNotification raiseSignal: msg.].
                                                        ].
                                                ];
                                                yourself.
        self addDecoration: validationError."
       
        self validateWith: [ :aPlay | | msg |
                                                        aPlay isNil ifFalse: [
                                                                msg := ''.
                                                                aPlay title isEmptyOrNil ifTrue: [
                                                                        msg := self addNewError: 'Vous devez renseigner le titre du spectacle.' toExistingError: msg.].
                                                                aPlay kind isEmptyOrNil ifTrue: [
                                                                        msg := self addNewError: 'Vous devez renseigner le type du spectacle.' toExistingError: msg.].
                                                                aPlay author isEmptyOrNil ifTrue: [
                                                                        msg := self addNewError: 'Vous devez renseigner l''auteur du spectacle.' toExistingError: msg.].
                                                                aPlay description isEmptyOrNil ifTrue: [
                                                                        msg := msg := self addNewError: 'Vous devez renseigner la description du spectacle.' toExistingError: msg.].
                                                                msg isEmptyOrNil ifFalse: [
                                                                        WAValidationNotification raiseSignal: msg.].
                                                        ].
                                                ].! !

!STEditPlay methodsFor: 'processing' stamp: 'JB 5/29/2007 11:48'!
buttons

        ^ #(Ok Cancel)! !


!STEditPlay methodsFor: 'initialization' stamp: 'JB 6/11/2007 11:55'!
initialize
        super initialize.
        self addValidation.
        self addFormByDefault ifTrue: [self addForm]! !


!STEditPlay methodsFor: 'rendering' stamp: 'JB 5/29/2007 10:42'!
renderContentOn: html
        (html div)
                class: 'Edit-Play';
                with:
                                [(html table)
                                        "border: 1;"
                                        align: 'center';
                                        with:
                                                        [html tableCaption: 'Edit a play'.
                                                        "(html tableHead)
                                                                title: 'Edition d''un spectacle';
                                                                with:
                                                                                [html tableRow with: [
                                                                                        html tableHeading: '1st Column'.
                                                                                        html tableHeading: '2nd Column'.
                                                                                        ]
                                                                                ]."
                                                        html tableBody with:
                                                                        [html tableRow with:
                                                                                        [html tableHeading: 'Title :'.
                                                                                        html tableData with:
                                                                                                        [(html textInput)
                                                                                                                on: #title of: self play;
                                                                                                                size: 30]].
                                                                        html tableRow with:
                                                                                        [html tableHeading: 'Kind :'.
                                                                                        html tableData with:
                                                                                                        [(html textInput)
                                                                                                                size: 30;
                                                                                                                on: #kind of: self play]].
                                                                        html tableRow with:
                                                                                        [html tableHeading: 'Author :'.
                                                                                        html tableData with:
                                                                                                        [(html textInput)
                                                                                                                size: 30;
                                                                                                                on: #author of: self play]].
                                                                        html tableRow with:
                                                                                        [html tableHeading: 'Description :'.
                                                                                        html tableData with:
                                                                                                        [(html textArea)
                                                                                                                columns: 60;
                                                                                                                rows: 10;
                                                                                                                on: #description of: self play]]]]]! !


!STEditPlay methodsFor: 'accessing' stamp: 'JB 5/28/2007 20:06'!
play
        ^ play! !

!STEditPlay methodsFor: 'accessing' stamp: 'JB 5/28/2007 20:06'!
play: anObject
        play := anObject! !


!STEditPlay methodsFor: 'as yet unclassified' stamp: 'JB 6/1/2007 11:48'!
defaultButton

        ^ self buttons first.! !

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

STEditPlay class
        instanceVariableNames: ''!

!STEditPlay class methodsFor: 'as yet unclassified' stamp: 'JB 5/29/2007 10:34'!
withPlay: aPlay

^ self new initialize;
        play: aPlay;
        yourself.! !


WATask subclass: #STExchangeTicketTask
        instanceVariableNames: 'ticketID selectedTicket selectedShow'
        classVariableNames: ''
        poolDictionaries: ''
        category: 'Tutorial-Theater-View'!

!STExchangeTicketTask methodsFor: 'running' stamp: 'JB 5/11/2007 15:41'!
go
        | doIT |
        [self isTicketIDValid] whileFalse:
                        [ticketID ifNotNil:
                                        [self inform: 'Your ticket was not found !! Please check you ticket ID.'].
                        ticketID := self request: 'On your ticket, find the ID and enter it.'
                                                label: 'Next'].
        doIT := false.
        [doIT] whileFalse:
                        [selectedShow := self
                                                call: (STShowChooser withShows: (selectedTicket show play shows
                                                                                select: [:show | show = selectedTicket show ifTrue: [false] ifFalse: [true]])).
                        doIT := self
                                                call: (STTicketExchanger withTicket: ((selectedTicket copy)
                                                                                setShow: selectedShow;
                                                                                yourself))].
        doIT ifTrue: [ selectedTicket setShow: selectedShow. ].
       
        self call: (STTicketPrinter withTickets: (Array with: selectedTicket)).! !


!STExchangeTicketTask methodsFor: 'initialization' stamp: 'JB 5/11/2007 11:38'!
initialize

        ticketID := nil.
        selectedTicket := nil.! !


!STExchangeTicketTask methodsFor: 'validation' stamp: 'JB 5/11/2007 11:55'!
isTicketIDValid
        "Renvoie VRAI si le ticket est effectivement trouvé
                sinon FAUX"
       
        "TicketID Nil => FAUX"
        ticketID isNil ifTrue: [^ false].
        "TicketID non entier => FAUX"
        [ticketID := ticketID asInteger]
                on: Exception
                do: [^ false].
        "Existe-t'il un ticket correspondant à ce numéro ?
                Si OUI => VRAI
                Sinon => FAUX
        "
        STTheater default do: [ :play |
                play do: [ :show |
                        show do: [ :ticket |
                                (ticketID = ticket id) ifTrue: [selectedTicket := ticket.].
                                ].
                        ].
                ].
        selectedTicket isNil ifTrue: [ ^ false].
        ^ true.
       

"do: [ :ticket | (ticket id = ticketID) ifTrue: [^ true].]"! !


WAComponent subclass: #STMainFrame
        instanceVariableNames: 'buyTicketTask changeTicketTask currentTask editPlayTask showReportTask showTicketTask'
        classVariableNames: ''
        poolDictionaries: ''
        category: 'Tutorial-Theater-View'!

!STMainFrame methodsFor: 'rendering' stamp: 'JB 5/29/2007 11:30'!
children

        | childrens |
        "childrens := Array with: buyTicketTask."
        childrens := OrderedCollection new
                                add: changeTicketTask;
                                add: buyTicketTask;
                                add: showReportTask;
                                add: showTicketTask;
                                add: editPlayTask;
                                yourself.
        ^ childrens asArray.! !

!STMainFrame methodsFor: 'rendering' stamp: 'JB 5/11/2007 10:52'!
renderContentOn: html

        (html div)
        class: 'page';
        with: [
                self renderHeaderOn: html.
                self renderMenuOn: html.
                (html div)
                class: 'main-view';
                with: [ html render: currentTask. ].
        ].! !

!STMainFrame methodsFor: 'rendering' stamp: 'JB 5/9/2007 00:17'!
renderHeaderOn: html
       
        (html div)
        class: 'banniere';
        with: [
                (html div)
                class: 'haute';
                with: [
                        (html span)
                        class: 'theater-name';
                        with: (STTheater default name).
                        (html span)
                        class: 'theater-season';
                        with: (STTheater default season).
                ].
                (html div)
                class: 'basse';
                with: [html space].
        ].! !

!STMainFrame methodsFor: 'rendering' stamp: 'JB 5/29/2007 11:06'!
renderMenuOn: html

        (html div)
        class: 'menu';
        with: [ (html anchor)
                        callback: [self buyTicket.];
                        with: 'Buy Ticket'.
                       
                        html break.
                       
                        (html anchor)
                        callback: [self changeTicket.];
                        with: 'Change Ticket'.
                       
                        html break.
                       
                        (html anchor)
                        callback: [self showTicket.];
                        with: 'Show Ticket'.
                       
                        html break.
                       
                        (html anchor)
                        callback: [self showReport.];
                        with: 'Show Report'.
                       
                        html break.
                       
                        (html anchor)
                        callback: [self editPlay.];
                        with: 'Edit Play'.
        ].! !

!STMainFrame methodsFor: 'rendering' stamp: 'JB 5/29/2007 11:57'!
style ^ 'div.page {
  clear:both;
  float:left;
  width:820px;
}

div.banniere {
  clear:both;
  float:left;
}

div.banniere div {
  clear:both;
  float:left;
}

div.banniere div.haute {
  background-color:LightSteelBlue;
  padding:10px;
  width:780px;
}

div.banniere div.basse {
  background-color:LightSlateGray;
  width:800px;
}

div.banniere div.haute span {
  clear:both;
  float:left;
}

div.banniere div.haute span.theater-name {
  font-size:36px;
}

div.banniere div.haute span.theater-season {
  font-size:18px;
}

div.menu {
  border:4px dotted;
  clear:left;
  float:left;
  padding:10px;
  width:130px;
}

div.main-view {
  float:left;
  width:642px;
}

div.dialog-buttons {
  display:none;
}

form div.dialog-buttons {
  display:block;
}'! !


!STMainFrame methodsFor: 'accessing' stamp: 'JB 5/9/2007 00:26'!
buyTicketTask
        ^ buyTicketTask! !

!STMainFrame methodsFor: 'accessing' stamp: 'JB 5/9/2007 00:26'!
buyTicketTask: anObject
        buyTicketTask := anObject! !

!STMainFrame methodsFor: 'accessing' stamp: 'JB 5/11/2007 10:44'!
changeTicketTask
        ^ changeTicketTask! !

!STMainFrame methodsFor: 'accessing' stamp: 'JB 5/11/2007 10:44'!
changeTicketTask: anObject
        changeTicketTask := anObject! !

!STMainFrame methodsFor: 'accessing' stamp: 'JB 5/29/2007 11:05'!
editPlayTask
        ^ editPlayTask! !

!STMainFrame methodsFor: 'accessing' stamp: 'JB 5/29/2007 11:05'!
editPlayTask: anObject
        editPlayTask := anObject! !

!STMainFrame methodsFor: 'accessing' stamp: 'JB 5/11/2007 18:09'!
showReportTask
        ^ showReportTask! !

!STMainFrame methodsFor: 'accessing' stamp: 'JB 5/11/2007 18:09'!
showReportTask: anObject
        showReportTask := anObject! !

!STMainFrame methodsFor: 'accessing' stamp: 'JB 5/11/2007 15:49'!
showTicketTask
        ^ showTicketTask! !

!STMainFrame methodsFor: 'accessing' stamp: 'JB 5/11/2007 15:49'!
showTicketTask: anObject
        showTicketTask := anObject! !


!STMainFrame methodsFor: 'initialization' stamp: 'JB 5/11/2007 11:03'!
buyTicket

        self buyTicketTask: (STBuyTicketTask new).
        self currentTask: self buyTicketTask.
        ! !

!STMainFrame methodsFor: 'initialization' stamp: 'JB 5/11/2007 11:04'!
changeTicket

        self changeTicketTask: (STExchangeTicketTask new).
        self currentTask: self changeTicketTask.
        ! !

!STMainFrame methodsFor: 'initialization' stamp: 'JB 5/29/2007 11:25'!
editPlay

        self editPlayTask: (STEditPlay withPlay: STTheater default plays someElement).
        self currentTask: self editPlayTask.
        ! !

!STMainFrame methodsFor: 'initialization' stamp: 'JB 5/29/2007 11:22'!
initialize
        super initialize.
        self buyTicket.
        self changeTicket.
        self showTicket.
        self showReport.
        self editPlay.
        currentTask := self buyTicketTask.
        self session registerObjectForBacktracking: buyTicketTask.
        self session registerObjectForBacktracking: changeTicketTask.
        self session registerObjectForBacktracking: showTicketTask.
        self session registerObjectForBacktracking: showReportTask.
        self session registerObjectForBacktracking: editPlayTask.! !

!STMainFrame methodsFor: 'initialization' stamp: 'JB 5/29/2007 11:34'!
showReport

        self showReportTask: (STShowReport new).
        self currentTask: self showReportTask.
        ! !

!STMainFrame methodsFor: 'initialization' stamp: 'JB 5/11/2007 15:49'!
showTicket

        self showTicketTask: (STShowTicketTask new).
        self currentTask: self showTicketTask.
        ! !


!STMainFrame methodsFor: 'private api' stamp: 'JB 5/11/2007 10:49'!
currentTask: aNewTaskToRun

        currentTask ifNotNil: [ currentTask := aNewTaskToRun. ].! !

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

STMainFrame class
        instanceVariableNames: ''!

!STMainFrame class methodsFor: 'testing' stamp: 'JB 5/8/2007 23:54'!
canBeRoot

        ^ true! !


!STMainFrame class methodsFor: 'as yet unclassified' stamp: 'JB 6/11/2007 11:56'!
initialize

        self registerAsApplication: 'Theater'.! !


WAComponent subclass: #STPlayChooser
        instanceVariableNames: 'plays criteria'
        classVariableNames: ''
        poolDictionaries: ''
        category: 'Tutorial-Theater-View'!

!STPlayChooser methodsFor: 'initialization' stamp: 'JB 5/1/2007 01:55'!
initialize
        self plays: STTheater default plays asOrderedCollection.
        criteria := nil.! !


!STPlayChooser methodsFor: 'rendering' stamp: 'JB 5/1/2007 02:02'!
renderContentOn: html

        html div class: 'sort';
                with: [
                        html anchor callback: [self sortBy: #title.];
                                with: 'Title'.
                        html space.
                        html anchor callback: [self sortBy: #kind.];
                                with: 'Kind'.
                        html space.
                        html anchor callback: [self sortBy: #author.];
                                with: 'Author'.
                ].
       
        html break.
       
        self plays do: [ :play |
                html div class: 'play';
                        with: [
                                html div class: 'head';
                                        with: [
                                                html anchor callback: [self answer: play.];
                                                        with: play title.
                                                html space.
                                                html text:'(', play kind , ') - ', play author.
                                        ].
                                html div class: 'body';
                                        with: [
                                                html text: play description.
                                        ].
                        ].
                html break.
                ].! !

!STPlayChooser methodsFor: 'rendering' stamp: 'JB 5/10/2007 00:14'!
style ^ 'div.sort {
  background-color: #eeeeee;
  clear:both;
  float:left;
  padding:10px;
  width:622px;
}

div.play {
  clear:both;
  float:left;
  margin-top: 10px;
  width:642px;
}

div.play div {
  float:left;
}

div.play div.head {
  font-size: 16pt;
}

div.play div.body {
  margin-left: 10px;
  width: 490px;
}'! !


!STPlayChooser methodsFor: 'accessing' stamp: 'JB 5/1/2007 00:22'!
plays
        ^ plays! !

!STPlayChooser methodsFor: 'accessing' stamp: 'JB 5/1/2007 00:22'!
plays: anArrayOfPlays
        plays := anArrayOfPlays.! !


!STPlayChooser methodsFor: 'sorting' stamp: 'JB 5/1/2007 02:01'!
sortBy: aSymbol
        Transcript
                cr;
                show: 'was here ... ' , aSymbol.
        criteria = aSymbol
                ifTrue:
                        [self plays: plays reversed.
                        criteria := aSymbol]
                ifFalse:
                        [| temp |
                        temp := SortedCollection
                                                sortBlock: [:play1 :play2 | (play1 perform: aSymbol) <= (play2 perform: aSymbol)].
                        temp addAll: self plays.
                        temp reSort.
                        self plays: temp asOrderedCollection.
                        criteria := aSymbol]! !


WAComponent subclass: #STShowChooser
        instanceVariableNames: 'shows selected dateStart dateEnd listDate'
        classVariableNames: ''
        poolDictionaries: ''
        category: 'Tutorial-Theater-View'!

!STShowChooser methodsFor: 'accessing' stamp: 'JB 5/2/2007 00:29'!
dateEnd
        ^ dateEnd! !

!STShowChooser methodsFor: 'accessing' stamp: 'JB 5/4/2007 11:21'!
dateEnd: aDate
        dateEnd := aDate! !

!STShowChooser methodsFor: 'accessing' stamp: 'JB 5/2/2007 00:29'!
dateStart
        ^ dateStart! !

!STShowChooser methodsFor: 'accessing' stamp: 'JB 5/4/2007 11:20'!
dateStart: aDate
        dateStart := aDate! !

!STShowChooser methodsFor: 'accessing' stamp: 'JB 5/4/2007 11:18'!
listDate
        ^ listDate! !

!STShowChooser methodsFor: 'accessing' stamp: 'JB 5/4/2007 11:21'!
listDate: aSortedCollection
        listDate := aSortedCollection! !

!STShowChooser methodsFor: 'accessing' stamp: 'JB 5/1/2007 23:08'!
selected
        ^ selected! !

!STShowChooser methodsFor: 'accessing' stamp: 'JB 5/1/2007 23:09'!
selected: aShow
        selected := aShow! !

!STShowChooser methodsFor: 'accessing' stamp: 'JB 5/1/2007 23:08'!
shows
        ^ shows! !

!STShowChooser methodsFor: 'accessing' stamp: 'JB 5/1/2007 23:09'!
shows: anArrayOfShows
        shows := anArrayOfShows! !


!STShowChooser methodsFor: 'initialization' stamp: 'JB 5/2/2007 01:32'!
initialize

        self shows: nil.
        self selected: nil.
        self dateEnd: nil.
        self dateStart: nil.! !


!STShowChooser methodsFor: 'rendering' stamp: 'JB 5/8/2007 00:38'!
renderContentOn: html

        | |

        html div class: 'show'; with: [
               
        html div class: 'filter'; with: [
                self renderFilterOn: html.
        ].

        html break.
       
        (html div)
          class: 'body'; with: [
                (html form)
                        with: [
                                (html div)
                                        id: 'liste';
                                        with: [ self renderHorairesOn: html. ].
                               
                                html break.
               
                                (html submitButton)
                                        callback: [self selected: ([(self shows select: [ :show |
                                                                (show date >= TimeStamp now asDate)
                                                                and: [self dateStart ifNotNil: [show date >= self dateStart]]
                                                                and: [self dateEnd ifNotNil: [show date <= self dateEnd]].]
                                                                                ) first] on: Error do: [:err | nil. ]). ];
                                        text: 'Next'.
               
                                html space.
               
                                (html submitButton)
                                                callback: [self selected ifNotNil: [self answer: self selected].];
                                                text: 'Ok'.
                        ]. "Fin Formulaire"
        ]. "Fin div.body"

        ]. "Fin div.show"! !

!STShowChooser methodsFor: 'rendering' stamp: 'JB 5/6/2007 02:40'!
renderFilterOn: html

        html form
                 id: 'horaires';
                 with: [
                        html text: 'Filter from: '.
                        html select
                                list: self listDate;
                                selected: self dateStart;
                                labels: [ :value | value printString.];
                                callback: [ :value | self dateStart: value.];
                                onChange: (html updater
                                                                id: 'liste';
                                                                triggerForm: 'horaires';
                                                                callback: [:render | self renderHorairesOn: render]
                                                        ).
                        html space.
                        html text: 'to: '.
                        (html select)
                                list: self listDate;
                                labels: [ :value | value printString.];
                                selected: self dateEnd;
                                callback: [ :value | self dateEnd: value.];
                                onChange: (html updater
                                        id: 'liste';
                                        triggerForm: 'horaires';
                                        callback: [ :r | self renderHorairesOn: r]).
                        "html space.
                        html submitButton
                                callback: [self inform: 'date début: ', self dateStart printString, ' et date fin: ', self dateEnd printString.];
                                text:  'Update'."
                ].! !

!STShowChooser methodsFor: 'rendering' stamp: 'JB 5/6/2007 02:27'!
renderHorairesOn: html

        html select
                "class: 'liste';"
                list: (self shows select: [ :show |
                                                                        (self dateStart ifNotNil: [show date >= self dateStart])
                                                                        and: [self dateEnd ifNotNil: [show date <= self dateEnd]]
                                                                ]
                        );
                callback: [ :value | self selected: value.];
                labels: [ :show | show play title, ' - ', show date printString, ' ', show time printString. ];
                selected: self selected;
                size: 10.
               
                ! !

!STShowChooser methodsFor: 'rendering' stamp: 'JB 5/2/2007 01:07'!
style ^ '.filter {
  background-color: #eeeeee;
  padding: 5px;
}

.show {
  margin-top: 10px;
}

.show .body {
  margin-left: 10px;
  width: 490px;
}

.show .body .liste {
  width: 400px;
}'! !

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

STShowChooser class
        instanceVariableNames: ''!

!STShowChooser class methodsFor: 'new instance' stamp: 'JB 5/8/2007 18:16'!
withShows: anArrayOfShows
        | sortedShows sortedDates |
        sortedDates := Set new.
        anArrayOfShows do: [:show | sortedDates add: show date].
        sortedDates := (SortedCollection new)
                                addAll: sortedDates;
                                yourself.
        sortedShows := (SortedCollection
                                sortBlock: [:show1 :show2 | show1 date <= show2 date])
                                addAll: anArrayOfShows;
                                reSort;
                                yourself.
        ^ (self new)
                shows: sortedShows;
                dateStart: sortedShows first date;
                dateEnd: sortedShows last date;
                listDate: sortedDates;
                yourself! !


WAComponent subclass: #STShowReport
        instanceVariableNames: 'rapport batchedList data'
        classVariableNames: ''
        poolDictionaries: ''
        category: 'Tutorial-Theater-View'!

!STShowReport methodsFor: 'processing' stamp: 'JB 5/12/2007 00:49'!
updateData
        "Il faut avoir une variable de stockage de la liste entière
        afin de pouvoir faire des tris dessus.
       
        Cependant la fonction de tri est déclenchée dans le rapport HTML.
       
        Il faut donc récupérer (pour une row donnée):
                -  la manière d'évaluer une donnée de la colonne (WATableReport::valueBlock sétté par selector:)
                -  la manière de tri cette colonne (WATableReport::sortBlock sétté par sortBlock:)
        Rq: Comme il n'y a pas d'accessor pour les deux précédentes variables, il faut ruser et
                utiliser Object>>instVarNamed: 'nom_de_la_variable'.
       
        Bien penser à inverser la liste si on re-clique sur la même colonne de tri.
       
        Une fois le tri fait globalement, il convient de n'afficher que les éléments demandés
        par l'utilisateur grâce au WABatchedList.
       
        On re-fournit les données triées au WABatchedList qui lui-même
        re-fournit ses données tronquées au rapport WAReportTable.
        "

        data := data sortBy: [:a :b |
                (rapport sortColumn instVarNamed: 'sortBlock')
                value: ((rapport sortColumn instVarNamed: 'valueBlock') value: a)
                value: ((rapport sortColumn instVarNamed: 'valueBlock') value: b)
                ].
        (rapport isReversed) ifTrue: [data := data reversed].
        batchedList items: data.
        rapport rows: batchedList batch.! !


!STShowReport methodsFor: 'accessing' stamp: 'JB 5/11/2007 23:05'!
children

        ^ Array
                with: rapport
                with: batchedList.! !


!STShowReport methodsFor: 'initialization' stamp: 'JB 5/29/2007 11:47'!
initialize
       
        | cols rows |
        cols := (OrderedCollection new)
                        add: ((WAReportColumn
                                        "selector: #play"
                                        renderBlock: [ :row :html |
                                                (html anchor)
                                                callback: [ | play |
                                                        play := self call: (STEditPlay withPlay: row play copy).
                                                        play ifNotNil: [
                                                                row play title: play title.
                                                                row play kind: play kind.
                                                                row play author: play author.
                                                                row play description: play description.
                                                        ].
                                                ];
                                                with: row play title.
                                        ]
                                        title: 'Play') formatBlock: [ :play | play title];
                                                                sortBlock: [ :a :b | a title < b title];
                                                                yourself);
                        add: (WAReportColumn
                                        renderBlock: [ :obj | obj play kind.]
                                        title: 'Kind');
                        add: ((WAReportColumn
                                        selector: #play
                                        title: 'Author') formatBlock: [ :play | (play author = 'n/a') ifTrue: ['-'] ifFalse: [play author]];
                                                                        sortBlock: [ :a :b | a author < b author];
                                                                        yourself);
                        add: ((WAReportColumn
                                        selector: #timestamp
                                        title: 'Timestamp') formatBlock: [ :obj | obj asDate printString, ' ', obj asTime printString. ];
                                                        "sortBlock: [:a :b | a timestamp < b timestamp];"
                                                        yourself);
                        add: (WAReportColumn
                                        selector: #placesFree
                                        title: 'Free');
                        add: (WAReportColumn
                                        selector: #placesSold
                                        title: 'Sold');
                        add: (WAReportColumn
                                        selector: #placesTotal
                                        title: 'Total');
                        yourself.
                       
                        rows := OrderedCollection new.
                        (STTheater default)
                                do: [ :play | rows addAll: play shows].
                        data := rows sortBy: [ :show1 :show2 | show1 timestamp < show2 timestamp ].
       
        batchedList := (WABatchedList new)
                                        items: data;
                                        batchSize: 10;
                                        yourself.
       
        rapport := WATableReport new
                                columns: cols;
                                rows: data;
                                rowPeriod: 1;
                                rowColors: #(lightblue lightyellow);
                                sortColumn: ((cols select: [ :column | column title = 'Timestamp']) at: 1);
                                yourself.
       
       



! !


!STShowReport methodsFor: 'rendering' stamp: 'JB 5/12/2007 01:19'!
renderContentOn: html

        "updateData a un rôle de contrôlleur et ne modifie pas les données du modèle.
        Il s'agit juste d'un tri conformément aux exigences de tri des deux composants réunis.
        "
        self updateData.

        (html div)
        class: 'rapport';
        with: [
                (html heading)
                        class: 'titre';
                        level1;
                        with: 'Liste des horaires'.
               
                html break.
               
                (html div)
                class: 'rapport';
                with: [
                        html render: rapport.
                        ].
               
                html break.
               
                (html div)
                class: 'navigation';
                with: [
                        html render: batchedList.
                        ].
               
                html break.
                ].! !

!STShowReport methodsFor: 'rendering' stamp: 'JB 5/12/2007 01:21'!
style ^ 'div.rapport .titre {
  text-align:center;
}

div.rapport div.rapport table {
  width:642px;
}

div.rapport div.navigation {
  text-align:center;
}'! !


WATask subclass: #STShowTicketTask
        instanceVariableNames: 'ticketID selectedTicket'
        classVariableNames: ''
        poolDictionaries: ''
        category: 'Tutorial-Theater-View'!

!STShowTicketTask methodsFor: 'running' stamp: 'JB 5/11/2007 15:46'!
go

        [self isTicketIDValid] whileFalse:
                        [ticketID ifNotNil:
                                        [self inform: 'Your ticket was not found !! Please check you ticket ID.'].
                        ticketID := self request: 'On your ticket, find the ID and enter it.'
                                                label: 'Next'].
       
        self call: (STTicketPrinter withTickets: (Array with: selectedTicket)).! !


!STShowTicketTask methodsFor: 'initialization' stamp: 'JB 5/11/2007 15:46'!
initialize

        ticketID := nil.
        selectedTicket := nil.! !


!STShowTicketTask methodsFor: 'validation' stamp: 'JB 5/11/2007 15:45'!
isTicketIDValid
        "Renvoie VRAI si le ticket est effectivement trouvé
                sinon FAUX"
       
        "TicketID Nil => FAUX"
        ticketID isNil ifTrue: [^ false].
        "TicketID non entier => FAUX"
        [ticketID := ticketID asInteger]
                on: Exception
                do: [^ false].
        "Existe-t'il un ticket correspondant à ce numéro ?
                Si OUI => VRAI
                Sinon => FAUX
        "
        STTheater default do: [ :play |
                play do: [ :show |
                        show do: [ :ticket |
                                (ticketID = ticket id) ifTrue: [selectedTicket := ticket.].
                                ].
                        ].
                ].
        selectedTicket isNil ifTrue: [ ^ false].
        ^ true.! !


WAComponent subclass: #STTicketChooser
        instanceVariableNames: 'requiredPlaces show tickets'
        classVariableNames: ''
        poolDictionaries: ''
        category: 'Tutorial-Theater-View'!

!STTicketChooser methodsFor: 'accessing' stamp: 'JB 5/7/2007 23:17'!
requiredPlaces
        ^ requiredPlaces! !

!STTicketChooser methodsFor: 'accessing' stamp: 'JB 5/7/2007 23:17'!
requiredPlaces: anObject
        requiredPlaces := anObject! !

!STTicketChooser methodsFor: 'accessing' stamp: 'JB 5/8/2007 11:34'!
setShow: anObject
        show := anObject! !

!STTicketChooser methodsFor: 'accessing' stamp: 'JB 5/8/2007 11:36'!
show
        ^ show! !

!STTicketChooser methodsFor: 'accessing' stamp: 'JB 5/7/2007 23:06'!
tickets
        ^ tickets! !

!STTicketChooser methodsFor: 'accessing' stamp: 'JB 5/7/2007 23:06'!
tickets: anObject
        tickets := anObject! !


!STTicketChooser methodsFor: 'initialization' stamp: 'JB 5/8/2007 11:34'!
initialize
        self tickets: nil.
        self setShow: nil.
        self requiredPlaces: -1! !


!STTicketChooser methodsFor: 'rendering' stamp: 'JB 5/8/2007 19:29'!
renderContentOn: html
        "self tickets do: [:each | html text: (each id)]."
        (html div)
                class: 'ticket';
                with: [
                        (html form)
                                with: [
                                (html table)
                                        with: [
                                                (html tableRow)
                                                        with: [
                                                                (html tableData)
                                                                        with: 'Places Left'.
                                                                (html tableData)
                                                                        with: (self show placesFree).
                                                                ].
                                                (html tableRow)
                                                        with: [
                                                                (html tableData)
                                                                        with: 'Required Places'.
                                                                (html tableData)
                                                                        with: [
                                                                                (html textInput)
                                                                                        value: '1';
                                                                                        callback: [ :value |
                                                                                                 | nbPlaces |
                                                                                                ((nbPlaces := self isRequiredPlacesValid: value) > 0)
                                                                                                        ifTrue: [
                                                                                                                self requiredPlaces: nbPlaces.
                                                                                                        ] ifFalse: [
                                                                                                                self inform: 'You need to choose a value between 1 and ', self show placesFree printString.
                                                                                                        ].
                                                                                               
                                                                                        ].
                                                                        ].
                                                        ].
                                        ].
                                (html submitButton)
                                        callback: [(self requiredPlaces > 0)
                                                                ifTrue: [
                                                                        self answer: (self show nextTickets: self requiredPlaces).
                                                                        ].
                                                        ];
                                        text: 'Ok'.
                                (html submitButton)
                                        callback: [self answer: nil.];
                                        text: 'Cancel'.
                                ].
                        ].
                                                ! !

!STTicketChooser methodsFor: 'rendering' stamp: 'JB 5/8/2007 11:50'!
style ^ 'div.ticket table {
  font-weight:bold;
}'! !


!STTicketChooser methodsFor: 'validation' stamp: 'JB 5/8/2007 19:25'!
isRequiredPlacesValid: aValue

        "aValue représente la valeur donnée par l'utilisateur.
        Tente de convertir en valeur entière puis teste les valeurs admises."

        | nbPlaces |
        nbPlaces := aValue asInteger.
        nbPlaces
                ifNil: [
                        ^ -1.
                ] ifNotNil: [
                        (nbPlaces > 0 and: [nbPlaces <= self show placesFree ])
                                ifTrue: [
                                        ^ nbPlaces.
                                ] ifFalse: [
                                        ^ -1.
                                ].
                ].
       
"self inform: 'You need to enter an integer !!'.
self inform: 'You need to choose a value between 1 and '
        , self show placesFree printString.
"! !

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

STTicketChooser class
        instanceVariableNames: ''!

!STTicketChooser class methodsFor: 'new instance' stamp: 'JB 5/8/2007 11:34'!
withShow: aShow
        ^ (self new)
                initialize;
                setShow: aShow;
                yourself! !


WAComponent subclass: #STTicketExchanger
        instanceVariableNames: 'printedTicket'
        classVariableNames: ''
        poolDictionaries: ''
        category: 'Tutorial-Theater-View'!

!STTicketExchanger methodsFor: 'accessing' stamp: 'JB 5/11/2007 15:22'!
children
        ^ Array with: printedTicket.! !

!STTicketExchanger methodsFor: 'accessing' stamp: 'JB 5/11/2007 15:24'!
printedTicket
        ^ printedTicket! !

!STTicketExchanger methodsFor: 'accessing' stamp: 'JB 5/11/2007 15:24'!
printedTicket: anObject
        printedTicket := anObject! !


!STTicketExchanger methodsFor: 'rendering' stamp: 'JB 5/11/2007 15:38'!
renderContentOn: html
        (html div)
                class: 'ticket-echange';
                with:
                                [(html heading)
                                        level1;
                                        with: 'Confirm your exchange order'.
                                html break.
                                html span with: 'This ticket will be the new one ?'.
                                html render: printedTicket.
                                html form with:
                                                [(html submitButton)
                                                        value: 'Yes, Change it !!';
                                                        callback: [self answer: true].
                                                (html submitButton)
                                                        value: 'Cancel';
                                                        callback: [self answer: false]]]! !


!STTicketExchanger methodsFor: 'initialization' stamp: 'JB 5/11/2007 15:22'!
initialize
       
        printedTicket := nil.! !

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

STTicketExchanger class
        instanceVariableNames: ''!

!STTicketExchanger class methodsFor: 'new instance' stamp: 'JB 5/11/2007 15:36'!
withTicket: aTicket
        ^ (self new)
                initialize;
                printedTicket: (STTicketPrinter withTickets: (Array with: aTicket));
                yourself! !


WAComponent subclass: #STTicketPrinter
        instanceVariableNames: 'tickets'
        classVariableNames: ''
        poolDictionaries: ''
        category: 'Tutorial-Theater-View'!

!STTicketPrinter methodsFor: 'initialization' stamp: 'JB 5/8/2007 12:03'!
initialize

        self tickets: nil.! !


!STTicketPrinter methodsFor: 'accessing' stamp: 'JB 5/8/2007 12:05'!
tickets
        "Return the collection of STTicket."
        ^ tickets! !

!STTicketPrinter methodsFor: 'accessing' stamp: 'JB 5/8/2007 12:04'!
tickets: aCollectionOfTicket
        tickets := aCollectionOfTicket! !


!STTicketPrinter methodsFor: 'rendering' stamp: 'JB 5/8/2007 14:17'!
formatNumberOfTicket: iRank

        (self tickets size <= 1)
        ifTrue: [
                ^ ''.
        ] ifFalse: [
                ^ '(', iRank printString, '/', self tickets size printString, ')'.
                ].

! !

!STTicketPrinter methodsFor: 'rendering' stamp: 'JB 5/8/2007 14:26'!
renderContentOn: html
        | iRank |
       
        (html div)
        class: 'tickets';
        with: [
       
                html heading: 'The ticket(s), you ordered' level: 1.
               
                html break.
               
                iRank := 0.
                tickets do: [:each |
                        iRank := iRank + 1.
                        self renderOneTicketReceipt: each order: iRank on: html.
                        ].
        ].

        "(html div)
        with: [ | plays |
                plays := (tickets collect: [:each | each show play]) asSet.
                plays do: [:play | html text: play title. html break.].
        ]."! !

!STTicketPrinter methodsFor: 'rendering' stamp: 'JB 5/8/2007 14:17'!
renderOneTicketReceipt: aTicket order: aRankInteger on: html

        (html div)
        class: 'ticket-receipt';
        with: [
                (html span)
                class: 'theater-name';
                with: (aTicket show play theater name).
               
                "html break."
               
                (html span)
                class: 'play-name';
                with: (aTicket show play title), ' ', (self formatNumberOfTicket: aRankInteger).
               
                "html break."
               
                (html span)
                class: 'show-date';
                with: (aTicket show date).
               
                "html break."
               
                (html span)
                class: 'show-time';
                with: (aTicket show time).
               
                "html break."
               
                (html span)
                class: 'ticket-no';
                with: 'Ticket: ', aTicket id printString.
                ].! !

!STTicketPrinter methodsFor: 'rendering' stamp: 'JB 5/8/2007 14:18'!
style ^ 'div.tickets {
  clear:both;
  float:left;
}

div.tickets h1 {
  clear:both;
  float:left;
  text-align:center;
  width:400px;
}

div.tickets div.ticket-receipt {
  border:2px solid SlateGray;
  clear:both;
  float: left;
  margin-bottom:15px;
  padding:10px;
  width:400px;
}

div.tickets div.ticket-receipt span {
  clear: left;
  float: left;
}

div.tickets div.ticket-receipt span.theater-name {
  font-size:18px;
  text-transform:capitalize;
}

div.tickets div.ticket-receipt span.play-name {
  font-size:30px;
  margin-bottom:20px;
}

div.tickets div.ticket-receipt span.ticket-no {
  margin-top:10px;
}'! !

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

STTicketPrinter class
        instanceVariableNames: ''!

!STTicketPrinter class methodsFor: 'new instance' stamp: 'JB 5/8/2007 13:58'!
withTickets: aCollectionOfTicket

        ^ (self new)
                initialize;
                tickets: (aCollectionOfTicket asSortedCollection: [ :a :b | a id < b id]);
                yourself.! !

STMainFrame initialize!
_______________________________________________
Seaside mailing list
[hidden email]
http://lists.squeakfoundation.org/cgi-bin/mailman/listinfo/seaside
Reply | Threaded
Open this post in threaded view
|

Re: Component with multiples decorations

Julien Berthaud
Sorry I have forgotten this part.
> I have file-out the model just in case but I think you already have it.

Julien



Object subclass: #STModel
        instanceVariableNames: ''
        classVariableNames: ''
        poolDictionaries: ''
        category: 'Tutorial-Theater-Model'!

!STModel methodsFor: 'enumerating' stamp: 'lr 3/29/2006 17:35'!
do: aBlock
        self subclassResponsibility! !


!STModel methodsFor: 'initialization' stamp: 'lr 2/12/2007 15:09'!
initialize! !


!STModel methodsFor: 'accessing-readonly' stamp: 'lr 3/29/2006 19:45'!
plays
        ^ Array streamContents: [ :stream |
                self do: [ :each | stream nextPutAll: each plays ] ]! !

!STModel methodsFor: 'accessing-readonly' stamp: 'lr 3/29/2006 19:45'!
shows
        ^ Array streamContents: [ :stream |
                self do: [ :each | stream nextPutAll: each shows ] ]! !

!STModel methodsFor: 'accessing-readonly' stamp: 'lr 3/29/2006 19:45'!
tickets
        ^ Array streamContents: [ :stream |
                self do: [ :each | stream nextPutAll: each tickets ] ]! !

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

STModel class
        instanceVariableNames: ''!

!STModel class methodsFor: 'instance-creation' stamp: 'lr 2/12/2007 15:09'!
new
        ^ self basicNew initialize! !


STModel subclass: #STPlay
        instanceVariableNames: 'title author kind description shows theater'
        classVariableNames: ''
        poolDictionaries: ''
        category: 'Tutorial-Theater-Model'!

!STPlay methodsFor: 'conveniance' stamp: 'lr 3/29/2006 19:48'!
addShow: aShow
        aShow setPlay: self.
        self shows add: aShow.
        ^ aShow! !


!STPlay methodsFor: 'accessing' stamp: 'lr 3/29/2006 19:45'!
author
        ^ author! !

!STPlay methodsFor: 'accessing' stamp: ' 25/2/05 18:54'!
author: aString
        author := aString! !

!STPlay methodsFor: 'accessing' stamp: 'lr 3/29/2006 19:45'!
description
        ^ description! !

!STPlay methodsFor: 'accessing' stamp: ' 25/2/05 18:54'!
description: aString
        description := aString! !

!STPlay methodsFor: 'accessing' stamp: 'lr 3/29/2006 19:46'!
kind
        ^ kind! !

!STPlay methodsFor: 'accessing' stamp: ' 25/2/05 18:54'!
kind: aString
        kind := aString! !

!STPlay methodsFor: 'accessing' stamp: 'lr 3/29/2006 19:46'!
title
        ^ title! !

!STPlay methodsFor: 'accessing' stamp: ' 25/2/05 18:54'!
title: aString
        title := aString! !


!STPlay methodsFor: 'enumerating' stamp: 'lr 3/29/2006 17:36'!
do: aBlock
        self shows do: aBlock! !


!STPlay methodsFor: 'initialization' stamp: 'lr 3/29/2006 17:36'!
initialize
        super initialize.
        self setShows: Set new! !


!STPlay methodsFor: 'printing' stamp: 'lr 3/29/2006 17:36'!
printOn: aStream
        super printOn: aStream.
        aStream nextPutAll: ' title: '; print: self title! !


!STPlay methodsFor: 'private' stamp: ' 25/2/05 18:54'!
setShows: aCollection
        shows := aCollection! !

!STPlay methodsFor: 'private' stamp: ' 25/2/05 18:54'!
setTheater: aTheater
        theater := aTheater! !


!STPlay methodsFor: 'accessing-readonly' stamp: 'lr 3/29/2006 19:47'!
shows
        ^ shows! !

!STPlay methodsFor: 'accessing-readonly' stamp: 'lr 3/29/2006 19:47'!
theater
        ^ theater! !


STModel subclass: #STShow
        instanceVariableNames: 'play timestamp tickets'
        classVariableNames: ''
        poolDictionaries: ''
        category: 'Tutorial-Theater-Model'!

!STShow methodsFor: 'conveniance' stamp: 'lr 3/29/2006 19:48'!
addTicket: aTicket
        self placesFree isZero
                ifTrue: [ self error: 'No more tickets available for this show.' ].
        aTicket setShow: self.
        self tickets add: aTicket.
        ^ aTicket! !

!STShow methodsFor: 'conveniance' stamp: 'lr 3/29/2006 19:48'!
nextTicket
        ^ self addTicket: STTicket new! !

!STShow methodsFor: 'conveniance' stamp: 'lr 3/29/2006 20:38'!
nextTickets: aNumber
        ^ (1 to: aNumber) collect: [ :each | self addTicket: STTicket new ]! !


!STShow methodsFor: 'accessing-readonly' stamp: 'lr 2/12/2007 15:10'!
date
        ^ self timestamp asDate! !

!STShow methodsFor: 'accessing-readonly' stamp: 'lr 2/12/2007 15:10'!
placesFree
        ^ self placesTotal - self placesSold! !

!STShow methodsFor: 'accessing-readonly' stamp: 'lr 2/12/2007 15:10'!
placesSold
        ^ self tickets size! !

!STShow methodsFor: 'accessing-readonly' stamp: 'lr 2/12/2007 15:10'!
placesTotal
        ^ 100! !

!STShow methodsFor: 'accessing-readonly' stamp: 'lr 2/12/2007 15:10'!
play
        ^ play! !

!STShow methodsFor: 'accessing-readonly' stamp: 'lr 2/12/2007 15:10'!
tickets
        ^ tickets! !

!STShow methodsFor: 'accessing-readonly' stamp: 'lr 2/12/2007 15:10'!
time
        ^ self timestamp asTime! !


!STShow methodsFor: 'enumerating' stamp: 'lr 3/29/2006 17:36'!
do: aBlock
        self tickets do: aBlock! !


!STShow methodsFor: 'initialization' stamp: 'lr 3/29/2006 17:36'!
initialize
        super initialize.
        self setTickets: Set new! !


!STShow methodsFor: 'printing' stamp: 'lr 3/29/2006 17:36'!
printOn: aStream
        super printOn: aStream.
        aStream nextPutAll: ' timestamp: '; print: self timestamp! !


!STShow methodsFor: 'private' stamp: ' 25/2/05 18:54'!
setPlay: aPlay
        play := aPlay! !

!STShow methodsFor: 'private' stamp: ' 25/2/05 18:54'!
setTickets: aCollection
        tickets := aCollection! !


!STShow methodsFor: 'accessing' stamp: ' 25/2/05 18:54'!
timestamp
        ^timestamp! !

!STShow methodsFor: 'accessing' stamp: ' 25/2/05 18:54'!
timestamp: aTimestamp
        timestamp := aTimestamp! !


STModel subclass: #STTheater
        instanceVariableNames: 'name season plays'
        classVariableNames: 'Default'
        poolDictionaries: ''
        category: 'Tutorial-Theater-Model'!

!STTheater methodsFor: 'conveniance' stamp: 'lr 3/29/2006 19:49'!
addPlay: aPlay
        aPlay setTheater: self.
        self plays add: aPlay.
        ^ aPlay! !


!STTheater methodsFor: 'enumerating' stamp: 'lr 3/29/2006 17:36'!
do: aBlock
        self plays do: aBlock! !


!STTheater methodsFor: 'initialization' stamp: 'lr 3/29/2006 17:36'!
initialize
        super initialize.
        self setPlays: Set new! !


!STTheater methodsFor: 'accessing' stamp: 'lr 3/29/2006 19:49'!
name
        ^ name! !

!STTheater methodsFor: 'accessing' stamp: ' 25/2/05 18:54'!
name: aString
        name := aString! !

!STTheater methodsFor: 'accessing' stamp: 'lr 3/29/2006 19:49'!
season
        ^ season! !

!STTheater methodsFor: 'accessing' stamp: ' 25/2/05 18:54'!
season: aString
        season := aString! !


!STTheater methodsFor: 'accessing-readonly' stamp: 'lr 3/29/2006 19:49'!
plays
        ^ plays! !


!STTheater methodsFor: 'printing' stamp: 'lr 3/29/2006 17:36'!
printOn: aStream
        super printOn: aStream.
        aStream nextPutAll: ' name: '; print: self name! !


!STTheater methodsFor: 'private' stamp: ' 25/2/05 18:54'!
setPlays: aCollection
        plays := aCollection! !

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

STTheater class
        instanceVariableNames: ''!

!STTheater class methodsFor: 'accessing' stamp: 'lr 3/29/2006 19:50'!
default
        ^ Default! !


!STTheater class methodsFor: 'initialization' stamp: 'lr 5/15/2006 16:23'!
initialize
        STTicket resetId.
        Default := self new
                name: 'Bedlam Theatre';
                season: 'Summer 2006';
                addPlay: (STPlay new
                        title: 'The Improverts';
                        kind: 'Theatre';
                        author: 'n/a';
                        description: 'Fresh from another year of sell-out shows at the Edinburgh Fringe Festival, Edinburgh''s resident late-night comedy show returns for its legendary weekly Friday night spot. Now in its 16th year, our crack improv troupe perform a one hour show of comedy scenes and sketches based only on audience suggestions given to them during each performance. The show is completely different every night, keep coming back for more!!';
                        yourself);
                addPlay: (STPlay new
                        title: 'Improvisation';
                        kind: 'Workshop';
                        author: 'Improverts';
                        description: 'Open to everyone with or without improv experience, this workshop goes back to the fundamentals of creating scenes on the spot, creating characters and relationships, and having spontaneous fun on stage. A relaxed and informal workshop, and we all go to the pub for lunch afterwards. A great Friday night hangover cure.';
                        yourself);
                addPlay: (STPlay new
                        title: 'Ghost Train';
                        kind: 'Theatre';
                        author: 'Arnold Ridley';
                        description: 'Arnold Ridley''s "The Ghost Train" was written in seven days in 1925. Suprisingly it still has an old fashioned fascination for today''s audiences. What are the magic ingredients? Well, this was just after the first world war with spies still the number one worry. Take the spies and mix with a remote railway station late at night and all sorts of things can be imagined. There are lots of comings and goings and strange goings on to make the audience enjoy themselves, all things that you would expect of a play of this age and Arnold Ridley knew how to mix it all up to make the outcome just right.';
                        yourself);
                yourself.
        self default do: [ :play |
                10 + 20 atRandom timesRepeat: [ | show |
                        play addShow: (show := STShow new
                                timestamp: (TimeStamp now
                                        plusSeconds: (6 * 30 * 24 * 60 * 60) atRandom - (2 * 30 * 24 * 60 * 60));
                                yourself).
                        show timestamp: (DateAndTime
                                year: show timestamp year
                                month: show timestamp month
                                day: show timestamp dayOfMonth
                                hour: show timestamp hour
                                minute: 0).
                        (50 atRandom - 1) timesRepeat: [
                                show nextTicket ] ] ]! !


STModel subclass: #STTicket
        instanceVariableNames: 'show id'
        classVariableNames: 'TicketId'
        poolDictionaries: ''
        category: 'Tutorial-Theater-Model'!

!STTicket methodsFor: 'enumerating' stamp: 'lr 3/29/2006 17:36'!
do: aBlock
        self shouldNotImplement! !


!STTicket methodsFor: 'accessing-readonly' stamp: 'lr 3/29/2006 19:50'!
id
        ^ id! !

!STTicket methodsFor: 'accessing-readonly' stamp: 'JB 5/8/2007 11:36'!
show
        ^ show! !


!STTicket methodsFor: 'initialization' stamp: 'lr 3/29/2006 17:36'!
initialize
        super initialize.
        self setId: self class nextId! !


!STTicket methodsFor: 'printing' stamp: 'lr 3/29/2006 17:36'!
printOn: aStream
        super printOn: aStream.
        aStream nextPutAll: ' id: '; print: self id! !


!STTicket methodsFor: 'private' stamp: ' 25/2/05 18:54'!
setId: aNumber
        id := aNumber! !

!STTicket methodsFor: 'private' stamp: ' 25/2/05 18:54'!
setShow: aShow
        show := aShow! !

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

STTicket class
        instanceVariableNames: ''!

!STTicket class methodsFor: 'accessing' stamp: 'lr 3/29/2006 19:50'!
nextId
        ^ TicketId := TicketId + 1! !

!STTicket class methodsFor: 'accessing' stamp: 'lr 3/29/2006 17:36'!
resetId
        TicketId := 1000! !

STTheater initialize!
_______________________________________________
Seaside mailing list
[hidden email]
http://lists.squeakfoundation.org/cgi-bin/mailman/listinfo/seaside