'VisualWorks(R), リリース 2.5.1J 1996年2月24日, 1997年5月5日 午後9時55分44秒'! RoseSingletonVariableTypeFinder subclass: #RoseObjyVariableTypeFinder instanceVariableNames: 'varNameTypeDict myRoseSelectionVar ' classVariableNames: 'MyOoScanner ' poolDictionaries: '' category: 'RationalRose-Objy/ST-Reverse'! RoseObjyVariableTypeFinder comment: 'Copyright(C) 1997 Masashi Umezawa All Rights Reserved Version: 1.0 Date: 1997 5/4 Description: Rose/Smalltalk Reverse TypeFinder for Objectivity/Smalltalk 説明: Rose/SmalltalkリバースにおいてObjyctivity/Smalltalk Interfaceで拡張されたクラス定義の情報を抽出できるタイプファインダ Support Environments: Rose/Smaltalk 3.0J* + Objectivyty 4.0* + VisualWorks 2.5* Distribution: WORLD (FREE) Contact: {mail: umejava@dtinet.or.jp} {www: http://www.mars.dtinet.or.jp/~umejava} sorry about following tedius expressions.. I MAKE NO REPRESENTATIONS OR WARRANTIES ABOUT THE SUITABILITY OF THIS CLASS,EITHER EXPRESS OR IMPLIED, FITNESS FOR A PARTICULAR PURPOSE, OR NON-INFRINGEMENT. I SHALL NOT BE LIABLE FOR ANY DAMAGES SUFFERED BY USING AS A RESULT OF USING, MODIFYING OR DISTRIBUTING THIS SOFTWARE OR ITS DERIVATIVES. (ANYWAY ENJOY YOURSELF!! ;->). '! !RoseObjyVariableTypeFinder methodsFor: 'initialize'! initDict "Copyright(C) 1997 Masashi Umezawa All Rights Reserved" "invoked when targetClass changes" varNameTypeDict := Dictionary new! ! !RoseObjyVariableTypeFinder methodsFor: 'accessing'! myRoseSelectionVar "Copyright(C) 1997 Masashi Umezawa All Rights Reserved" ^myRoseSelectionVar! myRoseSelectionVar: aRoseSelectionVariable "Copyright(C) 1997 Masashi Umezawa All Rights Reserved" myRoseSelectionVar := aRoseSelectionVariable! objyTypeAttributeMode "Copyright(C) 1997 Masashi Umezawa All Rights Reserved" ^self class objyTypeAttributeMode! objyTypes "Copyright(C) 1997 Masashi Umezawa All Rights Reserved" ^self class objyTypes! scanner "Copyright(C) 1997 Masashi Umezawa All Rights Reserved" ^MyOoScanner! varNameTypeDict "Copyright(C) 1997 Masashi Umezawa All Rights Reserved" ^varNameTypeDict isNil ifTrue: [varNameTypeDict := Dictionary new] ifFalse: [varNameTypeDict]! ! !RoseObjyVariableTypeFinder methodsFor: 'actions-type'! type "Copyright(C) 1997 Masashi Umezawa All Rights Reserved" "return the name of the Type represented by variable name. If it doesn't exist, simply return empty string" self kind ~~ #inst ifTrue: [^type := '']. ^(type isNil) ifTrue: [| find | find := self varNameTypeDict at: self varName ifAbsent: []. find isNil ifTrue: [type := ''] ifFalse: [type := self processVarType: find]] ifFalse: [type]! ! !RoseObjyVariableTypeFinder methodsFor: 'resetting'! setOn: aRoseSelectionVariable "Copyright(C) 1997 Masashi Umezawa All Rights Reserved" super setOn: aRoseSelectionVariable. self myRoseSelectionVar: aRoseSelectionVariable! ! !RoseObjyVariableTypeFinder methodsFor: 'private'! objyVarTypeAsAttribute: aString "Copyright(C) 1997 Masashi Umezawa All Rights Reserved" (self objyTypes includes: aString asLowercase) ifTrue: [self myRoseSelectionVar extra: [:selVar | selVar generateMode: #attribute] . ].! processRelationVarType: aParsedTypeInfo "Copyright(C) 1997 Masashi Umezawa All Rights Reserved" | return | (aParsedTypeInfo isKindOf: OoRelationInfo) ifTrue: [return := aParsedTypeInfo otherClassName asString] ifFalse: [return := aParsedTypeInfo]. ^return! processVarType: aParsedTypeInfo "Copyright(C) 1997 Masashi Umezawa All Rights Reserved" | return | return := self processRelationVarType: aParsedTypeInfo. self objyTypeAttributeMode ~~ #none ifTrue: [self objyVarTypeAsAttribute: return]. ^return! resetHelperOf: aClass "Copyright(C) 1997 Masashi Umezawa All Rights Reserved" self resetScannerOf: aClass! resetScannerOf: aClass "Copyright(C) 1997 Masashi Umezawa All Rights Reserved" "Note: Objy/ST only supports instnace variable attributes/relations" (self kind == #inst and: [aClass respondsTo: #ooTypedInstanceVariablesString]) ifTrue: [| dic parsedAssoc | self initDict. dic := self varNameTypeDict. parsedAssoc := self scanner scanTypedFieldNames: aClass ooTypedInstanceVariablesString. parsedAssoc key with: parsedAssoc value do: [:key :value | dic at: key put: value]]! ! RoseObjyVariableTypeFinder class instanceVariableNames: 'objyTypeAttributeMode objyTypes '! !RoseObjyVariableTypeFinder class methodsFor: 'class initialization'! initialize "Copyright(C) 1997 Masashi Umezawa All Rights Reserved" "self initialize" default isNil ifTrue: [self myMasterClass resetAfterLoad]. super initialize. MyOoScanner := self myScannerClass new. self initSetting! initObjyTypes "Copyright(C) 1997 Masashi Umezawa All Rights Reserved" "self initObjyTypes" | mode | objyTypes := OrderedCollection new. mode := self objyTypeAttributeMode. mode == #primTypes ifTrue: [objyTypes add: 'char'. objyTypes add: 'int8'. objyTypes add: 'int16'. objyTypes add: 'int32'. objyTypes add: 'uint8'. objyTypes add: 'uint16'. objyTypes add: 'uint32'. objyTypes add: 'float32'. objyTypes add: 'float64'. objyTypes add: 'oovstring'. objyTypes add: 'oovarray'. objyTypes add: 'ootransient'.]. mode == #allTypes ifTrue: [objyTypes add: 'oodictionary'. objyTypes add: 'oomap'. objyTypes add: 'ststorestring']! initSetting "Copyright(C) 1997 Masashi Umezawa All Rights Reserved" "self initSetting" objyTypeAttributeMode := #primTypes. "#options: #none, #primTypes #allTypes" self initObjyTypes.! ! !RoseObjyVariableTypeFinder class methodsFor: 'accessing'! objyTypeAttributeMode ^objyTypeAttributeMode! objyTypes ^objyTypes! ! !RoseObjyVariableTypeFinder class methodsFor: 'factory'! myScannerClass "Copyright(C) 1997 Masashi Umezawa All Rights Reserved" ^OoTypeScanner! ! !RoseObjyVariableTypeFinder class methodsFor: 'description'! description "Copyright(C) 1997 Masashi Umezawa All Rights Reserved" ^RoseTypeFinderDescription body: self default name: #objy priority: 4 isOn: true! ! RoseAbstractVariableTypeFinderSettingGUI subclass: #RoseObjyVariableTypeFinderSettingGUI instanceVariableNames: 'objyTypeAttributeMode myFinder ' classVariableNames: '' poolDictionaries: '' category: 'RationalRose-Objy/ST-Reverse'! RoseObjyVariableTypeFinderSettingGUI comment: 'Copyright(C) 1997 Masashi Umezawa All Rights Reserved Copyright(C) 1997 Masashi Umezawa All Rights Reserved Version: 1.0 Date: 1997 5/4 Description: Rose/Smalltalk Reverse TypeFinder Setting GUI for Objectivity/Smalltalk 説明: RoseObjyVariableTyprFinderの設定用GUI Support Environments: Rose/Smaltalk 3.0J* + Objectivyty 4.0* + VisualWorks 2.5* Distribution: WORLD (FREE) Contact: {mail: umejava@dtinet.or.jp} {www: http://www.mars.dtinet.or.jp/~umejava} sorry about following tedius expressions.. I MAKE NO REPRESENTATIONS OR WARRANTIES ABOUT THE SUITABILITY OF THIS CLASS,EITHER EXPRESS OR IMPLIED, FITNESS FOR A PARTICULAR PURPOSE, OR NON-INFRINGEMENT. I SHALL NOT BE LIABLE FOR ANY DAMAGES SUFFERED BY USING AS A RESULT OF USING, MODIFYING OR DISTRIBUTING THIS SOFTWARE OR ITS DERIVATIVES. (ANYWAY ENJOY YOURSELF!! ;->). '! !RoseObjyVariableTypeFinderSettingGUI methodsFor: 'initialize-release'! initialize "Copyright(C) 1997 Masashi Umezawa All Rights Reserved" myFinder := self class myFinderClass. self objyTypeAttributeMode value: myFinder objyTypeAttributeMode! ! !RoseObjyVariableTypeFinderSettingGUI methodsFor: 'actions'! accept "Copyright(C) 1997 Masashi Umezawa All Rights Reserved" self myFinder objyTypeAttributeMode: self objyTypeAttributeMode value. self closeRequest! backToDefault "Copyright(C) 1997 Masashi Umezawa All Rights Reserved" self myFinder initialize. self initialize! ! !RoseObjyVariableTypeFinderSettingGUI methodsFor: 'aspects'! objyTypeAttributeMode "Copyright(C) 1997 Masashi Umezawa All Rights Reserved" ^objyTypeAttributeMode isNil ifTrue: [objyTypeAttributeMode := nil asValue] ifFalse: [objyTypeAttributeMode]! ! RoseObjyVariableTypeFinderSettingGUI class instanceVariableNames: ''! !RoseObjyVariableTypeFinderSettingGUI class methodsFor: 'interface specs'! embedSpec "Copyright(C) 1997 Masashi Umezawa All Rights Reserved" "UIPainter new openOnClass: self andSelector: #embedSpec" ^#(#FullSpec #window: #(#WindowSpec #label: #(#UserMessage #key: #setting #defaultString: 'Rose Smalltalk Setting') #min: #(#Point 40 20) #bounds: #(#Rectangle 202 186 666 382)) #component: #(#SpecCollection #collection: #(#(#GroupBoxSpec #layout: #(#LayoutFrame 0 0.0107759 0 0.178571 0 0.967672 0 0.688776) #label: #(#UserMessage #key: #objyEmbeddedTypesAsAttribute #defaultString: 'Generate Objy Embedded Types as Attribute')) #(#RadioButtonSpec #layout: #(#LayoutOrigin 0 0.0689655 0 0.397959) #model: #objyTypeAttributeMode #label: #(#UserMessage #key: #none #defaultString: 'None') #select: #none) #(#RadioButtonSpec #layout: #(#LayoutOrigin 0 0.267241 0 0.392857) #model: #objyTypeAttributeMode #label: #(#UserMessage #key: #primTypes #defaultString: 'Primitive Types Only') #select: #primTypes) #(#RadioButtonSpec #layout: #(#LayoutOrigin 0 0.674569 0 0.392857) #model: #objyTypeAttributeMode #label: #(#UserMessage #key: #allTypes #defaultString: 'All Objy Types') #select: #allTypes) #(#ActionButtonSpec #layout: #(#LayoutFrame 0 0.840517 0 0.760204 0 0.963362 0 0.887755) #model: #backToDefault #label: #(#UserMessage #key: #backToDefault #defaultString: 'reset') #defaultable: true))))! windowSpec "Copyright(C) 1997 Masashi Umezawa All Rights Reserved" "UIPainter new openOnClass: self andSelector: #windowSpec" ^#(#FullSpec #window: #(#WindowSpec #label: #(#UserMessage #key: #setting #defaultString: 'Rose Smalltalk Setting') #min: #(#Point 40 20) #bounds: #(#Rectangle 181 199 645 495)) #component: #(#SpecCollection #collection: #(#(#ActionButtonSpec #layout: #(#LayoutFrame 0 0.0603448 0 0.841216 0 0.280172 0 0.962838) #model: #accept #label: #(#UserMessage #key: #Accept #defaultString: 'Accept') #isDefault: true #defaultable: true) #(#ActionButtonSpec #layout: #(#LayoutFrame 0 0.728448 0 0.841216 0 0.948276 0 0.962838) #model: #cancel #label: #(#UserMessage #key: #Cancel #defaultString: 'Cancel') #defaultable: true) #(#LabelSpec #layout: #(#LayoutOrigin 0 0.0280172 0 0.0743243) #label: #(#UserMessage #key: #objyTypeFinder #defaultString: 'Objy TypeFinder')) #(#GroupBoxSpec #layout: #(#LayoutFrame 0 0.0107759 0 0.179054 0 0.9375 0 0.638513) #label: #(#UserMessage #key: #objyEmbeddedTypesAsAttribute #defaultString: 'Generate Objy Embedded Types as Attribute')) #(#RadioButtonSpec #layout: #(#LayoutOrigin 0 0.0668103 0 0.378378) #model: #objyTypeAttributeMode #label: #(#UserMessage #key: #none #defaultString: 'None') #select: #none) #(#RadioButtonSpec #layout: #(#LayoutOrigin 0 0.258621 0 0.371622) #model: #objyTypeAttributeMode #label: #(#UserMessage #key: #primTypes #defaultString: 'Primitive Types Only') #select: #primTypes) #(#RadioButtonSpec #layout: #(#LayoutOrigin 0 0.653017 0 0.371622) #model: #objyTypeAttributeMode #label: #(#UserMessage #key: #allTypes #defaultString: 'All Objy Types') #select: #allTypes) #(#ActionButtonSpec #layout: #(#LayoutFrame 0 0.814655 0 0.702703 0 0.93319 0 0.780405) #model: #backToDefault #label: #(#UserMessage #key: #backToDefault #defaultString: 'reset') #defaultable: true))))! ! !RoseObjyVariableTypeFinderSettingGUI class methodsFor: 'factory'! myFinderClass "Copyright(C) 1997 Masashi Umezawa All Rights Reserved" ^RoseObjyVariableTypeFinder! ! RoseObjyVariableTypeFinder initialize!