MethodFinder.st
changeset 1491 8941fc515d83
parent 1114 f023be3e8cc0
child 1928 49fdf6083f86
--- a/MethodFinder.st	Fri May 05 14:33:06 2006 +0200
+++ b/MethodFinder.st	Wed May 10 17:02:42 2006 +0200
@@ -3,7 +3,7 @@
 Object subclass:#MethodFinder
 	instanceVariableNames:'data answers selector argMap thisData mapStage mapList
 		expressions cachedClass cachedArgNum cachedSelectorLists'
-	classVariableNames:'AddAndRemove Approved Blocks Dangerous'
+	classVariableNames:'AddAndRemove Approved Blocks BlocksOptional Dangerous'
 	poolDictionaries:''
 	category:'Interface-MethodFinder'
 !
@@ -344,7 +344,8 @@
         "The methods we are allowed to use.  (MethodFinder new initialize) "
         Approved _ Set new.
         AddAndRemove _ Set new.
-        Blocks _ Set new.                       
+        Blocks _ Set new.
+        BlocksOptional := Set new.
         "These modify an argument: longPrintOn: printOn: storeOn: sentTo: storeOn:base: printOn:base: absPrintExactlyOn:base: absPrintOn:base: absPrintOn:base:digitCount: writeOn: writeScanOn: possibleVariablesFor:continuedFrom:"
 
 "Object"  
@@ -677,6 +678,7 @@
         collect: #'collect:thenSelect:' count: detect: #'detect:ifNone:' detectMax: detectMin: detectSum: #'inject:into:' reject: select: #'select:thenCollect:'
     "converting" 
         asBag asCharacterSet asSet asSortedArray asSortedCollection asSortedCollection:
+        asStringWith:
     "printing"
     "private" 
         maxSize
@@ -1125,6 +1127,13 @@
         ) do: [:anArray |
             Blocks add: anArray].
 
+        #(
+            (ifFalse: 1 )
+            (ifTrue: 1 )
+            (#'ifFalse:ifTrue:' 1 ) (#'ifFalse:ifTrue:' 2 )
+            (#'ifTrue:ifFalse:' 1 ) (#'ifTrue:ifFalse:' 2 )
+        ) do: [:anArray |
+            BlocksOptional add: anArray].
 
 "
 MethodFinder new initialize.
@@ -1306,7 +1315,7 @@
                 (alist isKindOf: SequenceableCollection) ifFalse: [
                         ^ OrderedCollection with: 'first and third items are not Arrays']].
 
-        Approved ifNil: [self initialize].      "Sets of allowed selectors"
+        true "Approved isNil" ifTrue: [self initialize].      "Sets of allowed selectors"
         expressions _ OrderedCollection new.
         self search: true.      "multi"
         expressions isEmpty ifTrue: [^ OrderedCollection with: 'no single method does that function'].
@@ -1323,7 +1332,7 @@
         (thisData at: 1) size = 1 ifFalse: [^ self].    "only one arg, data1"
 
         self const ifTrue: [^ self].
-        self constEquiv ifTrue: [^ self].       " ==  ~= "
+"/        self constEquiv ifTrue: [^ self].       " ==  ~= "
         self constLessThan ifTrue: [^ self].    " <=  and  >= "
 
         self allNumbers ifFalse: [^ self].
@@ -1356,6 +1365,7 @@
 
         self insertConstants.
       "  old ifTrue: [Preferences enableGently: #autoAccessors]. "
+
 "/ (selector isEmpty not) ifTrue: [^ selector]].   " expression is the answer, not a selector"
         ^ #()
 !
@@ -1430,7 +1440,11 @@
                         ] ifFalse:[
                             argIsBlock := (argList at: num) class == BlockContext    
                         ].
-                        argIsBlock ifFalse: [^ false]]].
+                        argIsBlock ifFalse: [
+                            (BlocksOptional includes: (Array with: activeSel with: num)) ifFalse: [
+                                ^ false
+                            ]
+                        ]]].
      "   (activeSel = #capitalized) ifTrue:[self halt.].  "  "  used to test  "
 
         rec:=(AddAndRemove includes: activeSel) 
@@ -1465,19 +1479,19 @@
 Approved ifNil: [self initialize].      "Sets of allowed selectors"
 "/(MethodFinder new load: #( (0) 0  (30) 0.5  (45) 0.707106  (90) 1)
 "/        ) searchForOne asArray = #('data1 degreeSin') ifFalse: [self error: 'should have found it'].  "Squeak test"
