Explainer.st
changeset 3233 0761ca178615
parent 3209 af924bf746f3
child 3319 83ed09191e6b
--- a/Explainer.st	Thu Jul 25 03:24:02 2013 +0200
+++ b/Explainer.st	Sat Jul 27 10:22:18 2013 +0200
@@ -431,7 +431,10 @@
 fetchCommentOfMethod:mthd
     |methodComment lines|
 
-    methodComment := mthd comment.
+    "/ with wait cursor, because it accesses sourcecode (via SCM)
+    WindowGroup activeGroup withWaitCursorDo:[
+        methodComment := mthd comment.
+    ].
     methodComment isEmptyOrNil ifTrue:[^ nil].
 
     lines := methodComment asStringCollection.
@@ -440,7 +443,7 @@
     (methodComment endsWith:',') ifTrue:[ methodComment := methodComment copyButLast:1].
     methodComment := methodComment withoutSeparators.
     (lines size > 1) ifTrue:[
-	methodComment := methodComment , ' ...'
+        methodComment := methodComment , ' ...'
     ].
     ^ ('"' , methodComment , '"') colorizeAllWith:(UserPreferences current commentColor).
 
@@ -549,7 +552,7 @@
      message selector. I.e. the explanation should be context sensitive.
      Also, there could be much more detailed explanations."
 
-    |parser variables c string tmp
+    |parser variables c string tmp tmp1
      spc sym sel stringText cls clsName val valString|
 
     string := someText string withoutSeparators.
