Squeak
  links to this page:    
View this PageEdit this Page (locked)Uploads to this PageHistory of this PageTop of the SwikiRecent ChangesSearch the SwikiHelp Guide
How to work with multiple text morphs
Last updated at 11:55 am UTC on 8 December 2021
On January 01, 2004 ye juan asked: How do I work with multiple text morphs?
I have started to develop applications in Squeak, but I am not familiar with its GUI. When I put more than one pluggableTextMorph in a window, how can I confirm these different ones. For example, there are one list and three texts: one for displaying the name of a selected one in the list, one for displaying the id when the button "ID" is pressed, and another for inputting.
(1)How I define the second text:(When the button "ID" is not pressed, the second text is hoped to display nothing.)
      idText:= PluggableTextMorph on:self
              text:???
              accept:nil
              readSelection:nil
              menu:nil. 
(2) How I record the value users input in the third text:
      inputText:= PluggableTextMorph on:self
              text:???
              accept:???
              readSelection:nil
              menu:nil. 
Additionally, if you have any projects or codes related to such situations, please send to me. Thanks!

From: Boris Gaertner answered.
(1) Every text morph should have its own selector to access its display text. So you may have #text1, #text2, #text3 for three text fields.
(2) The argument of 'accept' is a selector that takes two arguments: e.g. #accept:from: The first argument is the string that is displayed by the morph, the second argument is the morph itself. The method is required to answer a boolean value: true to accept the text or false to refuse acceptance.
Class TextFieldDemo shows how you can have several text morphs in one window. To start the demo, evaluate:
TextFieldDemo new buildWindow openInWorld
after installing MorphicGUIDemo.cs.gz or creating the following:


Example1.png

Model subclass: #TextFieldDemo
	instanceVariableNames: 'collection selectedItem text1 text2 text3'
	classVariableNames: ''
	poolDictionaries: ''
	category: 'Morphic-Demos' 
To display three strings, this class has three instance variables, one for each string. The strings are accessed the instance methods text1, text2, text3 and these accessors are given to the text morphs (see method buildWindow) Every text morph has its own accept method, which stores the modified morph content. All three morphs share the same menu, which is sufficient, because all menues offer only the item 'accept'.
TextFieldDemo >> 
currentSelection
  "  Sent by a PluggableListMorph to get the current selection.
    Answer the index of the currently selected item.
    A value of 0 means that no item is currently selected. "
  ^selectedItem   
list
   " Sent by a PluggableListMorph to get a list to display.
     Answer a collection of strings, the items that are displayed by the morph."
 ^collection collect: [:item | item first].   
setSelection: anInteger
   " Sent by a PluggableListMorph to tell the current selection.
     anInteger is the index of the currently selected item.
     A value of zero means that no item is currently selected."
     | item |
  selectedItem := anInteger.
  anInteger ~= 0
    ifTrue:
      [item := collection at: selectedItem.
       text1 := item first.
       text2 := item at: 2.
       text3 := item last.]
   ifFalse:
     [text1 := text2 := text3 := ''.
	].
  "  The following messages are broadcasted to the morphs that have this instance as their model.
     A morph compare the symbol that is sent with the name of its own accessor method to decide whether the    
change requires a reaction from the side of the notified morph. A morph that finds that it has to react to a 
change notification ask its model for up-to-date display data and redisplays itself. "
  self changed: #currentSelection;
       changed: #text1;
       changed: #text2;
       changed: #text3.
accept1: string from: aPluggableTextMorph
 " Sent by a PluggableTextMorph to tell that its string has changed and can now be taken by the receiver. 
This method is sent from method accept of the PluggableTextMorph, a method that is frequently used as a menu activity.
    This method copies the changed string into the receiver and it answers 'true' to tell the =PluggableTextMorph that the string was accepted. "
  text1 := string.
  selectedItem ~= 0
    ifTrue: [(collection at: selectedItem) at: 1 put: string].
  ^true   
text1
  " Sent by a PluggableTextMorph to get a string to display."
  ^text1   
accept2: string from: aPluggableTextMorph
  " Sent by a PluggableTextMorph to tell that its string has changed and can now be taken by the receiver. 
This method is sent from method accept of the PluggableTextMorph, a method that is frequently used as a menu activity.
    This method copies the changed string into the receiver and it answers 'true' to tell the =PluggableTextMorph that the string was accepted. "
  text2 := string.
  selectedItem ~= 0
    ifTrue: [(collection at: selectedItem) at: 2 put: string].
  ^true   
 text2
  " Sent by a PluggableTextMorph to get a string to display."
   ^text2   
accept3: string from: aPluggableTextMorph
  " Sent by a PluggableTextMorph to tell that its string has changed and can now be taken by the receiver. 
This method is sent from method accept of the PluggableTextMorph, a method that is frequently used as a menu activity.
    This method copies the changed string into the receiver and it answers 'true' to tell the =PluggableTextMorph that the string was accepted. "

  text3 := string.
  selectedItem ~= 0
    ifTrue: [(collection at: selectedItem) at: 3 put: string].
  ^true   
text3
  " Sent by a PluggableTextMorph to get a string to display."
  ^text3   
menu: aMenuMorph
  " Sent by a PluggableTextMorph to get a menu.
    In this example, all text morphs use the same menu. This is not always a feasible solution, but here it is. "
aMenuMorph
     add: 'accept' action: #accept.
            " #accept is a method of PluggableTextMorph "
  ^aMenuMorph   
buildWindow
  "  create a window with a PluggableListMorph and
     three PluggableTextMorphs.  "
 
    | window |
   window := (SystemWindow labelled: 'Example1') model: self.
   window color: (Color lightGray).
   window addMorph:
               (PluggableListMorph on: self
                 	list: #list
	              selected: #currentSelection
		         changeSelected: #setSelection:
               )
             frame: (0.0 @ 0.0 extent: 0.28 @ 1.0). 
   window addMorph:
                (PluggableTextMorph on: self
                 text: #text1
                 accept: #accept1:from:
                 readSelection: nil
                 menu: #menu:)
             frame: (0.3 @ 0.1 extent: 0.6 @ 0.1).
   window addMorph:
                (PluggableTextMorph on: self
                 text: #text2
                 accept: #accept2:from:
                 readSelection: nil
                 menu: #menu:)
             frame: (0.3 @ 0.3 extent: 0.6 @ 0.1).
   window addMorph:
                (PluggableTextMorph on: self
                 text: #text3
                 accept: #accept3:from:
                 readSelection: nil
                 menu: #menu:)
             frame: (0.3 @ 0.5 extent: 0.6 @ 0.1).
   ^window
 "TextFieldDemo new buildWindow openInWorld"   
initExtent
  ^300@270   
initialize
  " define suitable initial values for all instance variables. "
  text1 := text2 := text3 := ''.
  selectedItem := 0.
  collection := OrderedCollection new.
  collection 
    add: (Array with: 'John' with: '34' with: 'Programmer');
    add: (Array with: 'Mary' with: '26' with: 'Typist');
    add: (Array with: 'Margaret' with: '32' with: 'Sales Manager').   
 TextFieldDemo reorganize 
('list view' currentSelection list setSelection:)
('text view 1' accept1:from: text1)
('text view 2' accept2:from: text2)
('text view 3' accept3:from: text3)
('common text menu' menu:)
('window creation' buildWindow initExtent)
('initialize-release' initialize)


See Tabbed text morphs for ideas on how to be able to tab from one text morph to the next.