gui/tests/PPGrammarRefactoringTest.st
changeset 342 27e30ee190b9
child 361 39a00be69192
equal deleted inserted replaced
341:feebcbacf8b1 342:27e30ee190b9
       
     1 "{ Package: 'stx:goodies/petitparser/gui/tests' }"
       
     2 
       
     3 TestCase subclass:#PPGrammarRefactoringTest
       
     4 	instanceVariableNames:'refactoring'
       
     5 	classVariableNames:''
       
     6 	poolDictionaries:''
       
     7 	category:'PetitGui-Tests'
       
     8 !
       
     9 
       
    10 
       
    11 !PPGrammarRefactoringTest methodsFor:'accessing'!
       
    12 
       
    13 change
       
    14 	^ self refactoring changes
       
    15 !
       
    16 
       
    17 changes
       
    18 	^ self change changes
       
    19 !
       
    20 
       
    21 refactoring
       
    22 	^ refactoring
       
    23 ! !
       
    24 
       
    25 !PPGrammarRefactoringTest methodsFor:'testing-parsers'!
       
    26 
       
    27 testAddParser
       
    28         self performRefactoring: (PPAddParserRefactoring
       
    29                 name: #PPMockParser
       
    30                 category: #'PetitGui-Mock').
       
    31         self assert: self changes size = 2.
       
    32         self assert: self changes first class = AddClassChange.
       
    33         self assert: self changes first definitionClass = PPCompositeParser.
       
    34         self assert: self changes first changeClassName = #PPMockParser.
       
    35         self assert: self changes first category = #'PetitGui-Mock'.
       
    36         self assert: self changes last class = AddMethodChange.
       
    37         self assert: self changes last parseTree = (RBParser parseMethod: 'start ^ self shouldBeImplemented')
       
    38 !
       
    39 
       
    40 testAddParserWithSuperclass
       
    41         self performRefactoring: (PPAddParserRefactoring
       
    42                 name: #PPMockParser
       
    43                 category: #'PetitGui-Mock'
       
    44                 superclass: PPArithmeticParser).
       
    45         self assert: self changes size = 2.
       
    46         self assert: self changes first class = AddClassChange.
       
    47         self assert: self changes first definitionClass = PPArithmeticParser.
       
    48         self assert: self changes first changeClassName = #PPMockParser.
       
    49         self assert: self changes first category = #'PetitGui-Mock'.
       
    50         self assert: self changes last class = AddMethodChange.
       
    51         self assert: self changes last parseTree = (RBParser parseMethod: 'start ^ self shouldBeImplemented')
       
    52 !
       
    53 
       
    54 testRemoveParser
       
    55 	self performRefactoring: (PPRemoveParserRefactoring onClass: PPArithmeticParser).
       
    56 	self assert: self changes size = 1.
       
    57 	self assert: self changes first class =  RBRemoveClassChange.
       
    58 	self assert: self changes first changeClassName = 'PPArithmeticParser'
       
    59 ! !
       
    60 
       
    61 !PPGrammarRefactoringTest methodsFor:'testing-productions'!
       
    62 
       
    63 testDefineProduction
       
    64 	self performRefactoring: (PPDefineProdcutionRefactoring
       
    65 		onClass: PPArithmeticParser
       
    66 		source: 'function ^ #any plus , $( , $) ==> [ :e | 0 ]'
       
    67 		protocols: (Array with: #productions)).
       
    68 	self assert: self changes size = 2.
       
    69 	self assert: self changes first class = RBAddInstanceVariableChange.
       
    70 	self assert: self changes first variable = 'function'.
       
    71 	self assert: self changes last class = RBAddMethodChange.
       
    72 	self assert: self changes last parseTree = (RBParser parseMethod: 'function ^ #any asParser plus , $( asParser , $) asParser ==> [ :e | 0 ]')
       
    73 !
       
    74 
       
    75 testExtractProduction
       
    76 	self performRefactoring: (PPExtractProdcutionRefactoring
       
    77 		onClass: PPArithmeticParser
       
    78 		production: #addition
       
    79 		interval: (36 to: 60)
       
    80 		to: #plusOrMinus).
       
    81 	self assert: self changes size = 3.
       
    82 	self assert: self changes first class = RBAddInstanceVariableChange.
       
    83 	self assert: self changes first variable = 'plusOrMinus'.
       
    84 	self assert: self changes second class = RBAddMethodChange.
       
    85 	self assert: self changes second parseTree = (RBParser parseMethod: 'plusOrMinus ^ $+ asParser / $- asParser').
       
    86 	self assert: self changes last class = RBAddMethodChange.
       
    87 	self assert: self changes last parseTree = (RBParser parseMethod: 'addition ^ (factors separatedBy: plusOrMinus trim) foldLeft: [ :a :op :b | a perform: op asSymbol with: b ]')
       
    88 !
       
    89 
       
    90 testRemoveProduction
       
    91 	self performRefactoring: (PPRemoveProdcutionRefactoring
       
    92 		onClass: PPArithmeticParser
       
    93 		production: #addition).
       
    94 	self assert: self changes size = 2.
       
    95 	self assert: self changes first class = RBRemoveMethodChange.
       
    96 	self assert: self changes first selector = #addition.
       
    97 	self assert: self changes last class = RBRemoveInstanceVariableChange.
       
    98 	self assert: self changes last variable = 'addition'
       
    99 !
       
   100 
       
   101 testRenameProduction
       
   102 	self performRefactoring: (PPRenameProdcutionRefactoring
       
   103 		onClass: PPArithmeticParser
       
   104 		rename: #addition
       
   105 		to: #add).
       
   106 	self assert: self changes size = 3.
       
   107 	self assert: self changes first class = RBRenameInstanceVariableChange.
       
   108 	self assert: self changes first oldName = 'addition'.
       
   109 	self assert: self changes first newName = 'add'.
       
   110 	self assert: self changes second class = RBAddMethodChange.
       
   111 	self assert: self changes second parseTree = (RBParser parseMethod: 'add ^ (factors separatedBy: ($+ asParser / $- asParser) trim) foldLeft: [ :a :op :b | a perform: op asSymbol with: b ]').
       
   112 	self assert: self changes last class = RBRemoveMethodChange.
       
   113 	self assert: self changes last selector = #addition
       
   114 ! !
       
   115 
       
   116 !PPGrammarRefactoringTest methodsFor:'utilities'!
       
   117 
       
   118 performRefactoring: aRefactoring
       
   119 	refactoring := aRefactoring.
       
   120 	aRefactoring primitiveExecute
       
   121 ! !
       
   122 
       
   123 !PPGrammarRefactoringTest class methodsFor:'documentation'!
       
   124 
       
   125 version
       
   126     ^ '$Header: /cvs/stx/stx/goodies/petitparser/gui/tests/PPGrammarRefactoringTest.st,v 1.1 2014-03-04 21:16:20 cg Exp $'
       
   127 !
       
   128 
       
   129 version_CVS
       
   130     ^ '$Header: /cvs/stx/stx/goodies/petitparser/gui/tests/PPGrammarRefactoringTest.st,v 1.1 2014-03-04 21:16:20 cg Exp $'
       
   131 ! !
       
   132