-"/(MethodFinder new load:   { { true. [3]. [4]}. 3.  { false. [0]. [6]}. 6}
-"/        ) searchForOne asArray = #('data1 ifTrue: data2 ifFalse: data3') ifFalse: [
-"/                self error: 'should have found it'].
-(MethodFinder2 new load: #(#(1) true #(2) false #(5) true #(10) false)
-        ) searchForOne asArray = #('data1 odd') ifFalse: [self error: 'should have found it'].
+(MethodFinder new load:   (Array with:(Array with:true with:[3] with:[4]) with:3 with:(Array with:false with:[0] with:[6]) with:6)
+        ) searchForOne asArray = #('data1 ifTrue: data2 ifFalse: data3') ifFalse: [
+                self error: 'should have found it'].
+(MethodFinder new load: #(#(1) true #(2) false #(5) true #(10) false)
+        ) searchForOne asArray = #('data1 odd' 'data1 isPrime') ifFalse: [self error: 'should have found it'].
                 "will correct the date type of #true, and complain"
 Smalltalk isSmalltalkX ifTrue:[        
-(MethodFinder2 new load: #((4 2) '2r100'   (255 16) '16rFF'    (14 8) '8r16')
+(MethodFinder new load: #((4 2) '2r100'   (255 16) '16rFF'    (14 8) '8r16')
         ) searchForOne asArray = 
                 #('data1 radixPrintStringRadix: data2' )
                           ifFalse: [self error: 'should have found it'].        
 ] ifFalse:[
-(MethodFinder2 new load: #((4 2) '2r100'   (255 16) '16rFF'    (14 8) '8r16')
+(MethodFinder new load: #((4 2) '2r100'   (255 16) '16rFF'    (14 8) '8r16')
         ) searchForOne asArray = 
                 #('data1 radix: data2' 'data1 printStringBase: data2' 'data1 storeStringBase: data2')                             
                           ifFalse: [self error: 'should have found it'].        
@@ -1485,40 +1499,40 @@
 "/(MethodFinder2 new load: #(#(3@4) 4 #(1@5) 5)
 "/        ) searchForOne asArray = #('data1 y') ifFalse: [self error: 'should have found it'].    
 Smalltalk isSmalltalkX ifTrue:[
-(MethodFinder2 new load: #(('abcd') $a  ('TedK') $T)
+(MethodFinder new load: #(('abcd') $a  ('TedK') $T)
         ) searchForOne asArray = #('data1 first' 'data1 removeFirst'  'data1 anyOne')   
                  ifFalse: [self error: 'should have found it']. 
 ] ifFalse:[
-(MethodFinder2 new load: #(('abcd') $a  ('TedK') $T)
+(MethodFinder new load: #(('abcd') $a  ('TedK') $T)
         ) searchForOne asArray = #('data1 asCharacter' 'data1 first' 'data1 anyOne')
                  ifFalse: [self error: 'should have found it']. 
 ].
-(((MethodFinder2 new load: #(('abcd' 1) $a  ('Ted ' 3) $d )
+(((MethodFinder new load: #(('abcd' 1) $a  ('Ted ' 3) $d )
         ) searchForOne asArray) includesAll: #('data1 at: data2' 'data1 atPin: data2' 'data1 atWrap: data2'))
                 ifFalse: [self error: 'should have found it'].  
-(MethodFinder2 new load: #(((12 4 8)) 24  ((1 3 6)) 10 )
+(MethodFinder new load: #(((12 4 8)) 24  ((1 3 6)) 10 )
         ) searchForOne asArray=  #('data1 sum') ifFalse: [self error: 'should have found it'].  
                 "note extra () needed for an Array object as an argument"
 
-(MethodFinder2 new load: #((14 3) 11  (-10 5) -15  (4 -3) 7)
+(MethodFinder new load: #((14 3) 11  (-10 5) -15  (4 -3) 7)
         ) searchForOne asArray = #('data1 - data2') ifFalse: [self error: 'should have found it'].
-((MethodFinder2 new load: #((4) 4  (-10) 10 (-3) 3 (2) 2 (-6) 6 (612) 612)
+((MethodFinder new load: #((4) 4  (-10) 10 (-3) 3 (2) 2 (-6) 6 (612) 612)
         ) searchForOne asArray includesAll: #('data1 abs')) ifFalse: [self error: 'should have found it'].
-(MethodFinder2 new load: #(#(4 3) true #(-7 3) false #(5 1) true #(5 5) false)
+(MethodFinder new load: #(#(4 3) true #(-7 3) false #(5 1) true #(5 5) false)
         ) searchForOne asArray = #('data1 > data2') ifFalse: [self error: 'should have found it'].      
-(MethodFinder2 new load: #((5) 0.2   (2) 0.5)
+(MethodFinder new load: #((5) 0.2   (2) 0.5)
         ) searchForOne asArray = #('data1 reciprocal') ifFalse: [self error: 'should have found it'].   
-(MethodFinder2 new load: #((12 4 8) 2  (1 3 6) 2  (5 2 16) 8)
+(MethodFinder new load: #((12 4 8) 2  (1 3 6) 2  (5 2 16) 8)
         ) searchForOne asArray = #()     " '(data3 / data2) ' want to be able to leave out args"  
                 ifFalse: [self error: 'should have found it'].  
-(MethodFinder2 new load: #((0.0) 0.0  (1.5) 0.997495  (0.75) 0.681639)
+(MethodFinder new load: #((0.0) 0.0  (1.5) 0.997495  (0.75) 0.681639)
         ) searchForOne asArray = #('data1 sin') ifFalse: [self error: 'should have found it'].  
-(MethodFinder2 new load: #((7 5) 2   (4 5) 4   (-9 4) 3)
+(MethodFinder new load: #((7 5) 2   (4 5) 4   (-9 4) 3)
         ) searchForOne asArray = #('data1 \\ data2') ifFalse: [self error: 'should have found it'].     
 ! !
 
 !MethodFinder class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic3/MethodFinder.st,v 1.10 2001-11-17 11:37:57 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libbasic3/MethodFinder.st,v 1.11 2006-05-10 15:02:42 cg Exp $'
 ! !