A simple AJAX batcher for Aida

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

A simple AJAX batcher for Aida

Nicolas Petton
Hi,

I needed a batcher for my blog to display posts, so I decided to write a
component. It is based on WebGrid, and uses AJAX to batch.
It batches a collection a webElements, and the batch size can be
specified. It still needs some clean up, but it seems to work fine (on
Squeak, not tested on VW yet).

Usage example :
WebBatcher new batchsize: 10; batchedElements: --a collection of
WebElements--

Any feedback is appreciated.

Nicolas
--
Nicolas Petton
http://nico.bioskop.fr
             ___
           ooooooo
          OOOOOOOOO
         |Smalltalk|
          OOOOOOOOO
           ooooooo
            \   /
             [|]
--------------------------------
Ma cl? GPG est disponible ici :
http://pgp.mit.edu:11371/pks/lookup?op=get&search=0xE788C34D

-------------- section suivante --------------
'From Squeak3.10beta of 22 July 2007 [latest update: #7158] on 27 October 2007 at 12:37:53 am'!
WebElement subclass: #WebBatcher
        instanceVariableNames: 'batchsize batchedElements currentPage'
        classVariableNames: ''
        poolDictionaries: ''
        category: 'Snoop2-Components'!
!WebBatcher commentStamp: 'np 10/26/2007 22:42' prior: 0!
WebBatcher batchs a collection of webElements unsing AJAX.
Default batch size is set to 10.
Usage exemple:
WebBatcher new batchsize: 5; batchedElements: --a collection of WebElements--!
!WebBatcher methodsFor: 'accessing' stamp: 'np 10/26/2007 19:05'!
batchedElements
        ^batchedElements! !
!WebBatcher methodsFor: 'accessing' stamp: 'np 10/26/2007 19:06'!
batchedElements: aCollection
        batchedElements := aCollection! !
!WebBatcher methodsFor: 'accessing' stamp: 'np 10/27/2007 00:37'!
batchsize
        batchsize < 1 ifTrue: [self batchsize: 1]. "Do not allow batchsize < 1!!"
        ^batchsize! !
!WebBatcher methodsFor: 'accessing' stamp: 'np 10/26/2007 19:04'!
batchsize: aNumber
        batchsize := aNumber! !
!WebBatcher methodsFor: 'accessing' stamp: 'np 10/26/2007 19:15'!
currentPage
        ^currentPage! !
!WebBatcher methodsFor: 'accessing' stamp: 'np 10/26/2007 19:24'!
currentPage: anInteger
        currentPage := anInteger! !
!WebBatcher methodsFor: 'accessing' stamp: 'np 10/26/2007 19:15'!
numberOfPages
        ^(self batchedElements size / self batchsize asInteger) ceiling ! !
!WebBatcher methodsFor: 'as yet unclassified' stamp: 'np 10/27/2007 00:14'!
ajaxUpdateWith: aParmString
        aParmString notNil ifTrue: [
                self currentPage: aParmString asInteger; batch].
        ^self! !
!WebBatcher methodsFor: 'as yet unclassified' stamp: 'np 10/26/2007 22:35'!
batch
        self initElements.
        self buildBatchedElements.! !
!WebBatcher methodsFor: 'as yet unclassified' stamp: 'np 10/26/2007 22:26'!
buildBatchedElements
        self buildPageNumber: self currentPage.
        self numberOfPages > 1 ifTrue: [self buildFooter]! !
!WebBatcher methodsFor: 'as yet unclassified' stamp: 'np 10/27/2007 00:36'!
buildFooter
        |pageNumber e|
        e := WebElement new class: #batcher.
        self currentPage = 1
                ifFalse: [e add: (self linkForFirstPage)]
                ifTrue:[e addText: '<<'].
        e addNbSp.
        pageNumber := 1.
        self numberOfPages timesRepeat: [
                pageNumber = self currentPage
                        ifFalse: [e add: (self linkForPage: pageNumber)]
                        ifTrue: [e addText: pageNumber printString].
                e addNbSp.
                pageNumber := pageNumber + 1].
        self currentPage = self numberOfPages
                ifFalse: [e add: (self linkForLastPage)]
                ifTrue:[e addText: '>>'].
        self add: e! !
