Attempting example - Adaptive Forms 3.6.3

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

Attempting example - Adaptive Forms 3.6.3

Jimmie Houchin-3
Hello,

I am attempting to implement the example for Adaptive Forms in Lukas'
thesis in Chapter 3 on Pier.  3.6.3 Adaptive Forms

I created a Category, MyPier-Tutorial with the Classes, MyForm and
EditMyFormCommand attempting to implement the example as written with
the exception of it being PRCommand and PRStructure.

When I add a page to Pier with 'MyForm' and save it. Then I click on the
command 'Edit MyForm' I get this stack trace which I truncated somewhat.

I do not understand why I am getting this message. I have the class
method in EditMyFormCommand.

label
        ^ 'Edit MyForm'

Any help in understanding, greatly appreciated. If I did not include
enough of the stack trace, let me know.

Also included is a fileout of my attempt.

Are there any small Pier tutorials or applications which can be filed in
for educational purposes?

I get lost in all the Pier, Magritte, framework code attempting to find
examples.

Where in the code can I find where the Pier frontpage is implemented? I
tried to find it for an example. But am overlooking it somewhere. Or
else I am still lacking understanding somewhere.

Thanks for any help.

Jimmie Houchin




MessageNotUnderstood: EditMyFormCommand>>label

Debug Proceed
Possible Causes

     * you sent a message this type of object doesn't understand

