Initial version of JSON report.
authorJan Vrany <jan.vrany@fit.cvut.cz>
Wed, 12 Jun 2013 14:27:14 +0100
changeset 29 00d2eaa41853
parent 28 97372503ad1e
child 30 e2b7fd4d1d24
Initial version of JSON report.
s/BenchmarkOutcome.st
s/BenchmarkReport.st
s/BenchmarkReportJSON.st
s/BenchmarkReportJSONWriter.st
s/BenchmarkReportText.st
s/BenchmarkResult.st
s/BenchmarkRunner.st
s/Make.proto
s/Make.spec
s/abbrev.stc
s/bc.mak
s/bmake.bat
s/jv_calipel_s.st
s/lccmake.bat
s/libInit.cc
s/mingwmake.bat
s/s.rc
s/tests/BenchmarkReportJSONWriterTests.st
s/tests/Make.proto
s/tests/Make.spec
s/tests/Makefile.init
s/tests/abbrev.stc
s/tests/bc.mak
s/tests/jv_calipel_s_tests.st
s/tests/libInit.cc
s/tests/tests.rc
s/vcmake.bat
--- a/s/BenchmarkOutcome.st	Tue Jun 11 22:54:56 2013 +0100
+++ b/s/BenchmarkOutcome.st	Wed Jun 12 14:27:14 2013 +0100
@@ -1,7 +1,7 @@
 "{ Package: 'jv:calipel/s' }"
 
 Object subclass:#BenchmarkOutcome
-	instanceVariableNames:'instance params times'
+	instanceVariableNames:'params times benchmark'
 	classVariableNames:''
 	poolDictionaries:''
 	category:'CalipeL-S-Core'
@@ -10,6 +10,12 @@
 
 !BenchmarkOutcome class methodsFor:'instance creation'!
 
+benchmark:benchmarkArg times:timesArg parameters:paramsArg 
+    ^self new benchmark:benchmarkArg times:timesArg parameters:paramsArg
+
+    "Created: / 11-06-2013 / 23:19:03 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
 instance:instanceArg times:timesArg parameters:paramsArg 
     ^self new instance:instanceArg times:timesArg parameters:paramsArg
 
@@ -18,8 +24,10 @@
 
 !BenchmarkOutcome methodsFor:'accessing'!
 
-instance
-    ^ instance
+benchmark
+    ^ benchmark
+
+    "Created: / 11-06-2013 / 23:19:53 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
 params
@@ -38,12 +46,12 @@
 
 !BenchmarkOutcome methodsFor:'initialization'!
 
-instance:instanceArg times:timesArg parameters:paramsArg 
-    instance := instanceArg.
+benchmark:benchmarkArg times:timesArg parameters:paramsArg 
+    benchmark := benchmarkArg.
     times := timesArg.
     params := paramsArg.
 
-    "Created: / 04-06-2013 / 22:26:52 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+    "Created: / 11-06-2013 / 23:19:23 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 ! !
 
 !BenchmarkOutcome class methodsFor:'documentation'!
--- a/s/BenchmarkReport.st	Tue Jun 11 22:54:56 2013 +0100
+++ b/s/BenchmarkReport.st	Wed Jun 12 14:27:14 2013 +0100
@@ -10,6 +10,12 @@
 
 !BenchmarkReport class methodsFor:'instance creation'!
 
+json
+    ^BenchmarkReportJSON new
+
+    "Created: / 12-06-2013 / 14:13:04 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
 text
     ^BenchmarkReportText new
 
@@ -46,9 +52,13 @@
 !BenchmarkReport methodsFor:'writing'!
 
 write
-    ^self subclassResponsibility.
+    self 
+        writeHeader;
+        writeOutcomes;
+        writeFooter.
 
     "Created: / 28-05-2013 / 00:34:14 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+    "Modified: / 11-06-2013 / 23:26:46 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
 write: aBenchmarkResult on: aStream
@@ -57,6 +67,30 @@
     self write.
 
     "Created: / 28-05-2013 / 00:33:37 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
+writeFooter
+    self subclassResponsibility
+
+    "Created: / 11-06-2013 / 23:26:46 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
+writeHeader
+    self subclassResponsibility
+
+    "Created: / 11-06-2013 / 23:26:45 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
+writeOutcome:arg
+    "raise an error: must be redefined in concrete subclass(es)"
+
+    ^ self subclassResponsibility
+!
+
+writeOutcomes
+    result outcomesDo:[:outcome | self writeOutcome: outcome ].
+
+    "Created: / 11-06-2013 / 23:26:09 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 ! !
 
 !BenchmarkReport class methodsFor:'documentation'!
