Google
 

Trailing-Edge - PDP-10 Archives - tops20tools_v6_9-jan-86_dumper - tools/dumper2/set.for
There are 3 other files named set.for in the archive. Click here to see a list.
	INTEGER*4 FUNCTION SET_ASCII(OPTION,SLEN,STRING,TLEN,
	1 TOKEN,CHARX,NUMBER,PARAM)
C
C	This is the action routine for setting the ASCII I/O mode.
C
C	Parameter list description:
C
C	OPT    -- Options given to LIB$TPARSE
C	SLEN   -- Length of remaining string
C	STRING -- Address of remaining string
C	TLEN   -- Length of the matched token
C	TOKEN  -- Address of the matched token
C	CHARX   -- Character matched by a single letter type
C	NUMBER -- Integer value of a matched numeric type
C	PARAM  -- Parameter supplied by state transition
C
	INTEGER*4 OPTION,SLEN,TLEN,NUMBER,PARAM
	BYTE STRING(1),TOKEN(1),CHARX
C
	INCLUDE 'DMPCOM.FOR/NOLIST'
C
	IOMODE = ASCII
	SET_ASCII = 1
	RETURN
	END
	INTEGER*4 FUNCTION SET_BINARY(OPTION,SLEN,STRING,TLEN,
	1 TOKEN,CHARX,NUMBER,PARAM)
C
C	This is the action routine for setting the BINARY I/O mode.
C
C	Parameter list description:
C
C	OPT    -- Options given to LIB$TPARSE
C	SLEN   -- Length of remaining string
C	STRING -- Address of remaining string
C	TLEN   -- Length of the matched token
C	TOKEN  -- Address of the matched token
C	CHARX   -- Character matched by a single letter type
C	NUMBER -- Integer value of a matched numeric type
C	PARAM  -- Parameter supplied by state transition
C
	INTEGER*4 OPTION,SLEN,TLEN,NUMBER,PARAM
	BYTE STRING(1),TOKEN(1),CHARX
C
	INCLUDE 'DMPCOM.FOR/NOLIST'
C
	IOMODE = BINARY
	SET_BINARY = 1
	RETURN
	END
	INTEGER*4 FUNCTION SET_SILENT(OPTION,SLEN,STRING,TLEN,
	1 TOKEN,CHARX,NUMBER,PARAM)
C
C	This is the action routine for setting the SILENT mode.
C
C	Parameter list description:
C
C	OPT    -- Options given to LIB$TPARSE
C	SLEN   -- Length of remaining string
C	STRING -- Address of remaining string
C	TLEN   -- Length of the matched token
C	TOKEN  -- Address of the matched token
C	CHARX   -- Character matched by a single letter type
C	NUMBER -- Integer value of a matched numeric type
C	PARAM  -- Parameter supplied by state transition
C
	INTEGER*4 OPTION,SLEN,TLEN,NUMBER,PARAM
	BYTE STRING(1),TOKEN(1),CHARX
C
	INCLUDE 'DMPCOM.FOR/NOLIST'
C
	PRMODE = SILENT
	SET_SILENT = 1
	RETURN
	END
	INTEGER*4 FUNCTION SET_FILES(OPTION,SLEN,STRING,TLEN,
	1 TOKEN,CHARX,NUMBER,PARAM)
C
C	This is the action routine for setting the FILES mode.
C
C	Parameter list description:
C
C	OPT    -- Options given to LIB$TPARSE
C	SLEN   -- Length of remaining string
C	STRING -- Address of remaining string
C	TLEN   -- Length of the matched token
C	TOKEN  -- Address of the matched token
C	CHARX   -- Character matched by a single letter type
C	NUMBER -- Integer value of a matched numeric type
C	PARAM  -- Parameter supplied by state transition
C
	INTEGER*4 OPTION,SLEN,TLEN,NUMBER,PARAM
	BYTE STRING(1),TOKEN(1),CHARX
C
	INCLUDE 'DMPCOM.FOR/NOLIST'
C
	PRMODE = FILES
	SET_FILES = 1
	RETURN
	END
	INTEGER*4 FUNCTION SET_LIST(OPTION,SLEN,STRING,TLEN,
	1 TOKEN,CHARX,NUMBER,PARAM)
