ListView with thumbnails?

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

ListView with thumbnails?

Sebastián Sastre
Hi there,

  I need to present some thumbnails of N images in some presenter.
Anybody knows wich is the best way to do this ?

  Right now I see 2 ways:

  A) using the listview in a thumbnail mode wich I think is not
supported (maybe there is a goodie I don't know arround there?)

  B) using some *hand made* ThumbnailPresenters (wich has a inset
margin an image presenter and static text below) over a
ThumbnailsPresenter wich has a flow layout and can dinamically add or
remove it's ThumbnailPresenters (perhaps loosing the list's selection
capabilities).

  Any thought?

Sebastian


Reply | Threaded
Open this post in threaded view
|

Re: ListView with thumbnails?

Chris Uppal-3
Sebastián wrote:

>   A) using the listview in a thumbnail mode wich I think is not
> supported (maybe there is a goodie I don't know arround there?)

I think "thumbnail mode" is just one of the forms which displays the icon
associated with each list element (a ListView in #largeIcons or #tileIcons
mode).  You can probably use the custom draw stuff to paint your own images.  I
have never tried that myself.  You might find the implementation of John
Aspinal's EditableListView a helpful guide, since it draws its own images in
some configurations.

Alternatively, I would be very tempted to create a custom view which could
display thumbnails.  But then that's because I'm working with custom graphic
views a lot just now, and have all (or most of) the necessary framework already
written -- I'm not sure it would be such a good idea otherwise.

    -- chris


Reply | Threaded
Open this post in threaded view
|

Re: ListView with thumbnails?

Chris Uppal-3
In reply to this post by Sebastián Sastre
Sebastián,

>   I need to present some thumbnails of N images in some presenter.
> Anybody knows wich is the best way to do this ?

Or here's a start to a way of doing it by setting the "image lists" explicitly.
It doesn't work perfectly -- the selected thumbnail is not painted, but someone
may be able to suggest a fix for that.

    -- chris

"find some files to show thumbs of (doesn't have to be files of course)"
files := OrderedCollection new.
File for: '*.jpg' in: '<somewhere>' do: [:each | files add: each path].
files := (files first: 30) asArray.

"we use GDI+ to generate the thumbnails, that is't a requirement, it's just
easy for the example"
thumbs := files collect:
 [:each || image thumb |
 image := GdiplusImage fromFile: each.
 thumb := image thumbnailScaledBy: 1/10.
 image free.
 thumb].

"create a WinImageList to hold the thumbnails"
extent := 0@0.
thumbs do: [:each | extent := extent max: each extent].
wil := WinImageList newExtent: extent initialSize: thumbs size masked: false.

"add a bitmap to the WinImageList for each thumbnail"
thumbs do: [:thumb || bitmap canvas |
 bitmap := DIBSection width: extent x height: extent y.
 canvas := bitmap canvas.
 thumb drawOn: canvas at: (extent - thumb extent / 2) rounded.
 canvas free.
 wil addBitmap: bitmap.
 bitmap free.
 thumb free].
thumbs := nil.

"set up a ListView in largeIcons mode, arrange for the text and image blocks
to point to our files and images"
lp := ListPresenter show: 'Enhanced list view' on: (ListModel on: (1 to: files
size)).
lv := lp view.
lv viewMode: #largeIcons.
lv getTextBlock: [:i | files at: i].
lv getImageBlock: [:i | i]. "answer the 0-based image index in wil"

"now use private method to tell Windows to use our WinImageList
for the icons"
lv lvmSetImageList: wil type: 0 "LVSIL_NORMAL".


Reply | Threaded
Open this post in threaded view
|

Re: ListView with thumbnails?

Chris Uppal-3
I wrote:

> Or here's a start to a way of doing it by setting the "image lists"
> explicitly.  It doesn't work perfectly -- the selected thumbnail is
> not painted, but someone may be able to suggest a fix for that.

Following myself up, I remembered that there's an abstraction already
in place
for this -- ImageManagers.  It's a little fiddly since ImageManagers
"want" to
supply images given a target extent, rather than being told what extent
to use.
Nevertheless it's no worse than the previous version and uses only
public
methods.

Incidentally, setting a maskColour (as below) also seems to fix the
problem
with displaying the current selection.

    -- chris

"find some files to show thumbs of (doesn't have to be files of course)"
files := OrderedCollection new.
File for: '*.jpg' in: '<somewhere>' do: [:each | files add: each path].
files := files asArray.

"we use GDI+ to generate the thumbnails, that is't a requirement, it's
just easy for the example"
thumbs := files collect:
        [:each || image thumb |
        image := GdiplusImage fromFile: each.
        thumb := image thumbnailScaledBy: 1/10.
        image free.
        thumb].

"choose a fixed extent for the thumbnails"
extent := 0@0.
thumbs do: [:each | extent := extent max: each extent].

"convert to bitmaps"
thumbs := thumbs collect:
        [:each || bitmap canvas |
        bitmap := DIBSection width: extent x height: extent y.
        canvas := bitmap canvas.
        "canvas fillRectangle: (0@0 extent: extent) brush: Color default
brush. -- only needed with D5"
        each drawOn: canvas at: (extent - each extent / 2) rounded.
        canvas free.
        bitmap].

"add the lot to an ImageManager"
im := ImageManager new.
im maskcolor: Color default.
thumbs do: [:each | im addImage: each].
"only safe if we don't change the view mode of the list view since that
would  ask for images with a different extent:
thumbs do: [:each | each free]."
thumbs := nil.

"set up a ListView in largeIcons mode, arrange for the text and image
blocks
to point to our files and images, and tell it to use our new image
manager"
lp := ListPresenter show: 'Enhanced list view' on: (ListModel on: (1
to: files size)).
(lp view)
        getTextBlock: [:i | files at: i];
        getImageBlock: [:i | i];                  "answers the 0-based image
indexesl"
        viewMode: #largeIcons;             "must do this before setting
#largeIconExtent"
        largeIconExtent: extent;               "should do this before setting
#imageManager"
        imageManager: im;
        backcolor: Color red faded.       "just to demonstrate that the
transparency has worked"

"just for the hell of it..."
openIt := [ShellLibrary default shellOpen: (files at: lp selection)
directory: ''].
lp when: #actionPerformed send: #value to: openIt.


Reply | Threaded
Open this post in threaded view
|

Re: ListView with thumbnails?

Sebastián Sastre
Dear Chris,

   frankly I can't imagine a better answer to my post. Your code was
clear and simple. Totally awsome !

   When I finish some stuff arround here I think I'll make a presenter
which will use the list view like you do and then I'll post it in
response.

   Thank you for this,

Sebastian

Chris Uppal escreveu:

> I wrote:
>
> > Or here's a start to a way of doing it by setting the "image lists"
> > explicitly.  It doesn't work perfectly -- the selected thumbnail is
> > not painted, but someone may be able to suggest a fix for that.
>
> Following myself up, I remembered that there's an abstraction already
> in place
> for this -- ImageManagers.  It's a little fiddly since ImageManagers
> "want" to
> supply images given a target extent, rather than being told what extent
> to use.
> Nevertheless it's no worse than the previous version and uses only
> public
> methods.
>
> Incidentally, setting a maskColour (as below) also seems to fix the
> problem
> with displaying the current selection.
>
>     -- chris
>
> "find some files to show thumbs of (doesn't have to be files of course)"
> files := OrderedCollection new.
> File for: '*.jpg' in: '<somewhere>' do: [:each | files add: each path].
> files := files asArray.
>
> "we use GDI+ to generate the thumbnails, that is't a requirement, it's
> just easy for the example"
> thumbs := files collect:
> [:each || image thumb |
> image := GdiplusImage fromFile: each.
> thumb := image thumbnailScaledBy: 1/10.
> image free.
> thumb].
>
> "choose a fixed extent for the thumbnails"
> extent := 0@0.
> thumbs do: [:each | extent := extent max: each extent].
>
> "convert to bitmaps"
> thumbs := thumbs collect:
> [:each || bitmap canvas |
> bitmap := DIBSection width: extent x height: extent y.
> canvas := bitmap canvas.
> "canvas fillRectangle: (0@0 extent: extent) brush: Color default
> brush. -- only needed with D5"
> each drawOn: canvas at: (extent - each extent / 2) rounded.
> canvas free.
> bitmap].
>
> "add the lot to an ImageManager"
> im := ImageManager new.
> im maskcolor: Color default.
> thumbs do: [:each | im addImage: each].
> "only safe if we don't change the view mode of the list view since that
> would  ask for images with a different extent:
> thumbs do: [:each | each free]."
> thumbs := nil.
>
> "set up a ListView in largeIcons mode, arrange for the text and image
> blocks
> to point to our files and images, and tell it to use our new image
> manager"
> lp := ListPresenter show: 'Enhanced list view' on: (ListModel on: (1
> to: files size)).
> (lp view)
> getTextBlock: [:i | files at: i];
> getImageBlock: [:i | i];                  "answers the 0-based image
> indexesl"
> viewMode: #largeIcons;             "must do this before setting
> #largeIconExtent"
> largeIconExtent: extent;               "should do this before setting
> #imageManager"
> imageManager: im;
> backcolor: Color red faded.       "just to demonstrate that the
> transparency has worked"
>
> "just for the hell of it..."
> openIt := [ShellLibrary default shellOpen: (files at: lp selection)
> directory: ''].
> lp when: #actionPerformed send: #value to: openIt.


Reply | Threaded
Open this post in threaded view
|

Re: ListView with thumbnails?

Sebastián Sastre
Hi, below the line it is the package I've made:

----------------------------------------------------------------------------------------------------------------------
| package |
package := Package name: 'Thumbnails'.
package paxVersion: 1;
        basicComment: '2006.08.09 This package provides the
ThumbnailsPresenter wich can show thumbnails of the images provided to
it.

To do:
- Automatic rearrange when resized.
- Customizable image border of thumbnails (using #borderPen in
ThumbnailsView class)
- Instant draw of thumbnails with a default image.
- Update each thumbnail replacing the default image with the
(backgroud?) calculated thumbnail.'.


package classNames
        add: #ThumbnailModel;
        add: #ThumbnailsPresenter;
        add: #ThumbnailsView;
        yourself.

package methodNames
        add: #GdiplusBitmapFromBitmapInitializer -> #absoluteFilename;
        add: #GdiplusImage -> #thumbnailWithWidth:;
        yourself.

package binaryGlobalNames: (Set new
        yourself).

package globalAliases: (Set new
        yourself).

package setPrerequisites: (IdentitySet new
        add: '..\..\..\Object Arts\Dolphin\IDE\Base\Development System';
        add: '..\..\..\Object Arts\Dolphin\Base\Dolphin';
        add: '..\..\..\Object Arts\Dolphin\MVP\Views\Common Controls\Dolphin
Common Controls';
        add: '..\..\..\Object Arts\Dolphin\MVP\Models\List\Dolphin List
Models';
        add: '..\..\..\Object Arts\Dolphin\MVP\Presenters\List\Dolphin List
Presenter';
        add: '..\..\..\Object Arts\Dolphin\MVP\Base\Dolphin MVP Base';
        add: '..\..\..\Object Arts\Dolphin\MVP\Gdiplus\Gdiplus';
        yourself).

package!

"Class Definitions"!

Model subclass: #ThumbnailModel
        instanceVariableNames: 'filename thumbnail description height'
        classVariableNames: ''
        poolDictionaries: ''
        classInstanceVariableNames: ''!
ListPresenter subclass: #ThumbnailsPresenter
        instanceVariableNames: 'thumbnails filenames thumbnailHeight'
        classVariableNames: ''
        poolDictionaries: ''
        classInstanceVariableNames: ''!
ListView subclass: #ThumbnailsView
        instanceVariableNames: 'borderPen'
        classVariableNames: ''
        poolDictionaries: ''
        classInstanceVariableNames: ''!

"Global Aliases"!


"Loose Methods"!

!GdiplusBitmapFromBitmapInitializer methodsFor!

absoluteFilename

        ^ bitmap fileLocator localFileSpecFor: bitmap identifier! !
!GdiplusBitmapFromBitmapInitializer categoriesFor:
#absoluteFilename!enquiries!public! !

!GdiplusImage methodsFor!

thumbnailWithWidth: anInteger
        "Answer an Image based on the receiver that is sized proportionally,
with width equal to anInteger."

        ^self thumbnailWithExtent: anInteger @ (self height / self width *
anInteger) rounded ! !
!GdiplusImage categoriesFor:
#thumbnailWithWidth:!operations!public!thumbnails! !

"End of package definition"!

"Source Globals"!

"Classes"!

ThumbnailModel guid: (GUID fromString:
'{E876A48F-6DC4-4616-A7FF-93B5BE655C46}')!
ThumbnailModel comment: ''!
!ThumbnailModel categoriesForClass!MVP-Models! !
!ThumbnailModel methodsFor!

description
        description isNil ifTrue: [self initializeDescription].
        ^description!

description: anObject
        description := anObject!

displayOn: aStream

        aStream nextPutAll: self description!

extent

        ^ self height @ self height!

filename
        ^filename!

filename: anObject
        filename := anObject!

height
        ^height!

height: anObject
        height := anObject!

initializeDescription
        description := filename!

initializeThumbnail

        thumbnail := self makeThumbnail !

isPortrait

        ^ (GdiplusBitmap fromFile: filename) isPortrait!

makeLandscapeThumbnailFrom: aFilename

        | image thumb bitmap canvas |

        image := GdiplusBitmap fromFile: aFilename.
        thumb := image thumbnailWithWidth: height.
        image free.
        bitmap := DIBSection width: self extent x height: self extent y.
        canvas := bitmap canvas.
        thumb drawOn: canvas at: (self extent - thumb extent) rounded.
        canvas free.
        ^ bitmap!

makePortraitThumbnailFrom: aFilename

        | image thumb bitmap canvas |

        image := GdiplusBitmap fromFile: aFilename.
        thumb := image thumbnailWithHeight: height.
        image free.
        bitmap := DIBSection width: self extent x height: self extent y.
        canvas := bitmap canvas.
        thumb drawOn: canvas at: (self extent - thumb extent) rounded.
        canvas free.
        ^ bitmap!

makeThumbnail

        ^ self isPortrait
                ifTrue:[ self makePortraitThumbnailFrom: filename ]
                ifFalse:[ self makeLandscapeThumbnailFrom: filename ]!

thumbnail
        thumbnail isNil ifTrue:[self initializeThumbnail].
        ^thumbnail!

thumbnail: anObject
        thumbnail := anObject! !
!ThumbnailModel categoriesFor: #description!accessing!public! !
!ThumbnailModel categoriesFor: #description:!accessing!public! !
!ThumbnailModel categoriesFor: #displayOn:!public! !
!ThumbnailModel categoriesFor: #extent!public! !
!ThumbnailModel categoriesFor: #filename!accessing!public! !
!ThumbnailModel categoriesFor: #filename:!accessing!public! !
!ThumbnailModel categoriesFor: #height!accessing!public! !
!ThumbnailModel categoriesFor: #height:!accessing!public! !
!ThumbnailModel categoriesFor:
#initializeDescription!accessing!private! !
!ThumbnailModel categoriesFor: #initializeThumbnail!accessing!private!
!
!ThumbnailModel categoriesFor: #isPortrait!public! !
!ThumbnailModel categoriesFor:
#makeLandscapeThumbnailFrom:!accessing!private! !
!ThumbnailModel categoriesFor:
#makePortraitThumbnailFrom:!accessing!private! !
!ThumbnailModel categoriesFor: #makeThumbnail!accessing!private! !
!ThumbnailModel categoriesFor: #thumbnail!accessing!public! !
!ThumbnailModel categoriesFor: #thumbnail:!accessing!public! !

ThumbnailsPresenter guid: (GUID fromString:
'{062B71A8-1CC2-4A57-A889-4C2E26CB57A7}')!
ThumbnailsPresenter comment: 'This class can manage a list of graphic
resources (images) based on a collection of bitmaps (in it''s
listModel) and show the thumbnails of them.
'!
!ThumbnailsPresenter categoriesForClass!MVP-Presenters! !
!ThumbnailsPresenter methodsFor!

defaultThumbnailHeight

        ^ 100!

filenames
        ^filenames!

filenames: someFilenames

        filenames := someFilenames.
        self refreshThumbnails.!

getTextBlock: aBlock

        ^ self view getTextBlock: aBlock!

initializeThumbnailHeight
        thumbnailHeight := self defaultThumbnailHeight!

makeThumbnailsModel

        ^ ListModel on: (filenames collect:[:filename|
                ThumbnailModel new
                        filename: filename;
                        height: self thumbnailHeight;
                        yourself])!

refreshThumbnails

        | imageManager |

        thumbnails := self makeThumbnailsModel.
        self model: (ListModel on: (1 to: filenames size)).

        imageManager := ImageManager new
                                        maskcolor: Color default;
                                        yourself.

        thumbnails do:[:e| imageManager addImage: e thumbnail].

        self view
                getImageBlock: [:i | i];                  "answers the 0-based image
indexesl"
                viewMode: #largeIcons;
                largeIconExtent: self thumbnailExtent;               "should do this
before setting #imageManager"
                imageManager: imageManager;
                getTextBlock:[:i| filenames at:i];
                yourself.

!

thumbnailExtent

        ^ self thumbnailHeight @ self thumbnailHeight
!

thumbnailHeight
        thumbnailHeight isNil ifTrue:[self initializeThumbnailHeight].
        ^thumbnailHeight!

thumbnailHeight: anObject
        thumbnailHeight := anObject! !
!ThumbnailsPresenter categoriesFor:
#defaultThumbnailHeight!accessing!private! !
!ThumbnailsPresenter categoriesFor: #filenames!accessing!public! !
!ThumbnailsPresenter categoriesFor: #filenames:!public! !
!ThumbnailsPresenter categoriesFor: #getTextBlock:!public! !
!ThumbnailsPresenter categoriesFor:
#initializeThumbnailHeight!accessing!private! !
!ThumbnailsPresenter categoriesFor: #makeThumbnailsModel!private! !
!ThumbnailsPresenter categoriesFor: #refreshThumbnails!public! !
!ThumbnailsPresenter categoriesFor: #thumbnailExtent!accessing!public!
!
!ThumbnailsPresenter categoriesFor: #thumbnailHeight!accessing!public!
!
!ThumbnailsPresenter categoriesFor: #thumbnailHeight:!accessing!public!
!

!ThumbnailsPresenter class methodsFor!

resource_Default_view
        "Answer the literal data from which the 'Default view' resource can be
reconstituted.
        DO NOT EDIT OR RECATEGORIZE THIS METHOD.

        If you wish to modify this resource evaluate:
        ViewComposer openOn: (ResourceIdentifier class: self selector:
#resource_Default_view)
        "

        ^#(#'!!STL' 3 788558 10 ##(Smalltalk.STBViewProxy)  8
##(Smalltalk.ListView)  98 30 0 0 98 2 8 1409355852 1025 416 590662 2
##(Smalltalk.ListModel)  202 208 98 0 0 1114638
##(Smalltalk.STBSingletonProxy)  8 ##(Smalltalk.SearchPolicy)  8
#identity 524550 ##(Smalltalk.ColorRef)  8 4278190080 0 5 0 0 0 416 0 8
4294902589 459270 ##(Smalltalk.Message)  8 #displayString 98 0 8
##(Smalltalk.IconicListAbstract)  570 8 ##(Smalltalk.IconImageManager)
8 #current 0 0 0 328198 ##(Smalltalk.Point)  65 65 0 0 202 208 98 1
920646 5 ##(Smalltalk.ListViewColumn)  8 'Column 1' 201 8 #left 690 720
736 8 ##(Smalltalk.SortedCollection)  0 0 416 0 1 0 0 8 #largeIcons 544
0 131169 0 0 983302 ##(Smalltalk.MessageSequence)  202 208 98 2 721670
##(Smalltalk.MessageSend)  8 #createAt:extent: 98 2 818 2559 21 818 491
311 416 1058 8 #text: 98 1 8 'Column 1' 416 983302
##(Smalltalk.WINDOWPLACEMENT)  8 #[44 0 0 0 0 0 0 0 1 0 0 0 255 255 255
255 255 255 255 255 255 255 255 255 255 255 255 255 255 4 0 0 10 0 0 0
244 5 0 0 165 0 0 0] 98 0 818 193 193 0 27 )! !
!ThumbnailsPresenter class categoriesFor:
#resource_Default_view!public!resources-views! !