Stack Trace

    1.
       thisContext
           EditMyFormCommand(Object)>>doesNotUnderstand: #label
       self
           an EditMyFormCommand
       aMessage
           label

    2.
       thisContext
           MASelectorAccessor>>read:
       self
           (MASelectorAccessor read: #label write: #label:)
       aModel
           an EditMyFormCommand

    3.
       thisContext
           EditMyFormCommand(Object)>>readUsing:
       self
           an EditMyFormCommand
       aDescription
           a MAStringDescription label: 'Label' comment: nil

    4.
       thisContext
           [] in MACheckedMemento(MAMemento)>>pullRaw {[:each | result
at: each put: (self model readUsing:...etc...
       self
           a MACheckedMemento model: an EditMyFormCommand
       result
           a Dictionary(a MAStringDescription label: 'Kind' comment:
nil->'Edit MyForm' )
       each
           a MAStringDescription label: 'Label' comment: nil

    5.
       thisContext
           SortedCollection(OrderedCollection)>>do:
       self
           a SortedCollection(a MAStringDescription label: 'Kind'
comment: nil a MAStringDescription label: 'La...etc...
       aBlock
           [] in MACheckedMemento(MAMemento)>>pullRaw {[:each | result
at: each put: (self model readUsing:...etc...
       index
           4

    6.
       thisContext
           MAPriorityContainer(MAContainer)>>do:
       self
           a MAPriorityContainer label: 'Container' comment: nil
       aBlock

PRCommand subclass: #EditMyFormCommand
        instanceVariableNames: 'metamodel'
        classVariableNames: ''
        poolDictionaries: ''
        category: 'MyPier-Tutorial'!

!EditMyFormCommand methodsFor: 'as yet unclassified' stamp: 'jlh 9/1/2007 09:29'!
description
        ^ self metamodel description! !

!EditMyFormCommand methodsFor: 'as yet unclassified' stamp: 'jlh 9/1/2007 09:30'!
doExecute

        super doExecute.
        self structure metamodel: self metamodel! !

!EditMyFormCommand methodsFor: 'as yet unclassified' stamp: 'jlh 9/1/2007 09:27'!
metamodel
"Answer the meta-model of the command, fetch it from the current structure if it is not initialized."
        ^ metamodel ifNil: [ metamodel := self structure metamodel ]! !

!EditMyFormCommand methodsFor: 'as yet unclassified' stamp: 'jlh 9/1/2007 09:28'!
metamodel: aDescription
"    the meta-model of the command, fetch it from the current structure if it is not initialized."

        metamodel := aDescription! !

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

EditMyFormCommand class
        instanceVariableNames: ''!

!EditMyFormCommand class methodsFor: 'as yet unclassified' stamp: 'jlh 9/1/2007 09:26'!
isAbstract

        ^ false! !

!EditMyFormCommand class methodsFor: 'as yet unclassified' stamp: 'jlh 9/1/2007 09:25'!
label
        ^ 'Edit MyForm'! !

!EditMyFormCommand class methodsFor: 'as yet unclassified' stamp: 'jlh 9/1/2007 09:25'!
structureClass
        ^ MyForm! !


PRStructure subclass: #MyForm
        instanceVariableNames: 'model metamodel'
        classVariableNames: ''
        poolDictionaries: ''
        category: 'MyPier-Tutorial'!

!MyForm methodsFor: 'as yet unclassified' stamp: 'jlh 9/1/2007 08:55'!
description
        ^ (MAContainer withAll: super description),
                (self metamodel do: [ :each | each beEditable ])! !

!MyForm methodsFor: 'as yet unclassified' stamp: 'jlh 9/1/2007 09:07'!
document
        ^ PRDocument new
                add: ( PRUnorderedList new
                        add: ( self metamodel children collect: [ :desc |
                                        PRListItem
                                                with: (Text with: '<b>' , desc label , '</b>');
                                                with: (Text with: (desc
                                                        toString: ( self readUsing: desc)));
                                                yourself]);
                                        yourself);
                                yourself! !

!MyForm methodsFor: 'as yet unclassified' stamp: 'jlh 9/1/2007 08:52'!
initialize

        super initialize.
        self model: Dictionary new.
        self metamodel: MAContainer new! !

!MyForm methodsFor: 'as yet unclassified' stamp: 'jlh 9/1/2007 08:49'!
metamodel
"Anser a Magritte container with the description of the receiver."

^ metamodel! !

!MyForm methodsFor: 'as yet unclassified' stamp: 'jlh 9/1/2007 08:50'!
metamodel: aDescription
"    a Magritte container with the description of the receiver."

metamodel := aDescription
! !

!MyForm methodsFor: 'as yet unclassified' stamp: 'jlh 9/1/2007 08:50'!
model
"Answer a dictionary mapping the descriptions of the receiver to actual values."

^ model! !

!MyForm methodsFor: 'as yet unclassified' stamp: 'jlh 9/1/2007 08:51'!
model: aDictionary
"   a dictionary mapping the descriptions of the receiver to actual values."

model := aDictionary! !

!MyForm methodsFor: 'as yet unclassified' stamp: 'jlh 9/1/2007 08:53'!
postCopy

        super postCopy.
        self model: self model copy! !

!MyForm methodsFor: 'as yet unclassified' stamp: 'jlh 9/1/2007 08:58'!
readUsing: aDescription
        "Answer the actual value described by aDescription. If our meta-model includes aDescription return the associated value from the dictionary, else use the super implementation."
       
        ^(self metamodel includes: aDescription )
                ifTrue: [
                        self model
                                at: aDescription
                                ifAbsent: [ aDescription default ]]
                ifFalse: [ super readUsing: aDescription ]! !

!MyForm methodsFor: 'as yet unclassified' stamp: 'jlh 9/1/2007 09:01'!
write: anObject using: aDescription
"Set the value described by aDescription to be anObject. If our meta-model includes aDescription put anObject into the dictionary, else use the super implementation."

        (self metamodel includes: aDescription )
                ifTrue: [ self model at: aDescription put: anObject ]
                ifFalse: [ super write: anObject using: aDescription ]! !

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

MyForm class
        instanceVariableNames: ''!

!MyForm class methodsFor: 'as yet unclassified' stamp: 'jlh 9/1/2007 08:48'!
isAbstract

^ false! !


_______________________________________________
SmallWiki, Magritte, Pier and Related Tools ...
https://www.iam.unibe.ch/mailman/listinfo/smallwiki
Reply | Threaded
Open this post in threaded view
|

Re: Attempting example - Adaptive Forms 3.6.3

Tapple Gao
On Sat, Sep 01, 2007 at 10:42:17AM -0500, Jimmie Houchin wrote:
> Hello,
>
> I am attempting to implement the example for Adaptive Forms in Lukas'
> thesis in Chapter 3 on Pier.  3.6.3 Adaptive Forms

I tried that too a while ago. Lukas replied that Pier has
changed a bit since then. The up-to-date code is in the pier MC
repository. The code is:
http://source.lukas-renggli.ch/pier/Pier-Forms-lr.20.mcz

--
Matthew Fulmer -- http://mtfulmer.wordpress.com/
Help improve Squeak Documentation: http://wiki.squeak.org/squeak/808

_______________________________________________
SmallWiki, Magritte, Pier and Related Tools ...
https://www.iam.unibe.ch/mailman/listinfo/smallwiki