The Trunk: Kernel-nice.365.mcz

Previous Topic Next Topic
 
classic Classic list List threaded Threaded
1 message Options
Reply | Threaded
Open this post in threaded view
|

The Trunk: Kernel-nice.365.mcz

commits-2
Nicolas Cellier uploaded a new version of Kernel to project The Trunk:
http://source.squeak.org/trunk/Kernel-nice.365.mcz

==================== Summary ====================

Name: Kernel-nice.365
Author: nice
Time: 3 January 2010, 3:40:17 am
UUID: 75d88db0-4bfc-4c43-9b99-9f82b770d85d
Ancestors: Kernel-ar.364

move #basicType to EToys
remove some #or:or: #and:and: sends
change categorizer duplicate strategy

=============== Diff against Kernel-ar.364 ===============

Item was changed:
  ----- Method: Categorizer>>changeFromCategorySpecs: (in category 'accessing') -----
  changeFromCategorySpecs: categorySpecs
  "Tokens is an array of categorySpecs as scanned from a browser 'reorganize' pane, or built up by some other process, such as a scan of an environment."
 
  | newCategories newStops temp cc currentStop oldElements newElements |
  oldElements := elementArray asSet.
  newCategories := Array new: categorySpecs size.
  newStops := Array new: categorySpecs size.
  currentStop := 0.
  newElements := WriteStream on: (Array new: 16).
  1 to: categorySpecs size do:
  [:i | | catSpec selectors |
  catSpec := categorySpecs at: i.
  newCategories at: i put: catSpec first asSymbol.
  selectors := catSpec allButFirst collect: [:each | each isSymbol
  ifTrue: [each]
  ifFalse: [each printString asSymbol]].
  selectors asSortedCollection do:
  [:elem |
  (oldElements remove: elem ifAbsent: [nil]) notNil ifTrue:
  [newElements nextPut: elem.
  currentStop := currentStop+1]].
  newStops at: i put: currentStop].
 
  "Ignore extra elements but don't lose any existing elements!!"
  oldElements := oldElements collect:
  [:elem | Array with: (self categoryOfElement: elem) with: elem].
  newElements := newElements contents.
  categoryArray := newCategories.
  (cc := categoryArray asSet) size = categoryArray size ifFalse: ["has duplicate element"
  temp := categoryArray asOrderedCollection.
  temp removeAll: categoryArray asSet asOrderedCollection.
+ temp do: [:dup | | ii dup2 num |
- temp do: [:dup | | ii |
  ii := categoryArray indexOf: dup.
+ num := 2..
+ [dup2 := (dup,' #', num printString) asSymbol.  cc includes: dup2] whileTrue: [num := num + 1].
+ cc add: dup2.
+ categoryArray at: ii put: dup2]].
- [dup := (dup,' #2') asSymbol.  cc includes: dup] whileTrue.
- cc add: dup.
- categoryArray at: ii put: dup]].
  categoryStops := newStops.
  elementArray := newElements.
  oldElements do: [:pair | self classify: pair last under: pair first].!

Item was changed:
  ----- Method: Metaclass>>nonTrivial (in category 'fileIn/Out') -----
  nonTrivial
  "Answer whether the receiver has any methods or instance variables."
 
+ ^ self instVarNames size > 0 or: [self methodDict size > 0 or: [self hasTraitComposition]]!
- ^ self instVarNames size > 0 or: [self methodDict size > 0] or: [self hasTraitComposition]!

Item was changed:
  ----- Method: Timespan>>= (in category 'ansi protocol') -----
  = comparand
  ^ self class = comparand class
+ and: [ self start = comparand start
+ and: [ self duration = comparand duration ] ]
- and: [ self start = comparand start ]
- and: [ self duration = comparand duration ]
  .!

Item was changed:
  ----- Method: BlockClosure>>valueSupplyingAnswers: (in category 'evaluating') -----
  valueSupplyingAnswers: aListOfPairs
  "evaluate the block using a list of questions / answers that might be called upon to
  automatically respond to Object>>confirm: or FillInTheBlank requests"
 
  ^ [self value]
  on: ProvideAnswerNotification
  do:
  [:notify | | answer caption |
 
  caption := notify messageText withSeparatorsCompacted. "to remove new lines"
  answer := aListOfPairs
  detect:
+ [:each | caption = each first
+ or: [(caption includesSubstring: each first caseSensitive: false)
+ or: [each first match: caption]]]
- [:each | caption = each first or:
- [caption includesSubstring: each first caseSensitive: false] or:
- [each first match: caption]]
  ifNone: [nil].
  answer
  ifNotNil: [notify resume: answer second]
  ifNil:
  [ | outerAnswer |
  outerAnswer := ProvideAnswerNotification signal: notify messageText.
  outerAnswer
  ifNil: [notify resume]
  ifNotNil: [notify resume: outerAnswer]]]!

Item was changed:
  ----- Method: BlockContext>>valueSupplyingAnswers: (in category 'evaluating') -----
  valueSupplyingAnswers: aListOfPairs
  "evaluate the block using a list of questions / answers that might be called upon to
  automatically respond to Object>>confirm: or FillInTheBlank requests"
 
  ^ [self value]
  on: ProvideAnswerNotification
  do:
  [:notify | | answer caption |
 
  caption := notify messageText withSeparatorsCompacted. "to remove new lines"
  answer := aListOfPairs
  detect:
+ [:each | caption = each first
+ or: [(caption includesSubstring: each first caseSensitive: false)
+ or: [each first match: caption]]]
- [:each | caption = each first or:
- [caption includesSubstring: each first caseSensitive: false] or:
- [each first match: caption]]
  ifNone: [nil].
  answer
  ifNotNil: [notify resume: answer second]
  ifNil:
  [ | outerAnswer |
  outerAnswer := ProvideAnswerNotification signal: notify messageText.
  outerAnswer
  ifNil: [notify resume]
  ifNotNil: [notify resume: outerAnswer]]]!

Item was removed:
- ----- Method: StringHolder>>openSyntaxView (in category 'tiles') -----
- openSyntaxView
- "Open a syntax view on the current method"
-
- | class selector |
-
- (selector := self selectedMessageName) ifNotNil: [
- class := self selectedClassOrMetaClass.
- SyntaxMorph testClass: class andMethod: selector.
- ]!

Item was removed:
- ----- Method: Object>>basicType (in category 'testing') -----
- basicType
- "Answer a symbol representing the inherent type of the receiver"
-
- ^ #Object!

Item was removed:
- ----- Method: Number>>basicType (in category 'testing') -----
- basicType
- "Answer a symbol representing the inherent type of the receiver"
-
- ^ #Number!

Item was removed:
- ----- Method: Boolean>>basicType (in category 'printing') -----
- basicType
- "Answer a symbol representing the inherent type of the receiver"
-
- ^ #Boolean!

Item was removed:
- ----- Method: Object>>newTileMorphRepresentative (in category 'user interface') -----
- newTileMorphRepresentative
- ^ TileMorph new setLiteral: self!