!WebBatcher methodsFor: 'as yet unclassified' stamp: 'np 10/26/2007 22:25'!
buildPageNumber: anInteger
        | selectedElements |
        selectedElements := self batchedElements
                copyFrom: (self batchsize * self currentPage - self batchsize + 1 )
                to: ((self batchsize * self currentPage) min: self batchedElements size).
        selectedElements do: [:each | self add: each]! !
!WebBatcher methodsFor: 'as yet unclassified' stamp: 'np 10/27/2007 00:16'!
linkForFirstPage
        | dummyLink |
        dummyLink := WebLink text: '<<' linkTo: (Array with: self app observee with: '-').
        dummyLink onClickUpdate: self with: 1 printString.
        ^dummyLink! !
!WebBatcher methodsFor: 'as yet unclassified' stamp: 'np 10/27/2007 00:16'!
linkForLastPage
        | dummyLink |
        dummyLink := WebLink text: '>>' linkTo: (Array with: self app observee with: '-').
        dummyLink onClickUpdate: self with: self numberOfPages printString.
        ^dummyLink! !
!WebBatcher methodsFor: 'as yet unclassified' stamp: 'np 10/27/2007 00:16'!
linkForPage: aNumber
        | dummyLink |
        dummyLink := WebLink text: aNumber printString linkTo: (Array with: self app observee with: '-').
        dummyLink onClickUpdate: self with: aNumber printString.
        ^dummyLink! !
!WebBatcher methodsFor: 'initialize-release' stamp: 'np 10/26/2007 21:24'!
initialize
        super initialize.
        batchsize := 10.
        currentPage := 1.
        self method: #ajaxUpdateWith:! !
!WebBatcher methodsFor: 'printing' stamp: 'np 10/26/2007 22:48'!
prepareToHTMLPrintOn: aSession
        super prepareToHTMLPrintOn: aSession.
        self batch! !
!WebBatcher methodsFor: 'printing' stamp: 'np 10/27/2007 00:34'!
printHTMLPageOn: aStream forSession: aSession
        self prepareToHTMLPrintOn: aSession.
        aStream nextPutAll: self ident, '<div'. self printAttributesOn: aStream for: aSession.
        aStream nextPutAll: '>', self eol.
        elements notNil ifTrue: [elements do: [:element |
                element notNil ifTrue: [element printHTMLPageOn: aStream forSession: aSession] ] ].
        aStream nextPutAll: self ident, '</div>', self eol.! !
"-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "!
WebBatcher class
        instanceVariableNames: ''!
!WebBatcher class methodsFor: 'instance creation' stamp: 'np 10/26/2007 19:06'!
new
        ^super new initialize! !
-------------- section suivante --------------
Une pi?ce jointe non texte a ?t? nettoy?e...
Nom: non disponible
Type: application/pgp-signature
Taille: 189 octets
Desc: Ceci est une partie de message
        =?ISO-8859-1?Q?num=E9riquement?= =?ISO-8859-1?Q?_sign=E9e?=
Url: http://lists.aidaweb.si/pipermail/aida/attachments/20071027/e64263f6/attachment-0001.sig 

Reply | Threaded
Open this post in threaded view
|

A simple AJAX batcher for Aida

Nicolas Petton

Le samedi 27 octobre 2007 ? 00:44 +0200, nicolas petton a ?crit :

> Hi,
>
> I needed a batcher for my blog to display posts, so I decided to write a
> component. It is based on WebGrid, and uses AJAX to batch.
> It batches a collection a webElements, and the batch size can be
> specified. It still needs some clean up, but it seems to work fine (on
> Squeak, not tested on VW yet).
>
> Usage example :
> WebBatcher new batchsize: 10; batchedElements: --a collection of
> WebElements--
>
> Any feedback is appreciated.
There was a problem with urls and extra parameters (like "?param=foo").
I had to save the request, because links redirect to the wrong view (ie
without extra parameters).

I did not try but I think this issue affect WebGrid too.

regards,

Nicolas
>
> Nicolas
--
Nicolas Petton
http://nico.bioskop.fr
             ___
           ooooooo
          OOOOOOOOO
         |Smalltalk|
          OOOOOOOOO
           ooooooo
            \   /
             [|]
--------------------------------
Ma cl? GPG est disponible ici :
http://pgp.mit.edu:11371/pks/lookup?op=get&search=0xE788C34D

