Skip to content

Commit

Permalink
Replace every & or | with and: and or: (issue 446)
Browse files Browse the repository at this point in the history
  • Loading branch information
Hernán Morales Durand committed Jan 5, 2023
1 parent fefc39a commit 521f055
Show file tree
Hide file tree
Showing 9 changed files with 79 additions and 75 deletions.
57 changes: 28 additions & 29 deletions smalltalksrc/VMMaker/BitBltSimulation.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -625,7 +625,7 @@ BitBltSimulation >> alphaBlendConst: sourceWord with: destinationWord paintMode:
unAlpha := 255 - sourceAlpha.
result := destinationWord.
destPPW = 1 ifTrue:["32bpp blends include alpha"
paintMode & (sourceWord = 0) "painting a transparent pixel" ifFalse:[
(paintMode and: [ sourceWord = 0 ]) "painting a transparent pixel" ifFalse:[

blendRB := ((sourceWord bitAnd: 16rFF00FF) * sourceAlpha) +
((destinationWord bitAnd: 16rFF00FF) * unAlpha) + 16rFF00FF. "blendRB red and blue"
Expand All @@ -647,8 +647,8 @@ BitBltSimulation >> alphaBlendConst: sourceWord with: destinationWord paintMode:
1 to: destPPW do:[:j |
sourcePixVal := sourceShifted bitAnd: pixMask.
((maskShifted bitAnd: pixMask) = 0 "no effect if outside of dest rectangle"
or: [paintMode & (sourcePixVal = 0) "or painting a transparent pixel"])
ifFalse:
or: [ (paintMode and: [ sourcePixVal = 0 ]) "or painting a transparent pixel"])
ifFalse:
[destPixVal := destShifted bitAnd: pixMask.
pixBlend := 0.
1 to: 3 do:
Expand Down Expand Up @@ -1034,30 +1034,29 @@ BitBltSimulation >> bitXor: sourceWord with: destinationWord [
{ #category : #setup }
BitBltSimulation >> checkSourceOverlap [
"check for possible overlap of source and destination"
"ar 10/19/1999: This method requires surfaces to be locked."
| t |

<inline: true>
(sourceForm = destForm and: [dy >= sy]) ifTrue:
[dy > sy ifTrue:
["have to start at bottom"
vDir := -1.
sy := sy + bbH - 1.
dy := dy + bbH - 1]
ifFalse:
[(dy = sy) & (dx > sx) ifTrue:
["y's are equal, but x's are backward"
hDir := -1.
sx := sx + bbW - 1.
"start at right"
dx := dx + bbW - 1.
"and fix up masks"
nWords > 1 ifTrue:
[t := mask1.
mask1 := mask2.
mask2 := t]]].
| t |
(sourceForm = destForm and: [ dy >= sy ]) ifTrue: [
dy > sy
ifTrue: [ "have to start at bottom"
vDir := -1.
sy := sy + bbH - 1.
dy := dy + bbH - 1 ]
ifFalse: [
(dy = sy and: [ dx > sx ]) ifTrue: [ "y's are equal, but x's are backward"
hDir := -1.
sx := sx + bbW - 1.
"start at right"
dx := dx + bbW - 1.
"and fix up masks"
nWords > 1 ifTrue: [
t := mask1.
mask1 := mask2.
mask2 := t ] ] ].
"Dest inits may be affected by this change"
destIndex := destBits + (dy * destPitch) + ((dx // destPPW) *4).
destDelta := (destPitch * vDir) - (4 * (nWords * hDir))]
destIndex := destBits + (dy * destPitch) + (dx // destPPW * 4).
destDelta := destPitch * vDir - (4 * (nWords * hDir)) ]
]

{ #category : #'combination rules' }
Expand Down Expand Up @@ -1213,11 +1212,11 @@ BitBltSimulation >> copyBitsFastPathSpecialised [

"we skip the tryCopyingBitsQuickly and leave that to falback code"

(combinationRule = 30) | (combinationRule = 31) ifTrue:
["Check and fetch source alpha parameter for alpha blend"
(combinationRule = 30 or: [ combinationRule = 31 ])
ifTrue: ["Check and fetch source alpha parameter for alpha blend"
interpreterProxy methodArgumentCount = 1
ifTrue: [sourceAlpha := interpreterProxy stackIntegerValue: 0.
(interpreterProxy failed not and: [(sourceAlpha >= 0) & (sourceAlpha <= 255)])
(interpreterProxy failed not and: [ sourceAlpha >= 0 and: [ sourceAlpha <= 255 ]])
ifFalse: [^ interpreterProxy primitiveFail]]
ifFalse: [^ interpreterProxy primitiveFail]].

Expand All @@ -1228,7 +1227,7 @@ BitBltSimulation >> copyBitsFastPathSpecialised [
"self performCopyLoop."

"this is done inversely to plain copyBitsLockedAndClipped"
(combinationRule ~= 22) & (combinationRule ~= 32) ifTrue:
(combinationRule ~= 22 and: [ combinationRule ~= 32 ]) ifTrue:
["zero width and height; return the count"
affectedL := dx.
affectedR := dx + bbW.
Expand Down
4 changes: 2 additions & 2 deletions smalltalksrc/VMMaker/CogARMv8Compiler.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -2015,7 +2015,7 @@ CogARMv8Compiler >> concretizeLd1VrRMw [
offset := operands at: 3.
opCode := 2r0111. "TODO support multiple-register variants"

(offset = 0 | (offset = 16))
(offset = 0 or: [ offset = 16 ])
ifTrue: [
size = 64
ifTrue: [ q := 1. t := 11 ]
Expand Down Expand Up @@ -3120,7 +3120,7 @@ CogARMv8Compiler >> concretizeSt1VrRMw [
offset := operands at: 3.
opCode := 2r0111. "TODO support multiple-register variants"

(offset = 0 | (offset = 16))
(offset = 0 or: [ offset = 16 ])
ifTrue: [
size = 64
ifTrue: [ q := 1. t := 11 ]
Expand Down
13 changes: 8 additions & 5 deletions smalltalksrc/VMMaker/CogSimStackEntry.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -307,19 +307,22 @@ CogSimStackEntry >> register: anObject [
{ #category : #accessing }
CogSimStackEntry >> registerMask [
"Answer a bit mask for the receiver's register, if any."
^ ((type = SSBaseOffset) | (type = SSRegister) | (type = SSVectorRegister))
ifTrue: [ cogit registerMaskFor: register ]
ifFalse: [ 0 ]
^ (type = SSBaseOffset) or: [
(type = SSRegister or: [ type = SSVectorRegister ])
ifTrue: [ cogit registerMaskFor: register ]
ifFalse: [ 0 ] ]
]

{ #category : #accessing }
CogSimStackEntry >> registerMaskOrNone [
^((type = SSRegister) | (type = SSVectorRegister)) ifTrue: [cogit registerMaskFor: register] ifFalse: [0]
^(type = SSRegister or: [ type = SSVectorRegister ]) ifTrue: [cogit registerMaskFor: register] ifFalse: [0]
]

{ #category : #accessing }
CogSimStackEntry >> registerOrNone [
^((type = SSRegister) | (type = SSVectorRegister)) ifTrue: [register] ifFalse: [NoReg]
^ ((type = SSRegister) or: [ type = SSVectorRegister ])
ifTrue: [register]
ifFalse: [NoReg]
]

{ #category : #accessing }
Expand Down
10 changes: 5 additions & 5 deletions smalltalksrc/VMMaker/FFTPlugin.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -74,11 +74,11 @@ FFTPlugin >> loadFFTFrom: fftOop [

"Check assumptions about sizes"
interpreterProxy success:
(1 << nu = fftSize) &
(fftSize // 4 + 1 = sinTableSize) &
(fftSize = realDataSize) &
(fftSize = imagDataSize) &
(realDataSize = imagDataSize).
((1 << nu = fftSize) and: [
(fftSize // 4 + 1 = sinTableSize) and: [
(fftSize = realDataSize) and: [
(fftSize = imagDataSize) and: [
(realDataSize = imagDataSize) ] ] ] ]).

^interpreterProxy failed == false
]
Expand Down
2 changes: 1 addition & 1 deletion smalltalksrc/VMMaker/LargeIntegersPlugin.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -125,7 +125,7 @@ LargeIntegersPlugin >> anyBitOfLargeInt: anOop from: start to: stopArg [
<var: #ix type: #usqInt>
self
debugCode: [self msg: 'anyBitOfLargeInt: anOop from: start to: stopArg'].
start < 1 | (stopArg < 1)
(start < 1 or: [ stopArg < 1 ])
ifTrue: [^ interpreterProxy primitiveFail].
magnitude := anOop.
stop := stopArg min: (self highBitOfLargeInt: magnitude).
Expand Down
20 changes: 10 additions & 10 deletions smalltalksrc/VMMaker/Matrix2x3Plugin.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -226,12 +226,12 @@ Matrix2x3Plugin >> primitiveIsIdentity [
matrix := self loadArgumentMatrix: (interpreterProxy stackValue: 0).
interpreterProxy failed ifFalse:
[interpreterProxy methodReturnBool:(
((matrix at: 0) = (self cCoerce: 1.0 to: #float)) &
((matrix at: 1) = (self cCoerce: 0.0 to: #float)) &
((matrix at: 2) = (self cCoerce: 0.0 to: #float)) &
((matrix at: 3) = (self cCoerce: 0.0 to: #float)) &
((matrix at: 4) = (self cCoerce: 1.0 to: #float)) &
((matrix at: 5) = (self cCoerce: 0.0 to: #float)))]
((matrix at: 0) = (self cCoerce: 1.0 to: #float)) and: [
((matrix at: 1) = (self cCoerce: 0.0 to: #float)) and: [
((matrix at: 2) = (self cCoerce: 0.0 to: #float)) and: [
((matrix at: 3) = (self cCoerce: 0.0 to: #float)) and: [
((matrix at: 4) = (self cCoerce: 1.0 to: #float)) and: [
((matrix at: 5) = (self cCoerce: 0.0 to: #float)) ] ] ] ] ]) ]
]

{ #category : #primitives }
Expand All @@ -242,10 +242,10 @@ Matrix2x3Plugin >> primitiveIsPureTranslation [
matrix := self loadArgumentMatrix: (interpreterProxy stackValue: 0).
interpreterProxy failed ifFalse:
[interpreterProxy methodReturnBool:(
((matrix at: 0) = (self cCoerce: 1.0 to: #float)) &
((matrix at: 1) = (self cCoerce: 0.0 to: #float)) &
((matrix at: 3) = (self cCoerce: 0.0 to: #float)) &
((matrix at: 4) = (self cCoerce: 1.0 to: #float)))]
((matrix at: 0) = (self cCoerce: 1.0 to: #float)) and: [
((matrix at: 1) = (self cCoerce: 0.0 to: #float)) and: [
((matrix at: 3) = (self cCoerce: 0.0 to: #float)) and: [
((matrix at: 4) = (self cCoerce: 1.0 to: #float)) ] ] ])]
]

{ #category : #primitives }
Expand Down
4 changes: 2 additions & 2 deletions smalltalksrc/VMMaker/SpurMemoryManager.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -3324,7 +3324,7 @@ SpurMemoryManager >> checkOkayOop: oop [

"format check"
fmt := self formatOf: oop.
(fmt = 6) | (fmt = 8) ifTrue:
(fmt = 6 or: [ fmt = 8 ]) ifTrue:
[self print: 'oop '; printHex: oop; print: ' has an unknown format type'. ^false].
(fmt = self forwardedFormat) ~= (classIndex = self isForwardedObjectClassIndexPun) ifTrue:
[self print: 'oop '; printHex: oop; print: ' has mis-matched format/classIndex fields; only one of them is the isForwarded value'. ^false].
Expand Down Expand Up @@ -9493,7 +9493,7 @@ SpurMemoryManager >> okayOop: signedOop [

"format check"
fmt := self formatOf: oop.
(fmt = 6) | (fmt = 8) ifTrue:
(fmt = 6 or: [ fmt = 8 ]) ifTrue:
[self error: 'oop has an unknown format type'. ^false].
(fmt = self forwardedFormat) ~= (classIndex = self isForwardedObjectClassIndexPun) ifTrue:
[self error: 'oop has mis-matched format/classIndex fields; only one of them is the isForwarded value'. ^false].
Expand Down
42 changes: 22 additions & 20 deletions smalltalksrc/VMMaker/StackInterpreter.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -1733,7 +1733,7 @@ StackInterpreter class >> writeVMHeaderTo: aStream bytesPerWord: bytesPerWord ge
as: 1
comment: 'Allow this to be overridden on the compiler command line'
on: aStream].
SistaVM | IMMUTABILITY ifTrue:
(SistaVM or: [ IMMUTABILITY ]) ifTrue:
[aStream cr].
aCCodeGenerator putDefineOf: #STACKVM as: 1 on: aStream.
(InitializationOptions at: #SpurObjectMemory ifAbsent: false) ifTrue:
Expand Down Expand Up @@ -3845,13 +3845,15 @@ StackInterpreter >> charsOfLong: long [

{ #category : #'debug support' }
StackInterpreter >> checkAllAccessibleObjectsOkay [

"Ensure that all accessible objects in the heap are okay."

<api>
| ok |
ok := true.
objectMemory allObjectsDo:
[:oop| ok := ok & (self checkOkayFields: oop)].
^ok
objectMemory allObjectsDo: [ :oop |
ok := ok and: [ self checkOkayFields: oop ] ].
^ ok
]

{ #category : #'primitive support' }
Expand Down Expand Up @@ -4216,25 +4218,25 @@ StackInterpreter >> checkOkayInterpreterObjects: writeBack [
<api>
| ok oopOrZero oop |
ok := true.
ok := ok & (self checkOkayFields: objectMemory nilObject).
ok := ok & (self checkOkayFields: objectMemory falseObject).
ok := ok & (self checkOkayFields: objectMemory trueObject).
ok := ok & (self checkOkayFields: objectMemory specialObjectsOop).
ok := ok & (self checkOkayFields: messageSelector).
ok := ok & (self checkOkayFields: newMethod).
ok := ok & (self checkOkayFields: lkupClass).
ok := ok and: [ (self checkOkayFields: objectMemory nilObject) ].
ok := ok and: [ (self checkOkayFields: objectMemory falseObject) ].
ok := ok and: [ (self checkOkayFields: objectMemory trueObject) ].
ok := ok and: [ (self checkOkayFields: objectMemory specialObjectsOop) ].
ok := ok and: [ (self checkOkayFields: messageSelector) ].
ok := ok and: [ (self checkOkayFields: newMethod) ].
ok := ok and: [ (self checkOkayFields: lkupClass) ].
0 to: MethodCacheEntries - 1 by: MethodCacheEntrySize do:
[ :i |
oopOrZero := methodCache at: i + MethodCacheSelector.
oopOrZero = 0 ifFalse:
[ok := ok & (self checkOkayFields: (methodCache at: i + MethodCacheSelector)).
ok := ok & (self checkOkayFields: (methodCache at: i + MethodCacheMethod))]].
[ok := ok and: [ (self checkOkayFields: (methodCache at: i + MethodCacheSelector)) ].
ok := ok and: [ (self checkOkayFields: (methodCache at: i + MethodCacheMethod))]] ].
1 to: objectMemory remapBufferCount do:
[ :i |
oop := objectMemory remapBuffer at: i.
(objectMemory isImmediate: oop) ifFalse:
[ok := ok & (self checkOkayFields: oop)]].
ok := ok & (self checkOkayStackZone: writeBack).
[ok := ok and: [ (self checkOkayFields: oop)]] ].
ok := ok and: [ (self checkOkayStackZone: writeBack) ].
^ok
]

Expand All @@ -4257,12 +4259,12 @@ StackInterpreter >> checkOkayStackPage: thePage [
[theSP <= frameRcvrOffset] whileTrue:
[oop := stackPages longAt: theSP.
(objectMemory isIntegerObject: oop) ifFalse:
[ok := ok & (self checkOkayFields: oop)].
[ok := ok and: [ (self checkOkayFields: oop)] ].
theSP := theSP + objectMemory wordSize].
(self frameHasContext: theFP) ifTrue:
[self assert: (objectMemory isContext: (self frameContext: theFP)).
ok := ok & (self checkOkayFields: (self frameContext: theFP))].
ok := ok & (self checkOkayFields: (self frameMethodObject: theFP)).
ok := ok and: [ (self checkOkayFields: (self frameContext: theFP))] ].
ok := ok and: [ (self checkOkayFields: (self frameMethodObject: theFP)) ].
(callerFP := self frameCallerFP: theFP) ~= 0] whileTrue:
[theSP := theFP + FoxCallerSavedIP + objectMemory wordSize.
theFP := callerFP].
Expand All @@ -4272,7 +4274,7 @@ StackInterpreter >> checkOkayStackPage: thePage [
[theSP <= thePage baseAddress] whileTrue:
[oop := stackPages longAt: theSP.
(objectMemory isIntegerObject: oop) ifFalse:
[ok := ok & (self checkOkayFields: oop)].
[ok := ok and: [ (self checkOkayFields: oop)] ].
theSP := theSP + objectMemory wordSize].
^ok
]
Expand All @@ -4291,7 +4293,7 @@ StackInterpreter >> checkOkayStackZone: writeBack [
[:i|
thePage := stackPages stackPageAt: i.
(stackPages isFree: thePage) ifFalse:
[ok := ok & (self checkOkayStackPage: thePage)]].
[ok := ok and: [ (self checkOkayStackPage: thePage)]] ].

^ok
]
Expand Down
2 changes: 1 addition & 1 deletion smalltalksrc/VMMaker/UnicodePlugin.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -103,7 +103,7 @@ UnicodePlugin >> primitiveClipboardPut [

utf16 := self cCoerce: (interpreterProxy firstIndexableField: strOop) to: #'unsigned short *'.
utf16Length := 2 * (interpreterProxy stSizeOf: strOop).
((count >= 0) & (count < utf16Length)) ifTrue: [utf16Length := count].
(count >= 0 and: [ (count < utf16Length) ]) ifTrue: [utf16Length := count].

self unicodeClipboard: utf16 Put: utf16Length.

Expand Down

0 comments on commit 521f055

Please sign in to comment.