--- /dev/null	Thu Jan 01 00:00:00 1970 +0000
+++ b/s/BenchmarkReportJSON.st	Wed Jun 12 14:27:14 2013 +0100
@@ -0,0 +1,88 @@
+"{ Package: 'jv:calipel/s' }"
+
+BenchmarkReport subclass:#BenchmarkReportJSON
+	instanceVariableNames:'json'
+	classVariableNames:''
+	poolDictionaries:''
+	category:'CalipeL-S-Core-Reports'
+!
+
+
+!BenchmarkReportJSON methodsFor:'accessing'!
+
+stream:something
+    stream := something.
+    json := BenchmarkReportJSONWriter on: stream.
+
+    "Created: / 12-06-2013 / 14:22:35 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+! !
+
+!BenchmarkReportJSON methodsFor:'writing'!
+
+write
+    json writeDictionaryWith:[
+        json writeKey: 'outcomes' valueWith: [ self writeOutcomes ]
+    ].
+
+    "Created: / 12-06-2013 / 14:03:27 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
+writeBenchmark: benchmark
+    json writeDictionaryWith:[
+        json writeKey: 'class' value: benchmark instance class name.
+        json writeElementSeparator.
+        json writeKey: 'selector' value: benchmark selector.
+    ]
+
+    "Created: / 12-06-2013 / 14:10:18 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
+writeFooter
+    "superclass BenchmarkReport says that I am responsible to implement this method"
+
+    "Modified: / 12-06-2013 / 14:14:23 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
+writeHeader
+    "superclass BenchmarkReport says that I am responsible to implement this method"
+
+    "Modified: / 12-06-2013 / 14:14:27 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
+writeOutcome:outcome
+    json writeDictionaryWith:[
+        json writeKey: 'benchmark' valueWith: [ self writeBenchmark: outcome benchmark ].
+        json writeElementSeparator.
+        json writeKey: 'times' value: outcome times.
+        json writeElementSeparator.        
+        json writeKey: 'parameters' valueWith: [ self writeParameters: outcome ].
+    ]
+
+    "Modified: / 12-06-2013 / 14:10:19 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
+writeOutcomes
+    "raise an error: must be redefined in concrete subclass(es)"
+    json writeArrayWith:[
+        result 
+           outcomesDo: [:outcome| self writeOutcome: outcome] 
+           separatedBy:[json writeElementSeparator]
+    ]
+
+    "Created: / 11-06-2013 / 23:39:42 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+    "Modified (format): / 12-06-2013 / 14:06:09 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
+writeParameters: outcome
+    json writeDictionaryWith: []
+
+    "Created: / 12-06-2013 / 14:10:19 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+! !
+
+!BenchmarkReportJSON class methodsFor:'documentation'!
+
+version_HG
+
+    ^ '$Changeset: <not expanded> $'
+! !
+
--- /dev/null	Thu Jan 01 00:00:00 1970 +0000
+++ b/s/BenchmarkReportJSONWriter.st	Wed Jun 12 14:27:14 2013 +0100
@@ -0,0 +1,294 @@
+"{ Package: 'jv:calipel/s' }"
+
+Object subclass:#BenchmarkReportJSONWriter
+	instanceVariableNames:'stream indent'
+	classVariableNames:'Rules EscapeTable'
+	poolDictionaries:''
+	category:'CalipeL-S-Core-Reports'
+!
+
+!BenchmarkReportJSONWriter class methodsFor:'documentation'!
+
+documentation
+"
+    Simple, portable JSON writer.
+    
+    [author:]
+        Jan Vrany <jan.vrany@fit.cvut.cz> (adaptation for CalipeL)
+
+    [instance variables:]
+
+    [class variables:]
+
+    [see also:]
+
+"
+! !
+
+!BenchmarkReportJSONWriter class methodsFor:'initialization'!
+
+initialize
+    "Invoked at system start or when the class is dynamically loaded."
+
+    EscapeTable := Dictionary new.
+    EscapeTable at:  8 put: '\b'.
+    EscapeTable at:  9 put: '\t'.
+    EscapeTable at: 10 put: '\n'.
+    EscapeTable at: 12 put: '\f'.
+    EscapeTable at: 13 put: '\r'.
+    EscapeTable at: 34 put: '\"'.
+    EscapeTable at: 92 put: '\\'.
+
+    Rules := OrderedCollection new.
+    Rules add: [:obj | obj isNil ];             add:#writeNull: .
+    Rules add: [:obj | obj isString ];          add:#writeString: .
+    Rules add: [:obj | obj isBoolean ];         add:#writeBoolean: .
+    Rules add: [:obj | obj isInteger ];         add:#writeInteger: .
+    Rules add: [:obj | obj isFloat ];           add:#writeFloat: .
+    "/ CalipeL/S specific mappings
+    Rules add: [:obj | obj isClass ];           add:#writeClass: .
+
+    "Modified: / 12-06-2013 / 13:53:31 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+! !
+
+!BenchmarkReportJSONWriter class methodsFor:'instance creation'!
+
+new
+    "return an initialized instance"
+
+    ^ self basicNew initialize.
+!
+
+on: writeStream
+	"Initialize on writeStream, which should be a character stream that 
+	implements #nextPut:, #nextPutAll:, #space and (optionally) #close."
+
+	^ self new
+		on: writeStream;
+		yourself
+! !
+
+!BenchmarkReportJSONWriter class methodsFor:'convenience'!
+
+toString: object
+	^ String streamContents: [ :stream |
+			(self on: stream) nextPut: object ]
+!
+
+toStringPretty: object
+	^ String streamContents: [ :stream |
+			(self on: stream)
+				prettyPrint: true; 
+				nextPut: object ]
+! !
+
+!BenchmarkReportJSONWriter methodsFor:'initialize-release'!
+
+close
+	stream ifNotNil: [
+		stream close.
+		stream := nil ]
+!
+
+initialize
+        super initialize.
+        indent := 0
+
+    "Modified: / 12-06-2013 / 14:00:44 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
+on: aWriteStream
+	"Initialize on aWriteStream, which should be a character stream that 
+	implements #nextPut:, #nextPutAll:, #space and (optionally) #close."
+
+	stream := aWriteStream
+! !
+
+!BenchmarkReportJSONWriter methodsFor:'private'!
+
+encode: string
+
+    string do:[:char|
+        | code escape |
+
+        code := char codePoint.
+        escape := EscapeTable at: code ifAbsent:[nil].
+        escape notNil ifTrue:[
+            stream nextPutAll: escape
+        ] ifFalse:[
+            (code < 32 or:[code > 127]) ifTrue:[
+                self error: 'Unimplemented \u escaping'.
+            ] ifFalse:[
+                stream nextPut: char.
+            ]
+        ]
+    ].
+
+    "Created: / 12-06-2013 / 13:42:12 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+! !
+
+!BenchmarkReportJSONWriter methodsFor:'stream protocol'!
+
+nextPut: anObject
+    self write: anObject
+
+    "Modified: / 12-06-2013 / 11:06:39 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
+nextPutAll: anObject
+    self write: anObject
+
+    "Created: / 12-06-2013 / 11:07:06 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+! !
+
+!BenchmarkReportJSONWriter methodsFor:'writing'!
+
+write: anObject
+
+    1 to: Rules size by: 2 do:[:i|
+        ((Rules at: i) value: anObject) ifTrue:[
+            self perform: (Rules at: i + 1) with: anObject.
+            ^self.
+        ]        
+    ].
+    anObject isSequenceable ifTrue:[
+        self writeArray: anObject.
+        ^self
+    ].
+    anObject isDictionary ifTrue:[
+        self writeDictionary: anObject.
+        ^self
+    ].
+    self writeObject: anObject
+
+    "Created: / 12-06-2013 / 11:00:39 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
+writeArray:collection 
+    self writeArrayWith:[
+        collection 
+            do:[:each | self write: each ]
+            separatedBy:[ self writeElementSeparator ].
+    ]
+
+    "Modified: / 12-06-2013 / 14:02:15 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
+writeArrayWith:block 
+    stream nextPut: $[.
+    indent := indent + 1.
+    block value.
+    indent := indent - 1.
+    stream nextPut: $]
+
+    "Created: / 12-06-2013 / 14:01:48 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
+writeBoolean: boolean
+	boolean printOn: stream
+!
+
+writeDictionary:dictionary 
+    self writeDictionaryWith:[
+        dictionary associations
+            do:[:each | self writeKey: each key value: each value ]
+            separatedBy:[ self writeElementSeparator ].
+    ]
+
+    "Modified: / 12-06-2013 / 14:02:30 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
+writeDictionaryWith:block
+    stream nextPut: ${.
+    indent := indent + 1.
+    block value.
+    indent := indent - 1.
+    stream nextPut: $}
+
+    "Created: / 12-06-2013 / 14:01:36 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
+writeFloat: float
+	float printOn: stream
+!
+
+writeInteger: integer
+	integer printOn: stream
+	
+!
+
+writeKey: key value: value 
+    self write: key.
+    stream nextPutAll:': '.
+    self write: value
+
+    "Created: / 12-06-2013 / 13:59:18 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
+writeKey: key valueWith: block 
+    self write: key.
+    stream nextPutAll:': '.
+    block value
+
+    "Created: / 12-06-2013 / 14:08:21 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
+writeNull: anObject
+    stream nextPutAll: 'null'
+
+    "Created: / 12-06-2013 / 11:09:22 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
+writeObject: anObject
+    "Objects are written as dictionaries instvarname -> instvar value"
+
+    | instvars |
+
+    instvars := anObject class allInstVarNames.
+    stream nextPut: ${.
+    indent := indent + 1.
+    instvars withIndexDo:[:nm :i|
+        self writeKey: nm value: (anObject instVarAt: i).        
+        i ~~ instvars size ifTrue:[
+            self writeElementSeparator.
+        ]
+    ].
+    indent := indent - 1.
+    stream nextPut: $}
+
+    "Modified: / 12-06-2013 / 13:59:58 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
+writeString: string
+    stream nextPut: $".
+    self encode: string.
+    stream nextPut: $"
+
+    "Modified: / 12-06-2013 / 13:43:19 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+! !
+
+!BenchmarkReportJSONWriter methodsFor:'writing - CalipeL-S extras'!
+
+writeClass: aClass
+    ^self writeString: aClass name
+
+    "Created: / 12-06-2013 / 13:52:59 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+! !
+
+!BenchmarkReportJSONWriter methodsFor:'writing - private'!
+
+writeElementSeparator
+    stream nextPut:$,.
+
+    "Modified: / 12-06-2013 / 13:42:39 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+! !
+
+!BenchmarkReportJSONWriter class methodsFor:'documentation'!
+
+version_HG
+
+    ^ '$Changeset: <not expanded> $'
+! !
+
+
+BenchmarkReportJSONWriter initialize!
--- a/s/BenchmarkReportText.st	Tue Jun 11 22:54:56 2013 +0100
+++ b/s/BenchmarkReportText.st	Wed Jun 12 14:27:14 2013 +0100
@@ -36,32 +36,47 @@
 
 !BenchmarkReportText methodsFor:'writing'!
 
