[Pkg] Sake : Sake-Core-damiencassou.92.mcz

squeak-dev-noreply at lists.squeakfoundation.org squeak-dev-noreply at lists.squeakfoundation.org
Tue Dec 23 09:19:02 UTC 2008


A new version of Sake-Core was added to project Sake :
http://www.squeaksource.com/Sake/Sake-Core-damiencassou.92.mcz

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

Name: Sake-Core-damiencassou.92
Author: damiencassou
Time: 23 December 2008, 10:19:01 am
UUID: 35406e41-6834-49bc-b93e-440dbefcdeab
Ancestors: Sake-Core-kph.91

- Categorization of methods

=============== Diff against Sake-Core-kph.91 ===============

Item was changed:
+ ----- Method: SakeClassTask class>>class:subclass: (in category 'instance creation') -----
- ----- Method: SakeClassTask class>>class:subclass: (in category 'as yet unclassified') -----
  class: aClassName subclass: bClassName
  
  	^ (self class: aClassName) subclass: bClassName!

Item was changed:
+ ----- Method: SakeMeta>>order (in category 'accessing') -----
- ----- Method: SakeMeta>>order (in category 'as yet unclassified') -----
  order
  
  	^ order!

Item was changed:
+ ----- Method: SakeTask class>>check:eval:onChanged: (in category 'instance creation') -----
- ----- Method: SakeTask class>>check:eval:onChanged: (in category 'as yet unclassified') -----
  check: key eval: aBlock onChanged: aTaskOrBlock
  
  	^ self define: [ :task |
  		task	 if: [ task statusAt: key hasChanged: aBlock value ].
  		task action: aTaskOrBlock. 
  	]!

Item was changed:
+ ----- Method: SakeMeta>>name (in category 'testing') -----
- ----- Method: SakeMeta>>name (in category 'as yet unclassified') -----
  name
  
   ^ self at: #name!

Item was changed:
+ ----- Method: SakeMeta>>initialize: (in category 'private') -----
- ----- Method: SakeMeta>>initialize: (in category 'as yet unclassified') -----
  initialize: n
  
  	super initialize: n.
  	order := OrderedCollection new.!

Item was changed:
+ ----- Method: SakeMeta>>removeKey: (in category 'removing') -----
- ----- Method: SakeMeta>>removeKey: (in category 'as yet unclassified') -----
  removeKey: key
  	
  	super removeKey: key.
  	order remove: key.!

Item was changed:
+ ----- Method: SakeClassTask class>>class: (in category 'instance creation') -----
- ----- Method: SakeClassTask class>>class: (in category 'as yet unclassified') -----
  class: aClassOrName
  
+ 	^ self new
+ 		theClassName: aClassOrName;
+ 		initialize;
+ 		yourself
- 	^ (self new theClassName: aClassOrName; initialize; yourself)
  		!

Item was changed:
+ ----- Method: SakeTask class>>action: (in category 'instance creation') -----
- ----- Method: SakeTask class>>action: (in category 'as yet unclassified') -----
  action: actionsOrBlock
  