ThumbnailsView guid: (GUID fromString:
'{F9112CE1-4826-4B2B-BF54-F51E5A88226F}')!
ThumbnailsView comment: ''!
!ThumbnailsView categoriesForClass!MVP-Views! !
!ThumbnailsView methodsFor!

borderPen
        ^borderPen!

borderPen: anObject
        borderPen := anObject!

onPositionChanged: aPositionEvent
        "Private - Handle a window position change event (move or
resize)."

        aPositionEvent isResize ifTrue: [self invalidate].

        ^super onPositionChanged: aPositionEvent! !
!ThumbnailsView categoriesFor: #borderPen!accessing!public! !
!ThumbnailsView categoriesFor: #borderPen:!accessing!public! !
!ThumbnailsView categoriesFor: #onPositionChanged:!event
handling!private! !

!ThumbnailsView class methodsFor!

publishedAspectsOfInstances
        "Answer a <LookupTable> of the <Aspect>s published by instances of the
receiver."

        | answer |
        answer := super publishedAspectsOfInstances.
        #(#borderPen) do: [:each | answer add: (Aspect name: each)].
        #(#canEditLabels #columnOrder #columnsList
        #hasColumnImages #hasCheckBoxes ) do:[:each| answer removeKey: each ].
        ^answer! !
!ThumbnailsView class categoriesFor:
#publishedAspectsOfInstances!constants!development!public! !

"Binary Globals"!