-------------- section suivante --------------
'From Squeak3.10beta of 22 July 2007 [latest update: #7158] on 27 October 2007 at 4:18:38 am'!
WebElement subclass: #WebBatcher
        instanceVariableNames: 'batchsize batchedElements currentPage request requestString'
        classVariableNames: ''
        poolDictionaries: ''
        category: 'Snoop2-Components'!
!WebBatcher commentStamp: 'np 10/26/2007 22:42' prior: 0!
WebBatcher batchs a collection of webElements unsing AJAX.
Default batch size is set to 10.
Usage exemple:
WebBatcher new batchsize: 5; batchedElements: --a collection of WebElements--!
!WebBatcher methodsFor: 'accessing' stamp: 'np 10/26/2007 19:05'!
batchedElements
        ^batchedElements! !
!WebBatcher methodsFor: 'accessing' stamp: 'np 10/26/2007 19:06'!
batchedElements: aCollection
        batchedElements := aCollection! !
!WebBatcher methodsFor: 'accessing' stamp: 'np 10/27/2007 00:37'!
batchsize
        batchsize < 1 ifTrue: [self batchsize: 1]. "Do not allow batchsize < 1!!"
        ^batchsize! !
!WebBatcher methodsFor: 'accessing' stamp: 'np 10/26/2007 19:04'!
batchsize: aNumber
        batchsize := aNumber! !
!WebBatcher methodsFor: 'accessing' stamp: 'np 10/26/2007 19:15'!
currentPage
        ^currentPage! !
!WebBatcher methodsFor: 'accessing' stamp: 'np 10/26/2007 19:24'!
currentPage: anInteger
        currentPage := anInteger! !
!WebBatcher methodsFor: 'accessing' stamp: 'np 10/26/2007 19:15'!
numberOfPages
        ^(self batchedElements size / self batchsize asInteger) ceiling ! !
!WebBatcher methodsFor: 'as yet unclassified' stamp: 'np 10/27/2007 00:14'!
ajaxUpdateWith: aParmString
        aParmString notNil ifTrue: [
                self currentPage: aParmString asInteger; batch].
        ^self! !
!WebBatcher methodsFor: 'as yet unclassified' stamp: 'np 10/26/2007 22:35'!
batch
        self initElements.
        self buildBatchedElements.! !
!WebBatcher methodsFor: 'as yet unclassified' stamp: 'np 10/26/2007 22:26'!
buildBatchedElements
        self buildPageNumber: self currentPage.
        self numberOfPages > 1 ifTrue: [self buildFooter]! !
!WebBatcher methodsFor: 'as yet unclassified' stamp: 'np 10/27/2007 00:36'!
buildFooter
        |pageNumber e|
        e := WebElement new class: #batcher.
        self currentPage = 1
                ifFalse: [e add: (self linkForFirstPage)]
                ifTrue:[e addText: '<<'].
        e addNbSp.
        pageNumber := 1.
        self numberOfPages timesRepeat: [
                pageNumber = self currentPage
                        ifFalse: [e add: (self linkForPage: pageNumber)]
                        ifTrue: [e addText: pageNumber printString].
                e addNbSp.
                pageNumber := pageNumber + 1].
        self currentPage = self numberOfPages
                ifFalse: [e add: (self linkForLastPage)]
                ifTrue:[e addText: '>>'].
        self add: e! !
!WebBatcher methodsFor: 'as yet unclassified' stamp: 'np 10/26/2007 22:25'!
buildPageNumber: anInteger
        | selectedElements |
        selectedElements := self batchedElements
                copyFrom: (self batchsize * self currentPage - self batchsize + 1 )
                to: ((self batchsize * self currentPage) min: self batchedElements size).
        selectedElements do: [:each | self add: each]! !
!WebBatcher methodsFor: 'as yet unclassified' stamp: 'np 10/27/2007 04:06'!
linkForFirstPage
        | dummyLink |
        self requestString isNil ifTrue: [requestString := self session lastRequest uri printString, '#-'].
        dummyLink := WebLink text: '<<' linkTo: self requestString.
        dummyLink onClickUpdate: self with: 1 printString.
        ^dummyLink! !
!WebBatcher methodsFor: 'as yet unclassified' stamp: 'np 10/27/2007 04:06'!
linkForLastPage
        | dummyLink |
        self requestString isNil ifTrue: [requestString := self session lastRequest uri printString, '#-'].
        dummyLink := WebLink text: '>>' linkTo: self requestString.
        dummyLink onClickUpdate: self with: self numberOfPages printString.
        ^dummyLink! !
