Trailing-Edge
-
PDP-10 Archives
-
decuslib10-11
-
43,50530/scn.mac
There are 2 other files named scn.mac in the archive. Click here to see a list.
title PASSCN - SCAN interface for PASCAL programs
;Note: This file is a prototype. Some tables and routines will need
;to be changed to fit your application. Hopefully the file is self-
;explanatory.
;page 1 of this file contains the two routines ISCAN and TSCAN, which
;actually scan the command line. These routines are more or less the
;same for all applications. Only some table entries change, as shown
;below. The things you will want to change are put near the beginning
;of the page.
;page 2 of this file contains prototypes for routines to actually open
;the files. These routines should be written by the user. There will
;need to be one routine for each file to be openned. Note that the
;examples supplied here are sufficiently general that normally you will
;only need to delete unwanted code (as the examples have all possible
;bells and whistles) and change a few SIXBIT constants for default
;names, extensions, etc. Again, the routines you need to worry about
;have been put at the beginning of the page
;page 3 of this file contains prototypes for routines that use WILD.
;You may safely delete page 3 (except the END statement) if you don't
;intend to use WILD. If you use only things on page 3, the example
;routines (OPENIN and OPENOU) may be deleted from page 2, but the
;various low level routines on page 2 are also used by the WILD
;package.
search macten,uuosym,scnmac
.request rel:scn7bx,rel:helpx
t0=0
t1=1
reg=2
reg1=3
reg2=4
reg3=5
reg4=6
reg5=7
reg6=10
p=17
.lklen==20 ;length of our extended lookup/enter blocks
FILPTR= 0 ;LH = FUNNY BUSINESS IF WE ARE DOING STRING I/O:
; BIT 0 IS ALWAYS ON FOR STRING I/O
; REST OF WORD IS LMAX FOR THE ARRAY
;FOR A FILE, LH=ERROR CODE IF REWRITE/RESET FAILS
FILEOF= 1 ;input: 0 = normal state
; 1 = eof or error - no more data in file (some
; errors will allow reading to continue, and
; thus will NOT set FILEOF)
;output:1 = normal state
; 0 = error (but program will abort so this will
; never show up)
FILEOL= 2
FILERR= 3
FILLKP= 4
FILENT= 5
FILIN= 6
FILOUT= 7
FILCLS=10
FILSTA=11 ; .+0 FOR FILESTATUS
FILDEV=12 ; .+1 FOR DEVICE
FILBFP=13 ; .+2 FOR POINTER TO BUFFERHEADER
FILNAM=14
FILEXT=15
FILPRO=16
FILPPN=20
FILBFH=26 ;BUFFER HEADER
FILBTP=27 ;BYTE POINTER
FILBTC=30 ;BYTE COUNT IN BUFFER
FILLNR=31 ;IF ASCII MODE - LINENR IN ASCIICHARACTERS
FILCNT=32 ;LH= if non-text file: neg. number of words in comp.
; if text file: zero
;test sign bit of this loc to see if an ASCII file
;RH= ADDRESS OF FIRST WORD IN COMPONENT
FILCMP=33 ;FIRST WORD OF COMPONENT
twoseg
reloc 400000
;here begin the magic blocks that you may want to edit
comnds: sixbit /FOO/ ;table of monitor commands this program processes
sixbit /BAR/
iblk: iowd 2,comnds ;length of comnds list, comnds
xwd %cclsw##,'FOO' ;RH=name of CCL or tmpcore file
reloc 0
retblk:: ;tscan returns a pointer to this block. Your PASCAL
;program will consider it a record with an entry for each
;possible switch. There should be one entry here for
;each switch.
asw: exp 0 ;These values don't matter
bsw: exp 0
csw: exp 0
reloc
define swtchs< ;This is the definition of the switches. It uses macros
;from SCNMAC. We will not document them here.
sn *A,asw,fs.nue
sn *B,bsw,fs.nue
sn *C,csw,fs.nue
>
clrans: ;This routine will be called before scanning each line. It
;should usually set all the switch values to -1, which is a
;special value that SCAN uses as a code to indicate that nothing
;has been typed yet. You should see to it that there is a
;SETOM for each location in retblk, unless you are dealing with
;wierd switch types. (Some should be set to 0 instead.)
setom asw
setom bsw
setom csw
setzm firsti ;from here we do reinitialing that you needn't
setzm firsto ;understand
move t1,oldff
movem t1,.jbff##
popj p,
defans: ;This routine is called after all switch values have been scanned.
;It should check all of the locations in retblk. If any is still
;-1, it should be given a default value (unless you like -1).
;Note that PASCAL assumes that Booleans are 0 for false, 1 for true.
seto t0, ;t0 gets -1, as it will be compared to the switches
movei t1,1 ;t1 gets 1, for ease in setting things to 1
camn t0,asw ;is asw still -1?
setzm asw ;yes - default it to 0
camn t0,bsw ;is bsw still -1?
movem t1,bsw ;yes - default it to 1
came t0,csw ;is csw still -1?
jrst .+3 ;no - skip defaulting
movei reg,100 ;yes -default it to 100 octal
movem reg,csw
popj p,
;This ends the section that most users will need to redefine. There
;are also a couple of things in tblk and oblk that you might want to
;play with, but probably not.
doscan(passw) ;defines symbols passwx - a macro in SCNMAC
tblk: iowd passwl,passwn
xwd passwd,passwm
xwd 0,passwp
exp -1 ;or sixbit /name/ to define file name for /HELP
;-1 to use name of prog from GETTAB
xwd clrans,0
xwd allin,allout
exp 0
exp 0 ;allows only one output file spec.
;use exp 1b18 to allow .gt. 1
;but if you turn on 1b18, it will require a =
exp 0
oblk: iowd passwl,passwn
xwd passwd,passwm
xwd 0,passwp
exp -1 ;as above
exp 0 ;or sixbit /option/ to define SWITCH.INI line
;0 to use name of progm from GETTAB
;function iscan:integer
;Must be done once only, before doing tscan, etc. Returns index in
;comnds for monitor command typed, if any.
iscan:: movsi t1,2 ;length of block
hrri t1,iblk
pushj p,.iscan##
movem t1,1(p) ;returned value goes in 1(p) for PASCAL
popj p,
;function tscan:retblkptr
;Must be done once for each command line. Returns pointer to a
;record containing values of switches. retblkptr must be defined
;as ^retblk, where retblk is a record (not packed) whose definition
;matches the structure of retblk, above.
;File names are put in scan blocks, which are put in one contiguous
;part of the HEAP (i.e. NEW is used to allocate the space. Thus
;to save on core, you should do mark and release at the beginning
;and end of the main loop of your program.
;You must not do release and expect the scan blocks to still be there!!
;FSCAN will not known that you have done that, and as likely as not
;will return garbage.
tscan:: setzm firsti ;sign that no input file spec seen
setzm firsto ;ditto, output
move t1,.jbff## ;we put scan blocks at .jbff, temporarily, so
movem t1,oldff ; we will want to restore old .jbff at the end, to
; return that space
movsi t1,10 ;length of tblk
hrri t1,tblk
pushj p,.tscan##
movsi t1,5 ;length of oblk
hrri t1,oblk
pushj p,.oscan##
pushj p,defans ;user's routine to give default values for switches
;that are still -1
;We now have the scan blocks at .jbff. We want to move them to the heap, so
;That the space is recoverable (by release). Then we restore the original
;.jbff, which reclaims the temporary storage (though we don't release the
;core -- sorry, folks)
move t1,firsti ;skip to noin if no input blocks to move
jumpe t1,noin
move reg,lasti ;reg _ length of input blocks
addi reg,.fxlen ; we now have addr of end of last block+1
sub reg,t1 ; now have length
push p,reg ;new will lose this, and we want it for later
pushj p,new## ;get space of this length on heap
;reg is set to first location of the block
pop p,t1 ;length of block
addi t1,-1(reg) ;t1 _last location in block on heap
hrl reg,firsti ;reg _ firsti,,first location in heap
hrrzm reg,firsti;update firsti to point into heap
blt reg,(t1) ;now blt from .jbff area to heap
subi t1,.fxlen-1;t1 _ begin. of last block (in heap)
hrrzm t1,lasti ;that becomes new lasti
noin: move t1,firsto ;now we to the same for output blocks, if any
jumpe t1,noout
move reg,lasto
addi reg,.fxlen
sub reg,t1
push p,reg
pushj p,new##
pop p,t1
addi t1,-1(reg)
hrl reg,firsto
hrrzm reg,firsto
blt reg,(t1)
subi t1,.fxlen-1
hrrzm t1,lasto
noout: move t1,oldff ;restore .jbff, since finished with temp storage
movem t1,.jbff##
movei t1,retblk ;this is return pointer for PASCAL caller
movem t1,1(p)
setzm wptr ;tell wild we are restarting
popj p,
;allin and allout are called by .tscan when it needs a place to put a
;scan block. They return the address in t1, length in reg. They just
;put it at .jbff and update .jbff. If this should overlap the heap,
;the NEW above will catch it, since .jbff is properly updated.
allin: move t1,.jbff## ;next location to use
skipn firsti ;see if firsti set up
movem t1,firsti ;no - do so
movem t1,lasti ;this is last input so far
;from here on we have common code for allin and allout
allall: move t0,t1 ;compute location for next time
addi t0,.fxlen ;length of a scan block
movem t0,.jbff##
subi t0,1 ;end of this block
camg t0,.jbrel##;see if memory exists
jrst all1 ;yes
core t0, ;no - get it
halt .
all1: movei reg,.fxlen ;length of block
;t1 already has its address
popj p,
allout: move t1,.jbff## ;as above, but for output
skipn firsto
movem t1,firsto
movem t1,lasto
jrst allall ;now go to common section
reloc
firsti: z
lasti: z
firsto: z
lasto: z
oldff: z
wptr: z ;pointer to scan block currently in use by WILD
reloc
;The following routine is an example of a routine to open an input
;file. It supplies defaults for anything that is missing (except
;the path - SCAN defaults that to your default path, which seems to
;be what one wants). If the user does not type an extension, we
;first try the default extension. If there is no such file, we then
;try a null extension. We call ANALYS, so an appropriate error
;message is printed if the lookup fails. However the user must still
;examine EOF and realize that he will have to ask for another command
;line if EOF is true, since that means there was no such file.
; (NB: If the file exists but is empty, i.e. is of zero length,
;EOF will still be set initially. If it is desired to be able to
;handle zero-length files, the implicit get should be surpressed,
;as explained below. Then EOF will be set if and only if the file
;does not exist. However then the user will have to do an explicit
;GET after checking EOF.)
;procedure openin(f:text);
;The file will appear in REG
openin::movei t1,1 ;This specifies the first file spec on
;the input side. -1 is the first spec on
;the output side.
pushj p,getscn ;returns addr of scan block in t1
jrst noinsp ;no input spec typed
move t0,.fxmod(t1) ;word of useful bits from the scan block
;Delete the following code if you don't want to define a default device.
;If you delete it SCAN will supply DSK for you
move reg1,[sixbit /DEFDEV/] ;default device
tlne t0,(fx.ndv) ;user supplied no device?
movem reg1,.fxdev(t1) ;yes - use our default
;Delete the following if you don't want to define a default file name.
move reg1,[sixbit /DEFNAM/] ;default file name
skipe .fxnam(t1) ;user supplied name?
jrst .+3 ;yes - use his
movem reg1,.fxnam(t1) ;no - use ours
setom .fxnmm(t1) ;and specify no wildcards in it
;Delete the following if you don't want to define a default extension.
hrloi reg1,'DEF' ;default extension - no wildcards
tlne t0,(fx.nul) ;user typed one?
movem reg1,.fxext(t1) ;no - use ours
;The following code should always be present.
movei reg1,0 ;I/O mode - use this for ASCII, 16 for binary
movem reg1,filsta(reg)
setzm xbloc1+1 ;clear extended lookup block
move reg1,[xwd xbloc1+1,xbloc1+2]
blt reg1,xbloc1+.lklen
movei reg1,xbloc1 ;address of extended lookup block for this file
pushj p,initfi ;t1 - addr of scan block
jrst oiwld ;reg - addr of file control block
;reg1 - addr of extended lookup block
;sets up the lookup block and file control block according to
;the file spec in the scan block
agn: setzb reg1,reg2 ;here we set up the args for the PASCAL open
setz reg3, ;use seto reg3, to surpress implicit GET
movei reg4,xbloc1
movei reg5,4 ;number of I/O buffers. Typically you will
;use 0 - which gives you default number
move reg6,filsta(reg)
;The following push's and pop's are needed only if you want to retry with
;null extension if defaulted extension is not found. (See below.)
push p,t1
push p,reg
pushj p,resetf## ;Use resetf,rewrit, or update as appropriate
pop p,reg
pop p,t1
skipn fileof(reg) ;Did we find the file?
popj p, ;yes - return
;The following code analyses the error and retries with a null extension
;under the following conditions: (1) The user did not supply an extension
;(2) We did supply a default extension. If you don't default the extension
;all you need at this point is
; pjrst analys##
;Which will print an error message and return to the user.
hlrz t0,(reg) ;get the error code
skipn t0 ;something other than file not found?
skipn filext(reg) ;or null extension used (i.e. 2nd time around)
pjrst analys## ;just print message and return
move t0,.fxmod(t1) ;get bits from scan block
tlnn t0,(fx.nul) ;user defaulted extension?
pjrst analys## ;no - no need to retry
setzm filext(reg) ;yes - try null extension
jrst agn
oiwld: ;here if input spec has wild cards in it
outstr [asciz /
? Wild card in input file spec
/]
jrst oierr
noinsp: ;here if no input spec typed
outstr [asciz /
? No input file spec given
/]
oierr: movni t0,10
movem t0,fileof(reg) ;set EOF so the user knows it failed
popj p,
reloc
xbloc1: exp .lklen ;length of the extended lookup block
block .lklen ;the block itself
reloc
;The following routine is for openning a file whose defaults come from
;another file spec. Typcially this would be an output file. Note that
;this is appropriate for the output file of a compiler, etc., where
;wild is not used. If wild cards appear in the file specs, a different
;routine using the secondary wildcard logic (which is in WILD) should
;be used. Note that I do not show how to default the path or the device
;from the input, as this is not normally done in this context. To do
;it correctly would require using the PATH. UUO on the input channel
;to get the path, and getting the logical device from the input lookup
;block. Again, the user should check EOF after calling this function
;to see whether it worked. (For an output file, EOF will be true
;if it worked.) We print the error message if it fails, but the
;user will have to see that another command line is gotten.
;procedure openout(f:text);
;the address of the file control block will be in REG
openou::movni t1,1 ;first file on the output side
pushj p,getscn ;returns scanblock addr in t1
jrst defblk ;no spec typed - use default
gotdef: move t0,.fxmod(t1) ;get bits from scan block
;Delete the following code if you don't want to default the device
move reg1,[sixbit /DEFDEV/] ;default device
tlne t0,(fx.ndv) ;did he supply one?
movem reg1,.fxdev(t1) ;no - use default
;Delete the following code if you don't want to default the file name
move reg1,xbloc1+.rbnam ;input file name
;following two instructions needed only if you don't
;default the input name.
skipn reg1 ;is there one?
move reg1,[sixbit /DEFNAM/] ;no - use fixed default
skipe .fxnam(t1) ;user supplied output file name?
jrst .+3 ;yes - use it
movem reg1,.fxnam(t1) ;no - use default
setom .fxnmm(t1) ;and note that no wildcards
;Delete the following code if you don't want to default the extension
;Usually you will use only one of the following two methods of
;defaulting.
hllo reg1,xbloc1+.rbext ;input file extension finally used
tlnn reg1,777777 ;is there any?
hrloi reg1,'DEF' ;no - use fixed default
tlne t0,(fx.nul) ;user supplied output file extension?
movem reg1,.fxext(t1) ;no - use default
;Delete the following code if you don't want to default the protection.
;This code uses the protection of the input file as the default. To
;use a fixed default, replace it with
; movei reg1,055 ;default protection.
;or movei reg1,0 for the system default protection (the usual case)
ldb reg1,[point 9,xbloc1+.rbprv,8] ;input file protection
move t0,.fxmom(t1) ;bits from output file spec scan block
trne t0,fx.pro ;protection specified?
jrst .+4 ;yes - use his
dpb reg1,[point 9,.fxmod(t1),35] ;no - use default
tro reg1,777
dpb reg1,[point 9,.fxmom(t1),35] ;and show we did so
;Delete the following code if you don't want to default the version
;number. To use a fixed default, use move reg1,[xxx] instead of
;the first instruction below
move reg1,xbloc1+.rbver ;use input version number as default
move t0,.fxver(t1) ;look at user's specified version no.
camn t0,[-1] ;did he set it?
movem reg1,.fxver(t1) ;no - use this one
;Delete the following code if you don't want to default the estimated
;file length from the length of the input. Actually this is a fairly
;unusual thing to do, though SOS does it.
move reg1,xbloc1+.rbsiz ;use input length as estimate
skipge .fxest(t1) ;unless user specified one
movem reg1,.fxest(t1)
;The following code should always be used
movei reg1,0 ;mode - 0 for ascii, 16 for binary
movem reg1,filsta(reg)
setzm xbloc2+1 ;clear enter block
move reg1,[xwd xbloc2+1,xbloc2+2]
blt reg1,xbloc2+.lklen
movei reg1,xbloc2
pushj p,initfi ;set up xtended enter block etc.
jrst oowld ;wild card in the spec - can't handle it
setzb reg1,reg2
ldb reg3,[point 9,filpro(reg),8] ;or movei reg3 protection if
;want to used a fixed value
movei reg4,xbloc2
movei reg5,4 ;number of buffers. Usually use 0,
;which gives default
move reg6,filsta(reg)
pushj p,rewrit## ;or resetf or update
pjrst analys ;print error if any and return to user
oowld: outstr [asciz /
? Wildcard in output file spec
/]
setzm fileof(reg) ;set error indicator
popj p,
defblk: ;here if no output spec typed. Use default scan block
move t0,[xwd nulpro,nulblk]
blt t0,nulblk+.fxlen-1
movei t1,nulblk
jrst gotdef
reloc
nulblk: block .fxlen
reloc
nulpro: sixbit /nul/ ;prototype for the default block
block 3
exp 600000000000
exp 607000000000
block 14
repeat 10,<exp -1>
reloc
xbloc2: exp .lklen ;length of block
block .lklen
reloc
;The following routines are used by the code above. You will not
;need to modify them (or even understand them).
getscn: ;serial number of file spec in t1. +n for nth input spec
;-n for nth output spec. Return addr of scan block in t1.
;skip return if find the specified file spec
;non-skip return if not enough typed (or t1=0)
;t0=last block user typed
;t1=counter for how many spec's . Count down to 0
;reg=spec being looked at now
;reg1=working reg
push p,reg
push p,reg1
cain t1,0 ;0 is illegal
jrst nospec
jumpge t1,getin ;see if input or output
move reg,firsto ;here for output
jumpe reg,nospec
move t0,lasto
jrst getio
getin: move reg,firsti ;here for input
jumpe reg,nospec
move t0,lasti
getio: movm t1,t1 ;turn t1 into positive count
soje t1,getgot ;if 1, want the first spec
getlop: camn reg,t0 ;need another spec
jrst nospec ;this is last - not enough
addi reg,.fxlen ;go to next one
move reg1,.fxmod(reg) ;look at funny bits in the new spec
tlne reg1,(fx.trm) ;is it 'and', etc.?
jrst getlop ;yes - it doesn't count as a new spec
sojg t1,getlop ;got new spec - go for more if counter isn't to zero
getgot: move t1,reg ;have desired spec - get it in return reg
pop p,reg1
pop p,reg ;and restore ac's
aos (p) ;good retur
popj p,
nospec: pop p,reg1 ;return if no such spec
pop p,reg ;may be error, or may just use a default
popj p,
initfi: ;reg=addr of PASCAL file control block
;t1=addr of scan block
;reg1=addr of lookup/enter block
;sets up PASCAL file control block and lookup block
;given a scan block that has been defaulted
;skip return if successful
;non-skip return if not (means there were wildcards
; in the file spec)
aos (p) ;assume successful return
push p,reg
push p,t1
push p,reg1
hrli t1,.fxlen ;length of scan block
movei reg,filsta(reg) ;open block
hrl reg1,(reg1) ;length of lookup/enter block
movei reg2,pathbl ;place to put path
pushj p,.stopb## ;converts scan block
sos -3(p) ;wildcards in file spec
pop p,reg1
pop p,t1
pop p,reg
;alternate entry to put stuff from the lookup block into
;the PASCAL file control block. Used when WILD has done
;the main conversion. Always returns non-skip.
cvblk: move t0,.rbnam(reg1) ;move other stuff from lookup block into
movem t0,filnam(reg) ; file control block
move t0,.rbext(reg1)
hllzm t0,filext(reg)
hllz t0,.rbprv(reg1)
tlz t0,777
movem t0,filpro(reg)
move t0,.rbppn(reg1) ;ppn or path pointer
caie t0,0 ;if zero
tlne t0,777777 ;or non-zero LH
jrst cvblk1 ;then it's simple
addi t0,2 ;else pointer - here is path
hrl t0,t0 ;now make it the source
hrri t0,filppn(reg) ;here is where path goes
blt t0,filppn+5(reg) ;now move it
popj p,
cvblk1: movem t0,filppn(reg) ;if simple ppn, put it there
setzm filppn+1(reg) ;and clear next so no SFD's
popj p,
reloc
pathbl: block 9
reloc
.request rel:wld7b
;The routine WILDIN is an example of a procedure for handling
;a list of files with wildcards and looking them all up. Each time
;you call WILDIN it will open a new file. It will return TRUE as
;long as there was another file. FALSE means you have come to the
;end of the list. Note that a return of TRUE does not necessarily
;mean that the lookup succeeded. You must still check EOF to be
;sure of that. However, if there was any trouble this routine has
;already printed an error message, so in most cases you just go on
;to the next file. There is little defaulting done in this routine.
;The only change you are likely to want to make is to modify it
;to read only one file spec instead of the whole input side, but even
;that doesn't seem likely. If you want a default device other than
;DSK:, you can mimic the code from OPENIN, above. Also, you will have
;to change a movei near the beginning if you want some I/O mode other
;than 0, and the stuff near the RESETF if you want other options for
;the RESET. (Note that here I specify 4 buffers. You may prefer to
;use zero, which gives the monitor default.)
;function wildin(f:text):Boolean;
;The file will appear in reg
wildin::move t1,firsti ;wild needs to know which scan blocks to use
;here we will say all on the input side
jumpe t1,widon ;none - treat it as an empty list
movem t1,wfirst
move t1,lasti
movem t1,wlast
;alternatively, if you wanted just one file spec, you would use
; movei t1,1 ;first file spec on the input side
; pushj p,getscn
; jrst widon
; movem t1,wfirst ;addr of scan block for that file spec
; setzm wlast ;a zero means use just one file spec
movei t1,filsta(reg)
hrlm t1,wblk+1 ;tell WILD where the OPEN block is
push p,reg ;because of loop below
wiagn: pop p,reg
movei t1,0 ;I/O mode
movem t1,filsta(reg) ;put it in the open block - must be done
setzm wxblk+1 ;clear lookup block
move t1,[xwd wxblk+1,wxblk+2]
blt t1,wxblk+.lklen
move t1,[xwd 5,wblk] ;each time, as WILD may change it
push p,reg
pushj p,.lkwld##
jrst widon-1 ;here if no more files
pop p,reg
movei reg1,wxblk ;extended lookup block
pushj p,cvblk ;puts the info WILD set up in the PASCAL file
setzb reg1,reg2 ;now we set up for the RESET
setz reg3, ;use seto reg3, to suppress the implicit GET
movei reg4,wxblk
movei reg5,4 ;number of buffers - 0 for default
move reg6,filsta(reg)
pushj p,resetf## ;open and lookup the file
skipe fileof(reg) ;worked?
jrst wilker ;no - analyse the error
push p,reg
pushj p,.chktm## ;yes - see if OK with /SINCE, etc.
jrst wiagn ;no - try the next one
pop p,reg
setom 1(p) ;yes - successful return
popj p,
wilker: hlrz t0,(reg) ;here if RESET failed. Get cause
movei t1,analys## ;The default error analyzer
cain t0,^D101 ;open failed
movei t1,e.dfo## ;WILD's open failure printer
caige t0,^D100 ;lookup failed
movei t1,e.dfl## ;WILD's lookup failure printer
pushj p,(t1)
setom 1(p) ;Successful return (there was a file)
popj p,
pop p,reg ;entry for when reg was saved
widon: setzm 1(p) ;here when no more files - return false
setom fileof(reg) ;and set end of file
popj p,
reloc
wblk: xwd wfirst,wlast
xwd 0,wxblk
xwd .fxlen,.lklen ;length of lookup block below
xwd 440000,wptr
0
wxblk: exp .lklen ;extended lookup block
block .lklen
wfirst: z
wlast: z
reloc
;The following is a routine for handling "secondary" files, i.e. files
;whose names are a function of the input file name. For example in
;the command *.doc=*.rno the .doc file is secondary to the .rno files.
;For each .rno file we produce a (hopefully) different .doc file.
;Thus this routine takes two inputs: The file spec for the secondary
;file (*.doc in this case) and that for the primary file that is to be
;the source of the names. Note that this routine is connected to the
;one above directly, in that it knows about the lookup block that WILDIN
;uses. It would not really be necessary to do any defaulting here, but
;most people don't like the way WILD handles wildcards in secondary files.
;One is accustomed to saying DSKB:=*.sai. This turns into DSKB:*.*=*.sai,
;which gives an error message because there are more wildcards on the
;left than on the right. As a convenience, I supply a defaulter below
;that simply copies the input spec into the output when no file name or
;extension is given. I also tell you how to supply a default extension
;for the output, which is useful in many applications. You can tell
;whether this routine succeeded by looking at EOF. It will be true
;(since this is for output) if the thing succeeds. An error message
;will be printed if anything goes wrong.
;procedure wildou(secondary,primary:text);
;the primary file will be in reg1, secondary in reg1. Note that it is
;the secondary that is actually being openned. The primary is merely
;the source of defaults.
wildou::movni t1,1 ;use the first spec on the output side
push p,reg1
pushj p,getscn ;returns addr of scan block in t1
movei t1,nulpro ;if none there, use default block
;The following code establishes various defaults. It may be completely
;skipped if you like. The thing just below with the BLT should be used
;if any defaulting is done, so that the original scan block is not
;changed, but rather a copy is used.
hrl t1,t1 ;source of copy
hrri t1,nulblk ;this is an empty place to copy it to
blt t1,nulblk+.fxlen-1 ;now copy it
movei t1,nulblk ;now we use the copy
move reg1,wptr ;this is the scan block currently being
;used by wild, and is the source for
;some of the defaults.
move t0,.fxmod(t1) ;the usual word of bits from scan block
;delete the following if you don't want to default the device
move reg2,[sixbit /DEFDEV/]
tlne t0,(fx.ndv) ;did he specify device?
movem reg2,.fxdev(t1) ;no - use default
;delete the following if you don't want to copy the input spec as default
;for name. Of course you could also have a fixed default name as with
;OPENOU above, but you normally wouldn't use wild to handle that.
skipe .fxnam(t1) ;name specified?
jrst .+5 ;yes - use it
move reg2,.fxnam(reg1) ;no - copy from input scan block
movem reg2,.fxnam(t1)
move reg2,.fxnmm(reg1) ;mask word
movem reg2,.fxnmm(t1)
;delete the following if you don't want to copy the input spec as default
;for extension.
tlnn t0,(fx.nul) ;extension specified?
jrst .+5 ;yes - use it
move reg2,.fxext(reg1) ;input spec
skipn reg2 ;is it null?
hrlzi reg2,'* ' ;yes - must use this on output to match
movem reg2,.fxext(t1)
;or to use a fixed default extension you would use the following code
; hrloi reg2,'DEF'
; tlne t0,(fx.nul)
; movem reg2,.fxext(t1)
;delete the following if you don't want to use the input version number
;as default.
move reg2,wxblk+.rbver ;version no. of input file
move t0,.fxver(t1) ;his version no. spec
camn t0,[-1] ;default?
movem reg2,.fxver(t1) ;yes - use input instead
;delete the following if you don't want to use the input length as an
;estimate of the output file length. This is fairly unusual.
move reg2,wxblk+.rbsiz ;input file length
skipge .fxest(t1) ;specified anything?
movem reg2,.fxest(t1) ;no - use default
;The code following here is always used, whether defaulting or not.
movem t1,sfirst ;addr of secondary scan block
pop p,reg1 ;restore the PASCAL file block for pri. file
hrlm reg1,sblk+1
movei t0,0 ;I/O mode - this is ASCII
movem t0,filsta(reg)
movei t0,filsta(reg)
hrrm t0,sblk+1 ;store addr of OPEN block for WILD
setzm sxblk+1 ;clear enter block
move t1,[xwd sxblk+1,sxblk+2]
blt t1,sxblk+.lklen
move t1,[xwd 4,sblk]
push p,filbfp(reg) ;.scwld zeros this for us - nice, huh?
push p,reg
pushj p,.scwld## ;does all the wild card fixups
jrst woerr ;couldn't convert names somehow
pop p,reg
pop p,filbfp(reg)
movei reg1,sxblk ;now we convert to PASCAL file block
pushj p,cvblk
setzb reg1,reg2 ;prepare for REWRITE
ldb reg3,[point 9,filpro(reg),8] ;or movei reg3,0 for monitor default
movei reg4,sxblk
movei reg5,4 ;no. of buffers. 0 for monitor default
move reg6,filsta(reg)
pushj p,rewrit##
skipe fileof(reg) ;did it work?
popj p, ;yes
hlrz t0,(reg) ;no - find cause
cain t0,^D101 ;OPEN failed
pjrst e.sco## ;wild's open failure printer
caige t0,^D100 ;ENTER failed
pjrst e.scl## ;wild lookup failure printer
pjrst analys## ;otherwise use normal printer
woerr: pop p,reg ;here if problem with wildcards
pop p,filbfp(reg)
setzm fileof(reg) ;tell him it didn't work
popj p,
reloc
sblk: xwd wptr,sfirst
0
xwd wxblk,sxblk
xwd 0,.lklen ;length of lookup blocks
sxblk: exp .lklen ;extended enter block
block .lklen
sfirst: z
;Here follows a routine to print the name of the last file used
;on the TTY:. Note that it is potentially usable to print any
;file spec you might want to, just by changing a couple of
;instructions at the beginning. Also, should you need the name
;in a string, you could open a file on the string with strset,
;and then redefine SCANs character output routine to use
;PUTCH. This can be done by calling .TYOCH## See the SCAN
;listing.
;procedure typein;
typein::hrl t1,wptr ;source is the current block being
;used by WILD. This could be any
;SCAN block.
hrri t1,nulblk ;a convenient working space
blt t1,nulblk+.fxlen-1
movei reg,wxblk ;this is the lookup block being used
;by WILD. It could be any lookup
;block, so long as it was used with
;the SCAN block loaded above.
skipn t1,.rbdev(reg) ;get real device
jrst .+7 ;none - use what we have
movem t1,dcblk ;this is physical name - get logical
move t0,[xwd 5,dcblk] ;using dskchr
dskchr t0,uu.phy
movem t1,dcblk+4 ;not a disk - use what we have
move t1,dcblk+4
movem t1,.fxdev+nulblk
skipe t1,.rbnam(reg) ;get real name found
movem t1,.fxnam+nulblk ;and use it
hllz t1,.rbext(reg) ;get real extension
movem t1,.fxext+nulblk
move t1,.rbppn(reg) ;see if we have a better PPN
tlne t1,-1
movem t1,.fxdir+nulblk ;yes - use it
tlne t1,-1
setom .fxdir+1+nulblk ;say no wildcards
movei t1,nulblk ;arg for routine
pjrst .tfblk## ;part of SCAN
dcblk: block 5 ;block for dskchr
end