SystemOrganization addCategory: #'Slime-Core'! SystemOrganization addCategory: #'Slime-Tests'! !ParseTreeEnvironment methodsFor: '*slime-core' stamp: 'lr 12/3/2009 18:32'! matcher ^ matcher ifNil: [ matcher := RBParseTreeSearcher new ]! ! !SmalllintContext methodsFor: '*slime-core' stamp: 'lr 1/11/2009 23:43'! isRenderingMethod (self selector numArgs > 0 and: [ self selector beginsWith: #render ]) ifFalse: [ ^ false ]. self compiledMethod literals do: [ :each | (each isSymbol and: [ WASlime isBrushSelector: each ]) ifTrue: [ ^ true ] ]. ^ false! ! RBTransformationRule subclass: #WASlimeTransformationRule instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Slime-Core'! WASlimeTransformationRule subclass: #WAAnsiBooleansRule instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Slime-Core'! !WAAnsiBooleansRule methodsFor: 'accessing' stamp: 'lr 2/24/2009 15:37'! group ^ 'ANSI Compatibility'! ! !WAAnsiBooleansRule methodsFor: 'initialization' stamp: 'lr 2/24/2009 15:27'! initialize super initialize. self rewriteRule replace: '``@expr1 and: [ | `@temp2 | ``@expr2 ] and: [ | `@temp3 | ``@expr3 ]' with: '``@expr1 and: [ | `@temp2 | ``@expr2 and: [ | `@temp3 | ``@expr3 ] ]'; replace: '``@expr1 and: [ | `@temp2 | ``@expr2 ] and: [ | `@temp3 | ``@expr3 ] and: [ | `@temp4 | ``@expr4 ]' with: '``@expr1 and: [ | `@temp2 | ``@expr2 and: [ | `@temp3 | ``@expr3 and: [ | `@temp4 | ``@expr4 ] ] ]'; replace: '``@expr1 and: [ | `@temp2 | ``@expr2 ] and: [ | `@temp3 | ``@expr3 ] and: [ | `@temp4 | ``@expr4 ] and: [ | `@temp5 | ``@expr5 ]' with: '``@expr1 and: [ | `@temp2 | ``@expr2 and: [ | `@temp3 | ``@expr3 and: [ | `@temp4 | ``@expr4 and: [ | `@temp5 | ``@expr5 ] ] ] ]'; replace: '``@expr1 or: [ | `@temp2 | ``@expr2 ] or: [ | `@temp3 | ``@expr3 ]' with: '``@expr1 or: [ | `@temp2 | ``@expr2 or: [ | `@temp3 | ``@expr3 ] ]'; replace: '``@expr1 or: [ | `@temp2 | ``@expr2 ] or: [ | `@temp3 | ``@expr3 ] or: [ | `@temp4 | ``@expr4 ]' with: '``@expr1 or: [ | `@temp2 | ``@expr2 or: [ | `@temp3 | ``@expr3 or: [ | `@temp4 | ``@expr4 ] ] ]'; replace: '``@expr1 or: [ | `@temp2 | ``@expr2 ] or: [ | `@temp3 | ``@expr3 ] or: [ | `@temp4 | ``@expr4 ] or: [ | `@temp5 | ``@expr5 ]' with: '``@expr1 or: [ | `@temp2 | ``@expr2 or: [ | `@temp3 | ``@expr3 or: [ | `@temp4 | ``@expr4 or: [ | `@temp5 | ``@expr5 ] ] ] ]'; replace: '``@expr1 or: [ | `@temp2 | ``@expr2 ] or: [ | `@temp3 | ``@expr3 ] or: [ | `@temp4 | ``@expr4 ] or: [ | `@temp5 | ``@expr5 ] or: [ | `@temp6 | ``@expr6 ]' with: '``@expr1 or: [ | `@temp2 | ``@expr2 or: [ | `@temp3 | ``@expr3 or: [ | `@temp4 | ``@expr4 or: [ | `@temp5 | ``@expr5 or: [ | `@temp6 | ``@expr6 ] ] ] ] ]'! ! !WAAnsiBooleansRule methodsFor: 'accessing' stamp: 'lr 2/24/2009 15:37'! name ^ 'Booleans'! ! WASlimeTransformationRule subclass: #WAAnsiCharactersRule instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Slime-Core'! !WAAnsiCharactersRule methodsFor: 'accessing' stamp: 'lr 7/16/2009 08:35'! group ^ 'ANSI Compatibility'! ! !WAAnsiCharactersRule methodsFor: 'initialization' stamp: 'lr 7/16/2009 08:36'! initialize super initialize. self rewriteRule replace: 'Character value: ``@expr' with: 'Character codePoint: ``@expr'! ! !WAAnsiCharactersRule methodsFor: 'accessing' stamp: 'lr 7/16/2009 08:35'! name ^ 'Characters'! ! WASlimeTransformationRule subclass: #WAAnsiCollectionsRule instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Slime-Core'! !WAAnsiCollectionsRule methodsFor: 'accessing' stamp: 'lr 2/24/2009 15:37'! group ^ 'ANSI Compatibility'! ! !WAAnsiCollectionsRule methodsFor: 'initialization' stamp: 'lr 2/28/2009 21:41'! initialize super initialize. self rewriteRule replace: '``@collection withIndexDo: [ :`each :`index | | `@temps | ``@.body ]' with: '``@collection keysAndValuesDo: [ :`index :`each | | `@temps | ``@.body ]'; replace: '``@collection doWithIndex: [ :`each :`index | | `@temps | ``@.body ]' with: '``@collection keysAndValuesDo: [ :`index :`each | | `@temps | ``@.body ]'; replace: '``@collection collect: ``@block1 thenDo: ``@block2' with: '(``@collection collect: ``@block1) do: ``@block2'; replace: '``@collection collect: ``@block1 thenSelect: ``@block2' with: '(``@collection collect: ``@block1) select: ``@block2'; replace: '``@collection pairsDo: [ :`t1 :`t2 | ``@.statements ]' with: '1 to: ``@collection size by: 2 do: [ :index | | `t1 `t2 | t1 := ``@collection at: index. t2 := ``@collection at: index + 1. ``@.statements ]'; replace: '``@collection reject: ``@block1 thenDo: ``@block2' with: '(``@collection reject: ``@block1) do: ``@block2'; replace: '``@collection select: ``@block1 thenCollect: ``@block2' with: '(``@collection select: ``@block1) collect: ``@block2'; replace: '``@collection select: ``@block1 thenDo: ``@block2' with: '(``@collection select: ``@block1) do: ``@block2'! ! !WAAnsiCollectionsRule methodsFor: 'accessing' stamp: 'lr 2/24/2009 15:37'! name ^ 'Collections'! ! WASlimeTransformationRule subclass: #WAAnsiConditionalsRule instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Slime-Core'! !WAAnsiConditionalsRule methodsFor: 'accessing' stamp: 'lr 2/24/2009 15:36'! group ^ 'ANSI Compatibility'! ! !WAAnsiConditionalsRule methodsFor: 'initialization' stamp: 'lr 2/28/2009 21:38'! initialize super initialize. self rewriteRule replace: '``@boolean ifNotNilDo: ``@block' with: '``@boolean ifNotNil: ``@block'; replace: '``@boolean ifNotNilDo: ``@block1 ifNil: ``@block2' with: '``@boolean ifNotNil: ``@block1 ifNil: ``@block2'; replace: '``@boolean ifNil: ``@block1 ifNotNilDo: ``@block2' with: '``@boolean ifNil: ``@block1 ifNotNil: ``@block2'; replace: '``@boolean ifNotNil: [ | `@temps | ``@.body ]' with: '``@boolean ifNotNil: [ :arg | | `@temps | ``@.body ]'; replace: '``@boolean ifNotNil: [ | `@temps | ``@.body ] ifNil: ``@block ' with: '``@boolean ifNotNil: [ :arg | | `@temps | ``@.body ] ifNil: ``@block'; replace: '``@boolean ifNil: ``@block ifNotNil: [ | `@temps | ``@.body ]' with: '``@boolean ifNil: ``@block ifNotNil: [ :arg | | `@temps | ``@.body ]'! ! !WAAnsiConditionalsRule methodsFor: 'accessing' stamp: 'lr 2/24/2009 15:37'! name ^ 'Conditionals'! ! WASlimeTransformationRule subclass: #WAAnsiConvertorRule instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Slime-Core'! !WAAnsiConvertorRule methodsFor: 'accessing' stamp: 'lr 4/14/2009 00:32'! group ^ 'ANSI Compatibility'! ! !WAAnsiConvertorRule methodsFor: 'initialization' stamp: 'lr 4/14/2009 00:33'! initialize super initialize. self rewriteRule replace: '``@object asString' with: '``@object seasideString'; replace: '``@object asInteger' with: '``@object seasideInteger'! ! !WAAnsiConvertorRule methodsFor: 'accessing' stamp: 'lr 4/14/2009 00:33'! name ^ 'Convertors'! ! WASlimeTransformationRule subclass: #WAAnsiExceptionsRule instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Slime-Core'! !WAAnsiExceptionsRule methodsFor: 'accessing' stamp: 'lr 2/24/2009 15:36'! group ^ 'ANSI Compatibility'! ! !WAAnsiExceptionsRule methodsFor: 'initialization' stamp: 'lr 2/28/2009 21:44'! initialize super initialize. self rewriteRule replace: '``@block on: `class do: [ | `@temps | ``@.body ]' with: '``@block on: `class do: [ :err | | `@temps | ``@.body ]'! ! !WAAnsiExceptionsRule methodsFor: 'accessing' stamp: 'lr 2/24/2009 15:37'! name ^ 'Exceptions'! ! WASlimeTransformationRule subclass: #WAAnsiStreamsRule instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Slime-Core'! !WAAnsiStreamsRule methodsFor: 'accessing' stamp: 'lr 2/24/2009 15:36'! group ^ 'ANSI Compatibility'! ! !WAAnsiStreamsRule methodsFor: 'initialization' stamp: 'lr 2/24/2009 15:29'! initialize super initialize. self rewriteRule replace: '`{ :node :context | node isVariable and: [ (Smalltalk includesKey: node name asSymbol) not and: [ context at: ''`receiver'' ifAbsentPut: [ node ]. true ] ] } cr' with: '`{ :context | context at: ''`receiver'' } nextPut: Character cr'; replace: '`{ :node :context | node isVariable and: [ (Smalltalk includesKey: node name asSymbol) not and: [ context at: ''`receiver'' ifAbsentPut: [ node ]. true ] ] } lf' with: '`{ :context | context at: ''`receiver'' } nextPut: Character lf'; replace: '``@stream nextPut: Character cr; nextPut: Character lf' with: '``@stream crlf'; replace: '``@collection writeStream' with: 'WriteStream on: ``@collection'! ! !WAAnsiStreamsRule methodsFor: 'accessing' stamp: 'lr 2/24/2009 15:52'! name ^ 'Streams'! ! WASlimeTransformationRule subclass: #WAHandleRequestRule instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Slime-Core'! !WAHandleRequestRule methodsFor: 'running' stamp: 'jf 3/16/2009 09:04'! checkMethod: aContext (WASlime class: aContext selectedClass includesBehaviorNamed: #WARequestHandler) ifTrue: [ super checkMethod: aContext ]! ! !WAHandleRequestRule methodsFor: 'accessing' stamp: 'lr 2/24/2009 15:37'! group ^ 'Seaside 2.9'! ! !WAHandleRequestRule methodsFor: 'initialization' stamp: 'lr 12/3/2009 18:32'! initialize super initialize. self rewriteRule replaceMethod: 'handleRequest: `aRequest | `@temps | `@.statements' withValueFrom: [ :node | RBParseTreeRewriter new replace: node arguments first name with: 'aRequestContext'; executeTree: node. RBParseTreeRewriter new replace: 'aRequestContext' with: 'aRequestContext request'; executeTree: node body. node selector: #handleFiltered:; arguments: (Array with: (RBVariableNode named: 'aRequestContext')); yourself ]! ! !WAHandleRequestRule methodsFor: 'accessing' stamp: 'lr 2/24/2009 15:22'! name ^ 'Rename WARequestHandler>>#handleRequest: to #handleFiltered:'! ! WASlimeTransformationRule subclass: #WASessionExpiredRule instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Slime-Core'! !WASessionExpiredRule methodsFor: 'running' stamp: 'jf 3/16/2009 08:56'! checkMethod: aContext (WASlime class: aContext selectedClass includesBehaviorNamed: #WASession) ifTrue: [ super checkMethod: aContext ]! ! !WASessionExpiredRule methodsFor: 'accessing' stamp: 'lr 2/24/2009 15:37'! group ^ 'Seaside 2.9'! ! !WASessionExpiredRule methodsFor: 'initialization' stamp: 'lr 2/24/2009 15:30'! initialize super initialize. self rewriteRule replace: 'expired | `@temps | `@.Statements' with: 'unregistered | `@temps | `@.Statements'! ! !WASessionExpiredRule methodsFor: 'accessing' stamp: 'lr 2/24/2009 15:22'! name ^ 'Rename WASession>>#expired to #unregistered'! ! !WASlimeTransformationRule class methodsFor: 'testing' stamp: 'lr 6/15/2009 10:32'! isVisible ^ self name ~= #WASlimeTransformationRule! ! TestCase subclass: #WASlimeTest instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Slime-Tests'! !WASlimeTest methodsFor: 'accessing' stamp: 'lr 7/31/2009 12:30'! classes ^ Array with: WASlimeMockComponent with: WASlimeMockObject with: WASlimeMockSession with: WASlimeMockWAObject! ! !WASlimeTest methodsFor: 'actions' stamp: 'lr 2/28/2009 21:01'! run: aRule changes: anArray self run: aRule changes: anArray in: self classes! ! !WASlimeTest methodsFor: 'actions' stamp: 'lr 8/18/2009 22:39'! run: aRule changes: anArray in: aClassCollection "aRule open" | expected selectors tree | aRule class isVisible ifFalse: [ ^ self ]. expected := anArray collect: [ :each | RBParser parseMethod: each ]. selectors := expected collect: [ :each | each selector ]. self run: aRule selectors: selectors in: aClassCollection. self assert: (aRule isKindOf: RBTransformationRule). self assert: (aRule changes size = anArray size). aRule changes do: [ :change | tree := expected detect: [ :each | change selector = each selector ] ifNone: [ nil ]. self assert: change parseTree = tree ]! ! !WASlimeTest methodsFor: 'actions' stamp: 'lr 2/28/2009 21:02'! run: aRule selectors: aSelectorCollection self run: aRule selectors: aSelectorCollection in: self classes! ! !WASlimeTest methodsFor: 'actions' stamp: 'lr 8/18/2009 22:39'! run: aRule selectors: aSelectorCollection in: aClassCollection "aRule open" | searchEnvironment resultEnvironment | aRule class isVisible ifFalse: [ ^ self ]. searchEnvironment := ClassEnvironment onEnvironment: BrowserEnvironment new classes: aClassCollection. SmalllintChecker runRule: aRule onEnvironment: searchEnvironment. resultEnvironment := aRule result. self assert: resultEnvironment name = aRule name. self assert: resultEnvironment problemCount = aSelectorCollection size. aSelectorCollection do: [ :selector | self assert: (resultEnvironment classes anySatisfy: [ :class | resultEnvironment includesSelector: selector in: class ]) ]! ! !WASlimeTest methodsFor: 'testing-transform' stamp: 'lr 2/28/2009 21:58'! testAnsiBooleansRule self run: WAAnsiBooleansRule new changes: #( 'and 1 and: [ 2 and: [ 3 and: [ 4 ] ] ]' 'or 1 or: [ 2 or: [ 3 or: [ 4 ] ] ]' )! ! !WASlimeTest methodsFor: 'testing-transform' stamp: 'lr 7/16/2009 09:23'! testAnsiCharacterRule self run: WAAnsiCharactersRule new changes: #( 'character Character codePoint: 123' )! ! !WASlimeTest methodsFor: 'testing-transform' stamp: 'lr 2/28/2009 21:35'! testAnsiCollectionsRule self run: WAAnsiCollectionsRule new changes: #( 'withIndexDo #() keysAndValuesDo: [ :index :each | each + index ]' 'collectThenDo (#() collect: [ :a | a ]) do: [ :b | b ]' )! ! !WASlimeTest methodsFor: 'testing-transform' stamp: 'lr 2/28/2009 21:58'! testAnsiConditionalsRule self run: WAAnsiConditionalsRule new changes: #( 'ifNotNil 1 ifNotNil: [ :arg | | a | self or. self and ]' 'ifNotNilDo 1 ifNotNil: [ :a | ^ a ]' )! ! !WASlimeTest methodsFor: 'testing-transform' stamp: 'lr 2/28/2009 21:58'! testAnsiExceptionsRule self run: WAAnsiExceptionsRule new changes: #( 'exception1 [ self or ] on: Error do: [ :err | self or ]' 'exception2 [ self or ] on: Error do: [ :err | self or. self or ]' 'exception3 [ self or ] on: Error do: [ :err | | a | a := 0 ]' )! ! !WASlimeTest methodsFor: 'testing-transform' stamp: 'lr 2/28/2009 22:03'! testAnsiStreamsRule self run: WAAnsiStreamsRule new changes: #( 'writeStream ^ WriteStream on: ''''' 'writeCr | stream | stream := WriteStream on: ''''. stream nextPut: Character cr. stream nextPut: Character cr' 'writeLf | stream | stream := WriteStream on: ''''. stream nextPut: Character lf. stream nextPut: Character lf')! ! !WASlimeTest methodsFor: 'testing-block' stamp: 'lr 2/24/2009 15:58'! testChangesStateWhileRendering self run: WAChangesStateWhileRenderingRule new selectors: #(renderChangesStateWhileRenderingOn:)! ! !WASlimeTest methodsFor: 'testing-block' stamp: 'lr 2/24/2009 15:58'! testDoNotUseWhileRendering self run: WADoNotUseWhileRenderingRule new selectors: #(renderDoNotUseWhileRenderingOn:)! ! !WASlimeTest methodsFor: 'testing-block' stamp: 'lr 2/24/2009 15:58'! testDoNotUseWithinCallback self run: WADoNotUseWithinCallbackRule new selectors: #(renderDoNotUseWithinCallbackOn:)! ! !WASlimeTest methodsFor: 'testing-parsetree' stamp: 'lr 2/24/2009 15:59'! testExtractCallbackCodeToMethod self run: WAExtractCallbackCodeToMethodRule new selectors: #(renderExtractCallbackCodeToMethodOn:)! ! !WASlimeTest methodsFor: 'testing-block' stamp: 'lr 2/24/2009 15:59'! testInstantiatesComponentWhileRendering self run: WAInstantiatesComponentWhileRenderingRule new selectors: #(renderInstantiatesComponentWhileRenderingOn:)! ! !WASlimeTest methodsFor: 'testing-parsetree' stamp: 'lr 2/24/2009 16:00'! testSendsRenderContentOn self run: WASendsRenderContentOnRule new selectors: #(sendsRenderContentOn)! ! !WASlimeTest methodsFor: 'testing-parsetree' stamp: 'lr 2/28/2009 21:18'! testUnnecessaryBlockPassedToBrush self run: WAUnnecessaryBlockPassedToBrushRule new selectors: #( renderUnnecessaryBlockPassedToBrush1On: renderUnnecessaryBlockPassedToBrush2On: renderUnnecessaryBlockPassedToBrush3On: renderUnnecessaryBlockPassedToBrush4On: renderUnnecessaryBlockPassedToBrush5On: renderUnnecessaryBlockPassedToBrush6On: renderUnnecessaryBlockPassedToBrush7On: )! ! !WASlimeTest methodsFor: 'testing-parsetree' stamp: 'lr 2/28/2009 21:19'! testUnnecessaryWithSentToBrush self run: WAUnnecessaryWithSentToBrushRule new selectors: #(renderUnnecessaryWithSentToBrushOn: renderUnnecessaryBlockPassedToBrush4On:)! ! !WASlimeTest methodsFor: 'testing-block' stamp: 'lr 2/24/2009 16:00'! testUsesCurlyBraceArrays self run: WAUsesCurlyBraceArraysRule new selectors: #(braceMessage)! ! !WASlimeTest methodsFor: 'testing-block' stamp: 'lr 2/24/2009 16:01'! testUsesLiteralByteArrays self run: WAUsesLiteralByteArraysRule new selectors: #()! ! !WASlimeTest methodsFor: 'testing-block' stamp: 'lr 2/28/2009 21:25'! testUsesMethodAnnotations self run: WAUsesMethodAnnotationsRule new selectors: #()! ! !WASlimeTest methodsFor: 'testing-block' stamp: 'lr 2/24/2009 16:01'! testUsesNotPortableClass self run: WAUsesNotPortableClassRule new selectors: #(someClass)! ! !WASlimeTest methodsFor: 'testing-parsetree' stamp: 'lr 2/24/2009 16:01'! testUsesWrongRenderer self run: WAUsesWrongRendererRule new selectors: #(renderUsesWrongRendererOn:)! ! !WASlimeTest methodsFor: 'testing-parsetree' stamp: 'lr 2/28/2009 20:55'! testWithHasToBeLastMessageInCascade self run: WAWithHasToBeLastMessageInCascadeRule new selectors: #(renderWithHasToBeLastMessageInCascadeOn:)! ! RBParseTreeLintRule subclass: #WASlimeParseTreeLintRule instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Slime-Core'! WASlimeParseTreeLintRule subclass: #WAExtractCallbackCodeToMethodRule instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Slime-Core'! !WAExtractCallbackCodeToMethodRule methodsFor: 'accessing' stamp: 'lr 2/24/2009 15:07'! group ^ 'Seaside'! ! !WAExtractCallbackCodeToMethodRule methodsFor: 'initialization' stamp: 'lr 2/28/2009 22:57'! initialize super initialize. self matcher matchesAnyOf: (WASlime callbackSelectors collect: [ :each | '`html `msg' , (self genericPatternForSelector: each) ]) do: [ :node :answer | (answer isNil and: [ WASlime isBrushSelector: node receiver selector ]) ifTrue: [ node arguments detect: [ :each | each isBlock and: [ each body statements size > 1 ] ] ifNone: [ answer ] ] ifFalse: [ answer ] ]! ! !WAExtractCallbackCodeToMethodRule methodsFor: 'accessing' stamp: 'lr 2/24/2009 15:07'! name ^ 'Extract callback code to separate method'! ! !WAExtractCallbackCodeToMethodRule methodsFor: 'accessing' stamp: 'lr 2/24/2009 15:07'! rationale ^ 'For clarity rendering code and callback code should not be mixed, extract the contents of the callback block to a separate method.'! ! WASlimeParseTreeLintRule subclass: #WASendsRenderContentOnRule instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Slime-Core'! !WASendsRenderContentOnRule methodsFor: 'accessing' stamp: 'lr 2/24/2009 15:07'! group ^ 'Seaside'! ! !WASendsRenderContentOnRule methodsFor: 'initialization' stamp: 'lr 2/28/2009 21:10'! initialize super initialize. self matcher matches: '`@object renderContentOn: `@html' do: [ :node :answer | (answer isNil and: [ (node methodNode selector ~= #visitPainter:) and: [ (node receiver isVariable and: [ node receiver name = 'super' ]) not ] ]) ifTrue: [ node ] ifFalse: [ answer ] ]! ! !WASendsRenderContentOnRule methodsFor: 'accessing' stamp: 'lr 2/24/2009 15:07'! name ^ 'Sends #renderContentOn:'! ! !WASendsRenderContentOnRule methodsFor: 'accessing' stamp: 'lr 2/24/2009 15:07'! rationale ^ 'Client code should never send #renderContentOn: directly but only #render:'! ! !WASlimeParseTreeLintRule class methodsFor: 'testing' stamp: 'lr 2/24/2009 17:10'! isVisible ^ self name ~= #WASlimeParseTreeLintRule! ! WASlimeParseTreeLintRule subclass: #WAUnnecessaryBlockPassedToBrushRule instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Slime-Core'! !WAUnnecessaryBlockPassedToBrushRule methodsFor: 'running' stamp: 'lr 2/27/2009 22:13'! checkMethod: aContext aContext isRenderingMethod ifTrue: [ super checkMethod: aContext ]! ! !WAUnnecessaryBlockPassedToBrushRule methodsFor: 'accessing' stamp: 'lr 2/24/2009 15:07'! group ^ 'Seaside'! ! !WAUnnecessaryBlockPassedToBrushRule methodsFor: 'initialization' stamp: 'lr 2/28/2009 21:09'! initialize super initialize. self matcher matchesAnyOf: #( '`html `msg: [ ]' '`html `msg: [ `html text: ``@arg ]' '`html `msg: [ `html render: ``@arg ]' ) do: [ :node :answer | (answer isNil and: [ WASlime isBrushSelector: node selector ]) ifTrue: [ node arguments first ] ifFalse: [ answer ] ]. self matcher matchesAnyOf: #( '`html `msg with: [ ]' '`html `msg with: [ `html text: ``@arg ]' '`html `msg with: [ `html render: ``@arg ]' ) do: [ :node :answer | (answer isNil and: [ WASlime isBrushSelector: node receiver selector ]) ifTrue: [ node arguments first ] ifFalse: [ answer ] ]! ! !WAUnnecessaryBlockPassedToBrushRule methodsFor: 'accessing' stamp: 'lr 2/24/2009 15:07'! name ^ 'Unnecessary block passed to brush'! ! !WAUnnecessaryBlockPassedToBrushRule methodsFor: 'accessing' stamp: 'lr 2/24/2009 15:07'! rationale ^ 'Sending a block as argument to #with: is only needed when nesting brushes.'! ! WASlimeParseTreeLintRule subclass: #WAUnnecessaryWithSentToBrushRule instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Slime-Core'! !WAUnnecessaryWithSentToBrushRule methodsFor: 'running' stamp: 'lr 2/27/2009 22:38'! checkMethod: aContext aContext isRenderingMethod ifTrue: [ super checkMethod: aContext ]! ! !WAUnnecessaryWithSentToBrushRule methodsFor: 'accessing' stamp: 'lr 2/24/2009 15:07'! group ^ 'Seaside'! ! !WAUnnecessaryWithSentToBrushRule methodsFor: 'initialization' stamp: 'lr 2/28/2009 21:09'! initialize super initialize. self matcher matches: '`html `msg with: ``@arg' do: [ :node :answer | (answer isNil and: [ (node parent isCascade not) and: [ (WASlime isBrushSelector: node receiver selector) and: [ (WASlime isBrushSelector: node receiver selector , ':') and: [ (WASlime isBrushSelector: node methodNode selector) not ] ] ] ]) ifTrue: [ node ] ifFalse: [ answer ] ]! ! !WAUnnecessaryWithSentToBrushRule methodsFor: 'accessing' stamp: 'lr 2/27/2009 22:40'! name ^ 'Unnecessary #with: sent to brush'! ! !WAUnnecessaryWithSentToBrushRule methodsFor: 'accessing' stamp: 'lr 2/24/2009 15:07'! rationale ^ 'Sending #with: is only required if attributes are specified too.'! ! WASlimeParseTreeLintRule subclass: #WAUsesWrongRendererRule instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Slime-Core'! !WAUsesWrongRendererRule methodsFor: 'accessing' stamp: 'lr 2/24/2009 15:07'! group ^ 'Seaside'! ! !WAUsesWrongRendererRule methodsFor: 'initialization' stamp: 'lr 2/24/2009 15:11'! initialize super initialize. self matcher matchesAnyOf: #( " JQuery: " '``@obj ajax html: [ :`r | | `@temps | `@.statements ]' '``@obj load html: [ :`r | | `@temps | `@.statements ]' '``@obj ajax script: [ :`r | | `@temps | `@.statements ]' '``@obj load script: [ :`r | | `@temps | `@.statements ]' '``@obj ajax text: [ :`r | | `@temps | `@.statements ]' '``@obj load text: [ :`r | | `@temps | `@.statements ]' " Scriptaculous: " '``@obj updater callback: [ :`r | | `@temps | `@.statements ]' '``@obj evaluator callback: [ :`r | | `@temps | `@.statements ]' '``@obj periodical callback: [ :`r | | `@temps | `@.statements ]' '``@obj autocompleter callback: [ :`r | | `@temps | `@.statements ]' '``@obj inPlaceEditor callback: [ :`r | | `@temps | `@.statements ]' '``@obj inPlaceCollectionEditor callback: [ :`r | | `@temps | `@.statements ]' ) do: [ :node :answer | (answer isNil and: [ node arguments first references: node receiver receiver name ]) ifTrue: [ node arguments first ] ifFalse: [ answer ] ]! ! !WAUsesWrongRendererRule methodsFor: 'accessing' stamp: 'lr 2/24/2009 15:07'! name ^ 'Uses the wrong renderer'! ! !WAUsesWrongRendererRule methodsFor: 'accessing' stamp: 'lr 2/24/2009 15:07'! rationale ^ 'Within AJAX callbacks you need to use the renderer that is passed into the block, the renderer from the outer context is only valid during the rendering of the outer context.'! ! WASlimeParseTreeLintRule subclass: #WAWithHasToBeLastMessageInCascadeRule instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Slime-Core'! !WAWithHasToBeLastMessageInCascadeRule methodsFor: 'running' stamp: 'lr 2/27/2009 22:13'! checkMethod: aContext aContext isRenderingMethod ifTrue: [ super checkMethod: aContext ]! ! !WAWithHasToBeLastMessageInCascadeRule methodsFor: 'accessing' stamp: 'lr 2/24/2009 15:07'! group ^ 'Seaside'! ! !WAWithHasToBeLastMessageInCascadeRule methodsFor: 'initialization' stamp: 'lr 2/28/2009 21:09'! initialize super initialize. self matcher matches: '`html `msg with: ``@arg' do: [ :node :answer | (answer isNil and: [ (node parent isCascade) and: [ (node parent messages last ~= node) and: [ (WASlime isBrushSelector: node receiver selector) ] ] ]) ifTrue: [ node ] ifFalse: [ answer ] ]! ! !WAWithHasToBeLastMessageInCascadeRule methodsFor: 'accessing' stamp: 'lr 2/24/2009 15:07'! name ^ '#with: has to be last message in cascade'! ! !WAWithHasToBeLastMessageInCascadeRule methodsFor: 'accessing' stamp: 'lr 2/24/2009 15:07'! rationale ^ 'Sending #with: triggers serialization of the brush attributes, any attribute being specified afterwards has no effect.'! ! WAComponent subclass: #WASlimeMockComponent instanceVariableNames: 'foo' classVariableNames: '' poolDictionaries: '' category: 'Slime-Tests'! !WASlimeMockComponent methodsFor: 'rendering' stamp: 'lr 7/15/2008 23:36'! renderChangesStateWhileRenderingOn: html html div: [ foo := nil ]! ! !WASlimeMockComponent methodsFor: 'rendering' stamp: 'lr 7/15/2008 23:24'! renderContentOn: html super renderContentOn: html! ! !WASlimeMockComponent methodsFor: 'rendering' stamp: 'lr 7/15/2008 22:17'! renderDoNotUseWhileRenderingOn: html html div: [ self call: foo ]! ! !WASlimeMockComponent methodsFor: 'rendering' stamp: 'jf 1/22/2009 22:44'! renderDoNotUseWithinCallbackOn: html html anchor callback: [ html document addLoadScript: nil ]; with: 'foo'! ! !WASlimeMockComponent methodsFor: 'rendering' stamp: 'lr 2/24/2009 17:16'! renderExtractCallbackCodeToMethodOn: html html anchor callback: [ 1. 2 ]; with: 'foo'! ! !WASlimeMockComponent methodsFor: 'rendering' stamp: 'lr 7/31/2009 12:29'! renderInstantiatesComponentWhileRenderingOn: html html div: WASlimeMockComponent new! ! !WASlimeMockComponent methodsFor: 'rendering' stamp: 'lr 7/15/2008 23:38'! renderSendsDeprecatedMessageOn: html html anchor src: 'http://www.foo.com'; with: 'Foo'! ! !WASlimeMockComponent methodsFor: 'rendering' stamp: 'lr 2/28/2009 21:13'! renderUnnecessaryBlockPassedToBrush1On: html html div: [ ]! ! !WASlimeMockComponent methodsFor: 'rendering' stamp: 'lr 2/28/2009 21:15'! renderUnnecessaryBlockPassedToBrush2On: html html div: [ html text: 'foo' ]! ! !WASlimeMockComponent methodsFor: 'rendering' stamp: 'lr 2/28/2009 21:14'! renderUnnecessaryBlockPassedToBrush3On: html html div: [ html render: 'foo' ]! ! !WASlimeMockComponent methodsFor: 'rendering' stamp: 'lr 2/28/2009 21:14'! renderUnnecessaryBlockPassedToBrush4On: html html div with: [ ]! ! !WASlimeMockComponent methodsFor: 'rendering' stamp: 'lr 2/28/2009 21:15'! renderUnnecessaryBlockPassedToBrush5On: html html div class: 'foo'; with: [ ]! ! !WASlimeMockComponent methodsFor: 'rendering' stamp: 'lr 2/28/2009 21:15'! renderUnnecessaryBlockPassedToBrush6On: html html div class: 'foo'; with: [ html text: 'bar' ]! ! !WASlimeMockComponent methodsFor: 'rendering' stamp: 'lr 2/28/2009 21:15'! renderUnnecessaryBlockPassedToBrush7On: html html div class: 'foo'; with: [ html render: 'bar' ]! ! !WASlimeMockComponent methodsFor: 'rendering' stamp: 'lr 2/28/2009 21:08'! renderUnnecessaryWithSentToBrushOn: html html div with: 'foo'! ! !WASlimeMockComponent methodsFor: 'rendering' stamp: 'lr 7/15/2008 23:08'! renderUsesWrongRendererOn: html html updater callback: [ :r | html div ]! ! !WASlimeMockComponent methodsFor: 'rendering' stamp: 'lr 2/28/2009 19:31'! renderWithHasToBeLastMessageInCascadeOn: html html div with: 'foo'; class: 'bar'. html div with: 'foo'; class: 'bar'; class: 'zork'! ! !WASlimeMockComponent methodsFor: 'actions' stamp: 'lr 7/15/2008 23:26'! sendsRenderContentOn self renderContentOn: nil! ! WASession subclass: #WASlimeMockSession instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Slime-Tests'! !WASlimeMockSession methodsFor: 'actions' stamp: 'pmm 10/18/2008 20:27'! expired! ! Object subclass: #WASlime instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Slime-Core'! WASlime class instanceVariableNames: 'brushSelectors callbackSelectors attributeSelectors'! WASlime class instanceVariableNames: 'brushSelectors callbackSelectors attributeSelectors'! !WASlime class methodsFor: 'accessing' stamp: 'lr 2/28/2009 23:09'! attributeSelectors ^ attributeSelectors ifNil: [ attributeSelectors := self findAttributeSelectors ]! ! !WASlime class methodsFor: 'accessing' stamp: 'lr 2/28/2009 23:09'! brushSelectors ^ brushSelectors ifNil: [ brushSelectors := self findBrushSelectors ]! ! !WASlime class methodsFor: 'accessing' stamp: 'lr 7/31/2009 12:32'! callbackSelectors ^ callbackSelectors ifNil: [ callbackSelectors := self findCallbackSelectors ]! ! !WASlime class methodsFor: 'testing' stamp: 'lr 7/31/2009 12:32'! class: aClass includesBehaviorNamed: aSymbol "In order to avoid static dependencies to classes, we do this check by name." ^ (Smalltalk includesKey: aSymbol) and: [ aClass includesBehavior: (Smalltalk at: aSymbol) ]! ! !WASlime class methodsFor: 'private' stamp: 'lr 12/3/2009 18:32'! findAttributeSelectors | matcher result | matcher := RBParseTreeSearcher new. matcher matchesAnyOf: #( 'self addClass: `@value' 'self addStyle: `@value' 'self addMedia: `@value' 'self attributeAt: `@key put: `@value' 'self attributeAt: `@key ifAbsentPut: `@block' 'self attributes at: `@key put: `@value' 'self attributes at: `@key ifAbsentPut: `@block' 'self attributes at: `@key append: `@value' 'self attributes at: `@key append: `@value separator: `@separator' ) do: [ :context :node | true ]. result := IdentitySet new. (self findClasses: #WABrush) , (self findClasses: #WAHtmlElement) do: [ :class | class methodDictionary keysAndValuesDo: [ :selector :method | (matcher executeTree: method parseTree initialAnswer: false) ifTrue: [ result add: selector ] ] ]. #(callback: enabled: labels:) do: [ :each | result add: each ]. ^ result! ! !WASlime class methodsFor: 'private' stamp: 'lr 12/3/2009 18:32'! findBrushSelectors | matcher result | matcher := RBParseTreeSearcher new. matcher matchesAnyMethodOf: #( '`selector ^ self tag: `#tag' '`selector ^ self brush: `@obj' '`selector: `aBlock self `selector with: `aBlock' '`selector ^ `class on: self' ) do: [ :context :node | true ]. result := IdentitySet new. (self findClasses: #WACanvas) do: [ :class | class methodDictionary keysAndValuesDo: [ :selector :method | (matcher executeTree: method parseTree initialAnswer: false) ifTrue: [ result add: selector ] ] ]. ^ result! ! !WASlime class methodsFor: 'private' stamp: 'lr 2/28/2009 23:07'! findCallbackSelectors ^ #( callback: callback:value: defaultAction: triggerArgument:callback: triggerAutocompleter: triggerInPlaceEditor: triggerPassenger: triggerSliderCallback: triggerSortable:callback: triggerTree:callback: ) asIdentitySet! ! !WASlime class methodsFor: 'private' stamp: 'lr 2/28/2009 23:02'! findClasses: aSymbol | class | class := Smalltalk classNamed: aSymbol. ^ class isNil ifTrue: [ #() ] ifFalse: [ class withAllSubclasses asArray ] ! ! !WASlime class methodsFor: 'initialization' stamp: 'lr 7/31/2009 12:19'! initialize SeasidePlatformSupport addToStartUpList: self! ! !WASlime class methodsFor: 'testing' stamp: 'lr 2/28/2009 23:13'! isBrushSelector: aString Symbol hasInterned: aString ifTrue: [ :symbol | ^ self brushSelectors includes: symbol ]. ^ false! ! !WASlime class methodsFor: 'testing' stamp: 'lr 2/28/2009 23:13'! isCallbackSelector: aString Symbol hasInterned: aString ifTrue: [ :symbol | ^ self callbackSelectors includes: symbol ]. ^ false! ! !WASlime class methodsFor: 'testing' stamp: 'lr 2/28/2009 23:13'! isWithinCallback: aNode | parent | parent := aNode parent ifNil: [ ^ false ]. (aNode isBlock and: [ parent isMessage and: [ self callbackSelectors includes: parent selector ] ]) ifTrue: [ ^ true ]. ^ self isWithinCallback: parent! ! !WASlime class methodsFor: 'initialization' stamp: 'lr 2/28/2009 23:10'! startUp brushSelectors := callbackSelectors := attributeSelectors := nil! ! Object subclass: #WASlimeMockObject instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Slime-Tests'! !WASlimeMockObject methodsFor: 'accessing' stamp: 'lr 2/28/2009 21:27'! and 1 and: [ 2 ] and: [ 3 ] and: [ 4 ]! ! !WASlimeMockObject methodsFor: 'accessing' stamp: 'lr 1/11/2009 23:41'! braceMessage Array braceWithNone! ! !WASlimeMockObject methodsFor: 'accessing' stamp: 'lr 7/16/2009 09:23'! character Character value: 123! ! !WASlimeMockObject methodsFor: 'accessing' stamp: 'lr 2/28/2009 21:35'! collectThenDo #() collect: [ :a | a ] thenDo: [ :b | b ]! ! !WASlimeMockObject methodsFor: 'accessing' stamp: 'lr 2/28/2009 21:45'! exception1 [ self or ] on: Error do: [ self or ]! ! !WASlimeMockObject methodsFor: 'accessing' stamp: 'lr 2/28/2009 21:46'! exception2 [ self or ] on: Error do: [ self or. self or ] ! ! !WASlimeMockObject methodsFor: 'accessing' stamp: 'lr 2/28/2009 21:45'! exception3 [ self or ] on: Error do: [ | a | a := 0 ]! ! !WASlimeMockObject methodsFor: 'accessing' stamp: 'lr 2/28/2009 22:36'! ifNotNil 1 ifNotNil: [ | a | self or. self and ]! ! !WASlimeMockObject methodsFor: 'accessing' stamp: 'lr 2/28/2009 22:36'! ifNotNilDo 1 ifNotNilDo: [ :a | ^ a ]! ! !WASlimeMockObject methodsFor: 'initialization' stamp: 'lr 11/14/2008 23:59'! initialize super initialize! ! !WASlimeMockObject methodsFor: 'accessing' stamp: 'lr 2/28/2009 21:27'! or 1 or: [ 2 ] or: [ 3 ] or: [ 4 ]! ! !WASlimeMockObject methodsFor: 'accessing' stamp: 'lr 7/15/2008 23:13'! someClass Semaphore new! ! !WASlimeMockObject methodsFor: 'accessing' stamp: 'lr 2/28/2009 21:34'! withIndexDo #() withIndexDo: [ :each :index | each + index ]! ! !WASlimeMockObject methodsFor: 'accessing' stamp: 'lr 2/28/2009 22:01'! writeCr | stream | stream := WriteStream on: ''. stream cr. stream nextPut: Character cr! ! !WASlimeMockObject methodsFor: 'accessing' stamp: 'lr 2/28/2009 22:01'! writeLf | stream | stream := WriteStream on: ''. stream lf. stream nextPut: Character lf! ! !WASlimeMockObject methodsFor: 'accessing' stamp: 'lr 2/28/2009 21:59'! writeStream ^ '' writeStream! ! Object subclass: #WASlimeMockWAObject instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Slime-Tests'! !WASlimeMockWAObject methodsFor: 'initialization' stamp: 'lr 11/14/2008 23:57'! initialize! ! !WASlimeMockWAObject methodsFor: 'initialization' stamp: 'lr 2/28/2009 21:24'! initializeFoo: a 1 + a! ! !WASlimeMockWAObject methodsFor: 'copying' stamp: 'lr 11/14/2008 23:57'! postCopy! ! RBBlockLintRule subclass: #WASlimeBlockLintRule instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Slime-Core'! WASlimeBlockLintRule subclass: #WACallSuperImplementationRule instanceVariableNames: 'classesAndSelectors superSelectors' classVariableNames: '' poolDictionaries: '' category: 'Slime-Core'! !WACallSuperImplementationRule methodsFor: 'running' stamp: 'lr 3/5/2009 20:07'! checkClass: aContext | current | aContext selectedClass isMeta ifTrue: [ ^ self ]. current := aContext selectedClass superclass. superSelectors := OrderedCollection new. [ current isNil ] whileTrue: [ classesAndSelectors at: current name ifPresent: [ :values | superSelectors addAll: values ]. current := current superclass ]! ! !WACallSuperImplementationRule methodsFor: 'running' stamp: 'lr 3/5/2009 20:08'! checkMethod: aContext aContext selectedClass isMeta ifTrue: [ ^ self ]. ((superSelectors includes: aContext selector) and: [ (aContext superMessages includes: aContext selector) not ]) ifTrue: [ result addClass: aContext selectedClass selector: aContext selector ]! ! !WACallSuperImplementationRule methodsFor: 'accessing' stamp: 'lr 2/28/2009 22:07'! group ^ 'Seaside'! ! !WACallSuperImplementationRule methodsFor: 'initialization' stamp: 'lr 2/28/2009 22:22'! initialize super initialize. classesAndSelectors := Dictionary new. classesAndSelectors at: #WAObject put: #( initialize postCopy ); at: #WAPainter put: #( updateRoot: updateUrl: ); at: #WAPresenter put: #( updateStates: ); at: #WADecoration put: #( renderContentOn: ); at: #WABrush put: #( setParent:canvas: with: ); at: #WATagBrush put: #( before after openTag closeTag ); at: #WARequestFilter put: #( handleFiltered: updateStates: ); at: #WASession put: #( updateRoot: updateUrl: updateStates: )! ! !WACallSuperImplementationRule methodsFor: 'accessing' stamp: 'lr 2/28/2009 22:07'! name ^ 'Call super implementation'! ! !WACallSuperImplementationRule methodsFor: 'accessing' stamp: 'lr 2/28/2009 22:09'! rationale ^ 'Some template methods provided by the framework require to call super to work correctly.'! ! WASlimeBlockLintRule subclass: #WAChangesStateWhileRenderingRule instanceVariableNames: 'matcher' classVariableNames: '' poolDictionaries: '' category: 'Slime-Core'! !WAChangesStateWhileRenderingRule methodsFor: 'running' stamp: 'lr 2/24/2009 16:09'! checkMethod: aContext | matches vars | aContext isRenderingMethod ifFalse: [ ^ self ]. matches := matcher executeTree: aContext parseTree initialAnswer: OrderedCollection new. matches isEmpty ifTrue: [ ^ self ]. vars := aContext instVarNames. matches do: [ :each | (vars includes: each name) ifTrue: [ result addClass: aContext selectedClass selector: aContext selector. result matcher matches: each name , ' := ``@obj' do: [ :node :answer | answer isNil ifTrue: [ node ] ifFalse: [ answer ] ] ] ]! ! !WAChangesStateWhileRenderingRule methodsFor: 'accessing' stamp: 'lr 2/24/2009 15:35'! group ^ 'Seaside'! ! !WAChangesStateWhileRenderingRule methodsFor: 'initialization' stamp: 'lr 12/3/2009 18:32'! initialize super initialize. matcher := RBParseTreeSearcher new. matcher matches: '`var' do: [ :node :answer | (node isWrite and: [ (WASlime isWithinCallback: node) not ]) ifTrue: [ answer add: node ]. answer ]! ! !WAChangesStateWhileRenderingRule methodsFor: 'accessing' stamp: 'lr 2/24/2009 15:35'! name ^ 'Changes state while rendering'! ! !WAChangesStateWhileRenderingRule methodsFor: 'accessing' stamp: 'lr 2/24/2009 15:35'! rationale ^ 'Application state should not be changed in the rendering code, use a callback to define state.'! ! !WAChangesStateWhileRenderingRule methodsFor: 'accessing' stamp: 'lr 2/24/2009 15:35'! resultClass ^ ParseTreeEnvironment! ! WASlimeBlockLintRule subclass: #WADoNotUseWhileRenderingRule instanceVariableNames: 'matcher' classVariableNames: '' poolDictionaries: '' category: 'Slime-Core'! !WADoNotUseWhileRenderingRule methodsFor: 'running' stamp: 'lr 2/24/2009 16:15'! checkMethod: aContext | matches | aContext isRenderingMethod ifFalse: [ ^ self ]. matches := matcher executeTree: aContext parseTree initialAnswer: OrderedCollection new. matches do: [ :each | result addClass: aContext selectedClass selector: aContext selector. result addSearchString: each selector ]! ! !WADoNotUseWhileRenderingRule methodsFor: 'accessing' stamp: 'lr 2/24/2009 15:35'! group ^ 'Seaside'! ! !WADoNotUseWhileRenderingRule methodsFor: 'initialization' stamp: 'lr 12/3/2009 18:32'! initialize super initialize. matcher := RBParseTreeSearcher new. matcher matchesAnyOf: (self selectors collect: [ :each | 'self' , (self genericPatternForSelector: each) ]) do: [ :node :answer | (WASlime isWithinCallback: node) ifFalse: [ answer add: node ]. answer ].! ! !WADoNotUseWhileRenderingRule methodsFor: 'accessing' stamp: 'lr 2/24/2009 15:35'! name ^ 'Do not use while rendering'! ! !WADoNotUseWhileRenderingRule methodsFor: 'accessing' stamp: 'lr 2/24/2009 15:35'! rationale ^ 'Certain functionaly should not be used while rendering. For example: #call: and #answer: should only be used from within callback code.'! ! !WADoNotUseWhileRenderingRule methodsFor: 'private' stamp: 'lr 2/27/2009 21:41'! selectors ^ #( answer answer: call: show: show:onAnswer: show:onAnswer:delegation: lightbox: chooseFrom: chooseFrom:caption: confirm: inform: request: request:default: request:label: request:label:default: wait: addDecoration: addMessage: answer answer: authenticateWith:during: call: chooseFrom: chooseFrom:caption: chooseFrom:caption:onAnswer: chooseFrom:onAnswer: confirm: confirm:onAnswer: decorateWith:during: filterWith:during: home inform: inform:onAnswer: isolate: lightbox: removeDecoration: request: request:default: request:default:onAnswer: request:label: request:label:default: request:label:default:onAnswer: request:label:onAnswer: request:onAnswer: show: show:onAnswer: show:onAnswer:delegation: validateWith: wait: )! ! WASlimeBlockLintRule subclass: #WADoNotUseWithinCallbackRule instanceVariableNames: 'matcher' classVariableNames: '' poolDictionaries: '' category: 'Slime-Core'! !WADoNotUseWithinCallbackRule methodsFor: 'running' stamp: 'lr 2/24/2009 16:16'! checkMethod: aContext | matches | aContext isRenderingMethod ifFalse: [ ^ self ]. matches := matcher executeTree: aContext parseTree initialAnswer: OrderedCollection new. matches do: [ :each | result addClass: aContext selectedClass selector: aContext selector. result addSearchString: each selector ]! ! !WADoNotUseWithinCallbackRule methodsFor: 'accessing' stamp: 'lr 2/24/2009 15:35'! group ^ 'Seaside'! ! !WADoNotUseWithinCallbackRule methodsFor: 'initialization' stamp: 'lr 12/3/2009 18:32'! initialize super initialize. matcher := RBParseTreeSearcher new. matcher matchesAnyOf: (self selectors collect: [ :each | '``@receiver' , (self genericPatternForSelector: each) ]) do: [ :node :answer | (WASlime isWithinCallback: node) ifTrue: [ answer add: node ]. answer ]! ! !WADoNotUseWithinCallbackRule methodsFor: 'accessing' stamp: 'lr 2/24/2009 15:35'! name ^ 'Do not use within callback'! ! !WADoNotUseWithinCallbackRule methodsFor: 'accessing' stamp: 'lr 2/24/2009 15:35'! rationale ^ 'Certain functionaly should not be used within callbacks. For example: #addLoadScript: should only be used while rendering.'! ! !WADoNotUseWithinCallbackRule methodsFor: 'private' stamp: 'lr 2/27/2009 21:44'! selectors ^ #( addLoadScript: )! ! WASlimeBlockLintRule subclass: #WAInstantiatesComponentWhileRenderingRule instanceVariableNames: 'matcher' classVariableNames: '' poolDictionaries: '' category: 'Slime-Core'! !WAInstantiatesComponentWhileRenderingRule methodsFor: 'running' stamp: 'lr 2/24/2009 16:17'! checkMethod: aContext | matches | aContext isRenderingMethod ifFalse: [ ^ self ]. matches := matcher executeTree: aContext parseTree initialAnswer: OrderedCollection new. matches do: [ :each | result addClass: aContext selectedClass selector: aContext selector. result addSearchString: each receiver name ]! ! !WAInstantiatesComponentWhileRenderingRule methodsFor: 'accessing' stamp: 'lr 2/24/2009 15:35'! group ^ 'Seaside'! ! !WAInstantiatesComponentWhileRenderingRule methodsFor: 'initialization' stamp: 'lr 12/3/2009 18:32'! initialize super initialize. matcher := RBParseTreeSearcher new. matcher matches: '`receiver `@message: ``@args' do: [ :node :answer | | class | ((class := Smalltalk classNamed: node receiver name) notNil and: [ class isBehavior and: [ (WASlime class: class includesBehaviorNamed: #WAPresenter) and: [ (WASlime isWithinCallback: node) not ] ] ]) ifTrue: [ answer add: node ]. answer ]! ! !WAInstantiatesComponentWhileRenderingRule methodsFor: 'accessing' stamp: 'lr 2/24/2009 15:35'! name ^ 'Instantiates component while rendering'! ! !WAInstantiatesComponentWhileRenderingRule methodsFor: 'accessing' stamp: 'lr 2/24/2009 15:35'! rationale ^ 'Components should only be instanciated in initialization-code, callbacks or through lazy initialization.'! ! !WASlimeBlockLintRule class methodsFor: 'testing' stamp: 'lr 2/24/2009 17:10'! isVisible ^ self name ~= #WASlimeBlockLintRule! ! WASlimeBlockLintRule subclass: #WAUsesCurlyBraceArraysRule instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Slime-Core'! !WAUsesCurlyBraceArraysRule methodsFor: 'running' stamp: 'lr 2/27/2009 21:47'! checkMethod: aContext aContext compiledMethod literals do: [ :each | (each isSymbol and: [ self selectors includes: each ]) ifTrue: [ result addClass: aContext selectedClass selector: aContext selector. result addSearchString: '{' ] ]! ! !WAUsesCurlyBraceArraysRule methodsFor: 'accessing' stamp: 'lr 2/24/2009 15:35'! group ^ 'Seaside Portability'! ! !WAUsesCurlyBraceArraysRule methodsFor: 'accessing' stamp: 'lr 2/24/2009 15:35'! name ^ 'Uses curly brace arrays'! ! !WAUsesCurlyBraceArraysRule methodsFor: 'accessing' stamp: 'lr 2/24/2009 15:35'! rationale ^ 'Curly brace expressions are not portable accross different Smalltalk dialects.'! ! !WAUsesCurlyBraceArraysRule methodsFor: 'private' stamp: 'lr 2/27/2009 21:47'! selectors ^ #( braceStream: braceWith: braceWith:with: braceWith:with:with: braceWith:with:with:with: braceWithNone )! ! WASlimeBlockLintRule subclass: #WAUsesLiteralByteArraysRule instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Slime-Core'! !WAUsesLiteralByteArraysRule methodsFor: 'running' stamp: 'lr 2/24/2009 16:21'! checkMethod: aContext aContext compiledMethod literals do: [ :each | (each isLiteral and: [ each isKindOf: ByteArray ]) ifTrue: [ result addClass: aContext selectedClass selector: aContext selector. result addSearchString: '#[' ] ]! ! !WAUsesLiteralByteArraysRule methodsFor: 'accessing' stamp: 'lr 2/24/2009 15:35'! group ^ 'Seaside Portability'! ! !WAUsesLiteralByteArraysRule methodsFor: 'accessing' stamp: 'lr 2/24/2009 15:35'! name ^ 'Uses literal byte arrays'! ! !WAUsesLiteralByteArraysRule methodsFor: 'accessing' stamp: 'lr 2/24/2009 15:35'! rationale ^ 'Literal byte arrays are not portable accross different Smalltalk dialects.'! ! WASlimeBlockLintRule subclass: #WAUsesMethodAnnotationsRule instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Slime-Core'! !WAUsesMethodAnnotationsRule methodsFor: 'running' stamp: 'lr 2/27/2009 21:51'! checkMethod: aContext aContext compiledMethod pragmas do: [ :each | result addClass: aContext selectedClass selector: aContext selector. result addSearchString: each keyword ]! ! !WAUsesMethodAnnotationsRule methodsFor: 'accessing' stamp: 'lr 2/27/2009 21:49'! group ^ 'Seaside Portability'! ! !WAUsesMethodAnnotationsRule methodsFor: 'accessing' stamp: 'lr 2/27/2009 21:49'! name ^ 'Uses method annotations'! ! !WAUsesMethodAnnotationsRule methodsFor: 'accessing' stamp: 'lr 2/27/2009 21:52'! rationale ^ 'As of now, it is unclear if method-annotations/pragmas are compatible across all supported platforms. Likely this rule will soon be removed.'! ! WASlimeBlockLintRule subclass: #WAUsesNotPortableClassRule instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Slime-Core'! !WAUsesNotPortableClassRule methodsFor: 'running' stamp: 'lr 2/27/2009 22:14'! checkClass: aContext aContext selectedClass allSuperclassesDo: [ :each | (self classNames includes: each name) ifTrue: [ result addClass: aContext selectedClass. result addSearchString: each name ] ]! ! !WAUsesNotPortableClassRule methodsFor: 'running' stamp: 'lr 2/27/2009 22:14'! checkMethod: aContext aContext compiledMethod literals do: [ :each | (each isVariableBinding and: [ self classNames includes: each key ]) ifTrue: [ result addClass: aContext selectedClass selector: aContext selector. result addSearchString: each key ] ]! ! !WAUsesNotPortableClassRule methodsFor: 'private' stamp: 'lr 2/27/2009 21:54'! classNames ^ #( Delay MIMEDocument Monitor Mutex MutexSet Random Semaphore TimeStamp )! ! !WAUsesNotPortableClassRule methodsFor: 'accessing' stamp: 'lr 2/24/2009 15:35'! group ^ 'Seaside Portability'! ! !WAUsesNotPortableClassRule methodsFor: 'accessing' stamp: 'lr 2/24/2009 15:35'! name ^ 'Uses not portable class'! ! !WAUsesNotPortableClassRule methodsFor: 'accessing' stamp: 'lr 2/24/2009 15:35'! rationale ^ 'Some classes are not portable accross different Smalltalk dialects.'! ! WASlime initialize!