Skip to content

Commit

Permalink
60499
Browse files Browse the repository at this point in the history
20102 SmallInteger>>#digitAt: not ready for 64-bit - Some Kernel-Tests-Numbers fail to take 64-bit into account
	https://pharo.fogbugz.com/f/cases/20102

20070 terminal color not reset after a error message
	https://pharo.fogbugz.com/f/cases/20070

19949 ensureEndsWith: does not handle start of stream case
	https://pharo.fogbugz.com/f/cases/19949

20101 Typos and general writing of release welcome text
	https://pharo.fogbugz.com/f/cases/20101

http://files.pharo.org/image/60/60499.zip
  • Loading branch information
Jenkins Build Server authored and ci committed Jun 6, 2017
1 parent 31c6d36 commit ba76c8e
Show file tree
Hide file tree
Showing 27 changed files with 201 additions and 152 deletions.
Expand Up @@ -15,26 +15,25 @@ printCompilerWarning: aSyntaxErrorNotification

stderr red;
nextPutAll: errorMessage; lf;
nextPutAll: ('' padLeftTo: errorMessage size with: $=); lf.
nextPutAll: ('' padLeftTo: errorMessage size with: $=); lf;
clear.

"print each source line and mark the found syntax error"
maxLineNumberSize := contents lines size asString size.
lineNumber := 0.
contents lineIndicesDo: [:start :endWithoutDelimiters :end |
lineNumber := lineNumber + 1.
lineNumber == errorLine
ifTrue: [ stderr red ]
ifFalse:[ stderr white ].
lineNumber == errorLine ifTrue: [ stderr errorColor ].
"0 pad the line numbers to the same size"
stderr
nextPutAll: (lineNumber asString padLeftTo: maxLineNumberSize with: $0);
nextPutAll: ': '.

stderr white;
nextPutAll: ': ';
nextPutAll: (contents copyFrom: start to: endWithoutDelimiters);
lf.
"print the marker under the error line"
(lineNumber == errorLine) ifTrue: [
stderr red
nextPutAll:( '_^_' padLeftTo: position - start + maxLineNumberSize + 4);
lf ]]
"print the marker under the error line"
(lineNumber == errorLine)
ifTrue: [
stderr nextPutAll:( '_^_' padLeftTo: position - start + maxLineNumberSize + 4);
lf;
clear]
]
@@ -1,5 +1,5 @@
ensureEndsWith: anObject
"Append anObject to the receiver IFF there is not one on the end."
"Append anObject to the receiver IFF it is non-empty and there is not one on the end."

(position > 0 and: [(collection at: position) = anObject]) ifTrue: [^self].
(position == 0 or: [(collection at: position) = anObject]) ifTrue: [^self].
self nextPut: anObject
Expand Up @@ -5,11 +5,16 @@ testEnsureEndsWith
stream nextPutAll: 'this is a test'.
stream ensureEndsWith: Character cr.
stream nextPutAll: 'for WriteStreamTest'.
self assert: stream contents = (('this is a test' copyWith: Character cr), 'for WriteStreamTest').
self assert: stream contents equals: (('this is a test' copyWith: Character cr), 'for WriteStreamTest').

"Manually put a new line and verify there are no 2 new lines"
stream := self newStream.
stream nextPutAll: ('this is a test' copyWith: Character cr).
stream ensureEndsWith: Character cr.
stream nextPutAll: 'for WriteStreamTest'.
self assert: stream contents = (('this is a test' copyWith: Character cr), 'for WriteStreamTest').
self assert: stream contents equals: (('this is a test' copyWith: Character cr), 'for WriteStreamTest').

"Test with a empty stream"
stream := self newStream.
stream ensureEndsWith: Character cr.
self assert: stream contents equals: ''.
@@ -1,9 +1,18 @@
testBitString
"self debug: #testBitString"

