" Module: AKG-VMSFILE.ST Date: 22-Nov-1990 Version: 2.02-00 This module provides faster file IO for VMS systems. The default GNU file IO is character oriented, which runs abysmally on VMS. Using this interface can speed up a program by up to a factor of 8. " " | Change Log | ============================================================================ | Author Date Change | ALISTAIR 8 Apr 91 V2.02-00 | Added class nl method. | | ALISTAIR 18 Jan 91 V2.00-02 | Changed storeString to printString in Object print | method. Makes output more readable. | | ALISTAIR 18 Jan 91 V2.00-01 | Commented out cr in nl and nl:. | Trying to get rid of spurious ^M's when editing the | results. | | ALISTAIR 17 Jan 91 V2.00-00 | Added nl and nl: methods. | | ALISTAIR 26 Nov 90 Fixed bug in print: method. fprintf:string: was | undefined. | | ALISTAIR 22 Nov 90 Tested for class string in method print. | " Object subclass: #VMSfile instanceVariableNames: 'fileId leftMargin' classVariableNames: 'cr lf ff' poolDictionaries: '' category: nil. ! !VMSfile class methodsFor: 'creation'! putStdOut: aString ((self printf: aString) = -1) ifTrue: [ ^self error: 'VMSfile: putStdOut failed' ]. ^self ! nextPut: aChar ((self putCh: aChar) = -1) ifTrue: [ ^self error: 'VMSfile: putCh failed' ]. ^self ! nl " self nextPut: cr. " self nextPut: lf. ! open: aString mode: aMode | newObj | newObj := super new. newObj setOpen: aString mode: aMode. ^newObj ! initClass cr := Character value: 13. ff := Character value: 12. lf := Character value: 10. !! !VMSfile methodsFor: 'using'! setOpen: aString mode: aMode fileId := self open: aString mode: aMode. ^self ! print: aString ((self fprintf: fileId string: aString) = -1) ifTrue: [ ^self error: 'VMSfile: print failed' ]. ^self ! nextPut: aChar self printChar: aChar file: fileId. ^self ! nl " self nextPut: cr. " self nextPut: lf. (leftMargin notNil) ifTrue: [self print: leftMargin]. ! nl: count 1 to: count do: [ " self nextPut: cr. " self nextPut: lf. ]. (leftMargin notNil) ifTrue: [self print: leftMargin]. ! ff self nextPut: ff. (leftMargin notNil) ifTrue: [self print: leftMargin]. ! close ^self fclose: fileId ! atEnd ((self feof: fileId) = 0) ifTrue: [^false] ifFalse: [^true] ! nextLine | status | ^self nextLine: fileId !! !Object methodsFor: 'printing'! print (self class = String) ifTrue: [ VMSfile putStdOut: self ] ifFalse: [ VMSfile putStdOut: self printString ] ! printNl self print. VMSfile nextPut: (Character value: 13). VMSfile nextPut: (Character value: 10). !! | dynfun | dynfun := VmsDynamicFunction new. dynfun addLibrary: 'AKG_VMSFILE'. dynfun defineExternFunc: 'closeFile' withSelectorArgs: 'fclose: anInt' forClass: VMSfile returning: #int args: #(int). dynfun defineExternFunc: 'nextLine' withSelectorArgs: 'nextLine: fileIdent' forClass: VMSfile returning: #string args: #(int). dynfun defineExternFunc: 'openFile' withSelectorArgs: 'open: aString mode: aMode' forClass: VMSfile returning: #int args: #(string string). dynfun defineExternFunc: 'putStdOut' withSelectorArgs: 'printf: aString' forClass: VMSfile class returning: #int args: #(string). dynfun defineExternFunc: 'putLine' withSelectorArgs: 'fprintf: aFile string: aString' forClass: VMSfile returning: #int args: #(int string). dynfun defineExternFunc: 'putCh' withSelectorArgs: 'putCh: aChar' forClass: VMSfile class returning: #int args: #(char). dynfun defineExternFunc: 'atEnd' withSelectorArgs: 'feof: fileIdent' forClass: VMSfile returning: #int args: #(int). dynfun clearLibraries. dynfun addLibrary: 'VAXCRTL'. dynfun defineExternFunc: 'fputc' withSelectorArgs: 'printChar: aChar file: fileIdent' forClass: VMSfile returning: #int args: #(char int). VMSfile initClass. !