Skip to content

Commit 9ce829e

Browse files
author
jenkins-pharo
committed
EXPORT VERSION 60499
1 parent 36fcdd2 commit 9ce829e

File tree

27 files changed

+202
-153
lines changed

27 files changed

+202
-153
lines changed

src/CodeImportCommandLineHandlers.package/STCommandLineHandler.class/class/printCompilerWarning..st

Lines changed: 11 additions & 12 deletions
Original file line numberDiff line numberDiff line change
@@ -16,26 +16,25 @@ printCompilerWarning: aSyntaxErrorNotification
1616

1717
stderr red;
1818
nextPutAll: errorMessage; lf;
19-
nextPutAll: ('' padLeftTo: errorMessage size with: $=); lf.
19+
nextPutAll: ('' padLeftTo: errorMessage size with: $=); lf;
20+
clear.
2021

2122
"print each source line and mark the found syntax error"
2223
maxLineNumberSize := contents lines size asString size.
2324
lineNumber := 0.
2425
contents lineIndicesDo: [:start :endWithoutDelimiters :end |
2526
lineNumber := lineNumber + 1.
26-
lineNumber == errorLine
27-
ifTrue: [ stderr red ]
28-
ifFalse:[ stderr white ].
27+
lineNumber == errorLine ifTrue: [ stderr errorColor ].
2928
"0 pad the line numbers to the same size"
3029
stderr
3130
nextPutAll: (lineNumber asString padLeftTo: maxLineNumberSize with: $0);
32-
nextPutAll: ': '.
33-
34-
stderr white;
31+
nextPutAll: ': ';
3532
nextPutAll: (contents copyFrom: start to: endWithoutDelimiters);
3633
lf.
37-
"print the marker under the error line"
38-
(lineNumber == errorLine) ifTrue: [
39-
stderr red
40-
nextPutAll:( '_^_' padLeftTo: position - start + maxLineNumberSize + 4);
41-
lf ]]
34+
"print the marker under the error line"
35+
(lineNumber == errorLine)
36+
ifTrue: [
37+
stderr nextPutAll:( '_^_' padLeftTo: position - start + maxLineNumberSize + 4);
38+
lf;
39+
clear]
40+
]
Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -1,6 +1,6 @@
11
accessing
22
ensureEndsWith: anObject
3-
"Append anObject to the receiver IFF there is not one on the end."
3+
"Append anObject to the receiver IFF it is non-empty and there is not one on the end."
44

5-
(position > 0 and: [(collection at: position) = anObject]) ifTrue: [^self].
5+
(position == 0 or: [(collection at: position) = anObject]) ifTrue: [^self].
66
self nextPut: anObject

src/Collections-Tests.package/WriteStreamTest.class/instance/testEnsureEndsWith.st

Lines changed: 7 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -6,11 +6,16 @@ testEnsureEndsWith
66
stream nextPutAll: 'this is a test'.
77
stream ensureEndsWith: Character cr.
88
stream nextPutAll: 'for WriteStreamTest'.
9-
self assert: stream contents = (('this is a test' copyWith: Character cr), 'for WriteStreamTest').
9+
self assert: stream contents equals: (('this is a test' copyWith: Character cr), 'for WriteStreamTest').
1010

1111
"Manually put a new line and verify there are no 2 new lines"
1212
stream := self newStream.
1313
stream nextPutAll: ('this is a test' copyWith: Character cr).
1414
stream ensureEndsWith: Character cr.
1515
stream nextPutAll: 'for WriteStreamTest'.
16-
self assert: stream contents = (('this is a test' copyWith: Character cr), 'for WriteStreamTest').
16+
self assert: stream contents equals: (('this is a test' copyWith: Character cr), 'for WriteStreamTest').
17+
18+
"Test with a empty stream"
19+
stream := self newStream.
20+
stream ensureEndsWith: Character cr.
21+
self assert: stream contents equals: ''.

src/Kernel-Tests.package/IntegerTest.class/instance/testBitString.st

Lines changed: 15 additions & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -2,9 +2,18 @@ tests - bitLogic
22
testBitString
33
"self debug: #testBitString"
44

