Skip to content

Commit

Permalink
Enhancements to StringRequestMorph
Browse files Browse the repository at this point in the history
  • Loading branch information
jvuletich committed Nov 29, 2024
1 parent 7a70c79 commit 2be82a0
Show file tree
Hide file tree
Showing 3 changed files with 201 additions and 0 deletions.
Original file line number Diff line number Diff line change
@@ -0,0 +1,92 @@
'From Cuis7.1 [latest update: #6868] on 28 November 2024 at 3:25:06 pm'!

!Object methodsFor: 'user interface' stamp: 'len 5/20/2020 04:00:44'!
request: queryString do: acceptBlock
"Non-modal. Method returns immediately.
Uses acceptBlock to process user's answer later, when provided by them."
^ self request: queryString initialAnswer: '' verifying: [:aString| true] do: acceptBlock orCancel: []! !

!Object methodsFor: 'user interface' stamp: 'len 5/20/2020 04:11:48'!
request: queryString initialAnswer: defaultAnswer do: acceptBlock
"Non-modal. Method returns immediately.
Uses acceptBlock to process user's answer later, when provided by them."
^ self request: queryString initialAnswer: defaultAnswer verifying: [:aString| true] do: acceptBlock orCancel: []! !

!Object methodsFor: 'user interface' stamp: 'len 5/20/2020 03:59:45'!
request: queryString initialAnswer: defaultAnswer do: acceptBlock orCancel: cancelBlock
"Non-modal. Method returns immediately.
Uses acceptBlock and cancelBlock to process user's answer later, when provided by them."
^ self request: queryString initialAnswer: defaultAnswer verifying: [:aString| true] do: acceptBlock orCancel: cancelBlock! !

!Object methodsFor: 'user interface' stamp: 'len 5/20/2020 07:37:39'!
request: queryString initialAnswer: defaultAnswer verifying: validationBlock do: acceptBlock
"Non-modal. Method returns immediately.
Uses acceptBlock to process user's answer later, when provided by them."
^ self request: queryString initialAnswer: defaultAnswer verifying: validationBlock do: acceptBlock orCancel: []! !

!Object methodsFor: 'user interface' stamp: 'jmv 5/23/2020 21:00:11'!
request: queryString initialAnswer: defaultAnswer verifying: validationBlock do: acceptBlock orCancel: cancelBlock
"Non-modal. Method returns immediately.
Uses acceptBlock and cancelBlock to process user's answer later, when provided by them."
^ UISupervisor ui request: queryString initialAnswer: defaultAnswer verifying: validationBlock do: acceptBlock orCancel: cancelBlock! !