self assert: 2 bitString = '0000000000000000000000000000010'.
self assert: -1 bitString = '1111111111111111111111111111111'.
self assert: -2 bitString = '1111111111111111111111111111110'.
self assert: 2 bitStringLength = 31.
"32 minus 1 for immediate encoding = 31 = 30 for number + 1 for sign"
self assert: 2 bitStringLength = (SmallInteger maxVal highBit + 1).
Smalltalk vm wordSize = 4
ifTrue: [
self assert: 2 bitString equals: '0000000000000000000000000000010'.
self assert: -1 bitString equals: '1111111111111111111111111111111'.
self assert: -2 bitString equals: '1111111111111111111111111111110'.
self assert: 2 bitStringLength equals: 31 ].
Smalltalk vm wordSize = 8
ifTrue: [
self assert: 2 bitString equals: '0000000000000000000000000000000000000000000000000000000000010'.
self assert: -1 bitString equals: '1111111111111111111111111111111111111111111111111111111111111'.
self assert: -2 bitString equals: '1111111111111111111111111111111111111111111111111111111111110'.
self assert: 2 bitStringLength equals: 61 ].
"32 minus 1 for immediate encoding = 31 = 30 for number + 1 for sign"
"64 minus 3 for immediate encoding = 61 = 60 for number + 1 for sign"
self assert: 2 bitStringLength equals: (SmallInteger maxVal highBit + 1).
Expand Up @@ -3,8 +3,8 @@ testCreationFromBytes1
"it is illegal for a LargeInteger to be less than SmallInteger maxVal."
"here we test that Integer>>byte!byte2:byte3:byte4: resconstructs SmallInteger maxVal as an instance of SmallInteger. "

| maxSmallInt hexString byte1 byte2 byte3 byte4
builtInteger |
| maxSmallInt hexString byte1 byte2 byte3 byte4 builtInteger |
Smalltalk vm wordSize = 4 ifFalse: [ ^ self skip ].
maxSmallInt := SmallInteger maxVal.
hexString := maxSmallInt printStringHex.
self assert: hexString size = 8.
Expand Down
Expand Up @@ -4,6 +4,7 @@ testCreationFromBytes2
"it is illegal for a LargeInteger to be less than SmallInteger maxVal."
"here we test that Integer>>byte!byte2:byte3:byte4: resconstructs (SmallInteger maxVal + 1) as an instance of LargePositiveInteger. "
| maxSmallInt hexString byte1 byte2 byte3 byte4 builtInteger |
Smalltalk vm wordSize = 4 ifFalse: [ ^ self skip ].
maxSmallInt := SmallInteger maxVal.
hexString := (maxSmallInt + 1) printStringHex.
self assert: hexString size = 8.
Expand Down
Expand Up @@ -3,8 +3,8 @@ testCreationFromBytes3

"it is illegal for a LargeInteger to be less than SmallInteger maxVal."
"here we test that Integer>>byte!byte2:byte3:byte4: resconstructs (SmallInteger maxVal - 1) as an instance of SmallInteger. "
| maxSmallInt hexString byte1 byte2 byte3 byte4
builtInteger |
| maxSmallInt hexString byte1 byte2 byte3 byte4 builtInteger |
Smalltalk vm wordSize = 4 ifFalse: [ ^ self skip ].
maxSmallInt := SmallInteger maxVal.
hexString := (maxSmallInt - 1) printStringHex.
self assert: hexString size = 8.
Expand Down
@@ -1,3 +1,5 @@
testMaxVal

self assert: (SmallInteger maxVal = 16r3FFFFFFF).
Smalltalk vm wordSize = 4
ifTrue: [ self assert: SmallInteger maxVal = 16r3FFFFFFF ].
Smalltalk vm wordSize = 8
ifTrue: [ self assert: SmallInteger maxVal = 16rFFFFFFFFFFFFFFF ]
@@ -1,3 +1,5 @@
testMinVal

self assert: (SmallInteger minVal = -16r40000000).
Smalltalk vm wordSize = 4
ifTrue: [ self assert: SmallInteger minVal = -16r40000000 ].
Smalltalk vm wordSize = 8
ifTrue: [ self assert: SmallInteger minVal = -16r1000000000000000 ]
@@ -1,20 +1,29 @@
testPrintString
self assert: 1 printString = '1'.
self assert: -1 printString = '-1'.
self assert: SmallInteger minVal printString = '-1073741824'.
self assert: SmallInteger maxVal printString = '1073741823'.
self assert: 12345 printString = '12345'.
self assert: -54321 printString = '-54321'.

