ShowMeHowItWorks.st
author Claus Gittinger <cg@exept.de>
Mon, 22 Jul 2019 17:26:46 +0200
changeset 3724 e513514f6ce7
parent 3717 26224649d91c
child 3727 6faffd2a64a3
permissions -rw-r--r--
#REFACTORING by exept class: ShowMeHowItWorks comment/format in: #pause changed: #intro

"{ Encoding: utf8 }"

"{ Package: 'stx:libtool2' }"

"{ NameSpace: Smalltalk }"

Object subclass:#ShowMeHowItWorks
	instanceVariableNames:'application opStream lastComponentName lastComponent lastResult'
	classVariableNames:''
	poolDictionaries:''
	category:'Interface-Help'
!

!ShowMeHowItWorks class methodsFor:'documentation'!

documentation
"
    automatic presentations.
    To see how it works, open a methodFinder:
        MethodFinderWindow open
    and select its 'Show me how it works' item in the help menu.

    [author:]
        Claus Gittinger
"
!

example
    MethodFinderWindow open.
    
    ShowMeHowItWorks do:#(
        ( showing: 'Choose the number of arguments' do:(
            moveTo: NumberOfArguments
            select: '1' 
        ))  
        (showing: 'Click into the "receiver" field' do:(
            moveTo: ReceiverEditor
            click: ReceiverEditor 
        ))
        (showing: 'Enter a value (or expression) into "receiver" field' do:(
            enter: '100'
        ))
        (showing: 'Click into the "first argument" field' do:(
            moveTo: Arg1Editor
            click: ReceiverEditor
        ))
        (showing: 'Enter a value (or expression) into "receiver" field' do:(
            enter: '100'
        ))

    )
! !

!ShowMeHowItWorks class methodsFor:'running'!

do:specArray
    self doStream:specArray readStream

    "Created: / 19-07-2019 / 10:52:59 / Claus Gittinger"
    "Modified: / 19-07-2019 / 14:30:43 / Claus Gittinger"
!

doStream:specStream
    "must run as a separate process;
     otherwise - if started by the app itself -
     no events will be processed while running"

    |appWhichStartedMe|
    
    appWhichStartedMe := WindowGroup activeMainApplication.
    
    [
        self new 
            application:appWhichStartedMe;
            doStream:specStream
    ] fork.

    "Created: / 19-07-2019 / 10:53:07 / Claus Gittinger"
    "Modified: / 19-07-2019 / 16:44:02 / Claus Gittinger"
! !

!ShowMeHowItWorks methodsFor:'accessing'!

application:something
    application := something.
! !

!ShowMeHowItWorks methodsFor:'commands'!

intro
    <action>

    self tell:(self class classResources 
                string:'you can stop the show - by pressing - the shift key').

    "Created: / 19-07-2019 / 15:49:19 / Claus Gittinger"
!

pause
    <action>
    
    Dialog information:(self class classResources 
                            stringWithCRs:'Show Paused.\Click on "OK" to proceed')

    "Created: / 19-07-2019 / 15:03:17 / Claus Gittinger"
    "Modified: / 19-07-2019 / 16:13:33 / Claus Gittinger"
!

show:message
    "showing (and speak) some message."

    <action>
    
    self showing:message do:nil

    "Created: / 19-07-2019 / 15:59:18 / Claus Gittinger"
    "Modified (comment): / 19-07-2019 / 18:54:36 / Claus Gittinger"
!

show:message for:seconds
    "showing (and speak) some message and wait for some time."

    <action>
    
    self show:message.
    self wait:seconds.

    "Created: / 19-07-2019 / 18:54:20 / Claus Gittinger"
!