!StringRequestMorph class methodsFor: 'instance creation' stamp: 'hlsf 6/24/2022 09:32:19'!
request: queryString centeredAt: aPoint initialAnswer: defaultAnswer validationBlock: validationBlock acceptBlock: acceptBlock cancelBlock: cancelBlock
"Non-modal. Method returns immediately.
Uses acceptBlock and cancelBlock to process user's answer later, when provided by them."
| answer |
answer := self newColumn
setQuery: queryString
initialAnswer: defaultAnswer;
validationBlock: validationBlock;
acceptBlock: acceptBlock;
cancelBlock: cancelBlock.
self runningWorld addMorph: answer centeredNear: aPoint - self deltaToTextPane.
(Preferences at: #focusFollowsMouse) ifFalse: [answer textBox focusText].
^ answer! !

!StringRequestMorph class methodsFor: 'instance creation' stamp: 'HAW 9/23/2020 18:47:29'!
request: queryString initialAnswer: defaultAnswer do: acceptBlock
"Non-modal. Method returns immediately.
Uses acceptBlock to process user's answer later, when provided by them."

^ self
request: queryString
centeredAt: self runningWorld activeHand morphPosition
initialAnswer: defaultAnswer
validationBlock: [:aString| true]
acceptBlock: acceptBlock
cancelBlock: []! !

!StringRequestMorph class methodsFor: 'instance creation' stamp: 'jmv 11/28/2024 15:14:52'!
request: queryString initialAnswer: defaultAnswer orCancel: cancelBlock
"Modal. This method returns after an answer is provided."

| morph world |
morph := self newColumn
setQuery: queryString
initialAnswer: defaultAnswer.
world := self runningWorld.
world ifNil: [
| answer |
answer := self. "Just a marker object, can not use nil, because it is a possible answer (if user cancels)"
UISupervisor whenUIinSafeState: [ answer := self request: queryString initialAnswer: defaultAnswer orCancel: cancelBlock ].
[ answer == self ] whileTrue: [ Processor yield ].
^answer ].
world addMorph: morph centeredNear: world activeHand morphPosition - self deltaToTextPane.
^ morph getUserResponseOrCancel: cancelBlock! !

!StringRequestMorph class methodsFor: 'instance creation' stamp: 'HAW 9/23/2020 18:48:44'!
request: queryString initialAnswer: defaultAnswer verifying: validationBlock do: acceptBlock orCancel: cancelBlock
"Non-modal. Method returns immediately.
Uses acceptBlock and cancelBlock to process user's answer later, when provided by them."

^ self
request: queryString
centeredAt: self runningWorld activeHand morphPosition
initialAnswer: defaultAnswer
validationBlock: validationBlock
acceptBlock: acceptBlock
cancelBlock: cancelBlock! !

Original file line number Diff line number Diff line change
@@ -0,0 +1,54 @@
'From Cuis7.1 [latest update: #6869] on 28 November 2024 at 4:29:21 pm'!

!Object methodsFor: 'user interface' stamp: 'jmv 11/28/2024 11:43:36'!
request: queryString initialAnswer: defaultAnswer verifying: validationBlock
"Modal. This method returns when an answer is provided."

^ UISupervisor ui request: queryString initialAnswer: defaultAnswer verifying: validationBlock! !

!Object methodsFor: 'user interface' stamp: 'jmv 11/28/2024 11:39:58'!
request: queryString initialAnswer: defaultAnswer verifying: validationBlock orCancel: cancelBlock
"Modal. This method returns when an answer is provided."

^ UISupervisor ui request: queryString initialAnswer: defaultAnswer verifying: validationBlock orCancel: cancelBlock! !


!StringRequestMorph class methodsFor: 'instance creation' stamp: 'jmv 11/28/2024 11:42:50'!
request: queryString initialAnswer: defaultAnswer verifying: validationBlock
"Modal. This method returns when an answer is provided."

^self request: queryString initialAnswer: defaultAnswer verifying: validationBlock orCancel: []! !

!StringRequestMorph class methodsFor: 'instance creation' stamp: 'jmv 11/28/2024 11:38:48'!
request: queryString initialAnswer: defaultAnswer verifying: validationBlock orCancel: cancelBlock
"Modal. This method returns when an answer is provided."

| morph world |
morph := self newColumn
setQuery: queryString
initialAnswer: defaultAnswer;
validationBlock: validationBlock.
world := self runningWorld.
world ifNil: [
| answer |
answer := self. "Just a marker object, can not use nil, because it is a possible answer (if user cancels)"
UISupervisor whenUIinSafeState: [
answer := self request: queryString initialAnswer: defaultAnswer verifying: validationBlock orCancel: cancelBlock ].
[ answer == self ] whileTrue: [ Processor yield ].
^answer ].
world addMorph: morph centeredNear: world activeHand morphPosition - self deltaToTextPane.
^ morph getUserResponseOrCancel: cancelBlock! !


!WorldMorph methodsFor: 'ui services' stamp: 'jmv 11/28/2024 11:46:28'!
request: queryString initialAnswer: defaultAnswer verifying: validationBlock
"Modal. This method returns when an answer is provided."

^ StringRequestMorph request: queryString initialAnswer: defaultAnswer verifying: validationBlock! !

!WorldMorph methodsFor: 'ui services' stamp: 'jmv 11/28/2024 11:39:50'!
request: queryString initialAnswer: defaultAnswer verifying: validationBlock orCancel: cancelBlock
"Modal. This method returns when an answer is provided."

^ StringRequestMorph request: queryString initialAnswer: defaultAnswer verifying: validationBlock orCancel: cancelBlock! !

Original file line number Diff line number Diff line change
@@ -0,0 +1,55 @@
'From Cuis7.1 [latest update: #6870] on 28 November 2024 at 4:34:43 pm'!
!classDefinition: #StringRequestMorph category: #'Morphic-Composite Widgets'!
LayoutMorph subclass: #StringRequestMorph
instanceVariableNames: 'response acceptBlock cancelBlock validationBlock textMorph titleLabelMorph '
classVariableNames: ''
poolDictionaries: ''
category: 'Morphic-Composite Widgets'!

!StringRequestMorph methodsFor: 'accessing' stamp: 'jmv 11/28/2024 15:40:51'!
response: aText
"Sent when text pane accepts."
| validationResult |
response := aText.

"ValidationBlock can evaluate to:
true: validation passed
false: validation failed
a String: validation failed, feedback to user."
validationBlock ifNotNil: [
validationResult := validationBlock value: aText asPlainString.
validationResult == true ifFalse: [
validationResult isString ifTrue: [
titleLabelMorph contents: validationResult ].
self flash.
^ false ]].

[
acceptBlock ifNotNil: [acceptBlock value: aText asPlainString]
] ensure: [ self delete ].
^ true! !

!StringRequestMorph methodsFor: 'initialization' stamp: 'jmv 11/28/2024 15:40:04'!
addTitle: aString
| titleBarMorph pp w |
titleBarMorph := ColoredBoxMorph new.
titleBarMorph color: Theme current menuTitleBar.
pp := `8@2`.
aString asPlainString linesDo: [ :line |
titleLabelMorph := LabelMorph new
contents: line;
font: (Preferences at: #standardMenuFont) bold.
titleBarMorph addMorphBack: titleLabelMorph position: pp.
pp := pp + (0@(titleLabelMorph morphHeight+2)) ].
w := titleBarMorph submorphs inject: 0 into: [ :prev :each |
prev max: each morphWidth ].
titleBarMorph morphExtent: (w + 24) @ (pp y).
self addMorphKeepMorphHeight: titleBarMorph.
^titleBarMorph morphExtent! !

!classDefinition: #StringRequestMorph category: #'Morphic-Composite Widgets'!
LayoutMorph subclass: #StringRequestMorph
instanceVariableNames: 'response acceptBlock cancelBlock validationBlock textMorph titleLabelMorph'
classVariableNames: ''
poolDictionaries: ''
category: 'Morphic-Composite Widgets'!

0 comments on commit 2be82a0

Please sign in to comment.