5-
self assert: 2 bitString = '0000000000000000000000000000010'.
6-
self assert: -1 bitString = '1111111111111111111111111111111'.
7-
self assert: -2 bitString = '1111111111111111111111111111110'.
8-
self assert: 2 bitStringLength = 31.
9-
"32 minus 1 for immediate encoding = 31 = 30 for number + 1 for sign"
10-
self assert: 2 bitStringLength = (SmallInteger maxVal highBit + 1).
5+
Smalltalk vm wordSize = 4
6+
ifTrue: [
7+
self assert: 2 bitString equals: '0000000000000000000000000000010'.
8+
self assert: -1 bitString equals: '1111111111111111111111111111111'.
9+
self assert: -2 bitString equals: '1111111111111111111111111111110'.
10+
self assert: 2 bitStringLength equals: 31 ].
11+
Smalltalk vm wordSize = 8
12+
ifTrue: [
13+
self assert: 2 bitString equals: '0000000000000000000000000000000000000000000000000000000000010'.
14+
self assert: -1 bitString equals: '1111111111111111111111111111111111111111111111111111111111111'.
15+
self assert: -2 bitString equals: '1111111111111111111111111111111111111111111111111111111111110'.
16+
self assert: 2 bitStringLength equals: 61 ].
17+
"32 minus 1 for immediate encoding = 31 = 30 for number + 1 for sign"
18+
"64 minus 3 for immediate encoding = 61 = 60 for number + 1 for sign"
19+
self assert: 2 bitStringLength equals: (SmallInteger maxVal highBit + 1).

src/Kernel-Tests.package/IntegerTest.class/instance/testCreationFromBytes1.st

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -4,8 +4,8 @@ testCreationFromBytes1
44
"it is illegal for a LargeInteger to be less than SmallInteger maxVal."
55
"here we test that Integer>>byte!byte2:byte3:byte4: resconstructs SmallInteger maxVal as an instance of SmallInteger. "
66

7-
| maxSmallInt hexString byte1 byte2 byte3 byte4
8-
builtInteger |
7+
| maxSmallInt hexString byte1 byte2 byte3 byte4 builtInteger |
8+
Smalltalk vm wordSize = 4 ifFalse: [ ^ self skip ].
99
maxSmallInt := SmallInteger maxVal.
1010
hexString := maxSmallInt printStringHex.
1111
self assert: hexString size = 8.

src/Kernel-Tests.package/IntegerTest.class/instance/testCreationFromBytes2.st

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -5,6 +5,7 @@ testCreationFromBytes2
55
"it is illegal for a LargeInteger to be less than SmallInteger maxVal."
66
"here we test that Integer>>byte!byte2:byte3:byte4: resconstructs (SmallInteger maxVal + 1) as an instance of LargePositiveInteger. "
77
| maxSmallInt hexString byte1 byte2 byte3 byte4 builtInteger |
8+
Smalltalk vm wordSize = 4 ifFalse: [ ^ self skip ].
89
maxSmallInt := SmallInteger maxVal.
910
hexString := (maxSmallInt + 1) printStringHex.
1011
self assert: hexString size = 8.

src/Kernel-Tests.package/IntegerTest.class/instance/testCreationFromBytes3.st

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -4,8 +4,8 @@ testCreationFromBytes3
44

