compiler/benchmarks/PPCBenchmarkResources.st
changeset 453 bd5107faf4d6
parent 451 989570319d14
parent 452 9f4558b3be66
child 454 a9cd5ea7cc36
--- a/compiler/benchmarks/PPCBenchmarkResources.st	Tue May 05 16:25:23 2015 +0200
+++ /dev/null	Thu Jan 01 00:00:00 1970 +0000
@@ -1,117 +0,0 @@
-"{ Package: 'stx:goodies/petitparser/compiler/benchmarks' }"
-
-"{ NameSpace: Smalltalk }"
-
-Object subclass:#PPCBenchmarkResources
-	instanceVariableNames:''
-	classVariableNames:'javaCache'
-	poolDictionaries:''
-	category:'PetitCompiler-Benchmarks-Core'
-!
-
-
-!PPCBenchmarkResources methodsFor:'as yet unclassified'!
-
-changesSized: size
-	| string changes |
-	changes := PharoFilesOpener default changesFileOrNil contents.
-	string :=  changes copyFrom: 1 to: size.
-	^ string
-	
-!
-
-javaInDirectory: directory
-	| files |
-	files := self readDirectory: directory.
-	files := self files: files withExtension: 'java'.
-	
-	^ files collect: [ :f | (FileStream fileNamed: f) contents asString ]
-!
-
-javaLangMath
-	^ (FileStream fileNamed: '../java-src/java/lang/Math.java') contents asString
-!
-
-javaSourcesBig
-	^ self javaInDirectory: '../java-src/java/util'.
-	"^ self workingJavaInDirectory: '../java-src/java/util'"
-!
-
-smalltalkInDirectory: directory
-	| files |
-	files := self readDirectory: directory.
-	files := self files: files withExtension: 'st'.
-	
-	^ files collect: [ :f | (FileStream fileNamed: f) contents asString ]
-!
-
-smalltalkObjectMethods
-	^ Object allMethods collect: [ :m | m sourceCode ].
-!
-
-smalltalkSourcesBig
-	^ self smalltalkInDirectory: '../smalltalk-src/'
-!
-
-smalltalkSourcesBig_old
-	^ ((Smalltalk allClasses copyFrom: 1 to: 30) collect: [ :c |
-			c allMethods collect: [ :m | m sourceCode ]
-	  ]) gather: [:each | each ].
-!
-
-workingJavaInDirectory: directory
-	| sources parser |
-	"return only such a files, that can be parsed by PPJavaSyntax"
-
-	javaCache ifNil: [ javaCache := Dictionary new ].
-	
-	^ javaCache at: directory ifAbsentPut: [ 
-		sources := self javaInDirectory: directory.
-		parser := PPJavaSyntax new.
-	
-		sources select: [ :source | ([parser parse: source ] on: Error do: [ PPFailure new ]) isPetitFailure not ]	
-	]
-! !
-
-!PPCBenchmarkResources methodsFor:'private utilities'!
-
-files: files withExtension: extension
-    ( (Smalltalk respondsTo: #isSmalltalkX) and:[ Smalltalk isSmalltalkX ] ) ifTrue:[ 
-        ^ files select: [ :f | f suffix = extension ] 
-    ] ifFalse:[ 
-        "Assuming Pharo..."    
-        ^ files select: [ :f | f extension = extension ] 
-    ]
-
-    "Modified: / 20-04-2015 / 10:58:38 / Jan Vrany <jan.vrany@fit.cvut.cz>"
-!
-
-readDirectory: directory
-        | file |
-
-        ( (Smalltalk respondsTo: #isSmalltalkX) and:[ Smalltalk isSmalltalkX ] ) ifTrue:[ 
-            file := directory asFilename.
-            file exists ifFalse:[  
-                self error: 'Directory does not exist'.
-            ].
-            ^ file recursiveDirectoryContentsAsFilenames select:[:each | each isRegularFile ]
-        ] ifFalse:[ 
-            "Assuming Pharo..."
-
-            file := directory asFileReference.
-            file exists ifFalse: [ 
-                self error: 'Directory does not exist'.
-            ].
-            ^ file allFiles
-        ]
-
-    "Modified: / 20-04-2015 / 11:12:33 / Jan Vrany <jan.vrany@fit.cvut.cz>"
-! !
-
-!PPCBenchmarkResources class methodsFor:'documentation'!
-
-version_HG
-
-    ^ '$Changeset: <not expanded> $'
-! !
-