self assert: 0 decimalDigitLength = 1.
self assert: 4 decimalDigitLength = 1.
self assert: 12 decimalDigitLength = 2.
self assert: 123 decimalDigitLength = 3.
self assert: 1234 decimalDigitLength = 4.
self assert: 56789 decimalDigitLength = 5.
self assert: 657483 decimalDigitLength = 6.
self assert: 6571483 decimalDigitLength = 7.
self assert: 65174383 decimalDigitLength = 8.
self assert: 625744831 decimalDigitLength = 9.
self assert: 1000001111 decimalDigitLength = 10.
self assert: SmallInteger maxVal decimalDigitLength = 10.
self assert: 1 printString equals: '1'.
self assert: -1 printString equals: '-1'.
Smalltalk vm wordSize = 4
ifTrue: [
self assert: SmallInteger minVal printString equals: '-1073741824'.
self assert: SmallInteger maxVal printString equals: '1073741823' ].
Smalltalk vm wordSize = 8
ifTrue: [
self assert: SmallInteger minVal printString equals: '-1152921504606846976'.
self assert: SmallInteger maxVal printString equals: '1152921504606846975' ].
self assert: 12345 printString equals: '12345'.
self assert: -54321 printString equals: '-54321'.

self assert: 0 decimalDigitLength equals: 1.
self assert: 4 decimalDigitLength equals: 1.
self assert: 12 decimalDigitLength equals: 2.
self assert: 123 decimalDigitLength equals: 3.
self assert: 1234 decimalDigitLength equals: 4.
self assert: 56789 decimalDigitLength equals: 5.
self assert: 657483 decimalDigitLength equals: 6.
self assert: 6571483 decimalDigitLength equals: 7.
self assert: 65174383 decimalDigitLength equals: 8.
self assert: 625744831 decimalDigitLength equals: 9.
self assert: 1000001111 decimalDigitLength equals: 10.
Smalltalk vm wordSize = 4
ifTrue: [ self assert: SmallInteger maxVal decimalDigitLength equals: 10 ].
Smalltalk vm wordSize = 8
ifTrue: [ self assert: SmallInteger maxVal decimalDigitLength equals: 19 ].
@@ -1,10 +1,13 @@
digitAt: n
"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."
n>4 ifTrue: [^ 0].
self < 0
ifTrue:
[self = SmallInteger minVal ifTrue:
["Can't negate minVal -- treat specially"
^ #(0 0 0 64) at: n].
^ ((0-self) bitShift: (1-n)*8) bitAnd: 16rFF]
ifFalse: [^ (self bitShift: (1-n)*8) bitAnd: 16rFF]
digitAt: n
"Answer the value of an apparent byte-indexable field in the receiver,
analogous to the large integers, which are organized as bytes."

n = 1
ifTrue: [
"Negate carefully in case the receiver is SmallInteger minVal"
^ self < 0
ifTrue: [ -256 - self bitAnd: 255 ]
ifFalse: [ self bitAnd: 255 ] ].
^ self < 0
ifTrue: [ (-256 - self bitShift: -8) + 1 digitAt: n - 1 ]
ifFalse: [ (self bitShift: 8 - (n bitShift: 3)) bitAnd: 255 ]
@@ -1,4 +1,5 @@
open
<script>
| group welcome help zen about window |

welcome := WelcomeHelp open.
Expand Down
@@ -1,4 +1,5 @@
openForRelease
<script>
| window |

World submorphs
Expand Down
102 changes: 52 additions & 50 deletions Pharo-Help.package/WelcomeHelp.class/class/pages/changeLog.st
@@ -1,50 +1,52 @@
changeLog
^ HelpTopic
title: 'ChangeLog'
contents: (self heading: 'New Stuff in Pharo 6.0'),
'- The PharoVM and image are now provided in 64-bit version in Linux and OSX and bring even better performance and stability
- A new code changes management system named Epica for easier reviewing and recovering of your code
- 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)
- Unified foreign function interface (UFFI) for interfacing with the outside world was significantly improved
contents: (self heading: 'Highlights (aka New Stuff) in Pharo 6.0'),
'- The PharoVM and image are also provided in a 64-bit version in Linux and macOS/OSX and bring even better performance and stability
- A new code changes management system named Epicea for reviewing and recovering of your code easily
- 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)
- The unified foreign function interface (UnifiedFFI) for interfacing with the outside world is significantly improved
- The PharoVM is now part of OpenSmalltalk initiative
- Introduction of objects immutability, alternative bytecode sets and block closures independent on outer context
- The whole Pharo is now able to be bootstrapped from source codes managed by Git and Pharo modularity was improved
- The Dark Theme was improved and set as default color theme for Pharo
- Introduction of object immutability, alternative bytecode sets and block closures independent of outer context
- Pharo can now be bootstrapped from source code managed by Git
- Pharo modularity is improved
- Pharo is faster
- The Dark Theme was improved and set as default color theme of Pharo
', (self heading: 'All Issues'),
'In Pharo 6 over 1400 fixes and enhancements was integrated.
'Over 1400 fixes and enhancements were integrated in this release.
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).',
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).',
(self subheading: 'Tools'),
'- Epicea - Code changes manager
- Iceberg - Git repositories manager
- GTInspector, GTDebugger and other tools are now based on FastTable to display list of items for better performances
- GToolkit, GTools update
- Quality Assistant improvements
- More reliable interruption by Cmd+.
'- Epicea provides a code changes manager
- Iceberg provides a Git repositories manager
- GTInspector, GTDebugger and other tools are now based on FastTable (long lists of items are rendered much faster)
- GToolkit and GTools have been updated
- Quality Assistant has been improved
- Interrupt key (Cmd+ /, Ctrl+.) has been made more reliable
- Playground variables are now visible from debugger
- Debugger temp names mapping is fixed
- Close all debuggers in taskbar context menu
- Run To Here in GTDebugger
- Filtering of the results and critiques in the MessageBrowser
- Improvements of the Dependency Analyzer
- Nautilus
- Split large variable entries in the Variables menu
- There is a "Close all debuggers" in the taskbar context menu
- GTDebugger has a "Run to here" feature
- Results and critiques can be filtered in the MessageBrowser
- Dependency Analyzer has been improved
- Nautilus enhancements
- Splitting of large variable entries in the Variables menu
- Deprecated methods are shown with strikethrough emphasis
- Abstract classes are shown in italic with a slight color adjustment',
- Abstract classes are shown in italics with a slight color adjustment',
(self subheading: 'VM related'),
'- 64-bits support
- Improve host platforms management (32-bit/64-bit)
- Improvement of host platforms management (32-bit/64-bit)
- Improved UnifiedFFI
- The PharoVM is now part of OpenSmalltalk initiative
- Introduction of objects immutability
- Introduction of FullBlockClosure which will help for future evolutions of Pharo
- Ephemerons support, introduce Ephemeron Registry
- 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',
- Introduction of object immutability
- Introduction of FullBlockClosure which will help in future evolutions of Pharo
- Ephemerons support, introduction of the EphemeronRegistry
- 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',
(self subheading: 'Reflectivity'),
'- General improvements
- haltOnce is active by default per method. It does not require global turning on and it is managed from source code area in Nautilus
- Execution counter for message nodes in source code area in Nautilus
- 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
- Execution counter for message nodes in the source code area in Nautilus
- API for Metalinks on AST nodes
- Mirror primitives (Those are reflection primitives which access object state without messaging them, see MirrorPrimitives class)
- Inlined method const can be implemented by Metalinks',
Expand All @@ -54,37 +56,37 @@ The complete list of fixed issues is too big to be placed here, but you can revi
- Support of two double quotes inside comments
- Standalone Morphic worlds in separate windows
- Fix of several memory leaks
- Improve working directory structure (introduction of a pharo-local directory to includes Pharo directories as package-cache)
- Better autocategorisation of methods
- Improvement of working directory structure (introduction of a ''pharo-local'' directory to include Pharo directories such as ''package-cache'')
- Better autocategorization of methods
- Introduction of a FuzzyMatcher for approximate string matching
- Glamour integration in Spec
- Renaming (Cmd+R) in Nautilus supports more AST nodes
- Renaming (Cmd+R / Ctrl+R) in Nautilus supports more AST nodes
- anObject asMethodConst to cache expressions dynamically
- GlobalIdentifier for computer identification
- NeoUUIDGenerator replace the old UUIDGenerator
- NeoUUIDGenerator replaces the old UUIDGenerator
- STON was improved and is now used by Monticello FileTree
- Storing of suspended announcements
- Storage of suspended announcements
- Improved newAnonymousSubclass
- Inheritable process specific variables
- Fuel improvements
- Enable <example> methods to be easily executed
- Enablement of <example> methods so that they can be executed easily
- Support for <sampleInstance>
- New class and methods API for tags as replacement for categories and protocols
- New class and method API for tags as replacement for categories and protocols
- TabMorph improvements
- Unify Dictionary APIs
- Unification of Dictionary APIs (including an OrderedDictionary)
- Package manifests improvements
- Improve RadioButton groups',
- Improvement of RadioButton groups',
(self subheading: 'Cleanups'),
'- Object>>#name is now deprecated and will be removed in Pharo 7
- Better system modularization
- Ability of the system to be fully bootstrapped from source codes
- Turn of catalog search in Spotter by default (This improve the stability of Pharo under poor internet connection)
- Remove Chroma-CubeHelix and TxWorkspace
- Rename Pragma>>#selector to Pragma>>#methodSelector
- Improve icons management (#iconNmaed: was introduce to replace DNUs)
- Ability for the system to be fully bootstrapped from source code
- Turn off of catalog search in Spotter by default (This improves the stability of Pharo when used with poor Internet connections)
- Removal of Chroma-CubeHelix and TxWorkspace
- Rename of Pragma>>#selector to Pragma>>#methodSelector
- Improvement of icons management (#iconNamed: introduced in order to replace DNU-based icons)
- Limit use of #asClass in order to rely on an environment
- It is now possible to give a rewrite rule when deprecating a method to automatically rewrite code with deprecation (#deprecated:transformWith:)
- Deprecation of:
- Deprecation of the following:
Object>>name
ShortRunArray class
Object>>confirm:orCancel:
Expand All @@ -94,14 +96,14 @@ The complete list of fixed issues is too big to be placed here, but you can revi
Collection>>ifEmpty:ifNotEmptyDo:
Collection>>ifNotEmptyDo:
Collection>>ifNotEmptyDo:ifEmpty:
SequenciableCollection>>copyLast:
SequenceableCollection>>copyLast:
Integer>>asBytesDescription
Pragma>>method:',
(self subheading: 'Unit testing/Documentation'),
'- RecursionStopper: It provides an easy way to check if we are in a recursion and execute code just once in a recursion.
- New process specific variable CurrentExecutionEnvironment with values: DefaultExecutionEnvironment by default and TestExecutionEnvironment during test run
- SUnit improvements: time limit for tests, preventing "forked debuggers"
- New assert extension to compare floats by closeTo:
'- RecursionStopper provides an easy way to check if we are in a recursion and execute code just once in a recursion
- New process specific variable ''CurrentExecutionEnvironment'' with value DefaultExecutionEnvironment by default and TestExecutionEnvironment during a test run
- SUnit is improved by introducing a time limit for tests, preventing "forked debuggers"
- New assert extension to compare floats with #closeTo:
- More class comments and documentation',
(self subheading: 'Network'),
'- Support Server Name Indication (SNI) in Zodiac/SSLPlugin
Expand Down

0 comments on commit ba76c8e

Please sign in to comment.