-write
-    | classes outcomes |
+writeFooter
+
+    "Modified: / 11-06-2013 / 23:28:44 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
+writeHeader
+    stream 
+        nextPutAll: 'Generated at :';
+        nextPutAll: Date today printString;
+        nextPutAll: ' ';
+        nextPutAll: Time now printString;
+        cr;
+        cr.
+
+    "Modified: / 11-06-2013 / 23:28:37 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
 
-    classes := SortedCollection sortBlock:[:a :b|a name < b name].
-    outcomes := Dictionary new.
-    result outcomes do:[:each|
-        (classes includes: each instance class) ifFalse:[
-            classes add: each instance class.
+writeOutcome: outcome
+    self format: outcome benchmark selector width: 15 align: #right.
+    stream nextPutAll: ' : '.
+    self format: outcome time width: 5 align: #right.
+    stream nextPutAll: ' [ms]'.
+    stream cr.
+
+    "Created: / 11-06-2013 / 23:24:52 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
+writeOutcomes
+    | class |
+
+    class := nil.
+    result outcomesDo:[:outcome |
+        outcome benchmark instance class == class ifFalse:[
+            class := outcome benchmark instance class.
+            stream nextPutAll: '== ', class name , ' =='; cr.
         ].
-        (outcomes at: each instance class ifAbsentPut:[SortedCollection sortBlock:[:a :b|a instance selector < b instance selector]])
-            add: each.
-    ].
-
-    classes do:[:class|
-        stream nextPutAll: '== '; nextPutAll:  class name; nextPutAll: ' =='; cr.
-        (outcomes at: class) do:[:outcome|
-            self format: outcome instance selector width: 15 align: #right.
-            stream nextPutAll: ' : '.
-            self format: outcome time width: 5 align: #right.
-            stream nextPutAll: ' [ms]'.
-            stream cr.
-        ].
+        self writeOutcome: outcome
     ].
     stream cr.
 
-    "Modified: / 31-05-2013 / 12:11:24 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+    "Created: / 11-06-2013 / 23:24:13 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 ! !
 
 !BenchmarkReportText class methodsFor:'documentation'!
--- a/s/BenchmarkResult.st	Tue Jun 11 22:54:56 2013 +0100
+++ b/s/BenchmarkResult.st	Wed Jun 12 14:27:14 2013 +0100
@@ -22,6 +22,38 @@
     ^ outcomes
 !
 
+outcomesDo: aBlock
+    "Iterate outcomes, perform given block.
+     outcomes are sorted by benchmark instance name first,
+     then by benchmark name"
+
+    ^self outcomesDo: aBlock separatedBy: nil
+
+    "Created: / 11-06-2013 / 23:11:28 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
+outcomesDo: aBlock separatedBy: anotherBlock
+    "Iterate outcomes, perform given block.
+     outcomes are sorted by benchmark instance name first,
+     then by benchmark name"
+
+    | classes classesOutcomes |
+    classes := SortedCollection sortBlock:[:a :b|a name < b name].
+    classesOutcomes := Dictionary new.
+    outcomes do:[:each|
+        (classes includes: each benchmark instance class) ifFalse:[
+            classes add: each benchmark instance class.
+        ].
+        (classesOutcomes at: each benchmark instance class ifAbsentPut:[SortedCollection sortBlock:[:a :b|a benchmark selector < b benchmark selector]])
+            add: each.
+    ].
+    classes 
+        do:[:class|(classesOutcomes at: class) do: aBlock separatedBy: anotherBlock]
+        separatedBy: anotherBlock
+
+    "Created: / 11-06-2013 / 23:37:21 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
 runs
     "Return how many times each benchmark is run." 
 
@@ -68,12 +100,12 @@
     times := (1 to: runs) collect: [:i | aBenchmarkInstance runBenchmarkWithParameters: aDictionary].
     outcomes add:
         (BenchmarkOutcome 
-            instance: aBenchmarkInstance
+            benchmark: aBenchmarkInstance
             times: times
             parameters: aBenchmarkInstance)
 
     "Created: / 27-05-2013 / 22:20:03 / Jan Vrany <jan.vrany@fit.cvut.cz>"
-    "Modified: / 05-06-2013 / 10:29:30 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+    "Modified: / 11-06-2013 / 23:18:48 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 ! !
 
 !BenchmarkResult class methodsFor:'documentation'!
--- a/s/BenchmarkRunner.st	Tue Jun 11 22:54:56 2013 +0100
+++ b/s/BenchmarkRunner.st	Wed Jun 12 14:27:14 2013 +0100
@@ -113,11 +113,11 @@
             arg = '--text' ifTrue:[
                 report := BenchmarkReport text.
             ].
-"
+
             arg = '--json' ifTrue:[
                 report := BenchmarkReport json.
             ].
-"
+
             arg second = $D ifTrue:[
                 | eqIdx |
 
@@ -161,14 +161,16 @@
 
     "Write report"
     file notNil ifTrue:[
-        report write: result on: file asFilename writeStream
+        file asFilename writingFileDo:[:s|
+            report write: result on: s 
+        ]
     ] ifFalse:[
         report write: result on: BenchmarkPlatform current stdout
     ].
 
     self exit: 0.
 
-    "Modified: / 10-06-2013 / 20:33:56 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+    "Modified: / 12-06-2013 / 14:25:55 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
 options
--- a/s/Make.proto	Tue Jun 11 22:54:56 2013 +0100
+++ b/s/Make.proto	Wed Jun 12 14:27:14 2013 +0100
@@ -21,7 +21,7 @@
 INCLUDE_TOP=$(TOP)/..
 
 # subdirectories where targets are to be made:
-SUBDIRS= tests stx benchmarks
+SUBDIRS= benchmarks stx benchmarks/micro tests
 
 
 # subdirectories where Makefiles are to be made:
@@ -125,10 +125,12 @@
 $(OUTDIR)BenchmarkOutcome.$(O) BenchmarkOutcome.$(H): BenchmarkOutcome.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
 $(OUTDIR)BenchmarkPlatform.$(O) BenchmarkPlatform.$(H): BenchmarkPlatform.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
 $(OUTDIR)BenchmarkReport.$(O) BenchmarkReport.$(H): BenchmarkReport.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
+$(OUTDIR)BenchmarkReportJSONWriter.$(O) BenchmarkReportJSONWriter.$(H): BenchmarkReportJSONWriter.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
 $(OUTDIR)BenchmarkResult.$(O) BenchmarkResult.$(H): BenchmarkResult.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
 $(OUTDIR)BenchmarkRunner.$(O) BenchmarkRunner.$(H): BenchmarkRunner.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
 $(OUTDIR)BenchmarkSuite.$(O) BenchmarkSuite.$(H): BenchmarkSuite.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
 $(OUTDIR)jv_calipel_s.$(O) jv_calipel_s.$(H): jv_calipel_s.st $(INCLUDE_TOP)/stx/libbasic/LibraryDefinition.$(H) $(INCLUDE_TOP)/stx/libbasic/ProjectDefinition.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
+$(OUTDIR)BenchmarkReportJSON.$(O) BenchmarkReportJSON.$(H): BenchmarkReportJSON.st $(INCLUDE_TOP)/jv/calipel/s/BenchmarkReport.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
 $(OUTDIR)BenchmarkReportText.$(O) BenchmarkReportText.$(H): BenchmarkReportText.st $(INCLUDE_TOP)/jv/calipel/s/BenchmarkReport.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
 
 # ENDMAKEDEPEND --- do not remove this line
--- a/s/Make.spec	Tue Jun 11 22:54:56 2013 +0100
+++ b/s/Make.spec	Wed Jun 12 14:27:14 2013 +0100
@@ -54,10 +54,12 @@
 	BenchmarkOutcome \
 	BenchmarkPlatform \
 	BenchmarkReport \
+	BenchmarkReportJSONWriter \
 	BenchmarkResult \
 	BenchmarkRunner \
 	BenchmarkSuite \
 	jv_calipel_s \
+	BenchmarkReportJSON \
 	BenchmarkReportText \
 
 
@@ -68,10 +70,12 @@
     $(OUTDIR_SLASH)BenchmarkOutcome.$(O) \
     $(OUTDIR_SLASH)BenchmarkPlatform.$(O) \
     $(OUTDIR_SLASH)BenchmarkReport.$(O) \
+    $(OUTDIR_SLASH)BenchmarkReportJSONWriter.$(O) \
     $(OUTDIR_SLASH)BenchmarkResult.$(O) \
     $(OUTDIR_SLASH)BenchmarkRunner.$(O) \
     $(OUTDIR_SLASH)BenchmarkSuite.$(O) \
     $(OUTDIR_SLASH)jv_calipel_s.$(O) \
+    $(OUTDIR_SLASH)BenchmarkReportJSON.$(O) \
     $(OUTDIR_SLASH)BenchmarkReportText.$(O) \
 
 
--- a/s/abbrev.stc	Tue Jun 11 22:54:56 2013 +0100
+++ b/s/abbrev.stc	Wed Jun 12 14:27:14 2013 +0100
@@ -5,8 +5,10 @@
 BenchmarkOutcome BenchmarkOutcome jv:calipel/s 'CalipeL-S-Core' 0
 BenchmarkPlatform BenchmarkPlatform jv:calipel/s 'CalipeL-S-Core' 0
 BenchmarkReport BenchmarkReport jv:calipel/s 'CalipeL-S-Core-Reports' 0
+BenchmarkReportJSONWriter BenchmarkReportJSONWriter jv:calipel/s 'CalipeL-S-Core-Reports' 0
 BenchmarkResult BenchmarkResult jv:calipel/s 'CalipeL-S-Core' 0
 BenchmarkRunner BenchmarkRunner jv:calipel/s 'CalipeL-S-Core' 0
 BenchmarkSuite BenchmarkSuite jv:calipel/s 'CalipeL-S-Core' 0
 jv_calipel_s jv_calipel_s jv:calipel/s '* Projects & Packages *' 3
+BenchmarkReportJSON BenchmarkReportJSON jv:calipel/s 'CalipeL-S-Core-Reports' 0
 BenchmarkReportText BenchmarkReportText jv:calipel/s 'CalipeL-S-Core-Reports' 0
--- a/s/bc.mak	Tue Jun 11 22:54:56 2013 +0100
+++ b/s/bc.mak	Wed Jun 12 14:27:14 2013 +0100
@@ -71,10 +71,12 @@
 $(OUTDIR)BenchmarkOutcome.$(O) BenchmarkOutcome.$(H): BenchmarkOutcome.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
 $(OUTDIR)BenchmarkPlatform.$(O) BenchmarkPlatform.$(H): BenchmarkPlatform.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
 $(OUTDIR)BenchmarkReport.$(O) BenchmarkReport.$(H): BenchmarkReport.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
+$(OUTDIR)BenchmarkReportJSONWriter.$(O) BenchmarkReportJSONWriter.$(H): BenchmarkReportJSONWriter.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
 $(OUTDIR)BenchmarkResult.$(O) BenchmarkResult.$(H): BenchmarkResult.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
 $(OUTDIR)BenchmarkRunner.$(O) BenchmarkRunner.$(H): BenchmarkRunner.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
 $(OUTDIR)BenchmarkSuite.$(O) BenchmarkSuite.$(H): BenchmarkSuite.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
 $(OUTDIR)jv_calipel_s.$(O) jv_calipel_s.$(H): jv_calipel_s.st $(INCLUDE_TOP)\stx\libbasic\LibraryDefinition.$(H) $(INCLUDE_TOP)\stx\libbasic\ProjectDefinition.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
+$(OUTDIR)BenchmarkReportJSON.$(O) BenchmarkReportJSON.$(H): BenchmarkReportJSON.st $(INCLUDE_TOP)\jv\calipel\s\BenchmarkReport.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
 $(OUTDIR)BenchmarkReportText.$(O) BenchmarkReportText.$(H): BenchmarkReportText.st $(INCLUDE_TOP)\jv\calipel\s\BenchmarkReport.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
 
 # ENDMAKEDEPEND --- do not remove this line
--- a/s/bmake.bat	Tue Jun 11 22:54:56 2013 +0100
+++ b/s/bmake.bat	Wed Jun 12 14:27:14 2013 +0100
@@ -10,9 +10,9 @@
 make.exe -N -f bc.mak  %DEFINES% %*
 
 @echo "***********************************"
-@echo "Buildung jv/calipel/s/tests
+@echo "Buildung jv/calipel/s/benchmarks
 @echo "***********************************"
-@cd tests
+@cd benchmarks
 @call bmake %1 %2
 @cd ..
 
@@ -24,9 +24,16 @@
 @cd ..
 
 @echo "***********************************"
-@echo "Buildung jv/calipel/s/benchmarks
+@echo "Buildung jv/calipel/s/benchmarks/micro
 @echo "***********************************"
-@cd benchmarks
+@cd benchmarks\micro
+@call bmake %1 %2
+@cd ..\..
+
+@echo "***********************************"
+@echo "Buildung jv/calipel/s/tests
+@echo "***********************************"
+@cd tests
 @call bmake %1 %2
 @cd ..
 
--- a/s/jv_calipel_s.st	Tue Jun 11 22:54:56 2013 +0100
+++ b/s/jv_calipel_s.st	Wed Jun 12 14:27:14 2013 +0100
@@ -36,9 +36,7 @@
      or classes which are extended by this package.
      This list can be maintained manually or (better) generated and
      updated by scanning the superclass hierarchies
-     (the browser has a menu function for that)
-     However, often too much is found, and you may want to explicitely
-     exclude individual packages in the #excludedFromPreRequisites method."
+     (the browser has a menu function for that)"
 
     ^ #(
         #'stx:libbasic'    "LibraryDefinition - superclass of jv_calipel_s "
@@ -54,7 +52,8 @@
      exclude individual packages in the #excludedFromPreRequisites method."
 
     ^ #(
-        #'jv:calipel/s/stx'
+        #'stx:goodies/monticello'    "MCDirectoryRepository - referenced by jv_calipel_s class>>monticelloExportTo: "
+        #'stx:libscm/mercurial/monticello'    "HGMCVersionInfo - referenced by jv_calipel_s class>>monticelloExportTo: "
     )
 !
 
@@ -65,9 +64,10 @@
      for those, redefine requiredPrerequisites"
 
     ^ #(
-        #'jv:calipel/s/tests'
+        #'jv:calipel/s/benchmarks'
         #'jv:calipel/s/stx'
-        #'jv:calipel/s/benchmarks'
+        #'jv:calipel/s/benchmarks/micro'
+        #'jv:calipel/s/tests'
     )
 ! !
 
@@ -95,10 +95,12 @@
         BenchmarkOutcome
         BenchmarkPlatform
         BenchmarkReport
+        BenchmarkReportJSONWriter
         BenchmarkResult
         BenchmarkRunner
         BenchmarkSuite
         #'jv_calipel_s'
+        BenchmarkReportJSON
         BenchmarkReportText
     )
 !
