[Pkg] Installer: Installer-Core-kph.268.mcz

squeak-dev-noreply at lists.squeakfoundation.org squeak-dev-noreply at lists.squeakfoundation.org
Wed Dec 10 00:23:58 UTC 2008


A new version of Installer-Core was added to project Installer:
http://www.squeaksource.com/Installer/Installer-Core-kph.268.mcz

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

Name: Installer-Core-kph.268
Author: kph
Time: 10 December 2008, 12:23:54 am
UUID: d06f8dd4-1cb2-4fc7-9e8d-ef900693a0a0
Ancestors: Installer-Core-kph.267

added mantis searching based upon the csv export

=============== Diff against Installer-Core-kph.267 ===============

Item was added:
+ ----- Method: InstallerMantis>>searchStatusConfirmed (in category 'public interface') -----
+ searchStatusConfirmed
+ 
+ 	^ self searchStatus: 'confirmed'.
+ !

Item was changed:
  InstallerWebBased subclass: #InstallerMantis
+ 	instanceVariableNames: 'ma bug desc date array'
+ 	classVariableNames: 'Fixes CSVFields'
- 	instanceVariableNames: 'ma bug desc date'
- 	classVariableNames: 'Fixes'
  	poolDictionaries: ''
  	category: 'Installer-Core'!
+ 
+ !InstallerMantis commentStamp: 'kph 12/10/2008 00:20' prior: 0!
+ Search feature
+ 
+ A := Installer mantis. 
+ 
+ A searchCategory: 'Collections'
+ 
+ self assert: (A searchStatusConfirmed size > 0).
+ self assert: (A searchStatusAcknowledged size > 0).
+ self assert: (A searchStatusConfirmed size > 0).
+ self assert: (A searchStatusResolved size > 0).
+ self assert: (A searchStatusAssigned size > 0).!

Item was changed:
  ----- Method: InstallerMantis>>setBug: (in category 'mantis') -----
  setBug: stringOrNumber
  
+ 	| newBug |
+ 	
+ 	(newBug := stringOrNumber asInteger) = bug ifTrue: [ ^ self ].
+ 	
+ 	self logCR: 'Installer accessing bug: ' , stringOrNumber asString.
+ 
+  	bug := newBug.
+ 	
+  	stringOrNumber = bug ifTrue: [ desc := ''. ^ self ].
- 	| str |
- 	self logCR: stringOrNumber.
-  	stringOrNumber isInteger ifTrue: [ bug := stringOrNumber. desc := ''. ^self ].
-  	bug := stringOrNumber asInteger.
- 	str := str printString. 
- 	desc := stringOrNumber copyFrom: (str size + 1) to: (stringOrNumber size) 
  
+ 	desc := stringOrNumber withoutLeadingDigits  !
- !

Item was changed:
  ----- Method: InstallerMantis>>fixBug:date: (in category 'public interface') -----
  fixBug: aBugNo date: aDate
  
  	self setBug: aBugNo.
   	self install: self maUrl from: self maScript.
  	self maCheckDateAgainst: aDate.
+ 		
+ 	self fixesAppliedNumbers in: [ :fixed |
+ 		(fixed isEmpty or: [ (fixed includes: aBugNo asInteger) not]) 
+ 		ifTrue: [ self fixesApplied add: aBugNo ]].
+ 
  	
  	
- 	
  !

Item was added:
+ ----- Method: InstallerMantis>>csvUpdated (in category 'search-private') -----
+ csvUpdated
+ 
+ 	^ (self csvKey: 'Updated') asDate!

Item was added:
+ ----- Method: InstallerMantis>>csvSummary (in category 'search-private') -----
+ csvSummary
+ 
+ 	^ self csvKey: 'Summary'!

Item was added:
+ ----- Method: InstallerMantis>>statusConfirmed (in category 'public interface') -----
+ statusConfirmed
+ 
+ 	^ self csvKey: 'Category'
+ 	
+  "
+ s bugs collect: [ :ea | ea category ]
+ "!

Item was added:
+ ----- Method: InstallerMantis>>searchStatusResolved (in category 'public interface') -----
+ searchStatusResolved
+ 
+ 	^ self searchStatus: 'resolved'.
+ !

Item was added:
+ ----- Method: InstallerMantis>>csvKey: (in category 'search-private') -----
+ csvKey: key
+ 	
+ 	^ array at: (CSVFields indexOf: key)!

Item was added:
+ ----- Method: InstallerMantis>>setArray: (in category 'public interface') -----
+ setArray: aCsvDataRow
+ 
+ 	array := aCsvDataRow asArray!

Item was added:
+ ----- Method: InstallerMantis>>updated (in category 'accessing') -----
+ updated
+ 
+ 	^ self csvKey: 'Updated'!

Item was changed:
  ----- Method: InstallerMantis>>bug:fix:date: (in category 'public interface') -----
  bug: aBugNo fix: aFileName date: aDate
   
+ 	| |
- 	| fixed |
  	self setBug: aBugNo.
  	self ditchOldChangeSetFor: aFileName.
  	self install: aFileName from: (self maThing: aFileName date: aDate).
- 
- 	fixed := self fixesApplied.
- 	(fixed isEmpty or: [ fixed last ~= aBugNo]) ifTrue: [ fixed add: aBugNo ].
  		
  	^ date!

