The Trunk: Nebraska-nice.23.mcz

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

The Trunk: Nebraska-nice.23.mcz

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

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

Name: Nebraska-nice.23
Author: nice
Time: 27 December 2009, 4:21:23 am
UUID: 9acf2b68-55fc-403a-acac-52f09fafbe5d
Ancestors: Nebraska-ar.22

Cosmetic: move or remove a few temps inside closures

=============== Diff against Nebraska-ar.22 ===============

Item was changed:
  ----- Method: CanvasEncoder>>purgeCacheInner (in category 'drawing') -----
  purgeCacheInner
 
+ | totalSize |
- | cachedObject totalSize thisSize |
 
  cachedObjects ifNil: [^0].
  totalSize := 0.
+ cachedObjects withIndexDo: [ :each :index | | cachedObject thisSize |
- cachedObjects withIndexDo: [ :each :index |
  cachedObject := each first first.
  cachedObject ifNil: [
  each second ifNotNil: [
  2 to: each size do: [ :j | each at: j put: nil].
  self sendCommand: {
  String with: CanvasEncoder codeReleaseCache.
  self class encodeInteger: index.
  }.
  ].
  ] ifNotNil: [
  thisSize := cachedObject depth * cachedObject width * cachedObject height // 8.
  totalSize := totalSize + thisSize.
  ].
  ].
  ^totalSize
  "---
  newEntry := {
  WeakArray with: anObject.
  1.
  Time millisecondClockValue.
  nil.
  }.
  ---"
  !

Item was changed:
  ----- Method: EToyCommunicatorMorph>>addGateKeeperMorphs (in category '*nebraska-*nebraska-Morphic-Collaborative') -----
  addGateKeeperMorphs
 
+ | list currentTime choices |
- | list currentTime choices age row |
 
  self setProperty: #gateKeeperCounterValue toValue: EToyGateKeeperMorph updateCounter.
  choices := #(
  (60 'm' 'in the last minute')
  (3600 'h' 'in the last hour')
  (86400 'd' 'in the last day')
  ).
  currentTime := Time totalSeconds.
  list := EToyGateKeeperMorph knownIPAddresses.
