The Trunk: SystemReporter-laza.2.mcz

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

The Trunk: SystemReporter-laza.2.mcz

commits-2
David T. Lewis uploaded a new version of SystemReporter to project The Trunk:
http://source.squeak.org/trunk/SystemReporter-laza.2.mcz

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

Name: SystemReporter-laza.2
Author: laza
Time: 18 January 2011, 12:12:52.537 pm
UUID: 40d39d22-fd7d-9647-9bea-11024447eefa
Ancestors: SystemReporter-laza.1

- added more reports
- use TextStream to have better formatting
- fixed menus
- preserve order of categories

=============== Diff against SystemReporter-laza.1 ===============

Item was changed:
  Object subclass: #SystemReporter
+ instanceVariableNames: 'categories categoriesSelected report tinyBenchmarksResult categoryList'
- instanceVariableNames: 'categories categoriesSelected report'
  classVariableNames: ''
  poolDictionaries: ''
  category: 'SystemReporter'!
 
+ !SystemReporter commentStamp: 'laza 1/18/2011 12:04' prior: 0!
- !SystemReporter commentStamp: 'laza 1/17/2011 13:37' prior: 0!
  SystemReporter offers a window where information about the system is gathered. This can be easily copied to the clipboard and be attached to a bug report for better identification of the context the bug occured in.
 
  To extend the SystemReporter:
+ - add a method
+ reportXYZ: aStream
+  to the reporting category
+ - insert a line
+ add: #XYZ method: #reportXYZ
+  to the initialize method
- - add a method reportXYZ:aStream to the reporting category
- - add an association like XYZ->reportXYZ to the initialize method
  !

Item was added:
+ ----- Method: SystemReporter>>add:method: (in category 'accessing-categories') -----
+ add: category method: aSymbol
+ ^self categoryList add: (self categories add: category -> aSymbol) key!

Item was changed:
  ----- Method: SystemReporter>>buildReportWith: (in category 'building') -----
  buildReportWith: aBuilder
  ^ aBuilder pluggableTextSpec new
  model: self;
  menu: #reportMenu:;
  getText: #reportText;
  yourself.!

Item was added:
+ ----- Method: SystemReporter>>categories (in category 'accessing-categories') -----
+ categories
+ ^ categories ifNil: [categories := IdentityDictionary new]!

Item was changed:
  ----- Method: SystemReporter>>categoryList (in category 'accessing-categories') -----
  categoryList
+ ^ categoryList ifNil: [categoryList := OrderedCollection new]!
- ^ categories keys!

Item was changed:
  ----- Method: SystemReporter>>categoryMenu: (in category 'accessing-categories') -----
  categoryMenu: aMenu
  ^ aMenu
  title: 'Categories';
  add: 'Select all' action: #selectAllCategories;
- add: 'Select inversion' action: #selectInverseCategories;
  add: 'Select none' action: #selectNoCategories;
  addLine;
+ add: 'Refresh' action: #refresh;
- add: 'Filter...' action: #filterCategories;
- addLine;
- add: 'Refresh' action: #updateCategories;
  yourself.!

Item was added:
+ ----- Method: SystemReporter>>copyReportToClipboard (in category 'accessing-report') -----
+ copyReportToClipboard
+ Clipboard clipboardText: self reportText.
+ UIManager default inform: 'Copied Report to Clipboard'!

Item was changed:
  ----- Method: SystemReporter>>header:on: (in category 'printing-report') -----
  header: aString on: aStream
+ aStream withAttribute: TextEmphasis bold do: [
+ aStream nextPutAll: aString; cr.
+ aString size timesRepeat: [aStream nextPut: $-].
+ aStream cr]!
- aStream nextPutAll: aString; cr.
- aString size timesRepeat: [aStream nextPut: $-].
- aStream cr!

Item was changed:
  ----- Method: SystemReporter>>initialize (in category 'initialize-release') -----
  initialize
+ self
+ add: #Image method: #reportImage;
+ add: #'Image Parameters' method: #reportImageParameters;
+ add: #'Image Sources' method: #reportSources;
+ add: #'VM General' method: #reportVM;
+ add: #'VM Options' method: #reportVMOptions;
+ add: #'VM Modules' method: #reportModules.
- categories := IdentityDictionary new
- add: #Image -> #reportImage;
- add: #'OS General' -> #reportOS;
- add: #'VM General' -> #reportVM;
- add: #Modules -> #reportModules;
- yourself.
  Smalltalk os platformName = 'Win32' ifTrue: [
+ self
+ add: #'VM Configuration' method: #reportINI.
+ ].
+ self
+ add: #'OS General' method: #reportOS.
+ Smalltalk os platformName = 'Win32' ifTrue: [
+ self
+ add: #'OS Details' method: #reportOSDetails;
+ add: #'Hardware Details' method: #reportHardwareDetails;
+ add: #'GFX Hardware Details' method: #reportGFXDetails.
+ ].
+ self add: #'Tiny Benchmarks' method: #reportTinyBenchmarks.
- categories
- add: #'Hardware Details' -> #reportHardwareDetails;
- add: #'Operating System Details' -> #reportOSDetails;
- add: #'Graphics Hardware Details' -> #reportGFXDetails
- ].
  categoriesSelected := Set with: #Image with: #'VM General'.
  self updateReport
  !