+ 	^ self define: [ :task |		
- 	^ SakeTask define: [ :task |		
  		task action: actionsOrBlock 
  	]!

Item was changed:
  Dictionary subclass: #SakeMeta
  	instanceVariableNames: 'order'
  	classVariableNames: ''
  	poolDictionaries: ''
  	category: 'Sake-Core'!
  
+ !SakeMeta commentStamp: 'damiencassou 12/23/2008 08:39' prior: 0!
+ I'm a dictionary which can be used using any method call instead of #at:put: and at:. Use me like:
+ 
+ - (aSakeMeta foo: 'bar') which is equivalent to (aSakeMeta at: 'foo' put: 'bar')
+ - (aSakeMeta foo) which is equivalent to (aSakeMeta at: 'foo')
+ 
+ The instance variable 'order' remembers the order in which the elements have been added. The methods #withIndexDo: and #printOn: use this variable to iterate in the same order.
+ 
- !SakeMeta commentStamp: 'kph 12/17/2008 22:40' prior: 0!
  | s |
  s := ReadWriteStream on: String new.
  (self new a: 1; b: 2; yourself) storeOn: s.
  s reset contents
  
  !

Item was changed:
  ----- Method: SakeWhat>>action: (in category 'accessing') -----
  action: anObject
- 	"Set the value of action"
  
  	action := anObject!

Item was changed:
+ ----- Method: SakeClassTask class>>exists: (in category 'instance creation') -----
- ----- Method: SakeClassTask class>>exists: (in category 'as yet unclassified') -----
  exists: aClassName
   
  	^ (SakeClassTask class: aClassName) exists!

Item was changed:
+ ----- Method: SakeTask>>dependsOn (in category 'accessing') -----
- ----- Method: SakeTask>>dependsOn (in category 'as yet unclassified') -----
  dependsOn
  
  	^ priors ifNil: [ #() ]!

Item was changed:
+ ----- Method: SakeWhat>>printOn: (in category 'printing') -----
- ----- Method: SakeWhat>>printOn: (in category 'accessing') -----
  printOn: stream
  
  	task printOn: stream!

Item was changed:
  ----- Method: SakeWhat>>action (in category 'accessing') -----
  action
- 	"Answer the value of action"
  
  	^ action!

Item was changed:
+ ----- Method: SakeClassTask class>>isMeta: (in category 'testing tasks') -----
- ----- Method: SakeClassTask class>>isMeta: (in category 'as yet unclassified') -----
  isMeta: aClassName
   
  	^ (self class: aClassName) isMeta!

Item was changed:
+ ----- Method: SakeTask>>dependsOn: (in category 'accessing') -----
- ----- Method: SakeTask>>dependsOn: (in category 'as yet unclassified') -----
  dependsOn: aList
  
  	priors := (aList reject: [ :ea | ea isNil ]) asArray!

Item was changed:
+ ----- Method: SakeTask>>printOn: (in category 'printing') -----
- ----- Method: SakeTask>>printOn: (in category 'as yet unclassified') -----
  printOn: stream
  	
  	stream  
  		nextPutAll: context asString;
  		print: args
  		 !

Item was changed:
+ ----- Method: SakeTask>>hash (in category 'comparing') -----
- ----- Method: SakeTask>>hash (in category 'as yet unclassified') -----
  hash
  
  	^ self hashParts hash!

Item was changed:
+ ----- Method: SakeMeta>>storeOn: (in category 'printing') -----
- ----- Method: SakeMeta>>storeOn: (in category 'as yet unclassified') -----
  storeOn: aStream
  
  	"writes metadata in a user readable format"
  
  	| noneYet |
  	aStream nextPutAll: '('.
  	aStream nextPutAll: self class name.
  	aStream nextPutAll: ' new'; cr.
  	noneYet := true.
  	self withIndexDo: [ :value :key | 
  			noneYet
  				ifTrue: [noneYet := false]
  				ifFalse: [aStream nextPut: $;; cr].
  			aStream nextPutAll: ' at: '.
  			aStream store: key.
  			aStream nextPutAll: ' put: '.
  			aStream store: value.
  			].
  	noneYet ifFalse: [aStream nextPut: $;; cr; nextPutAll: 'yourself'].
  	aStream nextPut: $)!

Item was changed:
+ ----- Method: SakeMeta>>initialize (in category 'initialize-release') -----
- ----- Method: SakeMeta>>initialize (in category 'as yet unclassified') -----
  initialize
  
  	super initialize.
  	order := OrderedCollection new.!

Item was changed:
+ ----- Method: SakeMeta>>doesNotUnderstand: (in category 'error handling') -----
- ----- Method: SakeMeta>>doesNotUnderstand: (in category 'as yet unclassified') -----
  doesNotUnderstand: aMessage
  
  	aMessage selector isUnary ifTrue: [ ^ self at: aMessage selector ifAbsent: [ nil ] ].
  	
  	aMessage selector keywords with: aMessage arguments do: [ :key :value |
  		self at: key allButLast put: value
  	].
  	
  	^ self
  	 
   !

Item was changed:
  ----- Method: SakeWhat>>if (in category 'accessing') -----
  if
- 	"Answer the value of if"
  
  	^ if!

Item was changed:
  ----- Method: SakeWhat>>prior: (in category 'accessing') -----
  prior: anObject
- 	"Set the value of prior"
  
  	prior := anObject!

Item was changed:
+ ----- Method: SakeTask class>>new (in category 'instance creation') -----
- ----- Method: SakeTask class>>new (in category 'as yet unclassified') -----
  new
  	self loopTrap.
  		
  	^ self basicNew initialize
  	
  "	
  self new id.
  self noop id.
  SakeTaskTest ruleA id.
  "!

Item was changed:
  ----- Method: SakeClassTask class>>remove: (in category 'as yet unclassified') -----
  remove: theClassName
  
+ 	^ (self class: theClassName) remove!
- 	^ (self class: theClassName)  remove!

Item was changed:
+ ----- Method: SakeClassTask class>>nonMeta: (in category 'testing tasks') -----
- ----- Method: SakeClassTask class>>nonMeta: (in category 'as yet unclassified') -----
  nonMeta: aClassName
   
  	^ (self class: aClassName) nonMeta!

Item was changed:
+ ----- Method: SakeMeta>>at:put: (in category 'accessing') -----
- ----- Method: SakeMeta>>at:put: (in category 'as yet unclassified') -----
  at: key put: value
  	
  	self at: key ifAbsent: [ order add: key ].
+ 	^ super at: key put: value.
- 	super at: key put: value.
  	!

Item was changed:
+ ----- Method: SakeTask>>= (in category 'comparing') -----
- ----- Method: SakeTask>>= (in category 'as yet unclassified') -----
  = other 
  	^  self class = other class and: [ self hashParts = other hashParts ]!

Item was changed:
  ----- Method: SakeWhat>>if: (in category 'accessing') -----
  if: anObject
- 	"Set the value of if"
  
  	if := anObject!

Item was changed:
+ ----- Method: SakeMeta>>withIndexDo: (in category 'enumerating') -----
- ----- Method: SakeMeta>>withIndexDo: (in category 'as yet unclassified') -----
  withIndexDo: aBlock
  
  	"use the order for readable printing"
  	
  	order do: [ :key |  aBlock value: (self at: key) value: key ]!

Item was changed:
  ----- Method: SakeWhat>>task (in category 'accessing') -----
  task
- 	"Answer the value of task"
  
  	^ task!

Item was changed:
  ----- Method: SakeWhat>>prior (in category 'accessing') -----
  prior
- 	"Answer the value of prior"
  
  	^ prior !

Item was changed:
  ----- Method: SakeWhat>>task: (in category 'accessing') -----
  task: anObject
- 	"Set the value of task"
  
  	task := anObject!



More information about the Packages mailing list