!TITLE Making a terminal locations file
!
! The program described in this section implements the MAKELOCS command,
! used   for   generating  a  file  which  describes  the  location  and
! characteristics of each terminal attached to the  network.   In  fact,
! the  characteristics of the terminal are held elsewhere: MAKELOCS just
! stores a unique number for each type of terminal.
!
!<Files used
!
! Currently,  four input files are required, and a single output file is
! produced.  In the descriptions given here, fields marked with  *  must
! be present, but are ignored.  The files are:
!
!<The PADs file
!
!     This  file  contains a line for each PAD in the network.  It gives
! the name of the PAD, and describes where the PAD may be found.
!
!     Each entry contains the following fields, separated by colons:
!
!     *PAD number    -  Line number of entry
!      PAD name      -  Name of PAD, up to 15 characters
!      PAD location  -  Where the PAD may be found
!
!>
!<The TTYs file
!
!     This file contains a line for each terminal in  the  network.   It
! describes  the type, building and location of each terminal, and gives
! much other information not needed here.
!
!     Each entry contains the following fields, separated by colons:
! 
!      PAD name      -  PAD to which the terminal is attached
!     *Line type     -  Multiplexer, PAD or interface type
!     *Hardware line -  Multiplexer port number or interface number
!      Line number   -  Unique line number of terminal on that PAD
!     *Line speed    -  Usually 'auto'
!     *Line interface-  Usually '20ma' or 'rs232'
!      Line status   -  Usually 'ok' or 'us' (null also means 'ok')
!      Last change   -  Date this entry was last altered
!      Local printer -  Nearest printer to the terminal
!      Terminal type -  Cryptic string (ignore part after comma)
!      Building      -  Building (or part) housing the terminal
!      Location      -  Identification of terminal within building
!>
!<The locations file
!
! This file contains a line  for  each  possible  PAD  location,  giving
! useful groupings of PADs.
!
!     Each entry contains the following fields, separated by colons:
!
!      Location A    -  All PADs in same building have the same number
!                       in this field
!      Location B    -  A number used to distinguish different PADs in
!                       the same building
!      Description   -  A string describing the location
!>
!<The mapping file
!
!     This file maps the cryptic terminal  type  names  to  the  numbers
! actually  stored  in  the  output file.  It contains one line for each
! mapping. Some mappings are one to one, and some are many to one.
!
!     Each entry contains the following fields, separated by colons:
!
!      Type name     -  The name found in the TTYs file
!      Type number   -  The number stored in the output file.
!>
!<The output file
!
! This  is  an  unstructured  data  file containing a compressed, easily
! accessed synopsis of the relevant information gleaned from  the  input
! files.   The  filename  '.'  causes  the  default  filename (currently
! TERMLOCFILE) to be used.
!>
!>
!<The MAKELOCS command
!
! This command is used to process the four input  files,  producing  the
! single output file.  It is called as follows:
!
!     MAKELOCS(padsfile,ttysfile,locationsfile,mappingfile,outputfile)
!
! If a parameter is omitted, a prompt is issued for it.  At any stage, a
! reply of ?  will cause a short help message to be output.
!
! The program outputs a small number of statistics during the run, which
! concern the number of items found in the input files.
!>
!***********************************************************************
!*
!*            Program to set up terminal locations database
!*
!*        Copyright R.D. Eager   University of Kent   MCMLXXXIII
!*
!***********************************************************************
!
!
!***********************************************************************
!*
!*          Constants
!*
!***********************************************************************
!
constantinteger  inchan = 1
constantinteger  ssdatafiletype = 4
constantstring (1) snl = "
"
constantstring (11) default termlocsfile = "TERMLOCFILE"
constantstring (85)array  params(1:5) = c 
"PADs file!Give the name of the file containing the names of all the PADs",
"TTYs file!Give the name of the file describing all the terminals",
"Locns file!Give the name of the file which describes all possible terminal locations",
"Map file!Give the name of the file which maps terminal names to types",
"Output file!Give the name of the new locations file to be built"
!
!
!***********************************************************************
!*
!*          Record formats
!*
!***********************************************************************
!
recordformat  fdf(integer  link,dsnum,byteinteger  status,accessroute,
                  valid action,cur state,byteinteger  mode of use,
                  mode,file org,dev code,byteinteger  rec type,flags,
                  lm,rm,integer  asvar,arec,recsize,minrec,maxrec,
                  maxsize,lastrec,conad,currec,cur,end,transfers,
                  darecnum,cursize,datastart,string (31) iden)
