Op 11-3-2019 om 00:03 schreef Ben Coman:


On Mon, 11 Mar 2019 at 01:09, Roelof Wobben <r.wob...@home.nl> wrote:
Op 10-3-2019 om 17:45 schreef Ben Coman:


On Sun, 10 Mar 2019 at 23:40, Roelof Wobben <r.wob...@home.nl> wrote:
Op 10-3-2019 om 16:19 schreef Ben Coman:


On Sun, 10 Mar 2019 at 17:55, Roelof Wobben <r.wob...@home.nl> wrote:
I could do something like this :

getImages
    | json numbers json2  |
    json := NeoJSONReader
        fromString:
            (ZnEasy
                get:
                    'https://www.rijksmuseum.nl/api/nl/collection?key=14OGzuak&format=json&type=schilderij&toppieces=True')
                contents.
    numbers := self class fromJSON: json
    numbers do: [each |  json :=  .........
                                           imageData = self class ???

I'm not sure what "numbers" refers to. It seems a quite non-domain related identifier.
To understand the domain, pasting the json contents of your link above into https://jsonformatter.curiousconcept.com/
and collapsing objects I see the structure is...
<snip> 

Did you work through this example I provided?   Please do so.
In a clean image...
Start with only your original code (which was good btw)...

    Paintings class >>  fromJSON: json
        | instance artObjects |
        instance := self new.
        artObjects := json at: #artObjects.
        artObjects
            do:
                [ :eachArtObject | instance addPainting: (Painting fromJSON: eachArtObject) ].
        ^ instance

except objectNumber(s) seem associated with each painting, so should be stored within the painting object, as ADDED here... 

 Painting class >> fromJSON: json
        | instance |
        instance := self new.
        instance
            objectNumber: (json at: #objectNumber);     "<<<<<<<<ADDED"
            title: (json at: #title);
            painter: (json at: #principalOrFirstMaker);
            imageUrl: ((json at: #webImage) at: #url).
        ^ instance

Evaluate the following in Playground... 
    collectionJson := NeoJSONReader fromString: (ZnEasy get: collectionUrl) contents.
    paintings := Paintings fromJSON: collectionJson.
    paintings inspect.
then clean the DNU errors as they occur (i.e. click the <Create> button shown by the debugger, and fill in as follows...)  
when you save the methods, choose <Declare new instance variable>"  

    Painting >> objectNumber: aString 
objectNumber := aString  
    Painting >> title: aString 
title := aString     

    Painting >> painter: aString 
painter := aString

    Painting >> imageUrl: aString 
imageUrl := aString

    Paintings >> addPainting: aPainting 
paintings := paintings ifNil: [ OrderedCollection new ].
paintings add: aPainting.

and an inspector will appear showing a list of paintings, which you can drill down to a painting and see each has the expected data.
Now just to round things off...

    Painting >> title
^ title

    Painting >> printOn: aStream
super printOn: aStream.
aStream << ' (' << self title << ')'

to help distinguish each item in the Inspector.


To extend the Playground code to download and display a painting, in Playground evaluate...

    painting := paintings first.
    imageResponse := ZnEasy get: painting imageUrl.
    image := ImageReadWriter formFromStream: imageResponse entity readStream.
    image inspect.

    Paintings >> first
^ paintings first

    Painting >> imageUrl
^ imageUrl

and an inspector on the `image` variable displays the painting on the Morph tab.


Now to mold the IDE to your domain... 
using Spotter to browser gtInspector* methods, a promising find is... AbstractFileReference>>gitInspectorJpegIn:
from which I produced...

    Painting  >>  gtInspectorJpegIn: composite
<gtInspectorPresentationOrder: 0>
composite morph
title: 'Painting';
display: [ ImageReadWriter formFromStream: self imageEntity readStream ] 

Then inspecting the `paintings` variable and drilling down to a painting 
pops up a DNU #imageEntity, which can be resolved by...

    Painting >> imageEntity
^ imageEntity ifNil: [ imageEntity := (ZnEasy get: self imageUrl) entity ].

and you get to see the painting shown in the Inspector.


Now if I understand your question... "Do I need to make some more object to get this working..."
I'd say... No. You only want one object for each painting. Once you have a painting object, it should handle all getting all further data it needs for itself.
You don't want duplicate objects each having half of the data.


can I for example name the function fromJson2 or fromJSONFromLink2  ?

By naming convention #fromJson: implies it sits on the class side.
To get further data for an existing object you want an instance-side method, maybe named #getLink2Json. 

HTH, 
cheers -ben


oke

numbers should be the objectNumbers because for the rest I need them


 


I use a instance variable called painting to hold the data.


so I can change the call to get data for the painting to :

Painting class >> fromJSON: json
        | instance |
        instance := self new.
        instance
            objectNumber: ((json at: #objectNumber).
        ^ instance


so numbers should be a collection of 10 ObjectNumbers

I'm presuming that 10 objectNumbers relate to 10 different paintings,
in which case, No, you should never need to deal with a collection of 10 objectNumbers.
What you should have is a collection of painting-objects which know their own objectNumber
and then iterate that collection sending each painting-object the message "getLink2Json".

 
so I should use a loop to make a call to the second api call

In Pharo OO approach, you don't "loop" on the "calls", 
you "iterate" on the "objects" asking them to use their own data to do the stuff they know how to do.
i.e. Let each object take care of itself.

Which class is getImages defined on?  That is really important to understand your proposed solution. 
I'm just presuming its defined on the class side of Paintings since your are referring to the same URL as before.

 getImages
    | json numbers  |
    json := NeoJSONReader
        fromString:
            (ZnEasy
                get:
                    'https://www.rijksmuseum.nl/api/nl/collection?key=14OGzuak&format=json&type=schilderij&toppieces=True')
                contents.
    numbers painting := self class fromJSON: json  

btw, it won't work with two identifiers "numbers painting" to the left of the assignment symbol.  Space here bad.
 

    numbers  do: [each |  json :=  call to the second url.here I used each 
                                           imageData = self class getLink2Json 
                                           json2 := call to the 3th url
                                           otherData := self class  getLink3Json
                                       

no :)    the "self class" seems wrong.
getting extra data about a painting should be handled by the instance side of its painting-object.

 
Then  I can  I hope on every json method fill in the data I need

Do I understand you well

I think not so well yet :)   (or else I am missing something)
Keep trying.  It will change the way you think about programming.

Please work though the example I provided.
cheers -ben

 

I did and it worked the same as my code
Still I do not see how to use then the objectNumber in a second call to the api
for example

lets say we have only 1 objectNumber now
for example
SK-C-5

then I need that one here :   
https://www.rijksmuseum.nl/api/nl/collection/SK-C-5?key=[API_KEY]&format=json

so I see a json response of this : 
<snip>
where I at this moment need only artObjects -> makers -> name and artobject -> title 
And I need to do that for all 10

But as far as I know I can only have one fromJson 
You can have as many Painting-class>>fromJsonXxxx methods as you like, 
but you only call one of them once per painting.  This has nothing to do with Json
and everything to do with your Painting-class>>fromJson method creating a new Painting-object, 
and you only want *one* Painting-object per Json-painting, so you can only call one.

But actually, you don't need any Painting>>fromJSON:.
Please delete it !!!!

Then modify the other one as follows...
    Paintings class >> fromJSON: json
    | instance |
    instance := self new.
    (json at: #artObjects)
        do:
            [ :artObjectJson | 
    |painting|
painting := Painting new.
    painting
        objectNumber: (artObjectJson  at: #objectNumber);
          title: (artObjectJson  at: #title);
        painter: (artObjectJson  at: #principalOrFirstMaker);
        imageUrl: ((artObjectJson  at: #webImage) at: #url).
instance addPainting: painting ].
    ^ instance
 
Does...
    json := NeoJSONReader fromString: (ZnEasy get: collectionUrl) contents.
    paintings := Paintings fromJSON: json.

give you the same result as before?

so how do I take care that the second one is called and parsed
and the right info is on the Painting object 

That is my question all the time 

As I said before...
> What you should have is a collection of painting-objects which know their own objectNumber
> and then iterate that collection sending each painting-object the message "getLink2Json".

So more generically, add something like...
    Painting >> getMoreData  "or a better name of your own"
            | url json artObjectJson | 
            url := 'https://www.rijksmuseum.nl/api/nl/collection/' , objectNumber , '?key=[API_KEY]&format=json'
Transcript crShow: 'Getting description from ', url.
json  := (NeoJSONReader fromString: (ZnEasy get: url) contents).
artObjectJson := json at: 'artObject.
             description := artObjectJson at: 'description'.
             title := artObjectJson at: 'title'.
Now in playground, variable paintings holds a collection 10 ten paintings.
So lets ask each of them to get more data.
paintings do: [ :painting | painting getMoreData ].
cheers -ben


I did try to make this idea work but now im complete lost.

Right now the collection that should contain the objectNumbers is total empty
anyone who can see where I went wrong.

I included my code so far.

Roelof


WAComponent subclass: #TBApplicationRootComponent
        instanceVariableNames: 'main'
        classVariableNames: ''
        poolDictionaries: ''
        category: 'Paintings-Components'!

!TBApplicationRootComponent methodsFor: 'updating' stamp: 'RoelofWobben 
3/8/2019 14:35'!
updateRoot: anHtmlRoot
        super updateRoot: anHtmlRoot.
        anHtmlRoot beHtml5.
        anHtmlRoot title: 'Paintings'.
        anHtmlRoot stylesheet
                url:
                        (WAUrl
                                absolute:
                                        
'https://code.getmdl.io/1.3.0/material.blue-cyan.min.css')! !


!TBApplicationRootComponent methodsFor: 'initialization' stamp: 'RoelofWobben 
3/8/2019 13:43'!
children
^ { main }! !

!TBApplicationRootComponent methodsFor: 'initialization' stamp: 'RoelofWobben 
3/8/2019 20:35'!
main: aComponent
main := aComponent! !

!TBApplicationRootComponent methodsFor: 'initialization' stamp: 'RoelofWobben 
3/8/2019 20:35'!
initialize
super initialize.
main := TBPostsListComponent new! !

!TBApplicationRootComponent methodsFor: 'initialization' stamp: 'EvelynCusi 
3/8/2019 09:57'!
renderContentOn: html
html render: main  .! !

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

TBApplicationRootComponent class
        instanceVariableNames: ''!

!TBApplicationRootComponent class methodsFor: 'class initialization' stamp: 
'RoelofWobben 3/8/2019 13:25'!
canBeRoot
^ true
! !

!TBApplicationRootComponent class methodsFor: 'class initialization' stamp: 
'RoelofWobben 3/8/2019 14:18'!
initialize
        "self initialize"

        | app |
        app := WAAdmin register: self asApplicationAt: 'Paintings'.
        app
                addLibrary: JQDeploymentLibrary;
                addLibrary: JQUiDeploymentLibrary;
                addLibrary: MDLLibrary! !


WAComponent subclass: #TBHeaderComponent
        instanceVariableNames: ''
        classVariableNames: ''
        poolDictionaries: ''
        category: 'Paintings-Components'!

!TBHeaderComponent methodsFor: 'rendering' stamp: 'EvelynCusi 3/8/2019 16:12'!
renderContentOfHeaderOn: html 
        self subclassResponsibility ! !

!TBHeaderComponent methodsFor: 'rendering' stamp: 'EvelynCusi 3/8/2019 16:12'!
renderContentOn: html
        html mdlLayout
                fixedHeader;
                with: [ html
                                mdlLayoutHeader: [ html mdlLayoutHeaderRow: [ 
html mdlLayoutTitle: 'Paintings' ] ].
                                self renderContentOfHeaderOn: html ]! !


WAComponent subclass: #TBPostComponent
        instanceVariableNames: 'post'
        classVariableNames: ''
        poolDictionaries: ''
        category: 'Paintings-Components'!

!TBPostComponent methodsFor: 'initialization' stamp: 'RoelofWobben 3/8/2019 
20:37'!
painter
        ^ post painter! !

!TBPostComponent methodsFor: 'initialization' stamp: 'RoelofWobben 3/8/2019 
22:11'!
renderContentOn: html
  html mdlCard
                shadow: 2;
                mdlTypographyTextLeft;
                with: [ html mdlCardTitleContainer
                                style:
                                        'background: url(''' , self imageUrl 
asString
                                                , ''') center / cover; color: 
#fff';
                                with: [ html mdlCardTitleText: self painter ] 
]! !

!TBPostComponent methodsFor: 'initialization' stamp: 'RoelofWobben 3/8/2019 
20:37'!
imageUrl
        ^ post imageUrl! !

!TBPostComponent methodsFor: 'initialization' stamp: 'RoelofWobben 3/8/2019 
20:36'!
initialize
super initialize.
post := Painting new! !

!TBPostComponent methodsFor: 'initialization' stamp: 'RoelofWobben 3/8/2019 
20:36'!
title 
  ^ post title 
! !


!TBPostComponent methodsFor: 'accessing' stamp: 'EvelynCusi 3/8/2019 16:11'!
post: aPost
        post := aPost! !


TBHeaderComponent subclass: #TBPostsListComponent
        instanceVariableNames: ''
        classVariableNames: ''
        poolDictionaries: ''
        category: 'Paintings-Components'!

!TBPostsListComponent methodsFor: 'rendering' stamp: 'EvelynCusi 3/8/2019 
16:12'!
renderContentOfHeaderOn: html
"       super renderContentOn: html."
        (Paintings new getImages) paintings
                do: [ :p | html render: (TBPostComponent new post: p) ]! !


WAComponent subclass: #TBScreenComponent
        instanceVariableNames: 'header'
        classVariableNames: ''
        poolDictionaries: ''
        category: 'Paintings-Components'!

!TBScreenComponent methodsFor: 'initialization' stamp: 'RoelofWobben 3/8/2019 
14:30'!
children
^ { header }! !

!TBScreenComponent methodsFor: 'initialization' stamp: 'RoelofWobben 3/8/2019 
14:29'!
createHeaderComponent
^ TBHeaderComponent new! !

!TBScreenComponent methodsFor: 'initialization' stamp: 'RoelofWobben 3/8/2019 
14:29'!
initialize
super initialize.
header := self createHeaderComponent! !


!TBScreenComponent methodsFor: 'rendering' stamp: 'RoelofWobben 3/8/2019 14:31'!
renderContentOn: html
html render: header! !

TBApplicationRootComponent initialize!Object subclass: #Painting
        instanceVariableNames: 'imageUrl'
        classVariableNames: ''
        poolDictionaries: ''
        category: 'Paintings'!

!Painting methodsFor: 'accessing' stamp: 'RoelofWobben 2/25/2019 20:17'!
imageUrl: anObject
        imageUrl := anObject! !

!Painting methodsFor: 'accessing' stamp: 'RoelofWobben 2/25/2019 20:17'!
imageUrl
        ^ imageUrl! !


Object subclass: #Paintings
        instanceVariableNames: 'paintings numbers'
        classVariableNames: ''
        poolDictionaries: ''
        category: 'Paintings'!


!Paintings methodsFor: 'accessing' stamp: 'RoelofWobben 3/11/2019 08:05'!
paintings
        ^ paintings! !

!Paintings methodsFor: 'accessing' stamp: 'RoelofWobben 3/11/2019 08:05'!
numbers: anObject
        numbers := anObject! !

!Paintings methodsFor: 'accessing' stamp: 'RoelofWobben 3/11/2019 08:05'!
paintings: anObject
        paintings := anObject! !

!Paintings methodsFor: 'accessing' stamp: 'RoelofWobben 3/11/2019 08:05'!
numbers
        ^ numbers! !


!Paintings methodsFor: 'instance creation' stamp: 'RoelofWobben 3/12/2019 
16:53'!
getImagesData: objectNumber
        | json |
        json := NeoJSONReader
                fromString:
                        (ZnEasy
                                get:
                                        
'https://www.rijksmuseum.nl/api/nl/collection/', objectNumber, 
'tiles?key=4OGzuak&format=json')
                                contents.
        ^ self class getImagesDataFromJSON: json
                
 ! !

!Paintings methodsFor: 'instance creation' stamp: 'RoelofWobben 3/11/2019 
07:58'!
addNumber: aNumber
        numbers add: aNumber! !

!Paintings methodsFor: 'instance creation' stamp: 'RoelofWobben 2/25/2019 
20:29'!
addPainting: aPainting
    paintings  add: aPainting. 
! !

!Paintings methodsFor: 'instance creation' stamp: 'RoelofWobben 3/11/2019 
08:05'!
initialize
        super initialize.
        numbers := OrderedCollection new! !

!Paintings methodsFor: 'instance creation' stamp: 'RoelofWobben 3/12/2019 
17:32'!
getData
        | collectionUrl json |
        collectionUrl := 
'https://www.rijksmuseum.nl/api/nl/collection?key=14OGzuak&format=json&type=schilderij&toppieces=True'.
        json := NeoJSONReader
                fromString: (ZnEasy get: collectionUrl) contents.
        numbers := Paintings GetNumbersfromJSON: json.
        ^ numbers ! !

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

Paintings class
        instanceVariableNames: 'numbers paintings'!

!Paintings class methodsFor: 'instance creation' stamp: 'RoelofWobben 3/12/2019 
17:26'!
getImagesDataFromJSON: json
        | instance |
        instance := Painting new.
        (json at: #values)
                do: [ :artObjectJson | 
                        | painting |
                        painting := Painting new.
                        painting imageUrl: (json at: #name).
                        instance addPainting: painting ].
        ^ instance! !

!Paintings class methodsFor: 'instance creation' stamp: 'RoelofWobben 3/12/2019 
17:31'!
GetNumbersfromJSON: json
        (json at: #artObjects)
                do: [ :artObjectJson | 
                        | number |
                        number := artObjectJson at: #objectNumber.
                        Paintings new addNumber: number ].
        ^ numbers! !

Reply via email to