compiler/benchmarks/PPCBenchmarkResources.st
changeset 453 bd5107faf4d6
parent 451 989570319d14
parent 452 9f4558b3be66
child 454 a9cd5ea7cc36
equal deleted inserted replaced
451:989570319d14 453:bd5107faf4d6
     1 "{ Package: 'stx:goodies/petitparser/compiler/benchmarks' }"
       
     2 
       
     3 "{ NameSpace: Smalltalk }"
       
     4 
       
     5 Object subclass:#PPCBenchmarkResources
       
     6 	instanceVariableNames:''
       
     7 	classVariableNames:'javaCache'
       
     8 	poolDictionaries:''
       
     9 	category:'PetitCompiler-Benchmarks-Core'
       
    10 !
       
    11 
       
    12 
       
    13 !PPCBenchmarkResources methodsFor:'as yet unclassified'!
       
    14 
       
    15 changesSized: size
       
    16 	| string changes |
       
    17 	changes := PharoFilesOpener default changesFileOrNil contents.
       
    18 	string :=  changes copyFrom: 1 to: size.
       
    19 	^ string
       
    20 	
       
    21 !
       
    22 
       
    23 javaInDirectory: directory
       
    24 	| files |
       
    25 	files := self readDirectory: directory.
       
    26 	files := self files: files withExtension: 'java'.
       
    27 	
       
    28 	^ files collect: [ :f | (FileStream fileNamed: f) contents asString ]
       
    29 !
       
    30 
       
    31 javaLangMath
       
    32 	^ (FileStream fileNamed: '../java-src/java/lang/Math.java') contents asString
       
    33 !
       
    34 
       
    35 javaSourcesBig
       
    36 	^ self javaInDirectory: '../java-src/java/util'.
       
    37 	"^ self workingJavaInDirectory: '../java-src/java/util'"
       
    38 !
       
    39 
       
    40 smalltalkInDirectory: directory
       
    41 	| files |
       
    42 	files := self readDirectory: directory.
       
    43 	files := self files: files withExtension: 'st'.
       
    44 	
       
    45 	^ files collect: [ :f | (FileStream fileNamed: f) contents asString ]
       
    46 !
       
    47 
       
    48 smalltalkObjectMethods
       
    49 	^ Object allMethods collect: [ :m | m sourceCode ].
       
    50 !
       
    51 
       
    52 smalltalkSourcesBig
       
    53 	^ self smalltalkInDirectory: '../smalltalk-src/'
       
    54 !
       
    55 
       
    56 smalltalkSourcesBig_old
       
    57 	^ ((Smalltalk allClasses copyFrom: 1 to: 30) collect: [ :c |
       
    58 			c allMethods collect: [ :m | m sourceCode ]
       
    59 	  ]) gather: [:each | each ].
       
    60 !
       
    61 
       
    62 workingJavaInDirectory: directory
       
    63 	| sources parser |
       
    64 	"return only such a files, that can be parsed by PPJavaSyntax"
       
    65 
       
    66 	javaCache ifNil: [ javaCache := Dictionary new ].
       
    67 	
       
    68 	^ javaCache at: directory ifAbsentPut: [ 
       
    69 		sources := self javaInDirectory: directory.
       
    70 		parser := PPJavaSyntax new.
       
    71 	
       
    72 		sources select: [ :source | ([parser parse: source ] on: Error do: [ PPFailure new ]) isPetitFailure not ]	
       
    73 	]
       
    74 ! !
       
    75 
       
    76 !PPCBenchmarkResources methodsFor:'private utilities'!
       
    77 
       
    78 files: files withExtension: extension
       
    79     ( (Smalltalk respondsTo: #isSmalltalkX) and:[ Smalltalk isSmalltalkX ] ) ifTrue:[ 
       
    80         ^ files select: [ :f | f suffix = extension ] 
       
    81     ] ifFalse:[ 
       
    82         "Assuming Pharo..."    
       
    83         ^ files select: [ :f | f extension = extension ] 
       
    84     ]
       
    85 
       
    86     "Modified: / 20-04-2015 / 10:58:38 / Jan Vrany <jan.vrany@fit.cvut.cz>"
       
    87 !
       
    88 
       
    89 readDirectory: directory
       
    90         | file |
       
    91 
       
    92         ( (Smalltalk respondsTo: #isSmalltalkX) and:[ Smalltalk isSmalltalkX ] ) ifTrue:[ 
       
    93             file := directory asFilename.
       
    94             file exists ifFalse:[  
       
    95                 self error: 'Directory does not exist'.
       
    96             ].
       
    97             ^ file recursiveDirectoryContentsAsFilenames select:[:each | each isRegularFile ]
       
    98         ] ifFalse:[ 
       
    99             "Assuming Pharo..."
       
   100 
       
   101             file := directory asFileReference.
       
   102             file exists ifFalse: [ 
       
   103                 self error: 'Directory does not exist'.
       
   104             ].
       
   105             ^ file allFiles
       
   106         ]
       
   107 
       
   108     "Modified: / 20-04-2015 / 11:12:33 / Jan Vrany <jan.vrany@fit.cvut.cz>"
       
   109 ! !
       
   110 
       
   111 !PPCBenchmarkResources class methodsFor:'documentation'!
       
   112 
       
   113 version_HG
       
   114 
       
   115     ^ '$Changeset: <not expanded> $'
       
   116 ! !
       
   117