!WebBatcher methodsFor: 'as yet unclassified' stamp: 'np 10/27/2007 04:06'!
linkForPage: aNumber
        | dummyLink |
        self requestString isNil ifTrue: [requestString := self session lastRequest uri printString, '#-'].
        dummyLink := WebLink text: aNumber printString linkTo: self requestString.
        dummyLink onClickUpdate: self with: aNumber printString.
        ^dummyLink! !
!WebBatcher methodsFor: 'as yet unclassified' stamp: 'np 10/27/2007 04:09'!
requestString
        ^requestString! !
!WebBatcher methodsFor: 'as yet unclassified' stamp: 'np 10/27/2007 04:03'!
requestString: aString
        requestString := aString! !
!WebBatcher methodsFor: 'initialize-release' stamp: 'np 10/26/2007 21:24'!
initialize
        super initialize.
        batchsize := 10.
        currentPage := 1.
        self method: #ajaxUpdateWith:! !
!WebBatcher methodsFor: 'printing' stamp: 'np 10/26/2007 22:48'!
prepareToHTMLPrintOn: aSession
        super prepareToHTMLPrintOn: aSession.
        self batch! !
!WebBatcher methodsFor: 'printing' stamp: 'np 10/27/2007 00:34'!
printHTMLPageOn: aStream forSession: aSession
        self prepareToHTMLPrintOn: aSession.
        aStream nextPutAll: self ident, '<div'. self printAttributesOn: aStream for: aSession.
        aStream nextPutAll: '>', self eol.
        elements notNil ifTrue: [elements do: [:element |
                element notNil ifTrue: [element printHTMLPageOn: aStream forSession: aSession] ] ].
        aStream nextPutAll: self ident, '</div>', self eol.! !
"-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "!
WebBatcher class
        instanceVariableNames: ''!
!WebBatcher class methodsFor: 'instance creation' stamp: 'np 10/26/2007 19:06'!
new
        ^super new initialize! !
-------------- section suivante --------------
Une pi?ce jointe non texte a ?t? nettoy?e...
Nom: non disponible
Type: application/pgp-signature
Taille: 189 octets
Desc: Ceci est une partie de message
        =?ISO-8859-1?Q?num=E9riquement?= =?ISO-8859-1?Q?_sign=E9e?=
Url: http://lists.aidaweb.si/pipermail/aida/attachments/20071027/9a36c3ab/attachment.sig 

Reply | Threaded
Open this post in threaded view
|

A simple AJAX batcher for Aida

Janko Mivšek
In reply to this post by Nicolas Petton
Nicolas,

Pardon my ignorance, but what is Ajax batcher?

Janko

nicolas petton a ?crit :

> I needed a batcher for my blog to display posts, so I decided to write a
> component. It is based on WebGrid, and uses AJAX to batch.
> It batches a collection a webElements, and the batch size can be
> specified. It still needs some clean up, but it seems to work fine (on
> Squeak, not tested on VW yet).
>
> Usage example :
> WebBatcher new batchsize: 10; batchedElements: --a collection of
> WebElements--
>
> Any feedback is appreciated.
>
> Nicolas

Reply | Threaded
Open this post in threaded view
|

A simple AJAX batcher for Aida

Nicolas Petton
Hi,

a batcher is a component wihich takes a list of elements, and creates pages
with them. For example, if you have 20 elements and if you want to display 5
elements per page, you'll have 4 pages, and a footer with links to pages :

"<< 1 2 3 4 >>"

In Seaside it's called a batched list. Maybe it's a better name ?

2007/10/28, Janko Miv?ek <janko.mivsek at eranova.si>:

>
> Nicolas,
>
> Pardon my ignorance, but what is Ajax batcher?
>
> Janko
>
> nicolas petton a ?crit :
> > I needed a batcher for my blog to display posts, so I decided to write a
> > component. It is based on WebGrid, and uses AJAX to batch.
> > It batches a collection a webElements, and the batch size can be
> > specified. It still needs some clean up, but it seems to work fine (on
> > Squeak, not tested on VW yet).
> >
> > Usage example :
> > WebBatcher new batchsize: 10; batchedElements: --a collection of
> > WebElements--
> >
> > Any feedback is appreciated.
> >
> > Nicolas
> _______________________________________________
> Aida mailing list
> Aida at aidaweb.si
> http://lists.aidaweb.si/mailman/listinfo/aida
>



