" Module XW.ST Date 17-Dec-1990 Version 2.02-00 Modified 04-Apr-1991 " " | Change Log | ============================================================================ | Author Date Change | ALISTAIR 13 Jul 91 Added doSelection and showSelection to pop up menu. | | KAREN 10 Apr 91 Fixed error trapping | | KAREN 4 Apr 91 Made use of new XTranscript class for main transcript | window | | KAREN 3 Apr 91 Filed in new definitions files for general classes | XWindow and XWindowController. | | KAREN 5 Mar 91 Changed to take account of new model-controller | structure | | KAREN 25 Feb 91 Made changes arising from renaming of text window | object from XDisplay to XTextWindow | | ALISTAIR 31 Jan 91 V2.02-00 | Added error: method to print error's in the | transcript window. | | ALISTAIR 30 Jan 91 V2.01-00 | Changed run loop from huge if-then-else to testing | for method definitions, and using those. Methods are | named key, e.g. key65293 inserts a | return. | | KAREN 29 Jan 91 Added code to handle key presses and invoke editing | functions | | | ALISTAIR 18 Jan 91 V2.00-02 | Handle X-Window Quit selection correctly. | | ALISTAIR 18 Jan 91 V2.00-01 | Changed storeString to printString to make output | more readable. | | ALISTAIR 8 Jan 91 Added code so that all IO to standard input/output | now goes to the transcript window. | " FileStream fileIn: 'smalltalk_image:xw-ctrl-defs.st'! FileStream fileIn: 'smalltalk_image:xw-defs.st'! FileStream fileIn: 'smalltalk_image:xw-text-ctrl-defs.st'! FileStream fileIn: 'smalltalk_image:xw-text-defs.st'! FileStream fileIn: 'smalltalk_image:xw-trans-ctrl-defs.st'! FileStream fileIn: 'smalltalk_image:xw-trans-defs.st'! FileStream fileIn: 'smalltalk_image:xw-list-ctrl-defs.st'! FileStream fileIn: 'smalltalk_image:xw-list-defs.st'! FileStream fileIn: 'smalltalk_image:xw-display-defs.st'! XTextWindow initialize! XTranscript initialize! Smalltalk at: #Display put: (XDisplay new) ! Smalltalk at: #Transcript put: (Display addTranscript) ! " Smalltalk at: #Transcript2 put: (Display addTextWindow) ! Smalltalk at: #List put: (Display addListBox: 'Box' with:'one\two\three')! Smalltalk at: #List2 put: (Display addListBox: 'Box2' with: 'a\b\c')! " !Object methodsFor: 'printing'! print (self class = String) ifTrue: [ Transcript print: self ] ifFalse: [ Transcript print: self printString ]. ! printNl self print. Transcript nextPut: (Character value: 13). !! !Object methodsFor: 'error trapping'! doesNotUnderstand: aMessage | n context | ' ' printNl. " start error message on new line" context _ thisContext. context receiver class print. ' did not understand selector ' print. aMessage selector printNl. n _ 0. context _ thisContext parentContext. [ context notNil ] whileTrue: [ n _ n + 1. context _ context parentContext ]. context _ thisContext parentContext. n to: 1 by: -1 do: [:i | context receiver class print. '>>' print. context selector printNl. ((context receiver class) == (Object class)) ifTrue: [ [Display activateController] fork. Processor terminateActive. ]. context _ context parentContext ]. [Display activateController] fork. Processor terminateActive !! !Message methodsFor: 'debugging'! selector ^selector ! arguments ^args !! !BlockContext methodsFor: 'debugging'! callers self inspect. caller notNil ifTrue: [ caller callers ] ! parentContext ^caller ! selector ^selector ! receiver ^'[] in ', home class name !! !MethodContext methodsFor: 'debugging'! callers self inspect. sender notNil ifTrue: [ sender callers ] ! parentContext ^sender ! receiver " ^receiver class name " ^receiver ! sender ^sender ! selector ^selector !! !XTranscript methodsFor: 'Transcript'! transcript " Smalltalk executionTrace: true. Smalltalk verboseTrace: true. " Transcript definePopUp: 'Do Selection\Show Selection' with: 'doSelection\showSelection'. Display searchForActiveController. !! Transcript transcript. !