recordformat  hf(integer  dataend,datastart,filesize,filetype,sum,
                 datetime,format,mark,npads,padsoffset,nttys,
                 ttysoffset,nlocns,locnsoffset,sp0,sp1)
recordformat  rf(integer  conad,filetype,datastart,dataend)
!
recordformat  padf(string (15) name,string (31) location,
                   integer  maxline,linestart)
recordformat  ttyf(string (15) loclp,integer  type,string (31) building,
                   location)
recordformat  locnf(halfinteger  major,minor,string (31) building)
recordformat  mapf(string (15) stype,integer  ntype)
!
!
!***********************************************************************
!*
!*          Subsystem references
!*
!***********************************************************************
!
externalroutinespec  cherish(string (255) s)
systemroutinespec  connect(string (31) file,integer  mode,hole,
                           prot,record (rf)name  r,integername  flag)
systemroutinespec  define(integer  chan,string (31) iden,
                          integername  afd,flag)
systemroutinespec  disconnect(string (31) file,integername  flag)
systemstringfunctionspec  failuremessage(integer  mess)
externalintegerfunctionspec  instream
systemintegerfunctionspec  iocp(integer  ep,parm)
systemstringfunctionspec  itos(integer  n)
systemintegermapspec  mapssfd(integer  dsnum)
systemroutinespec  move(integer  length,from,to)
systemroutinespec  newgen(string (31) file,newfile,integername  flag)
systemstringfunctionspec  nexttemp
systemroutinespec  outfile(string (31) file,integer  size,hole,
                           prot,integername  conad,flag)
externalintegerfunctionspec  outstream
systemintegerfunctionspec  parmap
systemroutinespec  permit(string (31) file,string (6) user,
                          integer  mode,integername  flag)
externalroutinespec  prompt(string (255) s)
systemintegerfunctionspec  pstoi(string (63) s)
systemroutinespec  rename(string (31) file,newfile,integername  flag)
systemroutinespec  setpar(string (255) s)
externalroutinespec  set return code(integer  i)
systemroutinespec  setwork(integername  ad,flag)
systemstringfunctionspec  spar(integer  n)
externalstringfunctionspec  ucstring(string (255) s)
systemroutinespec  uctranslate(integer  ad,len)
!
!
!***********************************************************************
!*
!*          Service routines
!*
!***********************************************************************
!
routine  closestream(integer  chan)
! Private version of 'closestream'.  Does  not  give  an  error  if  the
! operation fails.
integer  flag
!
return  unless  instream # chan # outstream
flag = iocp(16,chan)
end ;   ! of closestream
!
!-----------------------------------------------------------------------
!
routine  clearstream(integer  chan)
! Clears  out  a  channel  definition, but does not give an error if the
! channel was not defined.
record (fdf)name  f
!
if  mapssfd(chan) # 0 then  start 
   f == record(mapssfd(chan))
   if  f_status = 0 then  start 
      mapssfd(chan) = 0
      f_dsnum = 0;                      ! Mark descriptor as free
   finish 
finish 
end ;   ! of clearstream
!
!-----------------------------------------------------------------------
!
integerfunction  findpad(string (15) name,integer  padsad,npads)
! Locates the record describing the PAD  called  'name',  returning  the
! address  of  that  record.  If no record exists for the specified PAD,
! zero is returned.
integer  i
record (padf)name  pad
!
uctranslate(addr(name)+1,length(name))
for  i = 1,1,npads cycle 
   pad == record(padsad)
   if  pad_name = name then  result  = padsad
   padsad = padsad + sizeof(pad)