--
Nicolas

http://bioskop.wordpress.com
-------------- section suivante --------------
Une pi?ce jointe HTML a ?t? nettoy?e...
URL: http://lists.aidaweb.si/pipermail/aida/attachments/20071028/c2689800/attachment.htm 

Reply | Threaded
Open this post in threaded view
|

A simple AJAX batcher for Aida

Janko Mivšek
nicolas petton a ?crit :
> a batcher is a component wihich takes a list of elements, and creates
> pages with them. For example, if you have 20 elements and if you want
> to display 5 elements per page, you'll have 4 pages, and a footer with
> links to pages :
>
> "<< 1 2 3 4 >>"
>
> In Seaside it's called a batched list. Maybe it's a better name ?

In Aida there is a WebGrid which supports such paging. Is this the same
as "batching"?

Janko

>
> 2007/10/28, Janko Miv?ek < janko.mivsek na eranova.si
> <mailto:janko.mivsek na eranova.si>>:
>
>     Nicolas,
>
>     Pardon my ignorance, but what is Ajax batcher?
>
>     Janko
>
>     nicolas petton a ?crit :
>     > I needed a batcher for my blog to display posts, so I decided to
>     write a
>     > component. It is based on WebGrid, and uses AJAX to batch.
>     > It batches a collection a webElements, and the batch size can be
>     > specified. It still needs some clean up, but it seems to work
>     fine (on
>     > Squeak, not tested on VW yet).
>     >
>     > Usage example :
>     > WebBatcher new batchsize: 10; batchedElements: --a collection of
>     > WebElements--
>     >
>     > Any feedback is appreciated.
>     >
>     > Nicolas
>
>


Reply | Threaded
Open this post in threaded view
|

A simple AJAX batcher for Aida

Nicolas Petton

Le dimanche 28 octobre 2007 ? 14:07 +0100, Janko Miv?ek a ?crit :

> nicolas petton a ?crit :
> > a batcher is a component wihich takes a list of elements, and creates
> > pages with them. For example, if you have 20 elements and if you want
> > to display 5 elements per page, you'll have 4 pages, and a footer with
> > links to pages :
> >
> > "<< 1 2 3 4 >>"
> >
> > In Seaside it's called a batched list. Maybe it's a better name ?
>
> In Aida there is a WebGrid which supports such paging. Is this the same
> as "batching"?
Yes, I think. Did you see my code? In fact it's close to WebGrid.
Can WebGrid work without table (display a collection of elements for
example, with paging) ?

Nicolas

>
> Janko
> >
> > 2007/10/28, Janko Miv?ek < janko.mivsek at eranova.si
> > <mailto:janko.mivsek at eranova.si>>:
> >
> >     Nicolas,
> >
> >     Pardon my ignorance, but what is Ajax batcher?
> >
> >     Janko
> >
> >     nicolas petton a ?crit :
> >     > I needed a batcher for my blog to display posts, so I decided to
> >     write a
> >     > component. It is based on WebGrid, and uses AJAX to batch.
> >     > It batches a collection a webElements, and the batch size can be
> >     > specified. It still needs some clean up, but it seems to work
> >     fine (on
> >     > Squeak, not tested on VW yet).
> >     >
> >     > Usage example :
> >     > WebBatcher new batchsize: 10; batchedElements: --a collection of
> >     > WebElements--
> >     >
> >     > Any feedback is appreciated.
> >     >
> >     > Nicolas
> >
> >
>
> _______________________________________________
> Aida mailing list
> Aida at aidaweb.si
> http://lists.aidaweb.si/mailman/listinfo/aida
--
Nicolas Petton
http://nico.bioskop.fr
             ___
           ooooooo
          OOOOOOOOO
         |Smalltalk|
          OOOOOOOOO
           ooooooo
            \   /
             [|]
--------------------------------
Ma cl? GPG est disponible ici :
http://pgp.mit.edu:11371/pks/lookup?op=get&search=0xE788C34D

-------------- section suivante --------------
Une pi?ce jointe non texte a ?t? nettoy?e...
Nom: non disponible
Type: application/pgp-signature
Taille: 189 octets
Desc: Ceci est une partie de message
        =?ISO-8859-1?Q?num=E9riquement?= =?ISO-8859-1?Q?_sign=E9e?=
Url: http://lists.aidaweb.si/pipermail/aida/attachments/20071028/852e7690/attachment.sig