Item was added:
+ ----- Method: SystemReporter>>refresh (in category 'accessing-categories') -----
+ refresh
+ tinyBenchmarksResult := nil.
+ self updateReport!

Item was changed:
  ----- Method: SystemReporter>>reportGFXDetails: (in category 'reporting') -----
  reportGFXDetails: aStream
  self header: 'Graphics Hardware Details' on: aStream.
+ aStream nextPutAll: (SmalltalkImage current getSystemAttribute: 10003)!
- aStream
- tab; nextPutAll: (SmalltalkImage current getSystemAttribute: 10003); cr!

Item was changed:
  ----- Method: SystemReporter>>reportHardwareDetails: (in category 'reporting') -----
  reportHardwareDetails: aStream
  self header: 'Hardware Details' on: aStream.
+ aStream nextPutAll: (SmalltalkImage current getSystemAttribute: 10001)!
- aStream
- tab; nextPutAll: (SmalltalkImage current getSystemAttribute: 10001); cr!

Item was added:
+ ----- Method: SystemReporter>>reportINI: (in category 'reporting') -----
+ reportINI: aStream
+ | exePath iniData iniPath |
+ self header: 'VM Configuration' on: aStream.
+ exePath := SmalltalkImage current getSystemAttribute: 0.
+ iniPath := (exePath copyUpToLast: $.), '.ini'.
+ aStream nextPutAll: iniPath; cr.
+ iniData := [
+ (FileStream readOnlyFileNamed: iniPath)
+ contentsOfEntireFile
+ ] on: Error do:[:ex| ex return: ex printString].
+ aStream
+ nextPutAll: iniData!

Item was changed:
  ----- Method: SystemReporter>>reportImage: (in category 'reporting') -----
  reportImage: aStream
- | id value |
  self header: 'Image' on: aStream.
  aStream
+ nextPutAll: SystemVersion current version; cr;
+ nextPutAll: SmalltalkImage current lastUpdateString; cr;
+ nextPutAll: SmalltalkImage current currentChangeSetString; cr;
+ nextPutAll: (SmalltalkImage current getSystemAttribute: 1); cr!
- tab; nextPutAll: SystemVersion current version; cr;
- tab; nextPutAll: SmalltalkImage current lastUpdateString; cr;
- tab; nextPutAll: SmalltalkImage current currentChangeSetString; cr;
- tab; nextPutAll: (SmalltalkImage current getSystemAttribute: 1); cr.
- id := 3.
- [value := (SmalltalkImage current getSystemAttribute: id).
- value = nil or: [id > 1000]] whileFalse: [
- aStream nextPutAll: value; space.
- id := id + 1
- ].
- !

Item was added:
+ ----- Method: SystemReporter>>reportImageParameters: (in category 'reporting') -----
+ reportImageParameters: aStream
+ | id value |
+ self header: 'Image Commandline Parameters' on: aStream.
+ id := 3.
+ [value := (SmalltalkImage current getSystemAttribute: id).
+ value = nil or: [id > 1000]] whileFalse: [
+ aStream
+ nextPut: $#;
+ nextPutAll: id printString;
+ tab;
+ nextPutAll: value; cr.
+ id := id + 1
+ ].
+ id = 3 ifTrue: [aStream nextPutAll: 'none'; cr]
+ !

Item was added:
+ ----- Method: SystemReporter>>reportMenu: (in category 'accessing-report') -----
+ reportMenu: aMenu
+ ^ aMenu
+ title: 'Report';
+ add: 'Copy to Clipboard' action: #copyReportToClipboard;
+ yourself.!

Item was changed:
  ----- Method: SystemReporter>>reportModules: (in category 'reporting') -----
  reportModules: aStream
+ self header: 'Loaded VM Modules' on: aStream.
+ SmalltalkImage current listLoadedModules asSortedCollection do: [:each | aStream nextPutAll: each; cr].
- self header: 'Loaded Modules' on: aStream.
- SmalltalkImage current listLoadedModules do: [:each | aStream tab; nextPutAll: each; cr].
 
  !

Item was changed:
  ----- Method: SystemReporter>>reportOS: (in category 'reporting') -----
  reportOS: aStream
  self header: 'Operating System/Hardware' on: aStream.
  aStream