repeat 
result  = 0
end ;   ! of findpad
!
!-----------------------------------------------------------------------
!
integerfunction  otoi(string (7) s)
! Converts the octal  number  described  by  's'  to  a  binary  number,
! yielding this number as a result.
integer  i,n
!
n = 0
for  i = 1,1,length(s) cycle 
   n = (n << 3)!(charno(s,i) - '0')
repeat 
result  = n
end ;   ! of otoi
!
!-----------------------------------------------------------------------
!
routine  readline(stringname  s)
! Reads a line from the currently selected input stream, into 's'.  Null
! lines are ignored, and end of file causes ".END" to be returned.
integer  c
!
on  event  9 start ;                    ! Trap 'Input Ended'
   s = ".END"
   return 
finish 
!
s = ""
cycle 
   cycle 
      readsymbol(c)
      exit  if  c = nl
      s <- s.tostring(c)
   repeat 
   while  length(s) # 0 and  charno(s,length(s)) = ' ' cycle 
      length(s) = length(s) - 1
   repeat 
   while  length(s) # 0 and  charno(s,1) = ' ' cycle 
      s = substring(s,2,length(s))
   repeat 
repeat  until  s # ""
end ;   ! of readline
!
!-----------------------------------------------------------------------
!
routine  getfile(integer  n,stringname  file)
! Obtains a filename from parameter 'n'.  If the parameter is null,  the
! filename  is  read  from  the currently selected input after prompting
! with a suitable prompt.  If the reply  '?'  is  given,  a  short  help
! message is given and the prompt is then re-issued.
string (15) pr
string (255) help
!
file = spar(n)
return  if  file # ""
!
params(n) -> pr.("!").help
cycle 
   prompt(pr.": ")
   readline(file)
   uctranslate(addr(file)+1,length(file))
   exit  unless  file = "?"
   printstring(help.snl)
repeat 
end ;   ! of getfile
!
!-----------------------------------------------------------------------
!
integerfunction  openfile(string (31) file)
! Opens  'file'  on  stream  'inchan'.   Yields a result code indicating
! success or failure.
integer  flag,afd
record (rf) rr
!
connect(file,1,0,0,rr,flag)
if  flag = 0 then  define(inchan,file,afd,flag)
if  flag = 0 then  selectinput(inchan)
result  = flag
end ;   ! of openfile
!
!-----------------------------------------------------------------------
!
routine  invalid(string (255) s,string (31) file,integer  line)
! Prints  an  error  message  about  an invalid line in one of the input
! files.
printstring("Invalid line in file ".file." on line ".itos(line).":".snl)
printstring("   ".s.snl)
end ;   ! of invalid
!
!
!***********************************************************************
!*
!*          M A K E L O C S
!*
!***********************************************************************
!
externalroutine  makelocs(string (255) parms)
integer  flag,workad,npads,padsad,nttys,ttysad,nlocns,locnsad,nmaps
integer  mapsad,line,len,i,j,ad,conad,nextline,workbase,size,padsize
integer  ttysize,locnsize,mapsize,inputline
string (31) padsfile,ttysfile,locnsfile,mapsfile,out
string (255) s,work1,work2,work3,work4,linestr,typestr,status,loclp
string (255) building,location,padstr,work
record (hf)name  h
record (padf)name  pad
record (ttyf)name  tty
record (locnf)name  locn
record (mapf)name  map
!
setpar(parms)
if  parmap > 31 then  start 
   flag = 263;                          ! Wrong number of parameters
   -> err
finish 
!
if  parmap = 1 and  spar(1) = "?" then  start 
   printstring("If no parameters are given, suitable prompts are issued".snl)
   set return code(0)
   return 