--- a/s/lccmake.bat	Tue Jun 11 22:54:56 2013 +0100
+++ b/s/lccmake.bat	Wed Jun 12 14:27:14 2013 +0100
@@ -6,9 +6,9 @@
 make.exe -N -f bc.mak -DUSELCC=1 %*
 
 @echo "***********************************"
-@echo "Buildung jv/calipel/s/tests
+@echo "Buildung jv/calipel/s/benchmarks
 @echo "***********************************"
-@cd tests
+@cd benchmarks
 @call lccmake %1 %2
 @cd ..
 
@@ -20,9 +20,16 @@
 @cd ..
 
 @echo "***********************************"
-@echo "Buildung jv/calipel/s/benchmarks
+@echo "Buildung jv/calipel/s/benchmarks/micro
 @echo "***********************************"
-@cd benchmarks
+@cd benchmarks\micro
+@call lccmake %1 %2
+@cd ..\..
+
+@echo "***********************************"
+@echo "Buildung jv/calipel/s/tests
+@echo "***********************************"
+@cd tests
 @call lccmake %1 %2
 @cd ..
 
--- a/s/libInit.cc	Tue Jun 11 22:54:56 2013 +0100
+++ b/s/libInit.cc	Wed Jun 12 14:27:14 2013 +0100
@@ -31,10 +31,12 @@
 _BenchmarkOutcome_Init(pass,__pRT__,snd);
 _BenchmarkPlatform_Init(pass,__pRT__,snd);
 _BenchmarkReport_Init(pass,__pRT__,snd);