Item was added:
+ ----- Method: InstallerMantis>>csvFields: (in category 'search-private') -----
+ csvFields: firstRow
+ 
+ 	CSVFields := firstRow
+ !

Item was added:
+ ----- Method: InstallerMantis>>searchCategory: (in category 'public interface') -----
+ searchCategory: c
+ 
+ 	^ self searchAll select: [ :ea | ea csvCategory = c ] !

Item was added:
+ ----- Method: InstallerMantis>>fixesAppliedNumbers (in category 'public interface') -----
+ fixesAppliedNumbers
+ 	^ self fixesApplied collect: [ :fixDesc | fixDesc asInteger ]. !

Item was added:
+ ----- Method: InstallerMantis>>csvCategory (in category 'search-private') -----
+ csvCategory
+ 
+ 	^ self csvKey: 'Category'
+ 	
+  "
+ s bugs collect: [ :ea | ea category ]
+ "!

Item was added:
+ ----- Method: InstallerMantis>>csvGetData (in category 'search-private') -----
+ csvGetData
+ 
+ 	| rs line first |
+ 		
+ 	rs := HTTPSocket httpGet: ma, '/csv_export.php'.
+ 	
+ 	first := true.
+ 	
+ 	^ array := Array streamContents: [ :out |
+ 		 
+ 		[ rs atEnd ] whileFalse: [ 
+ 		
+ 			line := rs nextLine splitOn: ','.
+ 			rs next.
+ 			first ifTrue: [ self csvFields: line. first := false ]
+ 				ifFalse: [ out nextPut: (self class new setArray: line) ].
+ 		]
+ 	].
+ "
+ self reset.
+ self getBugsList 
+ "!

Item was added:
+ ----- Method: InstallerMantis>>all (in category 'public interface') -----
+ all
+ 
+ 	array ifNil: [ array := self csvGetData ]!

Item was added:
+ ----- Method: InstallerMantis>>searchStatusAssigned (in category 'public interface') -----
+ searchStatusAssigned
+ 
+ 	^ self searchStatus: 'assigned'.
+ !

Item was added:
+ ----- Method: InstallerMantis>>getFullCSV (in category 'public interface') -----
+ getFullCSV
+ 
+ 	| rs line first |
+ 		
+ 	rs := HTTPSocket httpGet: ma, '/csv_export.php'.
+ 	
+ 	first := true.
+ 	
+ 	^ array := Array streamContents: [ :out |
+ 		 
+ 		[ rs atEnd ] whileFalse: [ 
+ 		
+ 			line := rs nextLine splitOn: ','.
+ 			rs next.
+ 			first ifTrue: [ self csvFields: line. first := false ]
+ 				ifFalse: [ out nextPut: (self class new setArray: line) ].
+ 		]
+ 	].
+ "
+ self reset.
+ self getBugsList 
+ "!

Item was added:
+ ----- Method: InstallerMantis>>searchAll (in category 'public interface') -----
+ searchAll
+ 
+ 	^ array ifNil: [ array := self csvGetData ]!

Item was changed:
  ----- Method: InstallerMantis>>bug (in category 'accessing') -----
  bug
  	
+ 	^ bug ifNil: [ date := self csvUpdated. desc := self csvSummary. bug := self csvId.  ]!
- 	^ bug!

Item was added:
+ ----- Method: InstallerMantis>>searchUpdatedSince: (in category 'public interface') -----
+ searchUpdatedSince: aDate
+ 
+ 	"note this inlcudes items on the same day because only the date is available in csv"
+ 	
+ 	^ self searchAll select: [ :ea | ea csvUpdated >= aDate ] !

Item was added:
+ ----- Method: InstallerMantis>>csvId (in category 'search-private') -----
+ csvId
+ 
+ 	^ array at: 1!

Item was added:
+ ----- Method: InstallerMantis>>csvStatus (in category 'search-private') -----
+ csvStatus
+ 
+ 	^ self csvKey: 'Status'
+ 	
+ 	
+ !

Item was added:
+ ----- Method: InstallerMantis>>searchStatus: (in category 'public interface') -----
+ searchStatus: s
+ 
+ 	^ self searchAll select: [ :ea | ea csvStatus = s ] !

Item was added:
+ ----- Method: InstallerMantis>>searchSummary: (in category 'public interface') -----
+ searchSummary: match
+ 
+ 	^ self searchAll select: [ :ea | match match: ea csvSummary  ] !

Item was added:
+ ----- Method: InstallerMantis>>printOn: (in category 'accessing') -----
+ printOn: stream
+ 
+ 	super printOn: stream.
+ 	
+ 	(array ifNil: [ ^ self ]) printOn: stream.!

Item was added:
+ ----- Method: InstallerMantis>>submitted (in category 'accessing') -----
+ submitted
+ 
+ 	^ self csvKey: 'Date Sumbitted'.
+ 	
+ !

Item was added:
+ ----- Method: InstallerMantis>>searchStatusAcknowledged (in category 'public interface') -----
+ searchStatusAcknowledged
+ 
+ 	^ self searchStatus: 'acknowledged'.
+ !



More information about the Packages mailing list