showing:message do:operationsOrNothing
    "execute operationsOrNothing while showing (and speaking) some message."

    <action>
    
    |xLatedMessage messageView talkDone|

    xLatedMessage := application notNil 
                        ifTrue:[application resources string:message]
                        ifFalse:[message].
                        
    self assert:(operationsOrNothing isNil or:[operationsOrNothing isSequenceable]).

    messageView := ActiveHelpView for:xLatedMessage.
    "/ messageView shapeStyle:#cartoon.
    [
        messageView origin:(Screen current pointerPosition).
        messageView realize.

        self talking ifTrue:[
            talkDone := Semaphore new.
            [
                self tell:xLatedMessage.
                talkDone signal
            ] fork.
            
            "/
            "/ allow speaker some headoff
            Delay waitForSeconds:(xLatedMessage size / 30).
        ].

        operationsOrNothing notEmptyOrNil ifTrue:[
            self doStream:(operationsOrNothing readStream).
        ].
    ] ensure:[
        messageView destroy
    ].
    self talking ifTrue:[
        talkDone wait.
    ].

    "Created: / 19-07-2019 / 11:19:27 / Claus Gittinger"
    "Modified: / 19-07-2019 / 21:37:07 / Claus Gittinger"
!

wait:seconds
    <action>
    
    Delay waitForSeconds:seconds

    "Created: / 19-07-2019 / 15:09:45 / Claus Gittinger"
! !

!ShowMeHowItWorks methodsFor:'commands - checking'!

isEmpty:componentName
    <action>

    |component|
    
    component := self componentNamed:componentName.
    component isScrollWrapper ifTrue:[ component := component scrolledView ].
    component isTextView ifTrue:[
        ^ component contents isEmptyOrNil
    ] ifFalse:[
        self halt.
    ].
    self error:'isEmpty: unhandled component type: ',component displayString.

    "Created: / 19-07-2019 / 15:33:47 / Claus Gittinger"
!

unless:query do:actions
    <action>

    |result|
    
    result := self doCommand:query.
    result ifFalse:[
        self doCommand:actions
    ].

    "Created: / 19-07-2019 / 15:33:32 / Claus Gittinger"
! !

!ShowMeHowItWorks methodsFor:'commands - mouse & keyboard'!

click
    "press-release"
    
    <action>

    ^ self click:1 inComponent:lastComponent

    "Created: / 19-07-2019 / 16:11:03 / Claus Gittinger"
!

click:buttonNr
    "press-release"
    
    <action>

    self assert:(buttonNr isInteger).
    ^ self click:buttonNr inComponent:lastComponent

    "Created: / 19-07-2019 / 13:21:20 / Claus Gittinger"
    "Modified: / 19-07-2019 / 16:10:19 / Claus Gittinger"
!

clickIn:componentName
    "press-release"
    
    <action>

    ^ self click:1 inComponent:(self componentNamed:componentName)

    "Created: / 19-07-2019 / 16:09:58 / Claus Gittinger"
!

fastMoveTo:componentName
    "move the mouse to componentName without circling"

    <action>

    |component|

    component := self componentNamed:componentName.
    self movePointerToComponent:component speed:(self pointerMoveSpeedFast).

    "Created: / 19-07-2019 / 15:39:23 / Claus Gittinger"
    "Modified: / 20-07-2019 / 08:14:16 / Claus Gittinger"
!

moveTo:componentName
    "move the mouse to componentName,
     then circle around it a few times"

    <action>

    |component|

    component := self componentNamed:componentName.
    self movePointerToComponent:component.
    self circlePointerAroundComponent:component.

    "Created: / 19-07-2019 / 11:20:42 / Claus Gittinger"
    "Modified: / 19-07-2019 / 15:38:11 / Claus Gittinger"
!

select:itemsLabel
    "select an item by label,
     allowed after moving to:
        aComboBox
        aSelectionInListView
    "    

    <action>

    |idx|
    
    (lastComponent isKindOf:ComboView) ifTrue:[
        "/ click on the menubutton
        self movePointerToComponent:lastComponent menuButton.
        self click:1 inComponent:lastComponent menuButton.
        Delay waitForSeconds:0.3.
        (idx := lastComponent list indexOf:itemsLabel ifAbsent:[nil]) isNil ifTrue:[
            self error:'no such item in comboList: ',itemsLabel
        ].
        lastComponent select:idx.
        Delay waitForSeconds:0.3.
        lastComponent shownMenu notNil ifTrue:[
            lastComponent shownMenu hide.
        ].    
        ^ self
    ].    
    self error:'cannot select this component'

    "Created: / 19-07-2019 / 12:34:25 / Claus Gittinger"
    "Modified (format): / 19-07-2019 / 14:55:34 / Claus Gittinger"