finish 
!
getfile(1,padsfile)
getfile(2,ttysfile)
getfile(3,locnsfile)
getfile(4,mapsfile)
getfile(5,out)
out = default termlocsfile if  out = "."
!
padsize = sizeof(pad)
ttysize = sizeof(tty)
locnsize = sizeof(locn)
mapsize = sizeof(map)
workad = 0
setwork(workad,flag)
-> err if  flag # 0
workbase = workad
!
! Read  the  PADs  file,  and  set  up  a  record array of PAD names and
! locations.
!
flag = openfile(padsfile)
-> err if  flag # 0
npads = 0
padsad = workad
inputline = 0
cycle 
   readline(s)
   exit  if  s = ".END"
   inputline = inputline + 1
   pad == record(workad)
   unless  s -> work1.(":").padstr.(":").work2 then  start 
      invalid(s,padsfile,inputline)
      continue 
   finish 
   pad_name <- ucstring(padstr)
   pad_location <- work2
   pad_maxline = -1
   npads = npads + 1
   workad = workad + padsize
repeat 
printstring("Number of PADs: ".itos(npads).snl)
selectinput(0)
closestream(inchan)
!
! Read the TTYs file, and discover how many lines there are on each PAD.
! This number includes 'dead' lines on a sparsely allocated PAD.
!
flag = openfile(ttysfile)
-> err if  flag # 0
inputline = 0
cycle 
   readline(s)
   exit  if  s = ".END"
   inputline = inputline + 1
   continue  unless  s -> padstr.(":").work1.(":").work2.(":").linestr.(":")
   len = length(linestr)
   i = len - 2
   i = 1 if  i < 1
   line = otoi(substring(linestr,i,len))
   ad = findpad(padstr,padsad,npads)
   if  ad = 0 then  start 
      printstring("PAD not known in entry on line ".itos(inputline)." of file ".ttysfile.":".snl)
      printstring("   ".s.snl)
      continue 
   finish 
   pad == record(ad)
   pad_maxline = line if  pad_maxline < line
repeat 
nttys = 0
for  i = 0,1,npads-1 cycle 
   pad == record(padsad+padsize*i)
   nttys = nttys + pad_maxline + 1
repeat 
printstring("Number of TTYs: ".itos(nttys).snl)
selectinput(0)
closestream(inchan)
!
nextline = 0
ttysad = workad
for  i = 0,1,npads - 1 cycle 
   pad == record(padsad+padsize*i)
   pad_linestart = nextline
   nextline = nextline + pad_maxline + 1
   ad = workad
   workad = workad + ttysize*(pad_maxline+1)
   for  j = 0,1,pad_maxline cycle 
      tty == record(ad)
      tty = 0
      ad = ad + ttysize
   repeat 
repeat 
!
! Read the locations file, and set up  a  record  array  of  information
! about PAD locations.
!
flag = openfile(locnsfile)
-> err if  flag # 0
nlocns = 0
locnsad = workad
inputline = 0
cycle 
   readline(s)
   exit  if  s = ".END"
   inputline = inputline + 1
   locn == record(workad)
   unless  s -> work1.(":").work2.(":").building then  start 
      invalid(s,locnsfile,inputline)
      continue 
   finish 
   i = pstoi(work1)
   j = pstoi(work2)
   unless  0 <= i <= 255 and  0 <= j <= 255 then  start 
      invalid(s,locnsfile,inputline)
      continue 
   finish 
   locn_major = i
   locn_minor = j
   locn_building <- building
   nlocns = nlocns + 1
   workad = workad + locnsize
repeat 
printstring("Number of locations: ".itos(nlocns).snl)
selectinput(0)
closestream(inchan)
!
! Read  the  mapping  file,  and  set up a record array of terminal type
! names and type numbers.
!
flag = openfile(mapsfile)
-> err if  flag # 0
nmaps = 0
mapsad = workad
inputline = 0
cycle 
   readline(s)
   exit  if  s = ".END"
   inputline = inputline + 1
   map == record(workad)
   unless  s -> work1.(":").work2 then  start 
      invalid(s,mapsfile,inputline)
      continue 
   finish 
   map_stype <- work1
   i = pstoi(work2)
   unless  0 <= i <= 255 then  start 
      invalid(s,mapsfile,inputline)
      continue 
   finish 
   map_ntype = i
   nmaps = nmaps + 1
   workad = workad + mapsize