@@ -562,140 +565,149 @@
      ask parser for variable names
     "
     ParseError catch:[
-	parser := self parseMethod:source in:aClass ignoreErrors:true ignoreWarnings:true.
+        parser := self parseMethod:source in:aClass ignoreErrors:true ignoreWarnings:true.
     ].
     (parser notNil and:[parser ~~ #Error]) ifTrue:[
-	"look for variables"
+        "look for variables"
 
-	variables := parser methodVars.
-	(variables notNil and:[variables includes:string]) ifTrue:[
-	    ^ stringText , ' a method variable.'
-	].
-	variables := parser methodArgs.
-	(variables notNil and:[variables includes:string]) ifTrue:[
-	    ^ stringText , ' a method argument.'
-	]
+        variables := parser methodVars.
+        (variables notNil and:[variables includes:string]) ifTrue:[
+            ^ stringText , ' a method variable.'
+        ].
+        variables := parser methodArgs.
+        (variables notNil and:[variables includes:string]) ifTrue:[
+            ^ stringText , ' a method argument.'
+        ]
     ].
 
     parser isNil ifTrue:[
-	parser := self for:(ReadStream on:source) in:aClass
+        parser := self for:(ReadStream on:source) in:aClass
     ].
 
     "instvars/class instVars"
     c := aClass whichClassDefinesInstVar:string.
     c notNil ifTrue:[
-	c isMeta ifTrue:[
-	    clsName := c theNonMetaclass name.
-	    shortText ifTrue:[
-		stringText := stringText , ': a class instVar in ' , clsName
-	    ] ifFalse:[
-		stringText := stringText, ': a class instance variable inherited from ' , clsName
-	    ].
-	    val := aClass theNonMetaclass instVarNamed:string.
-	    valString := self valueStringFor:val.
-	    ^ stringText , ' (' , valString , ').'
-	].
+        c isMeta ifTrue:[
+            clsName := c theNonMetaclass name.
+            shortText ifTrue:[
+                stringText := stringText , ': a class instVar in ' , clsName
+            ] ifFalse:[
+                stringText := stringText, ': a class instance variable inherited from ' , clsName
+            ].
+            val := aClass theNonMetaclass instVarNamed:string.
+            valString := self valueStringFor:val.
+            ^ stringText , ' (' , valString , ').'
+        ].
 
-	clsName := c name.
-	shortText ifTrue:[
-	    ^ stringText , ': an instVar in ' , clsName , '.'
-	].
-	^ stringText , ': an instance variable inherited from ' , clsName , '.'
+        clsName := c name.
+        shortText ifTrue:[
+            ^ stringText , ': an instVar in ' , clsName , '.'
+        ].
+        ^ stringText , ': an instance variable inherited from ' , clsName , '.'
     ].
 
     string isWideString ifFalse:[
-	"classvars"
-	c := parser inWhichClassIsClassVar:string.
-	c notNil ifTrue:[
-	    clsName := c name.
-	    shortText ifTrue:[
-		stringText := stringText , ': a classVar in ' , clsName
-	    ] ifFalse:[
-		stringText := stringText , ': a class variable in ' , clsName
-	    ].
+        "classvars"
+        c := parser inWhichClassIsClassVar:string.
+        c notNil ifTrue:[
+            clsName := c name.
+            shortText ifTrue:[
+                stringText := stringText , ': a classVar in ' , clsName
+            ] ifFalse:[
+                stringText := stringText , ': a class variable in ' , clsName
+            ].
 
-	    val := c theNonMetaclass classVarAt:string. "/ Smalltalk at:(clsName , ':' , string) asSymbol.
-	    valString := self valueStringFor:val.
-	    ^ stringText , ' (' , valString , ').'
-	].
+            val := c theNonMetaclass classVarAt:string. "/ Smalltalk at:(clsName , ':' , string) asSymbol.
+            valString := self valueStringFor:val.
+            ^ stringText , ' (' , valString , ').'
+        ].
 
-	"private classes"
-	c := aClass theNonMetaclass.
-	c privateClasses do:[:pClass |
-	    (pClass name = string
-	     or:[pClass nameWithoutPrefix = string]) ifTrue:[
-		stringText := stringText , ': a private class in ''' , c name , '''.'.
-		shortText ifFalse:[
-		    stringText := (stringText , '\\It is only visible locally.') withCRs
-		].
-		^ stringText withCRs
-	    ].
-	].
+        "private classes"
+        c := aClass theNonMetaclass.
+        c privateClasses do:[:pClass |
+            (pClass name = string
+             or:[pClass nameWithoutPrefix = string]) ifTrue:[
+                stringText := stringText , ': a private class in ''' , c name , '''.'.
+                shortText ifFalse:[
+                    stringText := (stringText , '\\It is only visible locally.') withCRs
+                ].
+                ^ stringText withCRs
+            ].
+        ].
 
-	aClass theNonMetaclass sharedPoolNames do:[:eachPoolName |
-	    |sharedPool|
+        aClass theNonMetaclass sharedPoolNames do:[:eachPoolName |
+            |sharedPool|
 
-	    sharedPool := Smalltalk classNamed:eachPoolName.
-	    sharedPool notNil ifTrue:[
-		sharedPool isSharedPool ifFalse:[
-		    ^ 'oops - not a shared pool: ',eachPoolName
-		].
-		(sharedPool includesKey:string asSymbol) ifTrue:[
-		    stringText := stringText , ': a pool variable in ',sharedPool name.
-		    val := sharedPool at:string.
-		    valString := self valueStringFor:val.
-		    ^ stringText , ' (' , valString , ').'
-		].
-	    ].
-	].
+            sharedPool := Smalltalk classNamed:eachPoolName.
+            sharedPool notNil ifTrue:[
+                sharedPool isSharedPool ifFalse:[
+                    ^ 'oops - not a shared pool: ',eachPoolName
+                ].
+                (sharedPool includesKey:string asSymbol) ifTrue:[
+                    stringText := stringText , ': a pool variable in ',sharedPool name.
+                    val := sharedPool at:string.
+                    valString := self valueStringFor:val.
+                    ^ stringText , ' (' , valString , ').'
+                ].
+            ].
+        ].
 
-	"namespace & global variables"
-	(spc := aClass nameSpace) notNil ifTrue:[
-	    sym := (spc name , '::' , string) asSymbolIfInterned.
-	    sym notNil ifTrue:[
-		(cls := Smalltalk at:sym) isBehavior ifTrue:[
-		    string :=  stringText , ': '.
-		    cls name = sym ifFalse:[
-			string :=  string , 'refers to ',cls name,', '
-		    ].
-		    cls isSharedPool ifTrue:[
-			string := string , 'a sharedPool'.
-		    ] ifFalse:[
-			string := string , 'a class'.
-		    ].
+        "namespace & global variables"
+        (spc := aClass nameSpace) notNil ifTrue:[
+            sym := (spc name , '::' , string) asSymbolIfInterned.
+            sym notNil ifTrue:[
+                (cls := Smalltalk at:sym) isBehavior ifTrue:[
+                    string :=  stringText , ': '.
+                    cls name = sym ifFalse:[
+                        string :=  string , 'refers to ',cls name,', '
+                    ].
+                    cls isSharedPool ifTrue:[
+                        string := string , 'a sharedPool'.
+                    ] ifFalse:[
+                        string := string , 'a class'.
+                    ].
 
-		    string :=  string , ' in the ''' , spc name , ''' nameSpace'.
-		    string := string , ' {', cls category ,'}'.
-		    shortText ifFalse:[
-			string := (string
-			     , '\\It is only visible within this nameSpace.'
-			     , '\Access from the outside is possible'
-			     , '\by the special name ''' , spc name , '::' , string , '''.') withCRs
-		    ].
-		    ^ string withCRs
-		].
-	    ].
-	].
+                    string :=  string , ' in the ''' , spc name , ''' nameSpace'.
+                    string := string , ' {', cls category ,'}'.
+                    shortText ifFalse:[
+                        string := (string
+                             , '\\It is only visible within this nameSpace.'
+                             , '\Access from the outside is possible'
+                             , '\by the special name ''' , spc name , '::' , string , '''.') withCRs
+                    ].
+                    ^ string withCRs
+                ].
+            ].
+        ].
 
     "/    string knownAsSymbol ifTrue:[
-	    "globals & symbols"
-
-	    tmp := self explainKnownSymbol:string inClass:aClass short:shortText.
-	    tmp notNil ifTrue:[ ^ tmp].
+            "globals & symbols"
 
-	    "/ try with added colon ...
-	    sel := string , ':'.
-	    Symbol allInstancesDo:[:sym |
-		(sym startsWith:sel) ifTrue:[
-		    tmp := self explainKnownSymbol:sym inClass:aClass short:shortText.
-		    tmp notNil ifTrue:[ ^ tmp].
-		]
-	    ].
+            tmp := self explainKnownSymbol:string inClass:aClass short:shortText.
+            tmp notNil ifTrue:[ 
+                string isBinarySelector ifTrue:[
+                    "/ some are both known as syntax AND as selector (for example: #| )
+                    tmp1 := self explainSyntax:string short:shortText.
+                    tmp1 notNil ifTrue:[ 
+                        ^ tmp1 , '\\also:\\' withCRs , tmp
+                    ].
+                ].
+                ^ tmp
+            ].
+
+            "/ try with added colon ...
+            sel := string , ':'.
+            Symbol allInstancesDo:[:sym |
+                (sym startsWith:sel) ifTrue:[
+                    tmp := self explainKnownSymbol:sym inClass:aClass short:shortText.
+                    tmp notNil ifTrue:[ ^ tmp].
+                ]
+            ].
     "/    ].
 
-	"try for some obvious things"
-	tmp := self explainPseudoVariable:string in:aClass short:true.
-	tmp notNil ifTrue:[ ^ tmp].
+        "try for some obvious things"
+        tmp := self explainPseudoVariable:string in:aClass short:true.
+        tmp notNil ifTrue:[ ^ tmp].
     ].
 
     "try syntax ..."
@@ -704,17 +716,17 @@
     tmp notNil ifTrue:[ ^ tmp].
 
     shortText ifTrue:[
-	^ 'no explanation'
+        ^ 'no explanation'
     ].
 
     parser isNil ifTrue:[
-	^ 'parse error - no explanation'
+        ^ 'parse error - no explanation'
     ].
     ^ 'cannot explain this (could not figure out what this is).'
 
     "Created: / 03-12-1995 / 12:47:37 / cg"
     "Modified: / 16-04-1997 / 12:46:11 / stefan"
-    "Modified: / 14-02-2012 / 15:30:25 / cg"
+    "Modified: / 27-07-2013 / 09:53:30 / cg"
 !
 
 explainGlobal:string inClass:aClass short:shortText
@@ -968,205 +980,206 @@
     listOfSimilarSelectors := Set new.
 
     check :=
-	[:sel :mthd :cls |
-	    sel == sym ifTrue:[
-		listOfImplementingClasses add:(cls name).
-		firstImplementingClass isNil ifTrue:[
-		    firstImplementingClass := cls
-		]
-	    ] ifFalse:[
-		(sel startsWith:sym) ifTrue:[
-		    listOfSimilarSelectors add:sel.
-		    firstImplementingClassOfSimilar isNil ifTrue:[
-			firstImplementingClassOfSimilar := cls
-		    ]
-		]
-	    ]
-	].
+        [:sel :mthd :cls |
+            sel == sym ifTrue:[
+                listOfImplementingClasses add:(cls name).
+                firstImplementingClass isNil ifTrue:[
+                    firstImplementingClass := cls
+                ]
+            ] ifFalse:[
+                (sel startsWith:sym) ifTrue:[
+                    listOfSimilarSelectors add:sel.
+                    firstImplementingClassOfSimilar isNil ifTrue:[
+                        firstImplementingClassOfSimilar := cls
+                    ]
+                ]
+            ]
+        ].
 
     Smalltalk allClassesDo:[:c|
-	c methodDictionary keysAndValuesDo:[:sel :mthd |
-	    check value:sel value:mthd value:c
-	].
-	c class methodDictionary keysAndValuesDo:[:sel :mthd |
-	    check value:sel value:mthd value:c class
-	].
+        c methodDictionary keysAndValuesDo:[:sel :mthd |
+            check value:sel value:mthd value:c
+        ].
+        c class methodDictionary keysAndValuesDo:[:sel :mthd |
+            check value:sel value:mthd value:c class
+        ].
     ].
 
     (aClass canUnderstand:sym) ifTrue:[
-	s2 := ('Instances of ''' , aClass name , ''' respond to #') , sym "allBold" , '.'.
-	shortText ifFalse:[
-	    s2 := '\\' , s2
-		  , '\- inherited from ' withCRs
-		  , (aClass whichClassIncludesSelector:sym) name "allBold".
-	].
-	firstImplementingClass := (aClass whichClassIncludesSelector:sym)
+        s2 := ('Instances of ''' , aClass name , ''' respond to #') , sym "allBold" , '.'.
+        shortText ifFalse:[
+            s2 := '\\' , s2
+                  , '\- inherited from ' withCRs
+                  , (aClass whichClassIncludesSelector:sym) name "allBold".
+        ].
+        firstImplementingClass := (aClass whichClassIncludesSelector:sym)
     ] ifFalse:[
-	s2 := ''.
+        s2 := ''.
     ].
 
     count := listOfImplementingClasses size.
     (count ~~ 0) ifTrue:[
-	"
-	 for up-to 4 implementing classes,
-	 list them
-	"
-	listOfImplementingClasses := listOfImplementingClasses asOrderedCollection sort.
-	shortText ifTrue:[
-	    tmp := ' is implemented in '.
-	] ifFalse:[
-	    tmp := ' is a selector implemented in '.
-	].
-	s := "'#' ," string allBold.
+        "
+         for up-to 4 implementing classes,
+         list them
+        "
+        listOfImplementingClasses := listOfImplementingClasses asOrderedCollection sort.
+        shortText ifTrue:[
+            tmp := ' is implemented in '.
+        ] ifFalse:[
+            tmp := ' is a selector implemented in '.
+        ].
+        s := "'#' ," string allBold.
 
-	(count == 1) ifTrue:[
-	    (t := listOfImplementingClasses first) isMeta ifTrue:[
-		t := 'the ' , t
-	    ].
-	    msg := s , tmp , t , '.'.
-	    shortText ifFalse:[
-		msg := msg , s2.
-	    ]
-	] ifFalse:[
-	    (count == 2) ifTrue:[
-		msg := s,tmp,(listOfImplementingClasses at:1),' and ',(listOfImplementingClasses at:2),'.'.
-		shortText ifFalse:[
-		    msg := msg , s2.
-		].
-	    ] ifFalse:[
-		(count == 3) ifTrue:[
-		    msg := s,tmp,(listOfImplementingClasses at:1),',',(listOfImplementingClasses at:2),' and ',(listOfImplementingClasses at:3),'.'.
-		    shortText ifFalse:[
-			msg := msg , s2.
-		    ].
-		] ifFalse:[
-		    shortText ifTrue:[
-			msg := s , tmp , count printString , ' classes'.
-			commonSuperClass := Class commonSuperclassOf:listOfImplementingClasses.
-			(commonSuperClass == Object
-			and:[commonSuperClass includesSelector:sym]) ifTrue:[
-			    msg := msg , ' (including ' , 'Object' "allBold", ')'
-			] ifFalse:[
-			    (commonSuperClass ~= Object) ifTrue:[
-				msg := msg , ' (under ' , commonSuperClass name, ')'
-			    ]
-			].
-			msg := msg , '.'.
-			^ msg
-		    ].
+        (count == 1) ifTrue:[
+            (t := listOfImplementingClasses first) isMeta ifTrue:[
+                t := 'the ' , t
+            ].
+            msg := s , tmp , t , '.'.
+            shortText ifFalse:[
+                msg := msg , s2.
+            ]
+        ] ifFalse:[
+            (count == 2) ifTrue:[
+                msg := s,tmp,(listOfImplementingClasses at:1),' and ',(listOfImplementingClasses at:2),'.'.
+                shortText ifFalse:[
+                    msg := msg , s2.
+                ].
+            ] ifFalse:[
+                (count == 3) ifTrue:[
+                    msg := s,tmp,(listOfImplementingClasses at:1),',',(listOfImplementingClasses at:2),' and ',(listOfImplementingClasses at:3),'.'.
+                    shortText ifFalse:[
+                        msg := msg , s2.
+                    ].
+                ] ifFalse:[
+                    shortText ifTrue:[
+                        msg := s , tmp , count printString , ' classes'.
+                        commonSuperClass := Class commonSuperclassOf:listOfImplementingClasses.
+                        (commonSuperClass == Object
+                        and:[commonSuperClass includesSelector:sym]) ifTrue:[
+                            msg := msg , ' (including ' , 'Object' "allBold", ')'
+                        ] ifFalse:[
+                            (commonSuperClass ~= Object) ifTrue:[
+                                msg := msg , ' (under ' , commonSuperClass name, ')'
+                            ]
+                        ].
+                        msg := msg , '.'.
+                        ^ msg
+                    ].
 
-		    (count == 3) ifTrue:[
-			msg := s , tmp , '
+                    (count == 3) ifTrue:[
+                        msg := s , tmp , '
 ' , (listOfImplementingClasses at:1) , ', ' , (listOfImplementingClasses at:2) , ' and ' , (listOfImplementingClasses at:3) , '.' , s2
-		    ] ifFalse:[
-			(count == 4) ifTrue:[
-			    msg := s , tmp , '
+                    ] ifFalse:[
+                        (count == 4) ifTrue:[
+                            msg := s , tmp , '
 ' , (listOfImplementingClasses at:1) , ', ' , (listOfImplementingClasses at:2) , ', ' , (listOfImplementingClasses at:3), ' and ' , (listOfImplementingClasses at:4) , '.' , s2
-			] ifFalse:[
-			    "
-			     if there are more, look for a common
-			     superclass and show it ...
-			    "
-			    commonSuperClass := Behavior commonSuperclassOf:listOfImplementingClasses.
-			    (commonSuperClass ~~ Object
-			    and:[commonSuperClass ~~ Behavior
-			    and:[commonSuperClass ~~ Class
-			    and:[commonSuperClass ~~ ClassDescription]]]) ifTrue:[
-				(listOfImplementingClasses includes:commonSuperClass) ifTrue:[
-				    msg := s . tmp , count printString , commonSuperClass name
-					     , ' and redefined in ' , (count - 1) printString
-					     , ' subclasses'
-					     , s2.
-				    firstImplementingClass := commonSuperClass
-				] ifFalse:[
-				    msg := s , tmp, count printString , ' subclasses of ' , commonSuperClass name , s2
-				]
-			    ] ifFalse:[
-				(commonSuperClass == Object
-				and:[commonSuperClass includesSelector:sym]) ifTrue:[
-				    msg := s , tmp , count printString , ' classes.
+                        ] ifFalse:[
+                            "
+                             if there are more, look for a common
+                             superclass and show it ...
+                            "
+                            commonSuperClass := Behavior commonSuperclassOf:listOfImplementingClasses.
+                            (commonSuperClass ~~ Object
+                            and:[commonSuperClass ~~ Behavior
+                            and:[commonSuperClass ~~ Class
+                            and:[commonSuperClass ~~ ClassDescription]]]) ifTrue:[
+                                (listOfImplementingClasses includes:commonSuperClass) ifTrue:[
+                                    msg := s . tmp , count printString , commonSuperClass name
+                                             , ' and redefined in ' , (count - 1) printString
+                                             , ' subclasses'
+                                             , s2.
+                                    firstImplementingClass := commonSuperClass
+                                ] ifFalse:[
+                                    msg := s , tmp, count printString , ' subclasses of ' , commonSuperClass name , s2
+                                ]
+                            ] ifFalse:[
+                                (commonSuperClass == Object
+                                and:[commonSuperClass includesSelector:sym]) ifTrue:[
+                                    msg := s , tmp , count printString , ' classes.
 
 All objects seem to respond to that message,
 since there is an implementation in Object.' , s2.
 
-				    firstImplementingClass := Object
-				] ifFalse:[
-				    ((commonSuperClass == Behavior
-				     or:[commonSuperClass == Class
-				     or:[commonSuperClass == ClassDescription]])
-				    and:[commonSuperClass includesSelector:sym]) ifTrue:[
-					msg := s , tmp , count printString , ' classes.
+                                    firstImplementingClass := Object
+                                ] ifFalse:[
+                                    ((commonSuperClass == Behavior
+                                     or:[commonSuperClass == Class
+                                     or:[commonSuperClass == ClassDescription]])
+                                    and:[commonSuperClass includesSelector:sym]) ifTrue:[
+                                        msg := s , tmp , count printString , ' classes.
 
 All classes seem to respond to that message,
 since there is an implementation in ' , commonSuperClass name , '.' , s2.
 
-					firstImplementingClass := commonSuperClass
-				    ] ifFalse:[
-					"
-					 otherwise just give the number.
-					"
-					msg := s , tmp , count printString , ' classes.' , s2
-				    ]
-				]
-			    ]
-			]
-		    ]
-		]
-	    ].
-	].
-	shortText ifTrue:[
-	    count == 1 ifTrue:[
-		cm := self fetchCommentOfMethod:(firstImplementingClass compiledMethodAt:sym).
-		cm notNil ifTrue:[
-		    msg := msg,' ',cm
-		].
-	    ].
-	] ifFalse:[
-	    firstImplementingClass notNil ifTrue:[
-		WindowGroup activeGroup withWaitCursorDo:[
-		    cm := firstImplementingClass compiledMethodAt:sym.
-		    cm notNil ifTrue:[
-			cm := cm methodComment.
-		    ]
-		].
-		cm notNil ifTrue:[
-		    msg := msg , '\\The comment in ' withCRs
-			       , firstImplementingClass name "allBold" , ' is:\' withCRs
-			       , '"' , cm allItalic , '"'.
-		]
-	    ].
-	].
-	^ msg
+                                        firstImplementingClass := commonSuperClass
+                                    ] ifFalse:[
+                                        "
+                                         otherwise just give the number.
+                                        "
+                                        msg := s , tmp , count printString , ' classes.' , s2
+                                    ]
+                                ]
+                            ]
+                        ]
+                    ]
+                ]
+            ].
+        ].
+        shortText ifTrue:[
+            count == 1 ifTrue:[
+                cm := self fetchCommentOfMethod:(firstImplementingClass compiledMethodAt:sym).
+                cm notNil ifTrue:[
+                    msg := msg,' ',cm
+                ].
+            ].
+        ] ifFalse:[
+            firstImplementingClass notNil ifTrue:[
+                WindowGroup activeGroup withWaitCursorDo:[
+                    cm := self fetchCommentOfMethod:(firstImplementingClass compiledMethodAt:sym).
+"/                    cm := firstImplementingClass compiledMethodAt:sym.
+"/                    cm notNil ifTrue:[
+"/                        cm := cm methodComment.
+"/                    ]
+                ].
+                cm notNil ifTrue:[
+                    msg := msg , '\\The comment in ' withCRs
+                               , firstImplementingClass name "allBold" , ' is:\' withCRs
+                               , '"' , cm allItalic , '"'.
+                ]
+            ].
+        ].
+        ^ msg
     ].
 
     count := listOfSimilarSelectors size.
     (count ~~ 0) ifTrue:[
-	listOfSimilarSelectors := listOfSimilarSelectors asOrderedCollection sort.
-	shortText ifTrue:[
-	    tmp := ' is implemented in '.
-	] ifFalse:[
-	    tmp := ' is a selector implemented in '.
-	].
+        listOfSimilarSelectors := listOfSimilarSelectors asOrderedCollection sort.
+        shortText ifTrue:[
+            tmp := ' is implemented in '.
+        ] ifFalse:[
+            tmp := ' is a selector implemented in '.
+        ].
 
-	(count == 1) ifTrue:[
-	    msg := listOfSimilarSelectors first allBold , tmp , firstImplementingClassOfSimilar name , '.'.
-	    shortText ifFalse:[
-		msg := msg , s2.
-	    ]
-	] ifFalse:[
-	    msg := 'similar selectors: %1, %2' bindWith:listOfSimilarSelectors first allBold with:listOfSimilarSelectors second allBold.
-	    count > 2 ifTrue:[
-		msg := msg,'...'.
-	    ].
-	].
-	^ msg
+        (count == 1) ifTrue:[
+            msg := listOfSimilarSelectors first allBold , tmp , firstImplementingClassOfSimilar name , '.'.
+            shortText ifFalse:[
+                msg := msg , s2.
+            ]
+        ] ifFalse:[
+            msg := 'similar selectors: %1, %2' bindWith:listOfSimilarSelectors first allBold with:listOfSimilarSelectors second allBold.
+            count > 2 ifTrue:[
+                msg := msg,'...'.
+            ].
+        ].
+        ^ msg
     ].
 
     ^ nil
 
     "Modified: / 17-06-1996 / 17:09:30 / stefan"
     "Created: / 23-03-1999 / 13:29:33 / cg"
-    "Modified: / 28-02-2012 / 10:49:08 / cg"
+    "Modified: / 27-07-2013 / 09:59:46 / cg"
 !
 
 explainSelfIn:aClass short:shortText
@@ -1278,31 +1291,32 @@
     "try syntax ...; return explanation or nil"
 
     ((string = ':=') or:[string = '_']) ifTrue:[
-	shortText ifTrue:[
-	    ^ 'Assign to variable on the left side.'.
-	].
+        shortText ifTrue:[
+            ^ 'Assign to variable on the left side.'.
+        ].
 
-	^ '<variable> := <expression>
+        ^ '<variable> := <expression>
 
-'':='' and ''_'' (which is left-arrow in some fonts) mean assignment.
+":=" and "_" (which is left-arrow in some fonts) mean assignment.
+The "_" form is historic and should not be used with new code.
 The variable is bound to (i.e. points to) the value of <expression>.'
     ].
 
     (string = '^') ifTrue:[
-	shortText ifTrue:[
-	    ^ 'Return value from method.'.
-	].
-	^ '^ <expression>
+        shortText ifTrue:[
+            ^ 'Return value from method.'.
+        ].
+        ^ '^ <expression>
 
 returns the value of <expression> as value from the method.
 A return from within a block exits the method where the block is defined.'
     ].
 
     (string = ';') ifTrue:[
-	shortText ifTrue:[
-	    ^ 'Cascade expression.'.
-	].
-	^ '<expression> ; selector1 ; .... ; selectorN
+        shortText ifTrue:[
+            ^ 'Cascade expression.'.
+        ].
+        ^ '<expression> ; selector1 ; .... ; selectorN
 
 a cascade expression; evaluate expression, and send messages
 <selector1> ... <selectorN> to the first expression''s receiver.
@@ -1310,23 +1324,23 @@
     ].
 
     (string = '|') ifTrue:[
-	shortText ifTrue:[
-	    ^ ''.
-	].
-	^ '| locals |  or: [:arg | statements]
+        shortText ifTrue:[
+            ^ ''.
+        ].
+        ^ '| locals |  or: [:arg | statements]
 
-''|'' is used to mark a local variable declaration or separates arguments
+"|" is used to mark a local variable declaration or separates arguments
 from the statements in a block. Notice, that in a block-argument declaration
 these must be prefixed by a colon character.
-''|'' is also a selector understood by Booleans.'
+"|" is also a selector understood by Booleans.'
     ].
 
     (string startsWith:'#' ) ifTrue:[
-	(string startsWith:'#(' ) ifTrue:[
-	    shortText ifTrue:[
-		^ 'Array Literal.'.
-	    ].
-	    ^ 'is a constant Array.
+        (string startsWith:'#(' ) ifTrue:[
+            shortText ifTrue:[
+                ^ 'Array Literal.'.
+            ].
+            ^ 'is a constant Array.
 
 The array-object is created at compilation time and a reference to this is
 used at execution time (thus, the same object is referred to every time).
@@ -1334,35 +1348,35 @@
 other array constants or byte-arrays.
 (notice, that not all Smalltalk implementations allow true, false and nil as
  element in an Array-constant).'
-	].
+        ].
 
-	(string startsWith:'#[') ifTrue:[
-	    shortText ifTrue:[
-		^ 'ByteArray Literal.'.
-	    ].
-	    ^ 'is a constant ByteArray.
+        (string startsWith:'#[') ifTrue:[
+            shortText ifTrue:[
+                ^ 'ByteArray Literal.'.
+            ].
+            ^ 'is a constant ByteArray.
 
 The elements of a constant ByteArray must be Integer constants in the range
 0 .. 255.
 (notice, that not all Smalltalk implementations support constant ByteArrays).'
-	].
+        ].
 
-	(string startsWith:'#''') ifTrue:[
-	    shortText ifTrue:[
-		^ 'Symbol Literal.'.
-	    ].
-	    ^ 'is a constant symbol containing non-alphanumeric characters.
+        (string startsWith:'#''') ifTrue:[
+            shortText ifTrue:[
+                ^ 'Symbol Literal.'.
+            ].
+            ^ 'is a constant symbol containing non-alphanumeric characters.
 
 Symbols are unique strings, meaning that there exists
 exactly one instance of a given symbol. Therefore symbols can
 be compared using == (identity compare) in addition to = (contents compare).
 Beside this, Symbols behave mostly like Strings but are immutable.'
-	].
+        ].
 
-	shortText ifTrue:[
-	    ^ 'Symbol Literal.'.
-	].
-	^ 'is a symbol.
+        shortText ifTrue:[
+            ^ 'Symbol Literal.'.
+        ].
+        ^ 'is a symbol.
 
 Symbols are unique strings, meaning that there exists
 exactly one instance of a given symbol. Therefore symbols can
@@ -1370,20 +1384,20 @@
 Beside this, Symbols behave mostly like Strings but are immutable.'
     ].
     ((string startsWith:'(') or:[string endsWith:')']) ifTrue:[
-	shortText ifTrue:[
-	    ^ ''.
-	].
-	^ '( <expression> )
+        shortText ifTrue:[
+            ^ ''.
+        ].
+        ^ '( <expression> )
 
 expression grouping. Without them, expressions are evaluated left to right,
 with unary messages preceeding binary messages, preceeding keyword mesages.'
     ].
 
     ((string startsWith:'[') or:[string endsWith:']']) ifTrue:[
-	shortText ifTrue:[
-	    ^ 'a block (aka lambda/closure for experts)'.
-	].
-	^ '[:arg1 .. :argN | statements]
+        shortText ifTrue:[
+            ^ 'a block (aka lambda/closure for experts)'.
+        ].
+        ^ '[:arg1 .. :argN | statements]
 
 defines a block.
 Blocks represent pieces of executable code. The definition of a block does
@@ -1396,31 +1410,32 @@
     ].
 
     ((string startsWith:'{') or:[string endsWith:'}']) ifTrue:[
-	shortText ifTrue:[
-	    ^ 'array instantiation'.
-	].
-	^ '{ <expr1>. .. <exprN> }
+        shortText ifTrue:[
+            ^ 'array instantiation'.
+        ].
+        ^ '{ <expr1>. .. <exprN> }
 
 is syntactic sugar for "Array with:<expr1> .. with:<exprN>".
 A new array is created with N elements initialized from the N expressions.
 The expressions are separated by a period statement separator.
 The expressions are evaluated at execution time, and a new array is always created
 when executed (as opposed to an array literal, which is computed only once at
-compilation time) and which is shared.'
+compilation time) and which is shared.
+Notice that this construct is not supported by all Smalltalks'
     ].
 
     (string = ':') ifTrue:[
-	shortText ifTrue:[
-	    ^ ''.
-	].
-	^ 'colons have different meaning depending on context:
+        shortText ifTrue:[
+            ^ ''.
+        ].
+        ^ 'colons have different meaning depending on context:
 
 1) they separate keyword-parts in symbols and keyword-messages as in:
 
     #at:put:                     a constant keyword symbol
 
     rec at:index put:value       sends the #at:put: message to rec,
-				 passing index and value as arguments.
+                                 passing index and value as arguments.
 
 2) within block-argument declarations as in:
 