+_BenchmarkReportJSONWriter_Init(pass,__pRT__,snd);
 _BenchmarkResult_Init(pass,__pRT__,snd);
 _BenchmarkRunner_Init(pass,__pRT__,snd);
 _BenchmarkSuite_Init(pass,__pRT__,snd);
 _jv_137calipel_137s_Init(pass,__pRT__,snd);
+_BenchmarkReportJSON_Init(pass,__pRT__,snd);
 _BenchmarkReportText_Init(pass,__pRT__,snd);
 
 
--- a/s/mingwmake.bat	Tue Jun 11 22:54:56 2013 +0100
+++ b/s/mingwmake.bat	Wed Jun 12 14:27:14 2013 +0100
@@ -14,9 +14,9 @@
 make.exe -N -f bc.mak %DEFINES% %USEMINGW_ARG% %*
 
 @echo "***********************************"
-@echo "Buildung jv/calipel/s/tests
+@echo "Buildung jv/calipel/s/benchmarks
 @echo "***********************************"
-@cd tests
+@cd benchmarks
 @call mingwmake %1 %2
 @cd ..
 
@@ -28,9 +28,16 @@
 @cd ..
 
 @echo "***********************************"
-@echo "Buildung jv/calipel/s/benchmarks
+@echo "Buildung jv/calipel/s/benchmarks/micro
 @echo "***********************************"