repeat 
printstring("Number of mappings: ".itos(nmaps).snl)
selectinput(0)
closestream(inchan)
!
! Re-read  the  TTYs  file, and set up a record array of terminal names,
! locations and other information.
!
flag = openfile(ttysfile)
-> err if  flag # 0
inputline = 0
cycle 
   readline(s)
   exit  if  s = ".END"
   inputline = inputline + 1
   unless  s -> padstr.(":").work.(":").work1.(":").linestr.c 
      (":").work2.(":").work3.(":").status.(":").work4.(":").loclp.c 
      (":").typestr.(":").building.(":").location then  start 
      invalid(s,ttysfile,inputline)
      continue 
   finish 
   len = length(linestr)
   i = len - 2
   i = 1 if  i < 1
   line = otoi(substring(linestr,i,len))
   ad = findpad(padstr,padsad,npads)
   continue  if  ad = 0
   pad == record(ad)
   ad = ttysad + (pad_linestart+line)*ttysize
   tty == record(ad)
   uctranslate(addr(status)+1,length(status))
   continue  unless  status = "OK" or  status = "" or  status = "TEST"
   uctranslate(addr(loclp)+1,length(loclp))
   if  loclp = "LPEMAS" or  loclp = "LPR" then  loclp = "LP"
   tty_loclp <- loclp
   tty_building <- building
   tty_location <- location
   if  typestr = "" then  tty_type = 0 else  c 
   if  ucstring(typestr) = "UNKNOWN" then  tty_type = -1 else  start 
      if  typestr -> typestr.(",") then  start ; finish 
                                        ! Strip rubbish
      tty_type = 0
      ad = mapsad
      for  i = 1,1,nmaps cycle 
         map == record(ad)
         if  typestr = map_stype then  start 
            tty_type = map_ntype
            exit 
         finish 
         ad = ad + mapsize
      repeat 
      if  tty_type = 0 then  start 
         printstring("Warning - terminal type '".typestr."' on line ".c 
                         itos(inputline)." of file ".ttysfile." not known".snl)
      finish 
   finish 
repeat 
selectinput(0)
closestream(inchan)
!
! Now build the output file.
!
s = "T#".nexttemp;                      ! Workfile
size = mapsad - workbase + sizeof(h)
outfile(s,size,0,0,conad,flag)
-> err if  flag # 0
h == record(conad)
h_dataend = h_filesize
h_filetype = ssdatafiletype
h_format = 3;                           ! Un-structured
h_mark = 1;                             ! For future compatibility
h_npads = npads
h_nttys = nttys
h_nlocns = nlocns
h_sp0 = 0
h_sp1 = 0
ad = conad + sizeof(h);                 ! Point beyond header
h_padsoffset = ad - conad
move(npads*padsize,padsad,ad)
ad = ad + npads*padsize
h_ttysoffset = ad - conad
move(nttys*ttysize,ttysad,ad)
ad = ad + nttys*ttysize
h_locnsoffset = ad - conad
move(nlocns*locnsize,locnsad,ad)
disconnect(s,flag)
rename(s,out,flag)
if  flag # 0 then  newgen(s,out,flag)
-> err if  flag # 0
cherish(out)
permit(out,"",1,flag);                  ! Permit in read mode
-> err if  flag # 0
!
selectinput(0)
closestream(inchan)
clearstream(inchan)
printstring("Finished OK".snl)
set return code(0)
stop 
!
err:
selectinput(0)
closestream(inchan)
clearstream(inchan)
printstring(snl."MAKELOCS fails -".failuremessage(flag))
set return code(flag)
stop 
end ;   ! of makelocs
endoffile