TextBox.st
author Claus Gittinger <cg@exept.de>
Tue, 09 Jul 2019 20:53:39 +0200
changeset 6083 7a2c0a30e75c
parent 6080 a90e3bbb4c79
child 6086 00b0df472506
permissions -rw-r--r--
#REFACTORING by exept class: NoteBookView changed: #buttonPress:x:y: Transcript showCR:(... bindWith:...) -> Transcript showCR:... with:...

"{ Encoding: utf8 }"

"
 COPYRIGHT (c) 1992 by Claus Gittinger
	      All Rights Reserved

 This software is furnished under a license and may be used
 only in accordance with the terms of that license and with the
 inclusion of the above copyright notice.   This software may not
 be provided or otherwise made available to, or used by, any
 other person.  No title to or ownership of the software is
 hereby transferred.
"
"{ Package: 'stx:libwidg2' }"

"{ NameSpace: Smalltalk }"

EnterBox subclass:#TextBox
	instanceVariableNames:'textViewClass textView'
	classVariableNames:''
	poolDictionaries:''
	category:'Views-DialogBoxes'
!

!TextBox class methodsFor:'documentation'!

copyright
"
 COPYRIGHT (c) 1992 by Claus Gittinger
	      All Rights Reserved

 This software is furnished under a license and may be used
 only in accordance with the terms of that license and with the
 inclusion of the above copyright notice.   This software may not
 be provided or otherwise made available to, or used by, any
 other person.  No title to or ownership of the software is
 hereby transferred.
"
!

documentation
"
    this class implements a pop-up box to enter some text with 2 buttons,
    one to cancel, another to start some action.
    It is basically an enterBox, but allows entering of more than one line
    of text.
"
!