C
C	This is the action routine for setting the LISTING mode.
C
C	Parameter list description:
C
C	OPT    -- Options given to LIB$TPARSE
C	SLEN   -- Length of remaining string
C	STRING -- Address of remaining string
C	TLEN   -- Length of the matched token
C	TOKEN  -- Address of the matched token
C	CHARX   -- Character matched by a single letter type
C	NUMBER -- Integer value of a matched numeric type
C	PARAM  -- Parameter supplied by state transition
C
	INTEGER*4 OPTION,SLEN,TLEN,NUMBER,PARAM
	BYTE STRING(1),TOKEN(1),CHARX
C
	INCLUDE 'DMPCOM.FOR/NOLIST'
C
	INTEGER*4 L
	CHARACTER*256 NAM
C
	LIST = .TRUE.
	WRITE(6,100)
100	FORMAT(' Enter the listing file name:  ',$)
	READ(5,110) L,NAM
110	FORMAT(Q,A)
	IF (L.EQ.0) THEN
	 IF (LIST) CLOSE(UNIT=2)
	 LIST = .FALSE.
	 SET_LIST = %LOC(DUMPER_NOLIST)
	 RETURN
	ENDIF
	OPEN(UNIT=2,NAME=NAM(1:L),CARRIAGECONTROL='FORTRAN',ERR=120,
	1 INITIALSIZE=1,EXTENDSIZE=1,RECORDSIZE=132,STATUS='NEW')
	SET_LIST = 1
	RETURN
120	CONTINUE
	LIST = .FALSE.
	SET_LIST = %LOC(DUMPER_ABLIST)
	RETURN
	END
	INTEGER*4 FUNCTION SET_NONE(OPTION,SLEN,STRING,TLEN,
	1 TOKEN,CHARX,NUMBER,PARAM)
C
C	This is the action routine for setting the NONE mode.
C
C	Parameter list description:
C
C	OPT    -- Options given to LIB$TPARSE
C	SLEN   -- Length of remaining string
C	STRING -- Address of remaining string
C	TLEN   -- Length of the matched token
C	TOKEN  -- Address of the matched token
C	CHARX   -- Character matched by a single letter type
C	NUMBER -- Integer value of a matched numeric type
C	PARAM  -- Parameter supplied by state transition
C
	INTEGER*4 OPTION,SLEN,TLEN,NUMBER,PARAM
	BYTE STRING(1),TOKEN(1),CHARX
C
	INCLUDE 'DMPCOM.FOR/NOLIST'
C
	ORMODE =  NONE
	SET_NONE = 1
	RETURN
	END
	INTEGER*4 FUNCTION SET_CR(OPTION,SLEN,STRING,TLEN,
	1 TOKEN,CHARX,NUMBER,PARAM)
C
C	This is the action routine for setting the CR mode.
C
C	Parameter list description:
C
C	OPT    -- Options given to LIB$TPARSE
C	SLEN   -- Length of remaining string
C	STRING -- Address of remaining string
C	TLEN   -- Length of the matched token
C	TOKEN  -- Address of the matched token
C	CHARX   -- Character matched by a single letter type
C	NUMBER -- Integer value of a matched numeric type
C	PARAM  -- Parameter supplied by state transition
C
	INTEGER*4 OPTION,SLEN,TLEN,NUMBER,PARAM
	BYTE STRING(1),TOKEN(1),CHARX
C
	INCLUDE 'DMPCOM.FOR/NOLIST'
C
	ORMODE = CR
	SET_CR = 1
	RETURN
	END
	INTEGER*4 FUNCTION SET_FORT(OPTION,SLEN,STRING,TLEN,
	1 TOKEN,CHARX,NUMBER,PARAM)
C
C	This is the action routine for setting the FORTRAN mode.
C
C	Parameter list description:
C
C	OPT    -- Options given to LIB$TPARSE
C	SLEN   -- Length of remaining string
C	STRING -- Address of remaining string
C	TLEN   -- Length of the matched token
C	TOKEN  -- Address of the matched token
C	CHARX   -- Character matched by a single letter type
C	NUMBER -- Integer value of a matched numeric type
C	PARAM  -- Parameter supplied by state transition
C
	INTEGER*4 OPTION,SLEN,TLEN,NUMBER,PARAM
	BYTE STRING(1),TOKEN(1),CHARX
C
	INCLUDE 'DMPCOM.FOR/NOLIST'
C
	ORMODE = FORTRAN
	SET_FORT = 1
	RETURN
	END