+ nextPutAll: (SmalltalkImage current getSystemAttribute: 1001); space;
+ nextPutAll: (SmalltalkImage current getSystemAttribute: 1002); space;
+ nextPutAll: (SmalltalkImage current getSystemAttribute: 1003); cr
- tab; nextPutAll: (SmalltalkImage current getSystemAttribute: 1001); space;
- tab; nextPutAll: (SmalltalkImage current getSystemAttribute: 1002); space;
- tab; nextPutAll: (SmalltalkImage current getSystemAttribute: 1003).
  !

Item was changed:
  ----- Method: SystemReporter>>reportOSDetails: (in category 'reporting') -----
  reportOSDetails: aStream
  self header: 'Operating System Details' on: aStream.
+ aStream nextPutAll: (SmalltalkImage current getSystemAttribute: 10002)!
- aStream
- tab; nextPutAll: (SmalltalkImage current getSystemAttribute: 10002); cr!

Item was added:
+ ----- Method: SystemReporter>>reportSources: (in category 'reporting') -----
+ reportSources: aStream
+ self header: 'Image Sources' on: aStream.
+ aStream nextPutAll: SourceFiles class printString; cr.
+ SourceFiles do: [:each |
+ each ifNotNil: [aStream nextPutAll: each printString; cr]]!

Item was changed:
  ----- Method: SystemReporter>>reportText (in category 'accessing-report') -----
  reportText
  ^ (report isNil or: [categoriesSelected isEmpty])
+ ifTrue: ['-- Choose any category on the left --']
- ifTrue: ['-- empty --']
  ifFalse: [report]!

Item was added:
+ ----- Method: SystemReporter>>reportTinyBenchmarks: (in category 'reporting') -----
+ reportTinyBenchmarks: aStream
+ tinyBenchmarksResult ifNil: [
+ UIManager inform: 'Running the Benchmarks\will take a few seconds' withCRs.
+ tinyBenchmarksResult := 0 tinyBenchmarks].
+ self header: 'Tiny Benchmarks' on: aStream.
+ aStream nextPutAll: tinyBenchmarksResult!

Item was changed:
  ----- Method: SystemReporter>>reportVM: (in category 'reporting') -----
  reportVM: aStream
- | id value |
  self header: 'Virtual Machine' on: aStream.
  aStream
+ nextPutAll: (SmalltalkImage current getSystemAttribute: 1004); cr;
+ nextPutAll: (SmalltalkImage current getSystemAttribute: 0); cr!
- tab; nextPutAll: (SmalltalkImage current getSystemAttribute: 1004); cr;
- tab; nextPutAll: (SmalltalkImage current getSystemAttribute: 0); cr.
- aStream tab.
- id := -1.
- [value := (SmalltalkImage current getSystemAttribute: id).
- value = nil or: [id < -1000]] whileFalse: [
- aStream nextPutAll: value; space.
- id := id - 1
- ].
- !

Item was added:
+ ----- Method: SystemReporter>>reportVMOptions: (in category 'reporting') -----
+ reportVMOptions: aStream
+ | id value |
+ self header: 'Virtual Machine Commandline Options' on: aStream.
+ id := -1.
+ [value := (SmalltalkImage current getSystemAttribute: id).
+ value = nil or: [id < -1000]] whileFalse: [
+ aStream
+ nextPut: $#;
+ nextPutAll: id negated printString;
+ tab;
+ nextPutAll: value; cr.
+ id := id - 1
+ ].
+ id = -1 ifTrue: [aStream nextPutAll: 'none'; cr]
+
+ !

Item was added:
+ ----- Method: SystemReporter>>selectAllCategories (in category 'accessing-categories') -----
+ selectAllCategories
+ categoriesSelected addAll: categoryList.
+ self changed: #categorySelected.
+ self updateReport!

Item was added:
+ ----- Method: SystemReporter>>selectNoCategories (in category 'accessing-categories') -----
+ selectNoCategories
+ categoriesSelected removeAll.
+ self changed: #categorySelected.
+ self updateReport!

Item was changed:
  ----- Method: SystemReporter>>updateReport (in category 'updating') -----
  updateReport
+ report := Text streamContents: [:stream |
+ stream
+ withAttribute: (TextFontReference toFont: ((TextStyle named: 'BitstreamVeraSansMono') fontOfSize: 16))
+ do: [
+ self categoryList do: [:each |
+ (categoriesSelected includes: each) ifTrue: [
+ self perform: ((categories at: each), ':') asSymbol with: stream.
+ stream cr]]]].
- report := String streamContents: [:stream |  
- self categoryList do: [:each |
- (categoriesSelected includes: each) ifTrue: [
- self perform: ((categories at: each), ':') asSymbol with: stream.
- stream cr; cr]]].
  self changed: #reportText!