" Module: VmsDynamicFunction.St Author: A. Grant Date: 8-Nov-1990 This module allows SmallTalk to dynamically link to shareable images on VMS systems. To add a function :- 1. Create an instance of VmsDynamicFunction. 2. Load the list of shareable images to search with addLibrary:. 3. Define the function using defineExternFunc:withSelectorArgs:forClass:returning:args: Index :- addLibrary: anImageString Add the shareable image anImageString to the search list. This must be a simple file name with no directory or file type. By default the file type is '.EXE', and the directory 'SYS$SHARE:'. If a different file type or directory is required, define a logical name pointing to the image, and pass the logical name. clearLibraries Empty the search libraries. defineExternFunc: aFuncName withSelectorArgs: selector forClass: aClass returning: aReturnType args: argsArray The has the same affect as Behavior, except that the shareable image is linked in dynamically. See the documentation for Behavior. listLibraries List the search libraries on stdout. listLibrariesOn: aStream List the search libraries on aStream. new Create a new instance of VmsDynamicFunction. " " | Change Log | ============================================================================ | Author Date Change | ALISTAIR 22 Nov 90 Added clearLibraries method | " Object subclass: #VmsDynamicFunction instanceVariableNames: 'libraries' classVariableNames: '' poolDictionaries: '' category: 'Vms hacks' ! VmsDynamicFunction comment: 'The VMS version of DynamicLink (sort of) Version 1.02-00'! Behavior defineCFunc: 'vmsFindImageSymbol' withSelectorArgs: 'imageFile: fileNameString symbol: aString' forClass: VmsDynamicFunction returning: #int args: #(string string) ! !VmsDynamicFunction class methodsFor: 'creation'! new "Create a new instance of VmsDynamicFunction" | newInst | newInst := super new. ^newInst initialize !! !VmsDynamicFunction methodsFor: 'initialisation'! initialize "Initialise instance variables" libraries := OrderedCollection new. !! !VmsDynamicFunction methodsFor: 'library manipulation'! addLibrary: anImageString "add the shared image anImageString to the lookup list" ^libraries addFirst: anImageString ! clearLibraries libraries := OrderedCollection new. ! listLibrariesOn: aStream "List the libraries in the lookup list" | cr tab | cr := Character value: 13. tab := Character value: 9. 'Libraries...' printOn: aStream. cr printOn: aStream. libraries do: [ :libName | tab printOn: aStream. libName printOn: aStream. cr printOn: aStream ]. ^self ! listLibraries "Convenient version to stdout" | tab | tab := Character value: 9. 'Libraries...' printNl. libraries do: [ :libName | tab print. libName printNl. ]. ^self !! !VmsDynamicFunction methodsFor: 'method addition'! defineExternFunc: aFuncName withSelectorArgs: selector forClass: aClass returning: aReturnType args: argsArray "Add the function aFuncName as a method to class aClass using the selector selector." ((self loadFunction: aFuncName) isNil) ifTrue: [^self error: 'defineExternFunc: Cannot find symbol']. ^Behavior defineCFunc: aFuncName withSelectorArgs: selector forClass: aClass returning: aReturnType args: argsArray !! !VmsDynamicFunction methodsFor: 'private'! loadFunction: aString "Search the libraries for the funct aString" | status | libraries do: [ :libName | status := self imageFile: libName symbol: aString. (status = 1) ifTrue: [^aString] ]. ^nil !!