!

selectIndex:itemsIndex
    "select an item by index,
     allowed after moving to:
        aComboBox
        aSelectionInListView
    "    

    <action>

    self selectIndex:itemsIndex in:lastComponent

    "Created: / 19-07-2019 / 14:20:11 / Claus Gittinger"
    "Modified: / 19-07-2019 / 21:59:36 / Claus Gittinger"
!

selectIndex:itemsIndex in:widgetArg
    "select an item by index,
     allowed after moving to:
        aComboBox
        aSelectionInListView
    "    

    <action>

    |widget y offset possibleWidgets|

    (widget := widgetArg) isScrollWrapper ifTrue:[
        widget := widget scrolledView
    ].
    
    (widget isKindOf:ComboView) ifTrue:[
        "/ click on the menubutton
        self movePointerToComponent:widget menuButton.
        self click:1 inComponent:widget menuButton.
        Delay waitForSeconds:0.5.
        widget select:itemsIndex.
        Delay waitForSeconds:0.5.
self halt.
        ^ self
    ].    
    (widget isKindOf:SelectionInListView) ifTrue:[
        (widget isLineVisible:itemsIndex) ifFalse:[
            widget scrollToLine:itemsIndex
        ].    
        "/ click on the item
        y := widget yOfLine:itemsIndex.
        offset := (widget width // 2) @ y.
        self movePointerToComponent:widget offset:offset.
        widget simulateButtonPress:1 at:offset sendDisplayEvent:false.
        Delay waitForSeconds:(self clickTime).
        widget simulateButtonRelease:1 at:offset sendDisplayEvent:false.
        Delay waitForSeconds:0.5.
        ^ self
    ].
    (widget isKindOf:SelectionInListModelView) ifTrue:[
        (widget isLineVisible:itemsIndex) ifFalse:[
            widget scrollToLine:itemsIndex
        ].    
        y := widget yVisibleOfLine:itemsIndex.
        offset := (widget width // 2) @ y.
        self movePointerToComponent:widget offset:offset.
        widget simulateButtonPress:1 at:offset sendDisplayEvent:false.
        Delay waitForSeconds:(self clickTime).
        widget simulateButtonRelease:1 at:offset sendDisplayEvent:false.
        Delay waitForSeconds:0.5.
        ^ self
    ].

    "/ none of it - see what is in there
    possibleWidgets := OrderedCollection new.
    widget allSubViewsDo:[:each |
        ((each isKindOf:ComboView) 
          or:[(each isKindOf:SelectionInListView)
          or:[(each isKindOf:SelectionInListModelView)
        ]]) ifTrue:[
            possibleWidgets add:each
        ]
    ].
    possibleWidgets size == 1 ifTrue:[
        self selectIndex:itemsIndex in:(possibleWidgets first).
        ^ self
    ].    
    
    self error:'cannot select this component'

    "Created: / 19-07-2019 / 21:59:15 / Claus Gittinger"
    "Modified: / 20-07-2019 / 07:57:41 / Claus Gittinger"
!

type:aString
    "enter text into the last component"

    <action>

    lastComponent simulateTextInput:aString at:(lastComponent extent // 2) sendDisplayEvent:false

    "Created: / 19-07-2019 / 15:50:40 / Claus Gittinger"
! !

!ShowMeHowItWorks methodsFor:'defaults'!

circlingCount
    "circle around move-end position that many times"

    ^ 3

    "Created: / 19-07-2019 / 13:03:45 / Claus Gittinger"
!

circlingRadius 
    "radius when circling"
    
    ^ 30 "/ pixels

    "Created: / 19-07-2019 / 13:07:59 / Claus Gittinger"
!

circlingSpeed 
    "time per round when circling"
    
    ^ 0.3 seconds.       "/ time per round

    "Created: / 19-07-2019 / 13:02:34 / Claus Gittinger"
!

clickTime
    "when clicking"

    ^ self shortClickTime

    "Created: / 19-07-2019 / 13:17:20 / Claus Gittinger"
    "Modified: / 19-07-2019 / 15:21:51 / Claus Gittinger"
!

longClickTime
    "when clicking buttons"

    ^ 500 milliseconds

    "Created: / 19-07-2019 / 15:21:42 / Claus Gittinger"
!

pointerAnimationDelay
    ^ 50 milliseconds.   "/ 20 updates per second

    "Created: / 19-07-2019 / 13:04:45 / Claus Gittinger"
!

pointerMoveSpeed
    ^ 400.   "/ pixels per second

    "Created: / 19-07-2019 / 13:05:40 / Claus Gittinger"
!

pointerMoveSpeedFast
    ^ 600.   "/ pixels per second

    "Created: / 20-07-2019 / 08:13:58 / Claus Gittinger"
!

shortClickTime
    "when clicking"

    ^ 100 milliseconds

    "Created: / 19-07-2019 / 15:21:29 / Claus Gittinger"
!

talking
    ^ true

    "Created: / 19-07-2019 / 14:31:14 / Claus Gittinger"
! !

!ShowMeHowItWorks methodsFor:'helper'!

componentNamed:componentName
    "retrieve a component by name or report an error if not found"

    |component|

    lastComponentName := componentName.

    component := self findComponent:componentName.
    component isNil ifTrue:[
        self error:'no component found for: ',componentName.
    ].
    lastComponent := component.
    ^ component

    "Created: / 19-07-2019 / 15:37:35 / Claus Gittinger"
!

findComponent:componentName
    "find a component by name - in the active and possibly in any app"
    
    |component candidates|

    application notNil ifTrue:[ 
        component := self findComponent:componentName in:application.
    ].
    
    component isNil ifTrue:[
        "/ search through all current applications
        candidates := OrderedCollection new.
        WindowGroup scheduledWindowGroups do:[:eachWG |
            |eachApp|

            (eachApp := eachWG application) notNil ifTrue:[
                component := self findComponent:componentName in:eachApp.
                component notNil ifTrue:[ 
                    candidates add:component
                ].
            ].
        ].
        
        candidates size == 1 ifTrue:[
            component := candidates first
        ] ifFalse:[    
            candidates notEmpty ifTrue:[
                self error:'multiple components found by name: ',componentName.
            ]    
        ].    
    ].    
    ^ component

    "Created: / 19-07-2019 / 12:02:30 / Claus Gittinger"
    "Modified: / 19-07-2019 / 16:44:30 / Claus Gittinger"
!

findComponent:componentName in:anApplication
    |component componentNameSymbol foundByName foundByTitle foundByLabel|

    (component := anApplication componentAt:componentName) notNil ifTrue:[^ component].
    (componentNameSymbol := componentName asSymbolIfInterned) notNil ifTrue:[
        (component := anApplication componentAt:componentNameSymbol) notNil ifTrue:[^ component].
    ].
    
    "/ mhmh - search through all widgets of anApplication; 
    "/ maybe it was not created via the builder/spec,
    "/ or it has changed its name.
    "/ look for: widget's name, widget's title, widget's label
    foundByName := OrderedCollection new. 
    foundByTitle := OrderedCollection new. 
    foundByLabel := OrderedCollection new.
    
    anApplication window allSubViewsDo:[:each |
        [
            each name = componentName ifTrue:[ foundByName add:each ].
        ] on:MessageNotUnderstood do:[:ex | ].
        [
            each title = componentName ifTrue:[ foundByTitle add:each ].
        ] on:MessageNotUnderstood do:[:ex | ].
        [
            each label = componentName ifTrue:[ foundByLabel add:each ].
        ] on:MessageNotUnderstood do:[:ex | ].
    ].
    foundByName notEmpty ifTrue:[
        self assert:(foundByName size == 1) message:'multiple components found by name'.
        ^ foundByName first.
    ].
    foundByTitle notEmpty ifTrue:[
        self assert:(foundByTitle size == 1) message:'multiple components found by title'.
        ^ foundByTitle first.
    ].
    foundByLabel notEmpty ifTrue:[
        self assert:(foundByLabel size == 1) message:'multiple components found by label'.
        ^ foundByLabel first.
    ].
    ^ component

    "Created: / 19-07-2019 / 11:36:21 / Claus Gittinger"
!

randomThankYou
    ^ #(
        'thank you, for watching'
        'thank you for watching'
        'thank you'
        'have a good day'
        'have fun'
        'have fun with expecco'
        'have fun with expecco, by the way: expecco comes from the latin word: peccare, which means: "to sin"'
        'happy hacking'
        'happy hacking, I hope you liked what you saw'
        'hope you liked it'
        'see you again'
        'please give feedback, and let us know, if you liked it'
        'if you have any questions, please contact exept'
        'if you need more information, please take a look at the wiki'
    ) atRandom

    "
     OperatingSystem speak:'have fun with expecco'
     OperatingSystem speak:'have fun with expecco, by the way: expecco comes from the latin word: peccare, which means: to sin'
     OperatingSystem speak:'happy hacking, I hope you liked what you saw'
     OperatingSystem speak:'please give feedback, and let us know, if you liked it'
     OperatingSystem speak:'if you have any questions, please contact exept'
     OperatingSystem speak:'if you need more information, please take a look at the wiki'
    "

    "Created: / 19-07-2019 / 21:39:18 / Claus Gittinger"
!

tell:message
    self talking ifTrue:[
        OperatingSystem speak:message.
    ].

    "Created: / 19-07-2019 / 14:57:50 / Claus Gittinger"
! !

!ShowMeHowItWorks methodsFor:'helpers - broken'!

click:buttonNr atPosition:position
    "press-release at position"
    
    |screen|

    screen := Screen current.
    
    screen setPointerPosition:position.    
    screen flush.
    self click:buttonNr

    "Created: / 19-07-2019 / 13:14:51 / Claus Gittinger"
! !

!ShowMeHowItWorks methodsFor:'helpers - mouse movement'!

circlePointerAroundComponent:component
    "circle around it a few times"
    
    self circlePointerAroundPosition:(component screenBounds center rounded)

    "Created: / 19-07-2019 / 13:12:35 / Claus Gittinger"
!

circlePointerAroundPosition:position
    "circle around it a few times"
    
    |screen stepDelayTime numCircles circlingSpeed radius|

    screen := Screen current.
    
    circlingSpeed := self circlingSpeed.    "/ time per round
    numCircles := self circlingCount.
    stepDelayTime := self pointerAnimationDelay.   "/ update interval
    
    radius := self circlingRadius.

    "/ move it around a few times
    1 to:numCircles do:[:round |
        |n angle|

        n := circlingSpeed / stepDelayTime. "/ nr of steps per circle
        angle := 360 / n.                   "/ angle-delta per step
        1 to:n do:[:step |
            |a x y|
            
            a := angle * step.
            "/ clockwise starting above the center
            x := position x + (radius * a degreesToRadians sin).
            y := position y + (radius * a degreesToRadians cos).
"/ Transcript showCR:(x@y).
            screen setPointerPosition:(x@y) rounded.
            screen flush.
            Delay waitFor:stepDelayTime.
        ].    
        "/ and back
        screen setPointerPosition:position rounded.
        screen flush.
        Delay waitFor:stepDelayTime.
    ].

    "Created: / 19-07-2019 / 13:12:40 / Claus Gittinger"
!

movePointerToComponent:aWidget
    "move the mouse to aWidget's center"
    
    self movePointerToPosition:(aWidget screenBounds center rounded).

    "Created: / 19-07-2019 / 13:11:33 / Claus Gittinger"
!

movePointerToComponent:aWidget offset:offset
    "move the mouse to position inside aWidget's"
    
    self movePointerToPosition:(aWidget screenBounds origin + offset) rounded.

    "Created: / 19-07-2019 / 16:18:58 / Claus Gittinger"
!

movePointerToComponent:aWidget speed:pixelsPerSecond
    "move the mouse to aWidget's center"
    
    self movePointerToPosition:(aWidget screenBounds center rounded) speed:pixelsPerSecond.

    "Created: / 20-07-2019 / 08:12:49 / Claus Gittinger"
!

movePointerToPosition:newPosition
    "move the mouse to newPosition"

    self movePointerToPosition:newPosition speed:self pointerMoveSpeed

    "Created: / 19-07-2019 / 12:57:30 / Claus Gittinger"
    "Modified: / 20-07-2019 / 08:12:34 / Claus Gittinger"
!

movePointerToPosition:newPosition speed:pixelsPerSecond
    "move the mouse to newPosition"
    
    |screen distance start numSteps moveTime stepDelayTime delta|

    screen := Screen current.
    start := screen pointerPosition.   

    distance := start dist:newPosition.
    moveTime := (distance / pixelsPerSecond) seconds.   "/ time to move
    stepDelayTime := self pointerAnimationDelay.        "/ update every 50ms
    
    numSteps := moveTime / stepDelayTime.
    numSteps = 0 ifTrue:[
        "/ already there
        ^ self
    ].
    
    delta := (newPosition - start) / numSteps.
    1 to:numSteps do:[:step |
        |p|
        
        p := (start + (delta * step)) rounded.
"/ Transcript showCR:p.
        screen setPointerPosition:p.
        screen flush.
        Delay waitFor:stepDelayTime.
    ].

    "Created: / 20-07-2019 / 08:12:07 / Claus Gittinger"
! !

!ShowMeHowItWorks methodsFor:'menu actions - mouse buttons'!

click:buttonNr inComponent:component
    "press-release in a component"

    |t|

    t := self shortClickTime.
    (component isKindOf:Button) ifTrue:[
        t := self longClickTime
    ].    
    self click:buttonNr inComponent:component clickTime:t

    "Created: / 19-07-2019 / 13:18:27 / Claus Gittinger"
    "Modified: / 19-07-2019 / 15:22:47 / Claus Gittinger"
!

click:buttonNr inComponent:component clickTime:clickTime 
    "press-release in a component"

    component simulateButtonPress:buttonNr at:(component extent // 2) sendDisplayEvent:false.
    Delay waitForSeconds:clickTime.
    component simulateButtonRelease:buttonNr at:(component extent // 2) sendDisplayEvent:false.

"/    self click:buttonNr atPosition:(component extent // 2)

    "Created: / 19-07-2019 / 15:21:05 / Claus Gittinger"
!

press:buttonNr
    "press at the current position"
    
    |position screen x y|

    screen := Screen current.
    position := screen pointerPosition.
    x := position x.
    y := position y.
    
    self movePointerToPosition:position.

    false "OperatingSystem isOSXlike" ifTrue:[
        |osxPos|

        osxPos := OperatingSystem getMousePosition.
        x := osxPos x rounded.
        y := osxPos y rounded.
        OperatingSystem generateButtonEvent:buttonNr down:true x:x y:y.
        ^ self.
    ].

    screen sendKeyOrButtonEvent:#buttonPress x:x y:y keyOrButton:buttonNr state:0 toViewId:(screen rootWindowId).
    screen flush.

    "Created: / 19-07-2019 / 13:52:38 / Claus Gittinger"
!

release:buttonNr
    "press-release at the current position"
    
    |position screen x y|

    screen := Screen current.
    position := screen pointerPosition.
    x := position x.
    y := position y.
    
    self movePointerToPosition:position.

    false "OperatingSystem isOSXlike" ifTrue:[
        |osxPos|

        osxPos := OperatingSystem getMousePosition.
        x := osxPos x rounded.
        y := osxPos y rounded.
        OperatingSystem generateButtonEvent:buttonNr down:false x:x y:y.
        ^ self.
    ].

    screen sendKeyOrButtonEvent:#buttonRelease x:x y:y keyOrButton:buttonNr state:0 toViewId:(screen rootWindowId).
    screen flush.

    "Created: / 19-07-2019 / 13:53:05 / Claus Gittinger"
! !

!ShowMeHowItWorks methodsFor:'running'!

doCommand:op
    |numArgs sel args method|

    op isArray ifTrue:[
        op first isArray ifTrue:[
            self doStream:op readStream.
            ^ self.
        ].
        
        "/ construct a selector from keyword parts at odd indices
        sel := ((op with:(1 to:op size) select:[:el :idx | idx odd]) asStringWith:'') asSymbol.
        "/ construct arg vector from parts at even indices
        args := op with:(1 to:op size) select:[:el :idx | idx even].
    ] ifFalse:[
        sel := op.
        numArgs := sel argumentCount.
        args := opStream next:numArgs.
    ].
    
    (self respondsTo:sel) ifFalse:[
        self error:'bad operation: ',sel
    ].
    method := self class lookupMethodFor:sel.
    (method hasAnnotation:#action) ifFalse:[self halt].
    
    lastResult := self perform:sel withArguments:args.
    ^ lastResult
    
"<<END
     ShowMeHowItWorks do:#(
        showing: 'Choose the number of arguments'
        do: (
            moveTo: NumberOfArguments
            select: '1'
        )    
        showing: 'Click into the "receiver" field'
        do: (
            moveTo: ReceiverEditor
            click: ReceiverEditor
        )
        showing: 'Enter a value (or expression) into "receiver" field'
        do: (
            enter: '100'
        )
        showing: 'Click into the "first argument" field'
        do: (
            moveTo: Arg1Editor
            click: ReceiverEditor
        )
        showing: 'Enter a value (or expression) into "receiver" field'
        do: (
            enter: '100'
        )
     )
END"

    "Created: / 19-07-2019 / 15:34:55 / Claus Gittinger"
!

doStream:specStream
    |previousStream resources|

    resources := self class classResources.
    
    previousStream := opStream.
    [
        opStream := specStream.
        [opStream atEnd] whileFalse:[
            self nextCommand.
            Display shiftDown ifTrue:[
                self tell:(resources string:'you pressed the shift key, do you want to stop the show?').
                (Dialog confirm:(resources stringWithCRs:'Stop the demonstration?'))
                ifTrue:[
                    self tell:(resources string:'you stopped the show,').
                    self tell:(resources string:(self randomThankYou)).
                    ^ AbortOperationRequest raise
                ].    
            ].    
        ].    
    ] ensure:[
        opStream := previousStream
    ].
    
"<<END
     ShowMeHowItWorks do:#(
        showing: 'Choose the number of arguments'
        do: (
            moveTo: NumberOfArguments
            select: '1'
        )    
        showing: 'Click into the "receiver" field'
        do: (
            moveTo: ReceiverEditor
            click: ReceiverEditor
        )
        showing: 'Enter a value (or expression) into "receiver" field'
        do: (
            enter: '100'
        )
        showing: 'Click into the "first argument" field'
        do: (
            moveTo: Arg1Editor
            click: ReceiverEditor
        )
        showing: 'Enter a value (or expression) into "receiver" field'
        do: (
            enter: '100'
        )
     )
END"

    "Created: / 19-07-2019 / 10:52:24 / Claus Gittinger"
    "Modified: / 19-07-2019 / 21:41:43 / Claus Gittinger"
!

nextCommand
    self doCommand:(opStream next).

"<<END
     ShowMeHowItWorks do:#(
        showing: 'Choose the number of arguments'
        do: (
            moveTo: NumberOfArguments
            select: '1'
        )    
        showing: 'Click into the "receiver" field'
        do: (
            moveTo: ReceiverEditor
            click: ReceiverEditor
        )
        showing: 'Enter a value (or expression) into "receiver" field'
        do: (
            enter: '100'
        )
        showing: 'Click into the "first argument" field'
        do: (
            moveTo: Arg1Editor
            click: ReceiverEditor
        )
        showing: 'Enter a value (or expression) into "receiver" field'
        do: (
            enter: '100'
        )
     )
END"

    "Created: / 19-07-2019 / 10:54:04 / Claus Gittinger"
    "Modified: / 19-07-2019 / 15:35:15 / Claus Gittinger"
! !

!ShowMeHowItWorks class methodsFor:'documentation'!

version_CVS
    ^ '$Header$'
! !