55
"it is illegal for a LargeInteger to be less than SmallInteger maxVal."
66
"here we test that Integer>>byte!byte2:byte3:byte4: resconstructs (SmallInteger maxVal - 1) as an instance of SmallInteger. "
7-
| maxSmallInt hexString byte1 byte2 byte3 byte4
8-
builtInteger |
7+
| maxSmallInt hexString byte1 byte2 byte3 byte4 builtInteger |
8+
Smalltalk vm wordSize = 4 ifFalse: [ ^ self skip ].
99
maxSmallInt := SmallInteger maxVal.
1010
hexString := (maxSmallInt - 1) printStringHex.
1111
self assert: hexString size = 8.
Lines changed: 4 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -1,4 +1,6 @@
11
tests - Class Methods
22
testMaxVal
3-
4-
self assert: (SmallInteger maxVal = 16r3FFFFFFF).
3+
Smalltalk vm wordSize = 4
4+
ifTrue: [ self assert: SmallInteger maxVal = 16r3FFFFFFF ].
5+
Smalltalk vm wordSize = 8
6+
ifTrue: [ self assert: SmallInteger maxVal = 16rFFFFFFFFFFFFFFF ]
Lines changed: 4 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -1,4 +1,6 @@
11
tests - Class Methods
22
testMinVal
3-
4-
self assert: (SmallInteger minVal = -16r40000000).
3+
Smalltalk vm wordSize = 4
4+
ifTrue: [ self assert: SmallInteger minVal = -16r40000000 ].
5+
Smalltalk vm wordSize = 8
6+
ifTrue: [ self assert: SmallInteger minVal = -16r1000000000000000 ]
Lines changed: 28 additions & 19 deletions
Original file line numberDiff line numberDiff line change
@@ -1,21 +1,30 @@
11
tests - printing
22
testPrintString
3-
self assert: 1 printString = '1'.
4-
self assert: -1 printString = '-1'.
5-
self assert: SmallInteger minVal printString = '-1073741824'.
6-
self assert: SmallInteger maxVal printString = '1073741823'.
7-
self assert: 12345 printString = '12345'.
8-
self assert: -54321 printString = '-54321'.
9-
10-
self assert: 0 decimalDigitLength = 1.
11-
self assert: 4 decimalDigitLength = 1.
12-
self assert: 12 decimalDigitLength = 2.
13-
self assert: 123 decimalDigitLength = 3.
14-
self assert: 1234 decimalDigitLength = 4.
15-
self assert: 56789 decimalDigitLength = 5.
16-
self assert: 657483 decimalDigitLength = 6.
17-
self assert: 6571483 decimalDigitLength = 7.
18-
self assert: 65174383 decimalDigitLength = 8.
19-
self assert: 625744831 decimalDigitLength = 9.
20-
self assert: 1000001111 decimalDigitLength = 10.
21-
self assert: SmallInteger maxVal decimalDigitLength = 10.
3+
self assert: 1 printString equals: '1'.
4+
self assert: -1 printString equals: '-1'.
5+
Smalltalk vm wordSize = 4
6+
ifTrue: [
7+
self assert: SmallInteger minVal printString equals: '-1073741824'.
8+
self assert: SmallInteger maxVal printString equals: '1073741823' ].
9+
Smalltalk vm wordSize = 8
10+
ifTrue: [
11+
self assert: SmallInteger minVal printString equals: '-1152921504606846976'.
12+
self assert: SmallInteger maxVal printString equals: '1152921504606846975' ].
13+
self assert: 12345 printString equals: '12345'.
14+
self assert: -54321 printString equals: '-54321'.
15+
16+
self assert: 0 decimalDigitLength equals: 1.
17+
self assert: 4 decimalDigitLength equals: 1.
18+
self assert: 12 decimalDigitLength equals: 2.
19+
self assert: 123 decimalDigitLength equals: 3.
20+
self assert: 1234 decimalDigitLength equals: 4.
21+
self assert: 56789 decimalDigitLength equals: 5.
22+
self assert: 657483 decimalDigitLength equals: 6.
23+
self assert: 6571483 decimalDigitLength equals: 7.
24+
self assert: 65174383 decimalDigitLength equals: 8.
25+
self assert: 625744831 decimalDigitLength equals: 9.
26+
self assert: 1000001111 decimalDigitLength equals: 10.
27+
Smalltalk vm wordSize = 4
28+
ifTrue: [ self assert: SmallInteger maxVal decimalDigitLength equals: 10 ].
29+
Smalltalk vm wordSize = 8
30+
ifTrue: [ self assert: SmallInteger maxVal decimalDigitLength equals: 19 ].
Lines changed: 13 additions & 10 deletions
Original file line numberDiff line numberDiff line change
@@ -1,11 +1,14 @@
11
system primitives
2-
digitAt: n
3-
"Answer the value of an indexable field in the receiver. LargePositiveInteger uses bytes of base two number, and each is a 'digit' base 256. Fail if the argument (the index) is not an Integer or is out of bounds."
4-
n>4 ifTrue: [^ 0].
5-
self < 0
6-
ifTrue:
7-
[self = SmallInteger minVal ifTrue:
8-
["Can't negate minVal -- treat specially"
9-
^ #(0 0 0 64) at: n].
10-
^ ((0-self) bitShift: (1-n)*8) bitAnd: 16rFF]
11-
ifFalse: [^ (self bitShift: (1-n)*8) bitAnd: 16rFF]
2+
digitAt: n
3+
"Answer the value of an apparent byte-indexable field in the receiver,
4+
analogous to the large integers, which are organized as bytes."
5+
6+
n = 1
7+
ifTrue: [
8+
"Negate carefully in case the receiver is SmallInteger minVal"
9+
^ self < 0
10+
ifTrue: [ -256 - self bitAnd: 255 ]
11+
ifFalse: [ self bitAnd: 255 ] ].
12+
^ self < 0
13+
ifTrue: [ (-256 - self bitShift: -8) + 1 digitAt: n - 1 ]
14+
ifFalse: [ (self bitShift: 8 - (n bitShift: 3)) bitAnd: 255 ]

src/Pharo-Help.package/PharoWelcomePage.class/class/open.st

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -1,5 +1,6 @@
11
opening
22
open
3+
<script>
34
| group welcome help zen about window |
45

56
welcome := WelcomeHelp open.

src/Pharo-Help.package/PharoWelcomePage.class/class/openForRelease.st

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -1,5 +1,6 @@
11
opening
22
openForRelease
3+
<script>
34
| window |
45

56
World submorphs

src/Pharo-Help.package/WelcomeHelp.class/class/changeLog.st

Lines changed: 52 additions & 50 deletions
Original file line numberDiff line numberDiff line change
@@ -2,50 +2,52 @@ pages
22
changeLog
33
^ HelpTopic
44
title: 'ChangeLog'
5-
contents: (self heading: 'New Stuff in Pharo 6.0'),
6-
'- The PharoVM and image are now provided in 64-bit version in Linux and OSX and bring even better performance and stability
7-
- A new code changes management system named Epica for easier reviewing and recovering of your code
8-
- Integrated support for Git and easy-to-use tool for repositories and commits management named Iceberg (as preview for Pharo 6, it will be the default for Pharo 7)
9-
- Unified foreign function interface (UFFI) for interfacing with the outside world was significantly improved
5+
contents: (self heading: 'Highlights (aka New Stuff) in Pharo 6.0'),
6+
'- The PharoVM and image are also provided in a 64-bit version in Linux and macOS/OSX and bring even better performance and stability
7+
- A new code changes management system named Epicea for reviewing and recovering of your code easily
8+
- Integrated support for Git through an easy-to-use tool for repositories and commits management named Iceberg (as a preview in Pharo 6, it will be the default in Pharo 7)
9+
- The unified foreign function interface (UnifiedFFI) for interfacing with the outside world is significantly improved
1010
- The PharoVM is now part of OpenSmalltalk initiative
11-
- Introduction of objects immutability, alternative bytecode sets and block closures independent on outer context
12-
- The whole Pharo is now able to be bootstrapped from source codes managed by Git and Pharo modularity was improved
13-
- The Dark Theme was improved and set as default color theme for Pharo
11+
- Introduction of object immutability, alternative bytecode sets and block closures independent of outer context
12+
- Pharo can now be bootstrapped from source code managed by Git
13+
- Pharo modularity is improved
14+
- Pharo is faster
15+
- The Dark Theme was improved and set as default color theme of Pharo
1416
1517
', (self heading: 'All Issues'),
16-
'In Pharo 6 over 1400 fixes and enhancements was integrated.
18+
'Over 1400 fixes and enhancements were integrated in this release.
1719
18-
The complete list of fixed issues is too big to be placed here, but you can review all issues at FogBugz issue tracker (', (self url: 'https://pharo.fogbugz.com'), ') (requires account).',
20+
As the complete list of fixed issues is too large to be placed here, you can review it on the FogBugz issue tracker (', (self url: 'https://pharo.fogbugz.com'), ') (requires account).',
1921
(self subheading: 'Tools'),
20-
'- Epicea - Code changes manager
21-
- Iceberg - Git repositories manager
22-
- GTInspector, GTDebugger and other tools are now based on FastTable to display list of items for better performances
23-
- GToolkit, GTools update
24-
- Quality Assistant improvements
25-
- More reliable interruption by Cmd+.
22+
'- Epicea provides a code changes manager
23+
- Iceberg provides a Git repositories manager
24+
- GTInspector, GTDebugger and other tools are now based on FastTable (long lists of items are rendered much faster)
25+
- GToolkit and GTools have been updated
26+
- Quality Assistant has been improved
27+
- Interrupt key (Cmd+ /, Ctrl+.) has been made more reliable
2628
- Playground variables are now visible from debugger
2729
- Debugger temp names mapping is fixed
28-
- Close all debuggers in taskbar context menu
29-
- Run To Here in GTDebugger
30-
- Filtering of the results and critiques in the MessageBrowser
31-
- Improvements of the Dependency Analyzer
32-
- Nautilus
33-
- Split large variable entries in the Variables menu
30+
- There is a "Close all debuggers" in the taskbar context menu
31+
- GTDebugger has a "Run to here" feature
32+
- Results and critiques can be filtered in the MessageBrowser
33+
- Dependency Analyzer has been improved
34+
- Nautilus enhancements
35+
- Splitting of large variable entries in the Variables menu
3436
- Deprecated methods are shown with strikethrough emphasis
35-
- Abstract classes are shown in italic with a slight color adjustment',
37+
- Abstract classes are shown in italics with a slight color adjustment',
3638
(self subheading: 'VM related'),
3739
'- 64-bits support
38-
- Improve host platforms management (32-bit/64-bit)
40+
- Improvement of host platforms management (32-bit/64-bit)
3941
- Improved UnifiedFFI
4042
- The PharoVM is now part of OpenSmalltalk initiative
41-
- Introduction of objects immutability
42-
- Introduction of FullBlockClosure which will help for future evolutions of Pharo
43-
- Ephemerons support, introduce Ephemeron Registry
44-
- Support of alternative bytecode sets and introduction of Sista Encoder, the encoder for the SistaV1 bytecode set. This will be the base of future Pharo''s improvements',
43+
- Introduction of object immutability
44+
- Introduction of FullBlockClosure which will help in future evolutions of Pharo
45+
- Ephemerons support, introduction of the EphemeronRegistry
46+
- Support of alternative bytecode sets and introduction of Sista Encoder, the encoder for the SistaV1 bytecode set. This will be the bedrock on which Pharo will improve',
4547
(self subheading: 'Reflectivity'),
4648
'- General improvements
47-
- haltOnce is active by default per method. It does not require global turning on and it is managed from source code area in Nautilus
48-
- Execution counter for message nodes in source code area in Nautilus
49+
- haltOnce is active by default per method. It does not require global turning on (enable haltOnce) and it is managed from the source code area in Nautilus
50+
- Execution counter for message nodes in the source code area in Nautilus
4951
- API for Metalinks on AST nodes
5052
- Mirror primitives (Those are reflection primitives which access object state without messaging them, see MirrorPrimitives class)
5153
- Inlined method const can be implemented by Metalinks',
@@ -55,37 +57,37 @@ The complete list of fixed issues is too big to be placed here, but you can revi
5557
- Support of two double quotes inside comments
5658
- Standalone Morphic worlds in separate windows
5759
- Fix of several memory leaks
58-
- Improve working directory structure (introduction of a pharo-local directory to includes Pharo directories as package-cache)
59-
- Better autocategorisation of methods
60+
- Improvement of working directory structure (introduction of a ''pharo-local'' directory to include Pharo directories such as ''package-cache'')
61+
- Better autocategorization of methods
6062
- Introduction of a FuzzyMatcher for approximate string matching
6163
- Glamour integration in Spec
62-
- Renaming (Cmd+R) in Nautilus supports more AST nodes
64+
- Renaming (Cmd+R / Ctrl+R) in Nautilus supports more AST nodes
6365
- anObject asMethodConst to cache expressions dynamically
6466
- GlobalIdentifier for computer identification
65-
- NeoUUIDGenerator replace the old UUIDGenerator
67+
- NeoUUIDGenerator replaces the old UUIDGenerator
6668
- STON was improved and is now used by Monticello FileTree
67-
- Storing of suspended announcements
69+
- Storage of suspended announcements
6870
- Improved newAnonymousSubclass
6971
- Inheritable process specific variables
7072
- Fuel improvements
71-
- Enable <example> methods to be easily executed
73+
- Enablement of <example> methods so that they can be executed easily
7274
- Support for <sampleInstance>
73-
- New class and methods API for tags as replacement for categories and protocols
75+
- New class and method API for tags as replacement for categories and protocols
7476
- TabMorph improvements
75-
- Unify Dictionary APIs
77+
- Unification of Dictionary APIs (including an OrderedDictionary)
7678
- Package manifests improvements
77-
- Improve RadioButton groups',
79+
- Improvement of RadioButton groups',
7880
(self subheading: 'Cleanups'),
7981
'- Object>>#name is now deprecated and will be removed in Pharo 7
8082
- Better system modularization
81-
- Ability of the system to be fully bootstrapped from source codes
82-
- Turn of catalog search in Spotter by default (This improve the stability of Pharo under poor internet connection)
83-
- Remove Chroma-CubeHelix and TxWorkspace
84-
- Rename Pragma>>#selector to Pragma>>#methodSelector
85-
- Improve icons management (#iconNmaed: was introduce to replace DNUs)
83+
- Ability for the system to be fully bootstrapped from source code
84+
- Turn off of catalog search in Spotter by default (This improves the stability of Pharo when used with poor Internet connections)
85+
- Removal of Chroma-CubeHelix and TxWorkspace
86+
- Rename of Pragma>>#selector to Pragma>>#methodSelector
87+
- Improvement of icons management (#iconNamed: introduced in order to replace DNU-based icons)
8688
- Limit use of #asClass in order to rely on an environment
8789
- It is now possible to give a rewrite rule when deprecating a method to automatically rewrite code with deprecation (#deprecated:transformWith:)
88-
- Deprecation of:
90+
- Deprecation of the following:
8991
Object>>name
9092
ShortRunArray class
9193
Object>>confirm:orCancel:
@@ -95,14 +97,14 @@ The complete list of fixed issues is too big to be placed here, but you can revi
9597
Collection>>ifEmpty:ifNotEmptyDo:
9698
Collection>>ifNotEmptyDo:
9799
Collection>>ifNotEmptyDo:ifEmpty:
98-
SequenciableCollection>>copyLast:
100+
SequenceableCollection>>copyLast:
99101
Integer>>asBytesDescription
100102
Pragma>>method:',
101103
(self subheading: 'Unit testing/Documentation'),
102-
'- RecursionStopper: It provides an easy way to check if we are in a recursion and execute code just once in a recursion.
103-
- New process specific variable CurrentExecutionEnvironment with values: DefaultExecutionEnvironment by default and TestExecutionEnvironment during test run
104-
- SUnit improvements: time limit for tests, preventing "forked debuggers"
105-
- New assert extension to compare floats by closeTo:
104+
'- RecursionStopper provides an easy way to check if we are in a recursion and execute code just once in a recursion
105+
- New process specific variable ''CurrentExecutionEnvironment'' with value DefaultExecutionEnvironment by default and TestExecutionEnvironment during a test run
106+
- SUnit is improved by introducing a time limit for tests, preventing "forked debuggers"
107+
- New assert extension to compare floats with #closeTo:
106108
- More class comments and documentation',
107109
(self subheading: 'Network'),
108110
'- Support Server Name Indication (SNI) in Zodiac/SSLPlugin

0 commit comments

Comments
 (0)