Skip to content

Commit

Permalink
40574
Browse files Browse the repository at this point in the history
15192 revert 14890
	https://pharo.fogbugz.com/f/cases/15192

15151 TextInputFieldModel creation is slow
	https://pharo.fogbugz.com/f/cases/15151

15196 Simple before and after links with minimal disturbance
	https://pharo.fogbugz.com/f/cases/15196

15086 Ctrl + Arrow Behaviour
	https://pharo.fogbugz.com/f/cases/15086

http://files.pharo.org/image/40/40574.zip
  • Loading branch information
Jenkins Build Server authored and ci committed Mar 22, 2015
1 parent c936b07 commit 9129ade
Show file tree
Hide file tree
Showing 18 changed files with 66 additions and 47 deletions.
Expand Up @@ -39,7 +39,9 @@ generateKeyboardEvent: evtBuf

self flag: #fixme.
"This piece of code handles the creation of scrolling events. When a scroll is done by the user, the VM forwards a keystroke event with the up/down key. So we reconvert it to a MouseWheelEvent in that case."
(type = #keystroke and: [(buttons anyMask: 16) and: [ charCode asCharacter isArrow ]])
(type = #keystroke
and: [(buttons anyMask: 16)
and: [{Character arrowUp. Character arrowDown} includes: (charCode asCharacter)]])
ifTrue: [^ MouseWheelEvent
fromCharacter: charCode asCharacter
position: lastMouseEvent cursorPoint
Expand Down
@@ -1,5 +1,5 @@
updateMethodList: aMethodOrNil

self update: #getMethodItem:.
self selectMethod: aMethodOrNil.
aMethodOrNil ifNotNil: [
Expand Down
Expand Up @@ -7,8 +7,9 @@ updateOnClassSelection
self setWindowTitle.
self resetCategoriesListSelection.
self resetMethodsListSelection.

self updateCategoryAndMethodList: previousMethod.
"self updateCategoryAndMethodList: previousMethod
led to 14890 and was reverted"
self updateCategoryAndMethodList.
self changed: #isAClassSelected.
self changed: #getComments.
self changed: #instanceButtonLabel.
Expand Down
@@ -1,4 +1,9 @@
visitNode: aNode
methodBuilder mapToNode: aNode.
super visitNode: aNode.
methodBuilder popMap.
aNode hasMetalink
ifTrue: [
aNode beforeLinks do: [ :link | self visitNode: (link hook parent: aNode) ].
super visitNode: aNode.
aNode afterLinks do: [ :link | self visitNode: (link hook parent: aNode) ] ]
ifFalse: [ super visitNode: aNode ].
methodBuilder popMap
@@ -1,5 +1,5 @@
TestCase subclass: #ReflectiveMethodTest
instanceVariableNames: ''
instanceVariableNames: 'tag'
classVariableNames: ''
poolDictionaries: ''
category: 'Reflectivity-Tests'
@@ -0,0 +1,2 @@
tagExec
tag := #yes.
@@ -1,10 +1,12 @@
testUninstallLinkAndRun
| sendNode link |
sendNode := (ReflectivityExamples>>#exampleMethod) ast body statements first value.
link := MetaLink new metaObject: Halt; selector: #now.
link := MetaLink new metaObject: self; selector: #tagExec.
sendNode link: link.
self assert: sendNode hasMetalink.
self assert: (ReflectivityExamples>>#exampleMethod) class = ReflectiveMethod.
self assert: (tag isNil).
self assert: (ReflectivityExamples new exampleMethod = 5).
self assert: (tag = #yes).
self assert: (ReflectivityExamples>>#exampleMethod) class = CompiledMethod.
link uninstall.
@@ -0,0 +1,3 @@
uninstallAll
<script>
self allInstances do: #uninstall.
6 changes: 2 additions & 4 deletions Reflectivity.package/MetaLink.class/instance/ast/hook.st
@@ -1,8 +1,6 @@
hook
| hook meta arg |
meta := self metaObject isSymbol
ifFalse: [ RBMessageNode receiver: self asLiteralNode selector: #metaObject ].
hook := RBMessageNode receiver: meta selector: self selector arguments: (self arguments collect: #asLiteralNode).
| hook arg |
hook := RBMessageNode receiver: (RBLiteralNode value: metaObject) selector: self selector arguments: (self arguments collect: #asLiteralNode).
self hasCondition
ifTrue: [
arg := (RBBlockNode body: hook asSequenceNode).
Expand Down
@@ -0,0 +1,2 @@
afterLinks
^ self links select: [ :each | each control == #after ]
@@ -0,0 +1,2 @@
beforeLinks
^ self links select: [ :each | each control == #before ]
@@ -1,4 +1,4 @@
script573
script574

^ 'AST-Core-TheIntegrator.281.mcz
AST-Interpreter-Core-TheIntegrator.140.mcz
Expand Down Expand Up @@ -154,7 +154,7 @@ MonticelloFileTree-FileSystem-Utilities-MarcusDenker.32.mcz
MonticelloGUI-TheIntegrator.331.mcz
MonticelloMocks-EstebanLorenzano.2.mcz
Morphic-Base-TheIntegrator.441.mcz
Morphic-Core-TheIntegrator.161.mcz
Morphic-Core-StephaneDucasse.163.mcz
Morphic-Examples-TheIntegrator.40.mcz
Morphic-Widgets-Basic-TheIntegrator.41.mcz
Morphic-Widgets-ColorPicker-StephaneDucasse.17.mcz
Expand Down Expand Up @@ -183,7 +183,7 @@ NativeBoost-Pools-CamilloBruni.13.mcz
NativeBoost-Tests-TheIntegrator.90.mcz
NativeBoost-Unix-MarcusDenker.17.mcz
NativeBoost-Win32-TheIntegrator.57.mcz
Nautilus-TheIntegrator.901.mcz
Nautilus-StephaneDucasse.903.mcz
Nautilus-Tests-TheIntegrator.10.mcz
NautilusCommon-TheIntegrator.258.mcz
NautilusRefactoring-TheIntegrator.211.mcz
Expand All @@ -200,7 +200,7 @@ NonInteractiveTranscript-TheIntegrator.15.mcz
OSWindow-Core-EstebanLorenzano.18.mcz
OSWindow-SDL2-EstebanLorenzano.19.mcz
OSWindow-VM-IgorStasenko.2.mcz
OpalCompiler-Core-TheIntegrator.634.mcz
OpalCompiler-Core-StephaneDucasse.636.mcz
OpalCompiler-Tests-TheIntegrator.277.mcz
OpalDecompiler-TheIntegrator.31.mcz
OpalTools-TheIntegrator.16.mcz
Expand All @@ -223,8 +223,8 @@ Refactoring-Tests-Changes-MarcusDenker.38.mcz
Refactoring-Tests-Core-TheIntegrator.121.mcz
Refactoring-Tests-Critics-MarcusDenker.25.mcz
Refactoring-Tests-Environment-StephaneDucasse.11.mcz
Reflectivity-TheIntegrator.23.mcz
Reflectivity-Tests-TheIntegrator.12.mcz
Reflectivity-StephaneDucasse.25.mcz
Reflectivity-Tests-StephaneDucasse.14.mcz
Regex-Core-MarcusDenker.33.mcz
Regex-Help-MarcusDenker.5.mcz
Regex-Tests-Core-MarcusDenker.9.mcz
Expand Down Expand Up @@ -254,7 +254,7 @@ Slot-TheIntegrator.591.mcz
Slot-Tests-StephaneDucasse.31.mcz
SmartSuggestions-TheIntegrator.147.mcz
SmartSuggestions-Tests-TheIntegrator.2.mcz
Spec-Core-StephaneDucasse.385.mcz
Spec-Core-StephaneDucasse.386.mcz
Spec-Debugger-TheIntegrator.236.mcz
Spec-Examples-TheIntegrator.89.mcz
Spec-Help-TheIntegrator.8.mcz
Expand Down

This file was deleted.

@@ -0,0 +1,18 @@
update40574
"self new update40574"
self withUpdateLog: '15192 revert 14890
https://pharo.fogbugz.com/f/cases/15192
15151 TextInputFieldModel creation is slow
https://pharo.fogbugz.com/f/cases/15151
15196 Simple before and after links with minimal disturbance
https://pharo.fogbugz.com/f/cases/15196
15086 Ctrl + Arrow Behaviour
https://pharo.fogbugz.com/f/cases/15086
'.
self loadTogether: self script574 merge: false.
self flushCaches.
self cleanRepositories.
@@ -1,14 +1,14 @@
commentForCurrentUpdate
^ '15145 Spec TabManager selectedTab returns nil after first opening
https://pharo.fogbugz.com/f/cases/15145
^ '15192 revert 14890
https://pharo.fogbugz.com/f/cases/15192
15182 add basic inspector option
https://pharo.fogbugz.com/f/cases/15182
15151 TextInputFieldModel creation is slow
https://pharo.fogbugz.com/f/cases/15151
15195 test for redefined Slots on class side
https://pharo.fogbugz.com/f/cases/15195
15196 Simple before and after links with minimal disturbance
https://pharo.fogbugz.com/f/cases/15196
15188 Color ariphmetical operations are broken
https://pharo.fogbugz.com/f/cases/15188
15086 Ctrl + Arrow Behaviour
https://pharo.fogbugz.com/f/cases/15086
'
@@ -0,0 +1,2 @@
enableGlobalsCompletion
self entryCompletion: self globalsEntryCompletion
Expand Up @@ -4,7 +4,7 @@ initialize

ghostText := '' asValueHolder.
acceptOnCR := true asValueHolder.
entryCompletion := self defaultEntryCompletion asValueHolder.
entryCompletion := nil asValueHolder.
isEncrypted := false asValueHolder.

ghostText whenChangedDo: [ :txt | self changed: #ghostText: with: { txt } ].
Expand Down
@@ -1,4 +1,4 @@
defaultEntryCompletion
globalsEntryCompletion

| applicants |
applicants := (Array
Expand Down

0 comments on commit 9129ade

Please sign in to comment.