@@ -1435,7 +1450,7 @@
     ].
 
     (string = '.') ifTrue:[
-	^ 'statement. "<- period here"
+        ^ 'statement. "<- period here"
 statement
 
 within a method or block, individual statements are separated by periods.
@@ -1443,20 +1458,21 @@
     ].
 
     (string withoutSeparators startsWith:'"/') ifTrue:[
-	shortText ifTrue:[
-	    ^ 'an end-of-line comment'.
-	].
-	^ '"/ comment
+        shortText ifTrue:[
+            ^ 'an end-of-line comment'.
+        ].
+        ^ '"/ comment
 EOL (end-of-line) comment
 
 anything up to the end of line is a comment and ignored (but not inside a string).
+Notice that EOL-comments are only supported by Smalltalk/X (i.e. non-portable).
 '
     ].
     (string withoutSeparators startsWith:'"') ifTrue:[
-	shortText ifTrue:[
-	    ^ 'a comment'.
-	].
-	^ '" comment ... "
+        shortText ifTrue:[
+            ^ 'a comment'.
+        ].
+        ^ '" comment ... "
 comment
 
 anything between double quotes is a comment and ignored (but not inside a string).
@@ -1476,7 +1492,7 @@
 
     ^ nil
 
-    "Modified: / 31.10.1998 / 14:28:58 / cg"
+    "Modified: / 27-07-2013 / 10:08:57 / cg"
 !
 
 valueStringFor:aValue
@@ -1515,10 +1531,10 @@
 !Explainer class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libcomp/Explainer.st,v 1.127 2013-06-23 08:26:55 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libcomp/Explainer.st,v 1.128 2013-07-27 08:22:18 cg Exp $'
 !
 
 version_CVS
-    ^ '$Header: /cvs/stx/stx/libcomp/Explainer.st,v 1.127 2013-06-23 08:26:55 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libcomp/Explainer.st,v 1.128 2013-07-27 08:22:18 cg Exp $'
 ! !