gui/PPDefineProdcutionRefactoring.st
changeset 336 ce1f4383ef4d
equal deleted inserted replaced
335:30d654399277 336:ce1f4383ef4d
       
     1 "{ Package: 'stx:goodies/petitparser/gui' }"
       
     2 
       
     3 Refactoring subclass:#PPDefineProdcutionRefactoring
       
     4 	instanceVariableNames:'class source protocols method'
       
     5 	classVariableNames:''
       
     6 	poolDictionaries:''
       
     7 	category:'PetitGui-Refactoring'
       
     8 !
       
     9 
       
    10 
       
    11 !PPDefineProdcutionRefactoring class methodsFor:'instance creation'!
       
    12 
       
    13 onClass: aClass source: aString protocols: anArray
       
    14 	^ self new
       
    15 		setClass: aClass;
       
    16 		setSource: aString;
       
    17 		setProtocols: anArray;
       
    18 		yourself
       
    19 ! !
       
    20 
       
    21 !PPDefineProdcutionRefactoring methodsFor:'accessing'!
       
    22 
       
    23 selector
       
    24 	^ method selector
       
    25 ! !
       
    26 
       
    27 !PPDefineProdcutionRefactoring methodsFor:'initialization'!
       
    28 
       
    29 setClass: aClass
       
    30 	class := self classObjectFor: aClass
       
    31 !
       
    32 
       
    33 setProtocols: anArray
       
    34 	protocols := anArray
       
    35 !
       
    36 
       
    37 setSource: aString
       
    38 	source := aString
       
    39 ! !
       
    40 
       
    41 !PPDefineProdcutionRefactoring methodsFor:'preconditions'!
       
    42 
       
    43 preconditions
       
    44 	^ (self checkCompositeParser: class)
       
    45 		& (RBCondition withBlock: [ self checkSource ] errorString: 'Unable to parse source code')
       
    46 ! !
       
    47 
       
    48 !PPDefineProdcutionRefactoring methodsFor:'private'!
       
    49 
       
    50 checkSource
       
    51 	| rewriter |
       
    52 	method := RBParser
       
    53 		parseMethod: source
       
    54 		onError: [ :string :position | ^ false ].
       
    55 	rewriter := self sourceRewriter.
       
    56 	[ rewriter executeTree: method ]
       
    57 		whileTrue: [ method := rewriter tree ].
       
    58 	^ method selector isUnary
       
    59 !
       
    60 
       
    61 sourceRewriter
       
    62         ^ ParseTreeRewriter new
       
    63                 replace: '`#literal' with: '`#literal asParser' when: [ :node |
       
    64                         (node isLiteralNode and: [ node value isString or: [ node value isCharacter ] ])
       
    65                                 and: [ (node parent isNil or: [ node parent isMessage not or: [ node parent selector ~= #asParser ] ])
       
    66                                 and: [ (node parents noneSatisfy: [ :each | each isBlock ]) ] ] ];
       
    67                 replaceMethod: '`@method: `@args | `@temps | ``@.statements. ``.statement `{ :node | node isReturn not }' 
       
    68                         with: '`@method: `@args | `@temps | ``@.statements. ^ ``.statement';
       
    69                 yourself
       
    70 ! !
       
    71 
       
    72 !PPDefineProdcutionRefactoring methodsFor:'transforming'!
       
    73 
       
    74 transform
       
    75 	(class definesInstanceVariable: method selector asString)
       
    76 		ifFalse: [ class addInstanceVariable: method selector asString ].
       
    77 	class compile: method newSource classified: protocols
       
    78 ! !
       
    79 
       
    80 !PPDefineProdcutionRefactoring class methodsFor:'documentation'!
       
    81 
       
    82 version
       
    83     ^ '$Header: /cvs/stx/stx/goodies/petitparser/gui/PPDefineProdcutionRefactoring.st,v 1.1 2014-03-04 21:15:26 cg Exp $'
       
    84 !
       
    85 
       
    86 version_CVS
       
    87     ^ '$Header: /cvs/stx/stx/goodies/petitparser/gui/PPDefineProdcutionRefactoring.st,v 1.1 2014-03-04 21:15:26 cg Exp $'
       
    88 ! !
       
    89