-@cd benchmarks
+@cd benchmarks\micro
+@call mingwmake %1 %2
+@cd ..\..
+
+@echo "***********************************"
+@echo "Buildung jv/calipel/s/tests
+@echo "***********************************"
+@cd tests
 @call mingwmake %1 %2
 @cd ..
 
--- a/s/s.rc	Tue Jun 11 22:54:56 2013 +0100
+++ b/s/s.rc	Wed Jun 12 14:27:14 2013 +0100
@@ -25,7 +25,7 @@
       VALUE "LegalCopyright", "My CopyRight or CopyLeft\0"
       VALUE "ProductName", "LibraryName\0"
       VALUE "ProductVersion", "6.2.3.0\0"
-      VALUE "ProductDate", "Tue, 11 Jun 2013 01:27:07 GMT\0"
+      VALUE "ProductDate", "Wed, 12 Jun 2013 13:26:49 GMT\0"
     END
 
   END
--- /dev/null	Thu Jan 01 00:00:00 1970 +0000
+++ b/s/tests/BenchmarkReportJSONWriterTests.st	Wed Jun 12 14:27:14 2013 +0100
@@ -0,0 +1,139 @@
+"{ Package: 'jv:calipel/s/tests' }"
+
+TestCase subclass:#BenchmarkReportJSONWriterTests
+	instanceVariableNames:''
+	classVariableNames:''
+	poolDictionaries:''
+	category:'CalipeL-S-Tests'
+!
+
+!BenchmarkReportJSONWriterTests class methodsFor:'documentation'!
+
+documentation
+"
+    [author:]
+        Jan Vrany <jan.vrany@fit.cvut.cz> (adaptation for CalipeL)
+
+    [instance variables:]
+
+    [class variables:]
+
+    [see also:]
+
+"
+! !
+
+!BenchmarkReportJSONWriterTests methodsFor:'testing'!
+
+testBooleans
+	| writer |
+	writer := [ :object | 
+		String streamContents: [ :stream |
+			(BenchmarkReportJSONWriter on: stream) nextPut: object ] ].
+	self assert: (writer value: true) equals: 'true'.
+	self assert: (writer value: false) equals: 'false'.
+!
+
+testByteArray
+	| writer |
+	writer := [ :object | 
+		String streamContents: [ :stream |
+			(BenchmarkReportJSONWriter on: stream) nextPut: object ] ].
+	self assert: (writer value: #[1 2 3]) equals: '[1,2,3]'.
+	self assert: (writer value: #[]) equals: '[]'
+!
+
+testFloats
+	| writer |
+	writer := [ :object | 
+		String streamContents: [ :stream |
+			(BenchmarkReportJSONWriter on: stream) nextPut: object ] ].
+	self assert: (writer value: 123.0) equals: '123.0'.
+	self assert: (writer value: -123.0) equals: '-123.0'.
+	self assert: (writer value: 0.0) equals: '0.0'.
+!
+
+testIntegers
+	| writer |
+	writer := [ :object | 
+		String streamContents: [ :stream |
+			(BenchmarkReportJSONWriter on: stream) nextPut: object ] ].
+	self assert: (writer value: 123) equals: '123'.
+	self assert: (writer value: -123) equals: '-123'.
+	self assert: (writer value: 0) equals: '0'.
+!
+
+testLists
+	| writer |
+	writer := [ :object | 
+		String streamContents: [ :stream |
+			(BenchmarkReportJSONWriter on: stream) nextPut: object ] ].
+	self assert: (writer value: #(1 2 3)) equals: '[1,2,3]'.
+	self assert: (writer value: #()) equals: '[]'.
+!
+
+testMaps
+        | writer dictionary |
+        dictionary := Dictionary new.
+        dictionary at: #x put: 1.
+        dictionary at: #y put: 2.
+        writer := [ :object | 
+                String streamContents: [ :stream |
+                        (BenchmarkReportJSONWriter on: stream) nextPut: object ] ].
+        self assert: (writer value: dictionary) equals: '{"x": 1,"y": 2}'.
+        self assert: (writer value: Dictionary new) equals: '{}'.
+
+    "Modified: / 12-06-2013 / 13:23:25 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
+testNull
+	| writer |
+	writer := [ :object | 
+		String streamContents: [ :stream |
+			(BenchmarkReportJSONWriter on: stream) nextPut: object ] ].
+	self assert: (writer value: nil) equals: 'null'
+!
+
+testObject
+        | writer point |
+        point := 1@2.
+        writer := [ :object | 
+                String streamContents: [ :stream |
+                        (BenchmarkReportJSONWriter on: stream) nextPut: object ] ].
+        self assert: (writer value: point) equals: '{"x": 1,"y": 2}'.
+
+    "Created: / 12-06-2013 / 13:46:24 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
+testStrings
+        | writer |
+        writer := [ :object | 
+                String streamContents: [ :stream |
+                        (BenchmarkReportJSONWriter on: stream) nextPut: object ] ].
+        self assert: (writer value: 'foo') equals: '"foo"'.
+        self assert: (writer value: 'Foo BAR') equals: '"Foo BAR"'.
+        self assert: (writer value: '') equals: '""'.
+        self
+                assert: (writer value: (String withAll: { 
+                                        $". $\. $/. Character tab. Character lf.  Character newPage. Character backspace }))
+                equals: '"\"\\/\t\n\f\b"'
+
+    "Modified: / 12-06-2013 / 13:45:24 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
+testSymbol
+	| writer |
+	writer := [ :object | 
+		String streamContents: [ :stream |
+			(BenchmarkReportJSONWriter on: stream) nextPut: object ] ].
+	self assert: (writer value: #foo) equals: '"foo"'.
+	self assert: (writer value: #'FOO-1') equals: '"FOO-1"'
+! !
+
+!BenchmarkReportJSONWriterTests class methodsFor:'documentation'!
+
+version_HG
+
+    ^ '$Changeset: <not expanded> $'
+! !
+
--- a/s/tests/Make.proto	Tue Jun 11 22:54:56 2013 +0100
+++ b/s/tests/Make.proto	Wed Jun 12 14:27:14 2013 +0100
@@ -126,8 +126,7 @@
 
 # BEGINMAKEDEPEND --- do not remove this line; make depend needs it
 $(OUTDIR)BenchmarkInstanceTests.$(O) BenchmarkInstanceTests.$(H): BenchmarkInstanceTests.st $(INCLUDE_TOP)/stx/goodies/sunit/TestCase.$(H) $(INCLUDE_TOP)/stx/goodies/sunit/TestAsserter.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
-$(OUTDIR)jv_calipel_s_tests.$(O) jv_calipel_s_tests.$(H): jv_calipel_s_tests.st $(INCLUDE_TOP)/stx/libbasic/LibraryDefinition.$(H) $(INCLUDE_TOP)/stx/libbasic/ProjectDefinition.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
-$(OUTDIR)BenchmarkInstanceTests.$(O) BenchmarkInstanceTests.$(H): BenchmarkInstanceTests.st $(INCLUDE_TOP)/stx/goodies/sunit/TestCase.$(H) $(INCLUDE_TOP)/stx/goodies/sunit/TestAsserter.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
+$(OUTDIR)BenchmarkReportJSONWriterTests.$(O) BenchmarkReportJSONWriterTests.$(H): BenchmarkReportJSONWriterTests.st $(INCLUDE_TOP)/stx/goodies/sunit/TestCase.$(H) $(INCLUDE_TOP)/stx/goodies/sunit/TestAsserter.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
 $(OUTDIR)jv_calipel_s_tests.$(O) jv_calipel_s_tests.$(H): jv_calipel_s_tests.st $(INCLUDE_TOP)/stx/libbasic/LibraryDefinition.$(H) $(INCLUDE_TOP)/stx/libbasic/ProjectDefinition.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
 
 # ENDMAKEDEPEND --- do not remove this line
--- a/s/tests/Make.spec	Tue Jun 11 22:54:56 2013 +0100
+++ b/s/tests/Make.spec	Wed Jun 12 14:27:14 2013 +0100
@@ -51,6 +51,7 @@
 
 COMMON_CLASSES= \
 	BenchmarkInstanceTests \
+	BenchmarkReportJSONWriterTests \
 	jv_calipel_s_tests \
 
 
@@ -58,6 +59,7 @@
 
 COMMON_OBJS= \
     $(OUTDIR_SLASH)BenchmarkInstanceTests.$(O) \
+    $(OUTDIR_SLASH)BenchmarkReportJSONWriterTests.$(O) \
     $(OUTDIR_SLASH)jv_calipel_s_tests.$(O) \
 
 
--- a/s/tests/Makefile.init	Tue Jun 11 22:54:56 2013 +0100
+++ b/s/tests/Makefile.init	Wed Jun 12 14:27:14 2013 +0100
@@ -8,7 +8,7 @@
 #
 # MACOSX caveat:
 #   as filenames are not case sensitive (in a default setup),
-#   we cannot use tha above trick. Therefore, this file is now named
+#   we cannot use the above trick. Therefore, this file is now named
 #   "Makefile.init", and you have to execute "make -f Makefile.init" to
 #   get the initial makefile.  This is now also done by the toplevel CONFIG
 #   script.
--- a/s/tests/abbrev.stc	Tue Jun 11 22:54:56 2013 +0100
+++ b/s/tests/abbrev.stc	Wed Jun 12 14:27:14 2013 +0100
@@ -2,4 +2,5 @@
 # this file is needed for stc to be able to compile modules independently.
 # it provides information about a classes filename, category and especially namespace.
 BenchmarkInstanceTests BenchmarkInstanceTests jv:calipel/s/tests 'CalipeL-S-Tests' 1
+BenchmarkReportJSONWriterTests BenchmarkReportJSONWriterTests jv:calipel/s/tests 'CalipeL-S-Tests' 1
 jv_calipel_s_tests jv_calipel_s_tests jv:calipel/s/tests '* Projects & Packages *' 3
--- a/s/tests/bc.mak	Tue Jun 11 22:54:56 2013 +0100
+++ b/s/tests/bc.mak	Wed Jun 12 14:27:14 2013 +0100
@@ -72,7 +72,9 @@
 
 # BEGINMAKEDEPEND --- do not remove this line; make depend needs it
 $(OUTDIR)BenchmarkInstanceTests.$(O) BenchmarkInstanceTests.$(H): BenchmarkInstanceTests.st $(INCLUDE_TOP)\stx\goodies\sunit\TestCase.$(H) $(INCLUDE_TOP)\stx\goodies\sunit\TestAsserter.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
+$(OUTDIR)BenchmarkReportJSONWriterTests.$(O) BenchmarkReportJSONWriterTests.$(H): BenchmarkReportJSONWriterTests.st $(INCLUDE_TOP)\stx\goodies\sunit\TestCase.$(H) $(INCLUDE_TOP)\stx\goodies\sunit\TestAsserter.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
 $(OUTDIR)jv_calipel_s_tests.$(O) jv_calipel_s_tests.$(H): jv_calipel_s_tests.st $(INCLUDE_TOP)\stx\libbasic\LibraryDefinition.$(H) $(INCLUDE_TOP)\stx\libbasic\ProjectDefinition.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
+
 # ENDMAKEDEPEND --- do not remove this line
 
 # **Must be at end**
--- a/s/tests/jv_calipel_s_tests.st	Tue Jun 11 22:54:56 2013 +0100
+++ b/s/tests/jv_calipel_s_tests.st	Wed Jun 12 14:27:14 2013 +0100
@@ -24,9 +24,7 @@
      or classes which are extended by this package.
      This list can be maintained manually or (better) generated and
      updated by scanning the superclass hierarchies
-     (the browser has a menu function for that)
-     However, often too much is found, and you may want to explicitely
-     exclude individual packages in the #excludedFromPreRequisites method."
+     (the browser has a menu function for that)"
 
     ^ #(
         #'stx:goodies/sunit'    "TestAsserter - superclass of BenchmarkInstanceTests "
@@ -68,6 +66,7 @@
     ^ #(
         "<className> or (<className> attributes...) in load order"
         BenchmarkInstanceTests
+        BenchmarkReportJSONWriterTests
         #'jv_calipel_s_tests'
     )
 !
--- a/s/tests/libInit.cc	Tue Jun 11 22:54:56 2013 +0100
+++ b/s/tests/libInit.cc	Wed Jun 12 14:27:14 2013 +0100
@@ -28,6 +28,7 @@
 OBJ snd; struct __vmData__ *__pRT__; {
 __BEGIN_PACKAGE2__("libjv_calipel_s_tests", _libjv_calipel_s_tests_Init, "jv:calipel/s/tests");
 _BenchmarkInstanceTests_Init(pass,__pRT__,snd);
+_BenchmarkReportJSONWriterTests_Init(pass,__pRT__,snd);
 _jv_137calipel_137s_137tests_Init(pass,__pRT__,snd);
 
 
--- a/s/tests/tests.rc	Tue Jun 11 22:54:56 2013 +0100
+++ b/s/tests/tests.rc	Wed Jun 12 14:27:14 2013 +0100
@@ -25,7 +25,7 @@
       VALUE "LegalCopyright", "My CopyRight or CopyLeft\0"
       VALUE "ProductName", "ProductName\0"
       VALUE "ProductVersion", "6.2.3.0\0"
-      VALUE "ProductDate", "Fri, 07 Jun 2013 21:36:22 GMT\0"
+      VALUE "ProductDate", "Wed, 12 Jun 2013 13:26:41 GMT\0"
     END
 
   END
--- a/s/vcmake.bat	Tue Jun 11 22:54:56 2013 +0100
+++ b/s/vcmake.bat	Wed Jun 12 14:27:14 2013 +0100
@@ -18,9 +18,9 @@
 
 
 @echo "***********************************"
-@echo "Buildung jv/calipel/s/tests
+@echo "Buildung jv/calipel/s/benchmarks
 @echo "***********************************"
-@cd tests
+@cd benchmarks
 @call vcmake %1 %2
 @cd ..
 
@@ -32,9 +32,16 @@
 @cd ..
 
 @echo "***********************************"
-@echo "Buildung jv/calipel/s/benchmarks
+@echo "Buildung jv/calipel/s/benchmarks/micro
 @echo "***********************************"
-@cd benchmarks
+@cd benchmarks\micro
+@call vcmake %1 %2
+@cd ..\..
+
+@echo "***********************************"
+@echo "Buildung jv/calipel/s/tests
+@echo "***********************************"
+@cd tests
 @call vcmake %1 %2
 @cd ..