compiler/tests/extras/PPCResources.st
author Jan Vrany <jan.vrany@fit.cvut.cz>
Tue, 12 May 2015 01:24:03 +0100
changeset 459 4751c407bb40
parent 452 9f4558b3be66
child 460 87a3d30ab570
child 464 f6d77fee9811
permissions -rw-r--r--
Merged with PetitCompiler-JanKurs.20150510144201, PetitCompiler-Tests-JanKurs.20150510144201, PetitCompiler-Extras-Tests-JanKurs.20150510144201, PetitCompiler-Benchmarks-JanKurs.20150510144201 Name: PetitCompiler-JanKurs.20150510144201 Author: JanKurs Time: 10-05-2015, 04:42:29.192 PM UUID: 58a4786b-1182-4904-8b44-a13d3918f244 Name: PetitCompiler-Tests-JanKurs.20150510144201 Author: JanKurs Time: 10-05-2015, 04:32:12.870 PM UUID: 2a8fd41a-331b-4dcf-a7a3-752a50ce86e7 Name: PetitCompiler-Extras-Tests-JanKurs.20150510144201 Author: JanKurs Time: 10-05-2015, 04:59:25.308 PM UUID: ef43bd1a-be60-4e88-b749-8b635622c969 Name: PetitCompiler-Benchmarks-JanKurs.20150510144201 Author: JanKurs Time: 10-05-2015, 05:04:54.561 PM UUID: d8e764fd-016b-46e2-9fc1-17c38c18f0e5

"{ Package: 'stx:goodies/petitparser/compiler/tests/extras' }"

"{ NameSpace: Smalltalk }"

TestResource subclass:#PPCResources
	instanceVariableNames:'cache'
	classVariableNames:'javaCache'
	poolDictionaries:''
	category:'PetitCompiler-Extras-Tests-Support'
!

!PPCResources methodsFor:'expressions'!

expressionOfSize: size
    | stream |
    stream := WriteStream on: (String new: size * 5).
    self expressionOfSize: size stream: stream.
    ^ stream contents
!

expressionOfSize: size stream: stream
    | index rand |
    index := 0.
    rand := Random new.
    
    [index < size] whileTrue: [ 
 		(rand next < 0.1) ifTrue: [  
            | subSize |
            subSize := rand nextInt: (size - index - 1) + 1.
            stream nextPutAll: ' ('.
            self expressionOfSize: subSize stream: stream.
            stream nextPutAll: ') '.
            index := index + subSize.
        ] ifFalse: [ 
            stream nextPutAll: (rand nextInt: 10) asString.
            index := index + 1.
        ].
    
        (index < size) ifTrue: [ 
 			(rand next < 0.5) 
                ifTrue: [  stream nextPutAll: ' + ' ] 
                ifFalse: [ stream nextPutAll: ' * ' ]
        ]
    ]
!

expressionSourcesBig
    | sources |
    
    cache at: #expressionSourcesBig ifAbsentPut: [ 
        sources := OrderedCollection new.
        
        2000 timesRepeat: [ 
            sources add: (self expressionOfSize: 200).
        ].
        sources	
    ].

    ^ cache at: #expressionSourcesBig
    
!

expressionSourcesMedium
    | sources |
    
    cache at: #expressionSourcesMedium ifAbsentPut: [ 
        sources := OrderedCollection new.
        
        1000 timesRepeat: [ 
            sources add: (self expressionOfSize: 100).
        ].
        sources	
    ].

    ^ cache at: #expressionSourcesMedium
    
! !

!PPCResources methodsFor:'initialization'!

initialize
    super initialize.
    cache := IdentityDictionary new
! !

!PPCResources methodsFor:'java'!

javaInDirectory: directory
    | files |
    files := self readDirectory: directory.
    files := self files: files withExtension: 'java'.
    
    ^ files collect: [ :f | (FileStream fileNamed: f) contents ]
!

javaLangMath
    ^ (FileStream fileNamed: '../java-src/java/lang/Math.java') contents asString

    "Modified: / 10-05-2015 / 14:11:03 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

javaSourcesBig
    ^ self javaInDirectory: '../java-src/java/util'.
    "^ self workingJavaInDirectory: '../java-src/java/util'"
!

javaUtilTimer
    ^ (FileStream fileNamed: '../java-src/java/util/Timer.java') contents asString

    "Modified: / 10-05-2015 / 14:11:10 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

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 ]	
    ]
! !

!PPCResources methodsFor:'private utilities'!

files: files withExtension: extension
    ^ files select: [ :f | f extension = extension ] 
!

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: / 10-05-2015 / 07:54:14 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!PPCResources methodsFor:'smalltalk'!

smalltalkClassMethods
    ^ self smalltalkInDirectory: '../smalltalk-src/Class/'
    
!

smalltalkInDirectory: directory
    | files |
    files := self readDirectory: directory.
    files := self files: files withExtension: 'st'.
    
    ^ files collect: [ :f | (FileStream fileNamed: f) contents ]
!

smalltalkObjectMethods
    ^ self smalltalkInDirectory: '../smalltalk-src/Object/'
    
!

smalltalkSourcesBig
    ^ self smalltalkInDirectory: '../smalltalk-src/'
!

smalltalkSourcesSmall
    ^ (self smalltalkInDirectory: '../smalltalk-src/') copyFrom: 1 to: 5000.
! !