Skip to content

Commit

Permalink
Change some isNil ifTrue: and variants to use ifNil: and friends.
Browse files Browse the repository at this point in the history
Remove an unused variable in OSWindowWorldMorph (it was assigned but never used again)
  • Loading branch information
gcotelli committed Jul 19, 2019
1 parent 2c335da commit 700246b
Show file tree
Hide file tree
Showing 6 changed files with 56 additions and 52 deletions.
30 changes: 18 additions & 12 deletions src/Alien-Core/Callback.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -120,26 +120,32 @@ Callback class >> ensureNotifiedAtStartup [
]

{ #category : #evaluation }
Callback class >> evaluateCallbackForContext: callbackContext [ "<VMCallbackContext32|VMCallbackContext64> ^<FFICallbackReturnValue>"
(ThunkToCallbackMap
Callback class >> evaluateCallbackForContext: callbackContext [

"<VMCallbackContext32|VMCallbackContext64> ^<FFICallbackReturnValue>"

( ThunkToCallbackMap
at: callbackContext thunkp
ifAbsent: [^self error: 'could not locate Callback instance corresponding to thunk address'])
ifNil: [self error: 'Callback instance for this thunk address has been garbage collected']
ifNotNil:
[:callback|
^callback valueInContext: callbackContext]
ifAbsent: [ ^ self error: 'could not locate Callback instance corresponding to thunk address' ] )
ifNil: [ self error: 'Callback instance for this thunk address has been garbage collected' ]
ifNotNil: [ :callback | ^ callback valueInContext: callbackContext ]
]

{ #category : #evaluation }
Callback class >> evaluateCallbackForThunk: thunkPtr "<Integer>" stack: stackPtr [ "<Integer>" "^<FFICallbackReturnValue>"
Callback class >> evaluateCallbackForThunk: thunkPtr stack: stackPtr [

"<Integer>"
"^<FFICallbackReturnValue>"

<legacy>
| callback |

callback := ThunkToCallbackMap
at: thunkPtr
ifAbsent: [^self error: 'could not locate Callback instance corresponding to thunk address'].
callback isNil
ifTrue: [self error: 'Callback instance for this thunk address has been garbage collected']
ifFalse: [^callback valueWithStackPointer: stackPtr]
ifAbsent: [ ^ self error: 'could not locate Callback instance corresponding to thunk address' ].
callback
ifNil: [ self error: 'Callback instance for this thunk address has been garbage collected' ]
ifNotNil: [ ^ callback valueWithStackPointer: stackPtr ]
]

{ #category : #finalization }
Expand Down
8 changes: 3 additions & 5 deletions src/Morphic-Base/HaloMorph.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -706,11 +706,9 @@ HaloMorph >> createHandleAt: aPoint color: aColor iconName: iconName [
handle borderColor: aColor muchDarker.
handle wantsYellowButtonMenu: false.
iconName
ifNotNil: [ | form |

form := self iconNamed: iconName.
form isNil
ifFalse: [ | image |
ifNotNil: [ ( self iconNamed: iconName )
ifNotNil: [ :form |
| image |

image := ImageMorph new.
image form: form.
Expand Down
2 changes: 1 addition & 1 deletion src/NECompletion/TestCompletionModel.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -27,7 +27,7 @@ TestCompletionModel >> clazz [
{ #category : #accessing }
TestCompletionModel >> clazz: anObject [
clazz := anObject.
clazz isNil ifTrue: [ clazz := UndefinedObject ]
clazz ifNil: [ clazz := UndefinedObject ]
]

{ #category : #accessing }
Expand Down
15 changes: 7 additions & 8 deletions src/OSWindow-Core/OSWindowWorldMorph.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -14,8 +14,7 @@ Class {
'display',
'closeCallback',
'isResizeable',
'osWindow',
'session'
'osWindow'
],
#category : #'OSWindow-Core-Morphic'
}
Expand Down Expand Up @@ -117,8 +116,7 @@ OSWindowWorldMorph >> osWindowRenderer [

{ #category : #'session management' }
OSWindowWorldMorph >> recreateOSWindow [
| attributes driver |
session := Smalltalk session.
| attributes driver |
attributes := OSWindowAttributes new.
attributes
extent: self extent;
Expand Down Expand Up @@ -155,10 +153,11 @@ OSWindowWorldMorph >> title: aTitle [

{ #category : #private }
OSWindowWorldMorph >> updateDisplay [
display isNil ifTrue: [
display := Form extent: self extent depth: 32.
worldState display: display
]

display
ifNil: [ display := Form extent: self extent depth: 32.
worldState display: display
]
]

{ #category : #accessing }
Expand Down
10 changes: 4 additions & 6 deletions src/Spec-Core/ButtonPresenter.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -73,18 +73,16 @@ ButtonPresenter >> addShortcutTipFor: aString [

{ #category : #private }
ButtonPresenter >> addShortcutTipFor: aCharacter on: aString [

| index text |
aString isNil ifTrue: [ ^ nil ].

aString ifNil: [ ^ nil ].
text := aString asText.
aCharacter ifNil: [ ^ text ].
index := aString asLowercase indexOf: aCharacter asLowercase.
index isZero ifTrue: [ ^ text ].

^ text
addAttribute: (TextEmphasis underlined)
from: index
to: index;
addAttribute: TextEmphasis underlined from: index to: index;
yourself
]

Expand Down
43 changes: 23 additions & 20 deletions src/Spec-MorphicAdapters/NotebookMorph.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -213,30 +213,33 @@ NotebookMorph >> suspendAnnouncementsDuring: aBlock [

{ #category : #private }
NotebookMorph >> updatePageIndex: index [

"Change to the given page index, update the toolbar and send the announcement"
| page oldPage |

index = 0 ifTrue: [ ^ self ].


| oldPage |

index = 0
ifTrue: [ ^ self ].
oldPage := self tabSelectorMorph selectedTab.
page := self pageMorph.
page isNil
ifTrue: [
self contentMorph addMorph: (self pageAt: index).]
ifFalse: [ | pageBounds |
self pageMorph
ifNil: [ self contentMorph addMorph: ( self pageAt: index ) ]
ifNotNil: [ :page | | pageBounds |

pageBounds := self pageMorph bounds.
self contentMorph replaceSubmorph: page by: (self pageAt: index).
self flag: 'Without setting here the bounds the pange moves a few pizels when refreshing the inspector'.
self contentMorph replaceSubmorph: page by: ( self pageAt: index ).
self
flag: 'Without setting here the bounds the pange moves a few pizels when refreshing the inspector'.
self pageMorph bounds: pageBounds.
self pageMorph layoutChanged ].

self pageMorph layoutChanged
].
self headerMorph layoutChanged.
self pageMorph layoutChanged.
self adoptPaneColor: (self owner ifNil: [self]) paneColor.
(self tabSelectorMorph tabs at: index) font: self tabSelectorMorph font.

self announcer announce: (NotebookPageChanged new
page: (self pages at: index);
oldPage: oldPage;
pageIndex: index)
self adoptPaneColor: ( self owner ifNil: [ self ] ) paneColor.
( self tabSelectorMorph tabs at: index ) font: self tabSelectorMorph font.
self announcer
announce:
( NotebookPageChanged new
page: ( self pages at: index );
oldPage: oldPage;
pageIndex: index )
]

0 comments on commit 700246b

Please sign in to comment.