examples
"
  Example (using ok-action callBack):
                                                                        [exBegin]
    |textBox|

    textBox := TextBox new.
    textBox title:'enter some text'.
    textBox action:[:text | Transcript showCR:('the entered text was:\' , text) withCRs].
    textBox showAtPointer.
                                                                        [exEnd]


  Example (asking afterwards):
                                                                        [exBegin]
    |textBox|

    textBox := TextBox new.
    textBox title:'enter some text'.
    textBox showAtPointer.
    textBox accepted ifTrue:[
        Transcript showCR:'accepted text is:'.
        Transcript showCR:textBox contents
    ].
                                                                        [exEnd]

  Example - readonly text (useful for status display):
                                                                        [exBegin]
    |textBox|

    textBox := TextBox new.
    textBox initialText:('Makefile' asFilename contents).
    textBox title:'Makefile:'.
    textBox readOnly:true.
    textBox noCancel.
    textBox label:'Makefile'.
    textBox extent:(600@250); sizeFixed:true.
    textBox showAtPointer.
                                                                        [exEnd]
"
! !

!TextBox class methodsFor:'common dialogs'!

openOn:someText
    "open a textBox on some text, 
     return (the possibly modified) text if accepted; nil otherwise."

    ^ self openOn:someText title:'Enter Text:'

    "
     TextBox openOn:'hello'
    "
!

openOn:someText title:titleString
    "open a textBox on some text, the titleString is shown above the text area as information 
     return (the possibly modified) text if accepted; nil otherwise."

    ^ self openOn:someText title:titleString readOnly:false

"/    |box returnValue|
"/
"/    box := self new.
"/    box title:titleString.
"/    box initialText:someText.
"/    box action:[:text | returnValue := text].
"/    box showAtPointer.
"/    ^ returnValue.

    "
     TextBox openOn:'hello' title:'hi there'
     TextBox openOn:'hello' title:'hi there
this is a very long title
but only the first line is shown in the
caption.
'
    "
!

openOn:someText title:titleString readOnly:readOnly
    "open a textBox on some text, 
     return (the possibly modified) text if accepted; nil otherwise."

    ^ self 
        openOn:someText 
        title:titleString 
        windowTitle:nil 
        readOnly:readOnly

    "
     TextBox openOn:'hello' title:'hi there' readOnly:true
     TextBox openOn:'hello' title:'hi there' readOnly:false
    "

    "Created: / 29-10-2010 / 17:10:04 / cg"
!

openOn:someText title:titleString windowTitle:windowTitle readOnly:readOnly
    "open a textBox on some text, the optional titleString is shown as label
     above the text areay. The optional windowTitle is used as title in the caption.        
     return (the possibly modified) text if accepted; nil otherwise."

    ^ self new 
        openOn:someText title:titleString windowTitle:windowTitle readOnly:readOnly

    "
     TextBox openOn:'hello' title:'hi there' windowTitle:'some Box' readOnly:true
     TextBox openOn:'hello' title:'hi there' windowTitle:'some Box' readOnly:false
     TextBox openOn:'hello' title:'hi there' windowTitle:nil readOnly:false
     TextBox openOn:'hello' title:nil windowTitle:'some Box' readOnly:false
     TextBox openOn:'hello' title:nil windowTitle:nil readOnly:false
     TextBox openOn:'hello' title:nil windowTitle:'foo' readOnly:false
    "

    "Created: / 29-10-2010 / 17:10:04 / cg"
    "Modified: / 26-06-2019 / 10:55:57 / Claus Gittinger"
! !

!TextBox class methodsFor:'defaults'!

defaultExtent
    ^ (Screen current pixelPerMillimeter * (120 @ 90)) rounded
! !

!TextBox methodsFor:'accessing'!

contents
    "return my contents (i.e. possibly modified text after accept)"

    ^ textView contents

    "Modified (comment): / 04-02-2017 / 18:01:03 / cg"
!

contents:newText
    "set my contents"

    textView contents:newText

    "Created: / 04-11-2018 / 21:38:13 / Claus Gittinger"
!

initialText:aString
    "define the initial text in the texteditor"

    textView contents:aString

    "Modified (comment): / 04-02-2017 / 18:01:16 / cg"
!

readOnly:aBoolean
    "make my text readOnly or readWrite"

    textView readOnly:aBoolean
! !

!TextBox methodsFor:'accessing-contents'!

textView
    ^ textView
!

textViewClass:something
    textViewClass := something.
! !

!TextBox methodsFor:'initialization'!

initialize
    |space2 space3 innerWidth|

    super initialize.

    enterField destroy.

    space2 := 2 * ViewSpacing.
    space3 := 3 * ViewSpacing.

    "kludge: preset extent to something useful since other subviews
     depend on it (extent blocks are not evaluated until view is realized)
     - avoid visible resizing when realized the first time"

    innerWidth := width - space2.

    textView := HVScrollableView for:(textViewClass ? EditTextView) miniScrollerH:true in:self.
    textView origin:(ViewSpacing @ (space2 + labelField height))
             extent:(innerWidth @ (height - ViewSpacing -
                                   labelField height - ViewSpacing -
                                   buttonPanel height - space3) ).
    textView origin:[ViewSpacing @ (space2 + labelField height)]
             extent:[(width - space2) @ (height - ViewSpacing -
                                   labelField height - ViewSpacing -
                                   buttonPanel height - space3) ].

    self delegate:(KeyboardForwarder toView:textView scrolledView)

    "TextBox new showAtPointer"

    "Modified: / 29-10-2010 / 17:14:49 / cg"
!

openOn:someText title:titleString windowTitle:windowTitle readOnly:readOnly
    "open a textBox on some text, the optional titleString is shown as label
     above the text areay. The optional windowTitle is used as title in the caption.        
     return (the possibly modified) text if accepted; nil otherwise."

    |returnValue usedWindowTitle|

    readOnly ifTrue:[ self textViewClass:TextView ].
    self initialize.
    titleString notNil ifTrue:[ self title:titleString ].
    self initialText:someText.
    self action:[:text | returnValue := text].
    self readOnly:readOnly.
    readOnly ifTrue:[ self abortButton destroy ].

    usedWindowTitle := windowTitle.
    usedWindowTitle isNil ifTrue:[
        titleString notNil ifTrue:[
            usedWindowTitle := titleString asString asStringCollection first
        ] ifFalse:[
            usedWindowTitle := readOnly ifTrue:'Value' ifFalse:'Input'
        ].
    ].
    self window label:usedWindowTitle.
    self showAtPointer.
    ^ returnValue.

    "
     TextBox openOn:'hello' title:'hi there' windowTitle:'some Box' readOnly:true
     TextBox openOn:'hello' title:'hi there' windowTitle:'some Box' readOnly:false
     TextBox openOn:'hello' title:'hi there' windowTitle:nil readOnly:false
     TextBox openOn:'hello' title:nil windowTitle:'some Box' readOnly:false
     TextBox openOn:'hello' title:nil windowTitle:nil readOnly:false
     TextBox openOn:'hello' title:nil windowTitle:'foo' readOnly:false
    "

    "Created: / 26-06-2019 / 10:55:37 / Claus Gittinger"
! !

!TextBox methodsFor:'queries'!

computePreferredExtent
    "return the extent needed to make everything visible"

    |wWanted hWanted wLabel wPanel wText hText|

    wLabel := labelField width + ViewSpacing + ViewSpacing.

    wPanel := ViewSpacing * 3.
    buttonPanel subViews do:[:aView |
        wPanel := wPanel + aView width + ViewSpacing
    ].

    wWanted := (width max:wPanel) max:wLabel.

    textView notNil ifTrue:[
        wText := (textView scrolledView widthOfContents + 30) min:1024.
        hText := (textView scrolledView heightOfContents + 20) min:400.
        wWanted := wWanted max:wText.
    ].

    hWanted := ViewSpacing + labelField height +
               ViewSpacing + hText +
               (ViewSpacing * 6) + buttonPanel preferredHeight +
               ViewSpacing.
    ^ (wWanted @ hWanted)

    "Created: / 09-11-2018 / 20:02:29 / Claus Gittinger"
    "Modified: / 28-06-2019 / 11:06:25 / Claus Gittinger"
! !

!TextBox class methodsFor:'documentation'!

version
    ^ '$Header$'
!

version_CVS
    ^ '$Header$'
! !