+ list do: [ :each | | age row |
- list do: [ :each |
  age := each timeBetweenLastAccessAnd: currentTime.
  age := choices
  detect: [ :x | age <= x first]
  ifNone: [{0. '-'. (age // 86400) printString,'days ago'}].
  row := self addARow:
  (EToyIncomingMessage allTypes collect: [ :type |
  self toggleButtonFor: each attribute: type]
  ),
  {
 
  (self inAColumn: {
  (StringMorph contents: age second) lock.
  }) layoutInset: 2; hResizing: #shrinkWrap; setBalloonText: 'Last attempt was ',age third.
 
  (self inAColumn: {
  (StringMorph contents: each ipAddress) lock.
  }) layoutInset: 2; hResizing: #shrinkWrap.
 
  (self inAColumn: {
  (StringMorph contents: each latestUserName) lock.
  }) layoutInset: 2.
  }.
  row
  color: (Color r: 0.6 g: 0.8 b: 1.0);
  borderWidth: 1;
  borderColor: #raised;
  vResizing: #spaceFill;
  "on: #mouseUp send: #mouseUp:in: to: self;"
  setBalloonText: each fullInfoString
  ].!

Item was changed:
  ----- Method: EToyChatMorph>>improveText:forMorph: (in category 'as yet unclassified') -----
  improveText: someText forMorph: aMorph
 
+ | betterText conversions fontForAll |
- | betterText conversions newAttr fontForAll |
 
  fontForAll := aMorph eToyGetMainFont.
  betterText := someText veryDeepCopy.
  conversions := OrderedCollection new.
  betterText runs withStartStopAndValueDo: [:start :stop :attributes |
  attributes do: [:att |
  (att isMemberOf: TextFontChange) ifTrue: [
  conversions add: {att. start. stop}
  ]
  ]
  ].
  conversions do: [ :old |
+ | newAttr |
  betterText removeAttribute: old first from: old second to: old third.
  newAttr := TextFontReference toFont: (fontForAll fontAt: old first fontNumber).
  newAttr fontNumber: old first fontNumber.
  betterText addAttribute: newAttr from: old second to: old third.
  ].
  ^betterText!

Item was changed:
  ----- Method: CanvasEncoder class>>showStats (in category 'as yet unclassified') -----
  showStats
  "
  CanvasEncoder showStats
  "
+ | answer |
- | answer bucket |
 
  SentTypesAndSizes ifNil: [^Beeper beep].
  answer := WriteStream on: String new.
+ SentTypesAndSizes keys asArray sort do: [ :each | | bucket |
- SentTypesAndSizes keys asArray sort do: [ :each |
  bucket := SentTypesAndSizes at: each.
  answer nextPutAll: each printString,' ',
  bucket first printString,'  ',
  bucket second asStringWithCommas,' ',
  (self nameForCode: each); cr.
  ].
  StringHolder new contents: answer contents; openLabel: 'send/receive stats'.
  !

Item was changed:
  ----- Method: CanvasEncoder>>testCache: (in category 'drawing') -----
  testCache: anObject
+ | newEntry firstFree |
- | firstFree cachedObject newEntry |
  cachingEnabled
  ifFalse:
  [cachedObjects := nil.
  ^nil].
  cachedObjects ifNil:
  [cachedObjects := (1 to: 100) collect:
  [:x |
  {
  WeakArray new: 1.
  nil.
  nil.
  nil}]].
  self purgeCache.
  firstFree := nil.
  cachedObjects withIndexDo:
+ [:each :index | | cachedObject |
- [:each :index |
  cachedObject := each first first.
  firstFree ifNil: [cachedObject ifNil: [firstFree := index]].
  cachedObject == anObject
  ifTrue:
  [each at: 2 put: (each second) + 1.
  ^{
  index.
  false.
  each}]].
  firstFree ifNil: [^nil].
  newEntry := {
  WeakArray with: anObject.
  1.
  Time millisecondClockValue.
  nil}.
  cachedObjects at: firstFree put: newEntry.
  ^{
  firstFree.
  true.
  newEntry}!

Item was changed:
  ----- Method: NebraskaDebug class>>showStats:from: (in category 'as yet unclassified') -----
  showStats: queueName from: aCollection
 
+ | answer prevTime |
- | xx answer prevTime currTime |
 
  prevTime := nil.
  answer := String streamContents: [ :s |
  s nextPutAll: (aCollection last first - aCollection first first) asStringWithCommas,' ms';cr;cr.
+ aCollection withIndexDo: [ :each :index | | xx currTime |
- aCollection withIndexDo: [ :each :index |
  (queueName == #allStats or: [queueName == each last]) ifTrue: [
  currTime := each first.
  xx := currTime printString.
  prevTime ifNil: [prevTime := currTime].
  s nextPutAll: index printString,'.  ',
  (xx allButLast: 3),'.',(xx last: 3),' ',(currTime - prevTime) printString,' '.
  s nextPutAll: each allButFirst printString; cr.
  prevTime := currTime.
  ].
  ]
  ].
  StringHolder new
  contents: answer;
  openLabel: queueName!

Item was changed:
  ----- Method: CanvasEncoder class>>explainTestVars (in category 'as yet unclassified') -----
  explainTestVars
  "
  CanvasEncoder explainTestVars
  "
+ | answer oneBillion total |
- | answer total oneBillion data putter nReps |
 
  SimpleCounters ifNil: [^ Beeper beep].
  total := 0.
  oneBillion := 1000 * 1000 * 1000.
+ answer := String streamContents: [ :strm | | data putter |
- answer := String streamContents: [ :strm |
  data := SimpleCounters copy.
+ putter := [ :msg :index :nSec | | nReps |
- putter := [ :msg :index :nSec |
  nReps := data at: index.
  total := total + (nSec * nReps).
  strm nextPutAll: nReps asStringWithCommas,' * ',nSec printString,' ',
  (nSec * nReps / oneBillion roundTo: 0.01) printString,' secs for ',msg; cr
  ].
  putter value: 'string socket' value: 1 value: 8000.
  putter value: 'rectangles' value: 2 value: 40000.
  putter value: 'points' value: 3 value: 18000.
  putter value: 'colors' value: 4 value: 8000.
  ].
  StringHolder new
  contents: answer;
  openLabel: 'put integer times'.
 
  !

Item was changed:
  ----- Method: AudioChatGUI>>sendOneOfMany: (in category 'sending') -----
  sendOneOfMany: aSampledSound
 
+ | null message aCompressedSound t ratio resultBuf maxVal |
- | null message aCompressedSound ratio resultBuf oldSamples newCount t fromIndex val maxVal |
 
  self samplingRateForTransmission = aSampledSound originalSamplingRate ifTrue: [
  aCompressedSound := mycodec compressSound: aSampledSound.
  ] ifFalse: [
+ t := [ | oldSamples val newCount fromIndex |
- t := [
  ratio := aSampledSound originalSamplingRate // self samplingRateForTransmission.
  oldSamples := aSampledSound samples.
  newCount := oldSamples monoSampleCount // ratio.
  resultBuf := SoundBuffer newMonoSampleCount: newCount.
  fromIndex := 1.
  maxVal := 0.
  1 to: newCount do: [ :i |
  maxVal := maxVal max: (val := oldSamples at: fromIndex).
  resultBuf at: i put: val.
  fromIndex := fromIndex + ratio.
  ].
  ] timeToRun.
  NebraskaDebug at: #soundReductionTime add: {t. maxVal}.
  maxVal < 400 ifTrue: [
  NebraskaDebug at: #soundReductionTime add: {'---dropped---'}.
  ^self
  ]. "awfully quiet"
  aCompressedSound := mycodec compressSound: (
  SampledSound new
  setSamples: resultBuf
  samplingRate: aSampledSound originalSamplingRate // ratio
  ).
  ].
 
  null := String with: 0 asCharacter.
  message := {
  EToyIncomingMessage typeAudioChatContinuous,null.
  Preferences defaultAuthorName,null.
  aCompressedSound samplingRate asInteger printString,null.
  aCompressedSound channels first.
  }.
  queueForMultipleSends ifNil: [
  queueForMultipleSends := EToyPeerToPeer new
  sendSomeData: message
  to: mytargetip
  for: self
  multiple: true.
  ] ifNotNil: [
  queueForMultipleSends nextPut: message
  ].
 
  !

Item was changed:
  ----- Method: ChatNotes>>storeAIFFOnFile: (in category 'file i/o') -----
  storeAIFFOnFile: file
  "In a better design, this would be handled by SequentialSound,
  but I figure you will need a new primitive anyway, so it can
  be implemented at that time."
+ | sampleCount |
- | sampleCount s |
-
  sampleCount := recorder recordedSound sounds inject: 0 into: [ :sum :rsound |
  sum + rsound samples monoSampleCount
  ].
  file nextPutAll: 'FORM' asByteArray.
  file nextInt32Put: (2 * sampleCount) + 46.
  file nextPutAll: 'AIFF' asByteArray.
  file nextPutAll: 'COMM' asByteArray.
  file nextInt32Put: 18.
  file nextNumber: 2 put: 1. "channels"
  file nextInt32Put: sampleCount.
  file nextNumber: 2 put: 16. "bits/sample"
  (AbstractSound new) storeExtendedFloat: (recorder samplingRate) on: file.
  file nextPutAll: 'SSND' asByteArray.
  file nextInt32Put: (2 * sampleCount) + 8.
  file nextInt32Put: 0.
  file nextInt32Put: 0.
  (recorder recordedSound sounds) do: [:rsound |
  1 to: (rsound samples monoSampleCount) do: [:i |
+ | s |
  s := rsound samples at: i.
  file nextPut: ((s bitShift: -8) bitAnd: 16rFF).
  file nextPut: (s bitAnd: 16rFF)]].!

Item was changed:
  ----- Method: CanvasEncoder class>>timeSomeThings (in category 'as yet unclassified') -----
  timeSomeThings
  "
  CanvasEncoder timeSomeThings
  "
+ | answer array color iter |
- | s iter answer ms pt rect bm writer array color |
 
  iter := 1000000.
  array := Array new: 4.
  color := Color red.
+ answer := String streamContents: [ :strm | | bm rect writer pt s |
+ writer := [ :msg :doer | | ms |
- answer := String streamContents: [ :strm |
- writer := [ :msg :doer |
  ms := [iter timesRepeat: doer] timeToRun.
  strm nextPutAll: msg,((ms * 1000 / iter) roundTo: 0.01) printString,' usec'; cr.
  ].
  s := String new: 4.
  bm := Bitmap new: 20.
  pt := 100@300.
  rect := pt extent: pt.
  iter := 1000000.
  writer value: 'empty loop ' value: [self].
  writer value: 'modulo ' value: [12345678 \\ 256].
  writer value: 'bitAnd: ' value: [12345678 bitAnd: 255].
  strm cr.
  iter := 100000.
  writer value: 'putInteger ' value: [s putInteger32: 12345678 at: 1].
  writer value: 'bitmap put ' value: [bm at: 1 put: 12345678].
  writer value: 'encodeBytesOf: (big) ' value: [bm encodeInt: 12345678 in: bm at: 1].
  writer value: 'encodeBytesOf: (small) ' value: [bm encodeInt: 5000 in: bm at: 1].
  writer value: 'array at: (in) ' value: [array at: 1].
  writer value: 'array at: (out) ' value: [array at: 6 ifAbsent: []].
  strm cr.
  iter := 10000.
  writer value: 'color encode ' value: [color encodeForRemoteCanvas].
  writer value: 'pt encode ' value: [pt encodeForRemoteCanvas].
  writer value: 'rect encode ' value: [self encodeRectangle: rect].
  writer value: 'rect encode2 ' value: [rect encodeForRemoteCanvas].
  writer value: 'rect encodeb ' value: [rect encodeForRemoteCanvasB].
  ].
 
  StringHolder new contents: answer; openLabel: 'send/receive stats'.
  !

Item was changed:
  ----- Method: EToySenderMorph>>startNebraskaClient (in category 'as yet unclassified') -----
  startNebraskaClient
 
+
- | newMorph |
  [
+ [ | newMorph |
- [
  newMorph := NetworkTerminalMorph connectTo: self ipAddress.
  WorldState addDeferredUIMessage: [newMorph openInStyle: #scaled] fixTemps.
  ]
  on: Error
  do: [ :ex |
  WorldState addDeferredUIMessage: [
  self inform: 'No connection to: '. self ipAddress,' (',ex printString,')'
  ] fixTemps
  ].
  ] fork
  !