Model subclass: #SimpleGuiBuilder instanceVariableNames: 'widgets title ' classVariableNames: '' poolDictionaries: '' category: 'Category-SimpleGuiBuilder'! !SimpleGuiBuilder methodsFor: 'initialization'! initialize widgets _ Dictionary new! ! !SimpleGuiBuilder methodsFor: 'initialization'! openAsMorphLabel: aString "SimpleGuiBuilder new openAsMorphLabel: 'GUI Builder' " | window | window _ SimpleGuiBuilderWindow labelled: aString. window model: self. window setWindowColor: Color yellow. window openInWorld! ! !SimpleGuiBuilder methodsFor: 'accessing'! codeForWidget: typeSym typeSym == #button ifTrue: [^ self codeForButton]. typeSym == #list ifTrue: [^ self codeForList]. ^ self codeForText! ! !SimpleGuiBuilder methodsFor: 'accessing'! widgets ^ widgets! ! !SimpleGuiBuilder methodsFor: 'mock selectors'! codePaneMenu: ignore shifted: ignoreToo ^ nil! ! !SimpleGuiBuilder methodsFor: 'mock selectors'! contents ^ Text new! ! !SimpleGuiBuilder methodsFor: 'mock selectors'! contents: ignore notifying: ignoreToo ^ true! ! !SimpleGuiBuilder methodsFor: 'mock selectors'! contentsSelection ^ 1 to: 0! ! !SimpleGuiBuilder methodsFor: 'mock selectors'! index ^ nil! ! !SimpleGuiBuilder methodsFor: 'mock selectors'! index: ignore ^ self! ! !SimpleGuiBuilder methodsFor: 'mock selectors'! indicate ^ self! ! !SimpleGuiBuilder methodsFor: 'mock selectors'! indicated ^ true! ! !SimpleGuiBuilder methodsFor: 'mock selectors'! list ^ Array new! ! !SimpleGuiBuilder methodsFor: 'mock selectors'! listKey: ignore form: ignoreToo ^ nil! ! !SimpleGuiBuilder methodsFor: 'mock selectors'! listMenu: ignore ^ nil! ! !SimpleGuiBuilder methodsFor: 'code for widget'! codeForButton ^ 'PluggableButtonMorph new on: model getState: #indicated action: #indicate label: nil menu: nil; label: ''unnamed''.'! ! !SimpleGuiBuilder methodsFor: 'code for widget'! codeForList ^ 'PluggableListMorph on: model list: #list selected: #index changeSelected: #index: menu: #listMenu: keystroke: #listKey:from:.'! ! !SimpleGuiBuilder methodsFor: 'code for widget'! codeForText ^ 'PluggableTextMorph on: model text: #contents accept: #contents:notifying: readSelection: #contentsSelection menu: #codePaneMenu:shifted:.'! ! !SimpleGuiBuilder methodsFor: 'add-delete'! add: widgetType frame: relFrame widgets at: relFrame put: widgetType. self changed! ! !SimpleGuiBuilder methodsFor: 'add-delete'! removeWidgetIn: relFrame widgets removeKey: relFrame ifAbsent: []. self changed: relFrame! ! !SimpleGuiBuilder methodsFor: 'menu messages'! saveCodeInFile | filename file digitSuffixes code varNames keys | digitSuffixes _ Dictionary new. code _ WriteStream on: (String new: 1000). varNames _ WriteStream on: String new. varNames nextPutAll: '| window model '. filename _ FillInTheBlank request: 'filename:' initialAnswer: 'UnnamedWindow.st' . filename ifNil: [^ self]. code nextPutAll: 'model _ ', self class printString, ' new.'. code cr. code nextPutAll: 'window _ (SystemWindow labelled: '''. code nextPutAll: filename sansPeriodSuffix. code nextPutAll: ''') model: model.'. code cr. keys _ widgets keys asSortedCollection: [: a : b | ((a top - b top) abs > 0.05) ifTrue: [a top < b top] ifFalse: [a left < b left]]. keys do: [: frame | | type digitSuffix varName | type _ widgets at: frame. digitSuffix _ digitSuffixes at: type put: (digitSuffixes at: type ifAbsentPut: [0]) + 1. varName _ type asString, digitSuffix printString. varNames nextPutAll: varName; space. code nextPutAll: varName, ' _ '. code nextPutAll: (self codeForWidget: type). code cr. code nextPutAll: 'window '; crtab. code nextPutAll: 'addMorph: ', varName; crtab. code nextPutAll: 'frame: (', frame printString, ').'. code cr]. varNames nextPut: $|. file _ FileStream newFileNamed: filename. [file nextPutAll: varNames contents; cr. file nextPutAll: code contents. file nextPutAll: 'window openInWorld'] ensure: [file close]! ! !SimpleGuiBuilder methodsFor: 'user interface'! addModelItemsToWindowMenu: aMenu | target | target _ aMenu defaultTarget. aMenu addLine. aMenu add: 'save source code to file...' target: self action: #saveCodeInFile. aMenu addLine. aMenu add: 'add list' target: target selector: #addWidget: argument: #list. aMenu add: 'add button' target: target selector: #addWidget: argument: #button. aMenu add: 'add text field' target: target selector: #addWidget: argument: #text. aMenu addLine. aMenu add: 'delete widget' target: target selector: #deleteWidget! ! SimpleGuiBuilder class instanceVariableNames: ''! !SimpleGuiBuilder class methodsFor: 'instance creation'! new ^ super new initialize; yourself! ! SystemWindow subclass: #SimpleGuiBuilderWindow instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Category-SimpleGuiBuilder'! !SimpleGuiBuilderWindow methodsFor: 'testing'! isWidgetExistIn: relFrame self submorphsDo: [: morph | | frame | frame _ self getFrameOf: morph. relFrame = frame ifTrue: [^ true]]. ^ false! ! !SimpleGuiBuilderWindow methodsFor: 'adding'! addWidget: typeSym | rect relRect relFrame myBounds | rect _ Rectangle fromUser. myBounds _ self layoutBounds. relRect _ rect align: myBounds topLeft with: 0 asPoint. relFrame _ (relRect left / myBounds width) @ (relRect top / myBounds height) corner: (relRect right / myBounds width) @ (relRect bottom / myBounds height). self model add: typeSym frame: relFrame! ! !SimpleGuiBuilderWindow methodsFor: 'accessing'! widgetAt: aPoint | candidates | candidates _ self submorphs select: [: morph | morph bounds containsPoint: aPoint]. candidates isEmpty ifTrue: [^ nil]. ^ candidates last! ! !SimpleGuiBuilderWindow methodsFor: 'accessing'! widgetIn: relFrame self submorphsDo: [: morph | (self getFrameOf: morph) = relFrame ifTrue: [^ morph]]. ^ nil! ! !SimpleGuiBuilderWindow methodsFor: 'deleting'! deleteWidget | point | point _ Point fromUser. model removeWidgetIn: (self getFrameOf: (self widgetAt: point))! ! !SimpleGuiBuilderWindow methodsFor: 'updating'! update: parameter model widgets keysAndValuesDo: [: frame : type | (self isWidgetExistIn: frame) not ifTrue: [ self addMorph: ( Compiler evaluate: (model codeForWidget: type) for: self logged: false) frame: frame]]. (parameter isKindOf: Rectangle) ifTrue: [(self widgetIn: parameter) delete].! ! !SimpleGuiBuilderWindow methodsFor: 'utilities'! getFrameOf: aMorph ^ (aMorph valueOfProperty: #layoutFrame) ifNotNilDo: [: layout | layout leftFraction @ layout topFraction corner: layout rightFraction @ layout bottomFraction]! !