missed commit mails

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

missed commit mails

Tobias Pape


Begin forwarded message:

> Date: Tue, 25 Oct 2016 08:31:34 0000
> From: [hidden email]
> To: [hidden email], [hidden email]
> Reply-To: [hidden email]
> Subject: The Trunk: EToys-tfel.269.mcz
> Message-Id: <E1byx91-0003nI-Fr@andreas>
>
> Tim Felgentreff uploaded a new version of EToys to project The Trunk:
> http://source.squeak.org/trunk/EToys-tfel.269.mcz
>
> ==================== Summary ====================
>
> Name: EToys-tfel.269
> Author: tfel
> Time: 24 October 2016, 12:41:29.211614 pm
> UUID: a11b6d00-95c1-054a-8ea6-237af529c724
> Ancestors: EToys-tfel.268
>
> remove unused methods
>
> =============== Diff against EToys-tfel.268 ===============
>
> Item was removed:
> - ObjectRepresentativeMorph subclass: #ClassRepresentativeMorph
> - instanceVariableNames: 'classRepresented'
> - classVariableNames: ''
> - poolDictionaries: ''
> - category: 'Etoys-Scripting'!
>
> Item was removed:
> - StandardScriptingSystem subclass: #EToySystem
> - instanceVariableNames: ''
> - classVariableNames: 'EToyVersion EToyVersionDate'
> - poolDictionaries: ''
> - category: 'Etoys-Experimental'!
> -
> - !EToySystem commentStamp: '<historical>' prior: 0!
> - A global object holding onto properties and code of the overall E-toy system of the moment.  Its code is entirely held on the class side; the class is never instantiated.!
>
> Item was removed:
> - ----- Method: EToySystem class>>cleanUp: (in category 'class initialization') -----
> - cleanUp: aggressive
> -
> - aggressive ifTrue: [
> - StandardScriptingSystem removeUnreferencedPlayers.
> - Player removeUninstantiatedSubclassesSilently.
> - Project allMorphicProjects do: [:mp | mp world dumpPresenter].
> - Preferences removePreference: #allowEtoyUserCustomEvents.]!
>
> Item was removed:
> - ----- Method: EToySystem class>>cleanupsForRelease (in category 'development support') -----
> - cleanupsForRelease
> - "Miscellaneous space cleanups to do before a release."
> - "EToySystem cleanupsForRelease"
> -
> - Socket deadServer: ''.  "Don't reveal any specific server name"
> - HandMorph initialize.  "free cached ColorChart"
> - PaintBoxMorph initialize. "forces Prototype to let go of extra things it might hold"
> - Smalltalk globals removeKey: #AA ifAbsent: [].
> - Smalltalk globals removeKey: #BB ifAbsent: [].
> - Smalltalk globals removeKey: #CC ifAbsent: [].
> - Smalltalk globals removeKey: #DD ifAbsent: [].
> - Smalltalk globals removeKey: #Temp ifAbsent: [].
> -
> - ScriptingSystem reclaimSpace.
> - Smalltalk cleanOutUndeclared.
> - Smalltalk reclaimDependents.
> - Smalltalk removeEmptyMessageCategories.
> - Symbol rehash.
> - !
>
> Item was removed:
> - ----- Method: EToySystem class>>fixComicCharacters (in category 'misc') -----
> - fixComicCharacters
> - "EToySystem fixComicCharacters"
> - ((TextConstants at:  #ComicBold) fontAt: 3) characterFormAt: $_ put:
> - (Form
> - extent: 9@16
> - depth: 1
> - fromArray: #( 0 0 0 134217728 402653184 805306368 2139095040 4278190080 2139095040 805306368 402653184 134217728 0 0 0 0)
> - offset: 0@0).
> -
> - ((TextConstants at:  #ComicBold) fontAt: 3) characterFormAt: $1 put:
> - (Form
> - extent: 5@16
> - depth: 1
> - fromArray: #( 0 0 0 0 1610612736 3758096384 3758096384 1610612736 1610612736 1610612736 1610612736 4026531840 4026531840 0 0 0)
> - offset: 0@0).
> -
> -
> - ((TextConstants at:  #ComicBold) fontAt: 3) characterFormAt: $2 put:
> - (Form
> - extent: 6@16
> - depth: 1
> - fromArray: #( 0 0 0 0 1879048192 4160749568 2550136832 939524096 1879048192 3758096384 3221225472 4160749568 4160749568 0 0 0)
> - offset: 0@0).
> -
> -
> - ((TextConstants at:  #ComicBold) fontAt: 3) characterFormAt: $4 put:
> - (Form
> - extent: 7@16
> - depth: 1
> - fromArray: #( 0 0 0 0 134217728 402653184 402653184 939524096 1476395008 4227858432 4227858432 402653184 402653184 0 0 0)
> - offset: 0@0).
> -
> - ((TextConstants at:  #ComicBold) fontAt: 3) characterFormAt: $j put:
> - (Form
> - extent: 4@16
> - depth: 1
> - fromArray: #( 0 0 0 0 1610612736 1610612736 0 1610612736 1610612736 1610612736 1610612736 1610612736 1610612736 1610612736 3758096384 3221225472)
> - offset: 0@0).
> -
> - !
>
> Item was removed:
> - ----- Method: EToySystem class>>loadJanForms (in category 'development support') -----
> - loadJanForms
> - "EToySystem loadJanForms"
> -
> - | aReferenceStream newFormDict |
> - aReferenceStream := ReferenceStream fileNamed: 'JanForms'.
> - newFormDict := aReferenceStream next.
> - aReferenceStream close.
> - newFormDict associationsDo:
> - [:assoc | Imports default importImage: assoc value named: assoc key]!
>
> Item was removed:
> - ----- Method: EToySystem class>>methodsToStripForExternalRelease (in category 'external release') -----
> - methodsToStripForExternalRelease
> - "Answer a list of triplets #(className, class/instance, methodName) of methods to be stripped in an external release."
> - ^ #(
> - (EToySystem class prepareRelease)
> - (EToySystem class previewEToysOn:)
> - )!
>
> Item was removed:
> - ----- Method: EToySystem class>>prepareRelease (in category 'stripped') -----
> - prepareRelease
> - self codeStrippedOut: '2.3External'!
>
> Item was removed:
> - ----- Method: EToySystem class>>previewEToysOn: (in category 'stripped') -----
> - previewEToysOn: arg1
> - self codeStrippedOut: '2.3External'!
>
> Item was removed:
> - Object subclass: #ExternalSemaphoreTable
> - instanceVariableNames: ''
> - classVariableNames: 'ProtectTable'
> - poolDictionaries: ''
> - category: 'Etoys-Squeakland-System-Support'!
> -
> - !ExternalSemaphoreTable commentStamp: '<historical>' prior: 0!
> - By John M McIntosh [hidden email]
> - This class was written to mange the external semaphore table. When I was writing a Socket test server I discovered various race conditions on the access to the externalSemaphore table. This new class uses class side methods to restrict access using a mutex semaphore. It seemed cleaner to deligate the reponsibility here versus adding more code and another class variable to SystemDictionary
> -
> - Note that in Smalltalk recreateSpecialObjectsArray we still directly play with the table.!
>
> Item was removed:
> - ----- Method: ExternalSemaphoreTable class>>clearExternalObjects (in category 'accessing') -----
> - clearExternalObjects
> - "Clear the array of objects that have been registered for use in non-Smalltalk code."
> -
> - ProtectTable critical: [Smalltalk specialObjectsArray at: 39 put: Array new].
> - !
>
> Item was removed:
> - ----- Method: ExternalSemaphoreTable class>>externalObjects (in category 'accessing') -----
> - externalObjects
> - ^ProtectTable critical: [Smalltalk specialObjectsArray at: 39].!
>
> Item was removed:
> - ----- Method: ExternalSemaphoreTable class>>initialize (in category 'initialize') -----
> - initialize
> - ProtectTable := Semaphore forMutualExclusion!
>
> Item was removed:
> - ----- Method: ExternalSemaphoreTable class>>registerExternalObject: (in category 'accessing') -----
> - registerExternalObject: anObject
> - ^ ProtectTable critical: [self safelyRegisterExternalObject: anObject]
> - !
>
> Item was removed:
> - ----- Method: ExternalSemaphoreTable class>>safelyRegisterExternalObject: (in category 'accessing') -----
> - safelyRegisterExternalObject: anObject
> - "Register the given object in the external objects array and return its index. If it is already there, just return its index."
> -
> - | objects firstEmptyIndex obj sz newObjects |
> - objects := Smalltalk specialObjectsArray at: 39.
> -
> - "find the first empty slot"
> - firstEmptyIndex := 0.
> - 1 to: objects size do: [:i |
> - obj := objects at: i.
> - obj == anObject ifTrue: [^ i].  "object already there, just return its index"
> - (obj == nil and: [firstEmptyIndex = 0]) ifTrue: [firstEmptyIndex := i]].
> -
> - "if no empty slots, expand the array"
> - firstEmptyIndex = 0 ifTrue: [
> - sz := objects size.
> - newObjects := objects species new: sz + 20.  "grow linearly"
> - newObjects replaceFrom: 1 to: sz with: objects startingAt: 1.
> - firstEmptyIndex := sz + 1.
> - Smalltalk specialObjectsArray at: 39 put: newObjects.
> - objects := newObjects].
> -
> - objects at: firstEmptyIndex put: anObject.
> - ^ firstEmptyIndex
> - !
>
> Item was removed:
> - ----- Method: ExternalSemaphoreTable class>>safelyUnregisterExternalObject: (in category 'accessing') -----
> - safelyUnregisterExternalObject: anObject
> - "Unregister the given object in the external objects array. Do nothing if it isn't registered.
> - JMM change to return if we clear the element, since it should only appear once in the array"
> -
> - | objects |
> - anObject ifNil: [^ self].
> - objects := Smalltalk specialObjectsArray at: 39.
> - 1 to: objects size do: [:i |
> - (objects at: i) == anObject ifTrue:
> - [objects at: i put: nil.
> - ^self]].
> - !
>
> Item was removed:
> - ----- Method: ExternalSemaphoreTable class>>unregisterExternalObject: (in category 'accessing') -----
> - unregisterExternalObject: anObject
> - ProtectTable critical: [self safelyUnregisterExternalObject: anObject]
> - !
>
> Item was removed:
> - Object subclass: #FreeTranslation
> - instanceVariableNames: ''
> - classVariableNames: ''
> - poolDictionaries: ''
> - category: 'Etoys-Squeakland-Network-TelNet WordNet'!
> -
> - !FreeTranslation commentStamp: '<historical>' prior: 0!
> - Squeak interface to the translation server at www.freetranslation.com.  Invoke it in any Squeak text pane by choosing 'translate it' from the shift-menu.  Languages are set by the 'choose language; menu item of the shift menu.  Or by changing (Preferences valueOfFlag: #languageTranslateFrom) and (Preferences valueOfFlag: #languageTranslateTo).  
> - See class method openScamperOn:.
> -
> - FreeTranslation openScamperOn: 'Why don''t you ever write anymore?'
> -
> - !
>
> Item was removed:
> - ----- Method: FreeTranslation class>>extract: (in category 'translation') -----
> - extract: aMimeDoc
> - | pageSource str |
> - "Extract the translated text from the web page"
> -
> - (aMimeDoc content beginsWith: 'error') ifTrue: [^ aMimeDoc content].
> - pageSource := aMimeDoc content.
> - "brute force way to pull out the result"
> - str := ReadStream on: pageSource.
> - str match: 'Translation Results by Transparent Language'.
> - str match: '<p>'.
> - ^ str upToAll: '</p>'!
>
> Item was removed:
> - ----- Method: FreeTranslation class>>openScamperOn: (in category 'scamper') -----
> - openScamperOn: currentSelection
> - "Submit the string to the translation server at www.freetranslation.com.  Ask it to translate from (Preferences parameterAt: #languageTranslateFrom) to (Preferences parameterAt: #languageTranslateTo).  Display the results in a Scamper window, reusing the previous one if possible."
> -
> - | inputs scamperWindow from to |
> - currentSelection size >= 10000 ifTrue: [^ self inform: 'Text selection is too long.'].
> - from := Preferences parameterAt: #languageTranslateFrom ifAbsentPut: ['English'].
> - to := Preferences parameterAt: #languageTranslateTo ifAbsentPut: ['German'].
> - from = to ifTrue:
> - [^ self inform: 'You asked to translate from ', from, ' to ', to, '.\' withCRs,
> - 'Use "choose language" to set these.'].  
> - inputs := Dictionary new.
> - inputs at: 'SrcText' put: (Array with: currentSelection).
> - inputs at: 'Sequence' put: #('core').
> - inputs at: 'Mode' put: #('html').
> - inputs at: 'template' put: #('TextResult2.htm').
> - inputs at: 'Language' put: (Array with: from, '/', to).
> - scamperWindow := (WebBrowser default ifNil: [^self]) newOrExistingOn: 'http://ets.freetranslation.com'.
> - scamperWindow model submitFormWithInputs: inputs
> - url: '<a href="http://ets.freetranslation.com:5081'">http://ets.freetranslation.com:5081' asUrl
> - method: 'post'.
> - scamperWindow activate.
> - !
>
> Item was removed:
> - ----- Method: FreeTranslation class>>translate:from:to: (in category 'translation') -----
> - translate: aString from: fromLang to: toLang
> - | inputs |
> - "Submit the string to the translation server at www.freetranslation.com.  Return the entire web page that freetranslation sends back."
> -
> - aString size >= 10000 ifTrue: [^ self inform: 'Text selection is too long.'].
> - inputs := Dictionary new.
> - inputs at: 'SrcText' put: (Array with: aString).
> - inputs at: 'Sequence' put: #('core').
> - inputs at: 'Mode' put: #('html').
> - inputs at: 'template' put: #('TextResult2.htm').
> - inputs at: 'Language' put: (Array with: fromLang, '/', toLang).
> - ^ '<a href="http://ets.freetranslation.com:5081'">http://ets.freetranslation.com:5081' asUrl postFormArgs: inputs.
> -
> - !
>
> Item was removed:
> - ----- Method: FreeTranslation class>>translatePanel:fromTo: (in category 'translation') -----
> - translatePanel: buttonPlayer fromTo: normalDirection
> - | ow fromTM toTM fromLang toLang tt doc answer width |
> - "Gather up all the info I need from the morphs in the button's owner and do the translation.  Insert the results in a TextMorph.  Use www.freeTranslation.com Refresh the banner ad.
> - TextMorph with 'from' in the title is starting text.
> - PopUpChoiceMorph  with 'from' in the title is the starting language.
> - TextMorph with 'from' in the title is place to put the answer.
> - PopUpChoiceMorph  with 'from' in the title is the target language.
> - If normalDirection is false, translate the other direction."
> -
> - ow := buttonPlayer costume ownerThatIsA: PasteUpMorph.
> - ow allMorphs do: [:mm |
> - (mm isTextMorph) ifTrue: [
> - (mm knownName asString includesSubString: 'from') ifTrue: [
> - fromTM := mm].
> - (mm knownName asString includesSubString: 'to') ifTrue: [
> - toTM := mm]].
> - (mm isKindOf: PopUpChoiceMorph) ifTrue: [
> - (mm knownName asString includesSubString: 'from') ifTrue: [
> - fromLang := mm contents asString].
> - (mm owner knownName asString includesSubString: 'from') ifTrue: [
> - fromLang := mm contents asString].
> - (mm knownName asString includesSubString: 'to') ifTrue: [
> - toLang := mm contents asString].
> - (mm owner knownName asString includesSubString: 'to') ifTrue: [
> - toLang := mm contents asString]]].
> - normalDirection ifFalse: ["switch"
> - tt := fromTM.  fromTM := toTM.  toTM := tt.
> - tt := fromLang.  fromLang := toLang.  toLang := tt].
> - Cursor wait showWhile: [
> - doc := self translate: fromTM contents asString from: fromLang to: toLang.
> - answer := self extract: doc]. "pull out the translated text"
> -
> - width := toTM width.
> - toTM contents: answer wrappedTo: width.
> - toTM changed.!
>
> Item was removed:
> - AppRegistry subclass: #MorphicTextEditor
> - instanceVariableNames: ''
> - classVariableNames: ''
> - poolDictionaries: ''
> - category: 'Etoys-Squeakland-System-Applications'!
>
> Item was removed:
> - AppRegistry subclass: #MvcTextEditor
> - instanceVariableNames: ''
> - classVariableNames: ''
> - poolDictionaries: ''
> - category: 'Etoys-Squeakland-System-Applications'!
> -
> - !MvcTextEditor commentStamp: 'tween 8/27/2004 12:24' prior: 0!
> - A subclass of AppRegistry which allows the user, or Browser add-ons, to control which class is used when creating the code editing view in mvc Browsers!
>
> Item was removed:
> - PrintableEncoder subclass: #PrintEncoder
> - instanceVariableNames: ''
> - classVariableNames: ''
> - poolDictionaries: ''
> - category: 'Etoys-Squeakland-MorphicExtras-Postscript Filters'!
>
> Item was removed:
> - ----- Method: PrintEncoder class>>filterSelector (in category 'configuring') -----
> - filterSelector
> - ^#printOnStream:!
>
> Item was removed:
> - PrintableEncoder subclass: #StoreEncoder
> - instanceVariableNames: ''
> - classVariableNames: ''
> - poolDictionaries: ''
> - category: 'Etoys-Squeakland-MorphicExtras-Postscript Filters'!
>
> Item was removed:
> - ----- Method: StoreEncoder class>>filterSelector (in category 'configuring') -----
> - filterSelector
> -     ^#storeOnStream:.
> - !
>