Google
 

Trailing-Edge - PDP-10 Archives - BB-AI48A-BM - datatrieve/dabsym.req
There are no other files named dabsym.req in the archive.
!+++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
!
!			   D A B S Y M
!
! 		User interface to callable Datatrieve-20
!
!		   COPYRIGHT (c) 1984 BY
!	       DIGITAL EQUIPMENT CORPORATION, MAYNARD
!		MASSACHUSETTS.  ALL RIGHTS RESERVED.
!
!	THIS SOFTWARE  IS FURNISHED UNDER A LICENSE AND MAY
!	BE USED  AND  COPIED  ONLY  IN  ACCORDANCE WITH THE
!	TERMS OF SUCH LICENSE AND WITH THE INCLUSION OF THE
!	ABOVE COPYRIGHT NOTICE.  THIS SOFTWARE OR ANY OTHER
!	COPIES THEREOF  MAY NOT  BE PROVIDED  OR  OTHERWISE
!	MADE  AVAILABLE TO  ANY OTHER  PERSON.  NO TITLE TO
!	AND   OWNERSHIP   OF   THE   SOFTWARE   IS   HEREBY
!	TRANSFERRED.
!	
!	THE  INFORMATION  IN  THIS  SOFTWARE IS  SUBJECT TO
!	CHANGE  WITHOUT  NOTICE AND SHOULD NOT BE CONSTRUED
!	AS A COMMITMENT  BY  DIGITAL EQUIPMENT CORPORATION.
!
!	DIGITAL ASSUMES  NO  RESPONSIBILITY  FOR THE USE OR
!	RELIABILITY OF  ITS  SOFTWARE ON  EQUIPMENT THAT IS
!	NOT SUPPLIED BY DIGITAL.
!
!-----------------------------------------------------------------------
! Callable Datatrieve is accessed through the following routines.
! All routines are called Fortran/Cobol style and passed a single
! argument, the address of the Datatrieve Access Block (DAB).
!
! All routines are included in the file SYS:DTRLIB.REL. To link your
! program, simply include DTRLIB:
!
!	@LOAD MAIN,SYS:DTRLIB/LIB
!
! Callable Datatrieve Entry Points:

EXTERNAL ROUTINE
    DTRINI : FORTRAN_SUB,	!Initialize a callable Datatrieve stream
    DTRUNW : FORTRAN_SUB,	!Abort the current DTR command (^C)
    DTRFIN : FORTRAN_SUB,	!Finish a callable Datatrieve stream

    DTRCOM : FORTRAN_SUB,	!Passes a command string to DTR
    DTRCON : FORTRAN_SUB,	!Continue Datatrieve
    DTRPVL : FORTRAN_SUB,	!Passes a value to DTR

    DTRGPT : FORTRAN_SUB,	!Get a record from a port
    DTRPPT : FORTRAN_SUB,	!Put a record into a port
    DTRPTE : FORTRAN_SUB,	!Indicate End of File on a port

    DTRPOT : FORTRAN_SUB,	!Outputs data to a log file
    DTRINF : FORTRAN_SUB;	!Get info about a Datatrieve object

! Define aliases for the Datatrieve entry points for VAX compatibility
MACRO
    DTR$COMMAND		= DTRCOM %,
    DTR$CONTINUE	= DTRCON %,
    DTR$FINISH		= DTRFIN %,
    DTR$GET_PORT	= DTRGPT %,
    DTR$INFO		= DTRINF %,
    DTR$INIT		= DTRINI %,
    DTR$PORT_EOF	= DTRPTE %,
    DTR$PUT_OUTPUT	= DTRPOT %,
    DTR$PUT_PORT	= DTRPPT %,
    DTR$PUT_VALUE	= DTRPVL %,
    DTR$UNWIND		= DTRUNW %;
! The Datatrieve Access Block (DAB)
!
!	Note that most of the fields are full words. This allows
!	easy access from higher level languages which have trouble
!	accessing half words and bytes.
!

FIELD DAB_FIELDS =
  SET
    DAB$B_BID =	[0,0,9,0],		! Block id (INTERNAL USE ONLY)
    DAB$B_BLN =	[0,9,9,0],		! Length of DAB (INTERNAL USE ONLY)

    DAB$L_CONDITION = [1,0,36,0],	! Returned condition code

    DAB$A_MSG_BUF = [2,0,36,0],		! Passed address of message buffer
    DAB$W_MSG_BUF_LEN = [3,0,36,0],	! Passed length of message buffer
    DAB$W_MSG_LEN = [4,0,36,0],		! Passed/Returned length of message

    DAB$A_AUX_BUF = [5,0,36,0],		! Passed address of aux buffer
    DAB$W_AUX_BUF_LEN = [6,0,36,0],	! Passed length of aux buffer
    DAB$W_AUX_LEN = [7,0,36,0],		! Passed/Returned length of message

    DAB$A_VAL_BUF = [8,0,36,0],		! Passed address of value buffer
    DAB$W_VAL_BUF_LEN = [9,0,36,0],	! Passed length of value buffer
    DAB$W_VAL_LEN = [10,0,36,0],	! Passed/Returned length of value

    DAB$W_IDI = [11,0,36,0],		! Returned stream number
    DAB$W_STATE = [12,0,36,0],		! Returned state (stall point)

    DAB$L_FLAGS = [13,0,36,0],		! Returned flags
	DAB$V_PRINT_HDR = [13,0,1,0],		! 1 = This line is a header
	DAB$V_EXIT = [13,1,1,0],		! 1 = EXIT was interpreted
	DAB$V_PW_PROMPT = [13,2,1,0],		! 1 = This prompt for PW
        DAB$V_PLOT = [13,3,1,0],		! 1 = Just finished a plot
	DAB$V_REGIS = [13,4,1,0],		! 1 = This line is regis text

    DAB$L_OPTIONS = [14,0,36,0],	! Passed option flags
	DAB$V_SEMI = [14,0,1,0],		! 1 = SEMI colon required
	DAB$V_FAST = [14,1,1,0],		! 1 = Direct output to TTY

    DAB$A_REC_BUF = [15,0,36,0],	! Passed port record address
    DAB$W_REC_LEN = [16,0,36,0],	! Passed/returned port rec len (bytes)
    DAB$W_REC_BYTE = [17,0,36,0],	! Passed/returned port byte size
    DAB$W_VERSION = [18,0,36,0]		! Returned version
  TES;

LITERAL
    DAB$K_BLK_LEN = 19,
    DAB$K_BUF_LEN = 256;
! State (stall point) codes

LITERAL
    DTR$K_STL_MIN=1,		! (Lowest value)

    DTR$K_STL_CMD=1,		! Waiting for command
    DTR$K_STL_PRMPT=2,		! Waiting for prompt value
    DTR$K_STL_LINE=3,		! Have a print line
    DTR$K_STL_MSG=4,		! Have a message
    DTR$K_STL_PGET=5,		! Waiting for port get
    DTR$K_STL_PPUT=6,		! Waiting for port put

    DTR$K_STL_MAX=6;		! (Highest value)
! Define fields in the condition word
FIELD
    CONDITION_FIELDS =
	SET
	STS$V_SEVERITY	= [0,0,3,0],	! Severity field
	STS$V_SUCCESS	= [0,0,1,0],	! Success field (part of severity)
	STS$V_COND_ID	= [0,3,29,0],	! Identity field
	STS$V_MSG_NO	= [0,3,15,0],	! Message number field
	STS$V_FAC_SP	= [0,17,1,0],	! Facility specific flag
	STS$V_CODE	= [0,3,14,0],	! Code for condition only
	STS$V_FAC_NO	= [0,18,14,0],	! Facility code
	STS$V_CUST_DEF	= [0,31,1,0]	! Customer definition flag
	TES;

! Define symbols for severity levels
LITERAL
    STS$K_WARNING = 0,	! Causes DTR to print %message and continue
    STS$K_SUCCESS = 1,	! Causes DTR to print message and continue
    STS$K_ERROR = 2,	! Causes DTR to print ?message and Unwind
    STS$K_INFO = 3,	! Causes DTR to print message and continue
    STS$K_SEVERE = 4;	! Causes DTR to print ??DATATRIEVE ERROR, message
			! and Unwind
! Here define the condition values

! Counter to count up condition values
COMPILETIME CMP$ERRORNUM=0;

! This macro builds the value which is signalled when an error
! occurs. It currently contains only the severity and the error
! code. On the VAX it would also contain the facility code, but
! since no other software that deals with Datatrieve internally
! signals anything, no facility code is needed.
!
! If you add a message to the message facility, change this file
!	and ERR.MAC where the strings really are.
!
!	Note that all messages must be written in plain proper English
!	sentences which end in periods. Info messages usually are surrounded
!	by brackets []. Severe messages are not capitalized because they
!	are preceded by another string which is.

MACRO
    MSGSTR(ERRORNAME,SEVERITY) =
	%ASSIGN(CMP$ERRORNUM,CMP$ERRORNUM + 1)
	LITERAL %NAME('DTR$_',ERRORNAME) =
	    %IF %IDENTICAL(SEVERITY,INFO) %THEN STS$K_INFO %ELSE
	    %IF %IDENTICAL(SEVERITY,WARN) %THEN STS$K_WARNING %ELSE
	    %IF %IDENTICAL(SEVERITY,ERROR) %THEN STS$K_ERROR %ELSE
	    %IF %IDENTICAL(SEVERITY,SEVERE) %THEN STS$K_SEVERE %FI %FI %FI %FI +
	    (CMP$ERRORNUM ^ 3);
    %;

MSGSTR (SUCCESS,INFO) !Request completed successfully.
MSGSTR (ERROR,ERROR) !Request failed.
MSGSTR (HOPELESS,SEVERE) !this should not happen, at PC=!O.
MSGSTR (BADBLK,SEVERE) !routine got wrong block, expected !U,!/ got !U at PC=!O.
MSGSTR (BADSUBBLK,SEVERE) !routine got wrong subblock in block !U,!/ expected !U, got !U at PC=!O.
MSGSTR (JSYS_ERROR,SEVERE) !JSYS error: !L at PC=!O.
MSGSTR (BLKTOOBIG,SEVERE) !block request too large !U at PC=!O.
MSGSTR (INVPOOLCL,SEVERE) !pool class !U, invalid at PC=!O.
MSGSTR (RELBADBLK,SEVERE) !request to release invalid block !U.
MSGSTR (NOPOOLIDS,ERROR) !No more dynamic memory pool identifiers at PC=!O.
MSGSTR (WRONGSTALL,ERROR) !Invalid call for current stall point.
MSGSTR (BADHANDLE,ERROR) !Invalid callable Datatrieve stream identifier in DAB.
MSGSTR (USESLOEXH,ERROR) !Too many concurrent callable Datatrieve streams active.
MSGSTR (UNWIND,ERROR) !Execution terminated by ^C.
MSGSTR (SHUTDOWN,INFO) !Datatrieve gracefully exits.
MSGSTR (SYSBADARG,SEVERE) !routine expected !U argument!p,!/ got !U at PC=!O.
MSGSTR (BADSYNTAX,ERROR) !This is not a proper !A,!/ possibly because '!E'.
MSGSTR (REPARSE,ERROR) !Reparse required.
MSGSTR (BACKTRACE,INFO) !!U:	!A
MSGSTR (TOOMANYIND,ERROR) !Too many indirect files or procedures.
MSGSTR (NOTYETIMP,SEVERE) !not yet implemented at PC=!O.
MSGSTR (SECTION_NUM,INFO) !Memory use, section !U:
MSGSTR (PAGE_USAGE,INFO) !	!U page!p free, !U page!p in use
MSGSTR (POOL_USAGE,INFO) !	!A pool !U% of !U page!p in use
MSGSTR (INVCOLPAG,ERROR) !Value for columns per page outside range of 1 to 255.
MSGSTR (SET_OPTIONS,INFO) !Set options:
MSGSTR (SET_OP_FLAG,INFO) !	!A!A
MSGSTR (SET_OP_CPP,INFO) !	!U Column!p per page
MSGSTR (BADHELP,ERROR) !Failed to find help for '!A' in help file.
MSGSTR (TEMPHELP,ERROR) !Help file was just edited. Please try help command again.
MSGSTR (INVMEM,SEVERE) !in page allocation at PC=!O.
MSGSTR (INVBLKTYP,SEVERE) !invalid block type !U at PC=!O.
MSGSTR (INVSRCTYP,SEVERE) !invalid PAR source type !U at PC=!O.
MSGSTR (MUSTBEDSK,ERROR) !Procedure and indirect files must be disk resident.
MSGSTR (BADPROC,ERROR) !Invalid continuation or control character in statement or command.
MSGSTR (BIGPREVTEXT,ERROR) !Statement or command too large for the edit buffer.
MSGSTR (BIGACTTEXT,ERROR) !Statement or command too large for the syntax error buffer.
MSGSTR (BIGBUFFER,ERROR) !Statement or command too large for the parsing buffer.
MSGSTR (LOOKINGFOR,INFO) ![Looking for !A]
MSGSTR (BADEDIT,ERROR) !The ADT, EDIT, and PUSH commands may only be invoked from the terminal.
MSGSTR (ASSUMELIT,WARN) !'!A' is not a field, assumed literal.
MSGSTR (NOCONTEXT,ERROR) !'!A' is undefined or used out of context.
MSGSTR (NOCURCOL,ERROR) !A current collection has not been established.
MSGSTR (MISNOTFLD,ERROR) !Object of Missing operator must be a field.
MSGSTR (MISCLAMIS,WARN) !MISSING VALUE not defined for !A, using default value.
MSGSTR (BADSYNTAX2,ERROR) !This is not a proper !A,!/ possibly because '!A'.
MSGSTR (DIRCMPSTK,SEVERE) !dirty compiler stack at level !U.
MSGSTR (BADDATEOP,ERROR) !Improper operation on a date.
MSGSTR (ABORT,ERROR) !Abort: !A
MSGSTR (DISPLAY,INFO) !Display: !A
MSGSTR (PROMPT,INFO) !Enter !A: 
MSGSTR (RE_PROMPT,INFO) !!BRe-enter !A: 
MSGSTR (BADCDD,ERROR) !Dictionary "!A", must contain only device and directory fields.
MSGSTR (INVDSCTYP,SEVERE) !invalid class or data type in descriptor during conversion.
MSGSTR (UNSCONV,ERROR) !Unsupported data conversion from datatype !U to datatype !U.
MSGSTR (OVERFLOW,WARN) !Overflow in arithmetic, conversion, or assignment, result is incorrect.
MSGSTR (UNDERFLOW,WARN) !Underflow in arithmetic, conversion, or assignment, result is incorrect.
MSGSTR (NONDIGIT,WARN) !Illegal character in numeric string '!A', ignoring character(s).
MSGSTR (TOOMANDEC,WARN) !Too many decimal points in string '!A', ignoring all but first.
MSGSTR (TOOMANSIG,WARN) !Sign in wrong position in string '!A' being ignored.
MSGSTR (BADNEG,ERROR) !Negative value is not proper as a count or record number.
MSGSTR (DIVBYZERO,WARN) !Attempt to divide by zero, result is incorrect.
MSGSTR (TXTOVRFLW,WARN) !Conversion impossible, or EDIT-STR violation, result replaced by *.
MSGSTR (LOSOFPREC,WARN) !Loss of precision in integer arithmetic or conversion; result is approximate.
MSGSTR (DUPCLASPE,ERROR) !Duplicate !A clause specified.
MSGSTR (CONSIGUSA,ERROR) !Conflicting SIGN and USAGE clauses.
MSGSTR (TOOMANDIG,ERROR) !Too many digits in numeric PICTURE or EDIT string.
MSGSTR (MISPICUSA,ERROR) !Either a PICTURE or USAGE clause is required.
MSGSTR (PICUSAMAT,ERROR) !The PICTURE and USAGE clauses do not match.
MSGSTR (EXPINVPIC,ERROR) !The exponential EDIT string is not allowed in a PICTURE clause.
MSGSTR (BADREPCNT,ERROR) !The repeat count, [edit-character(number)], is not a positive integer.
MSGSTR (CONTPREQ,ERROR) !All 'P's must be contiguous in a PICTURE or EDIT string.
MSGSTR (ILLPICSTR,ERROR) !PICTURE or EDIT string contains the illegal character '!A'.
MSGSTR (ONEXPERM,ERROR) !Only one '!A' permitted in PICTURE or EDIT string.
MSGSTR (EMPTYPIC,ERROR) !No USAGE clause and the PICTURE clause has only insertion characters.
MSGSTR (ASSVIRFLD,ERROR) !Cannot assign to a field containing a COMPUTED BY clause.
MSGSTR (TRUDURASS,WARN) !Overflow during assignment, result is incorrect.
MSGSTR (DATERR1,WARN) !Conversion error in day of the month in date string '!A', date made blank.
MSGSTR (DATERR2,WARN) !Conversion error in date string '!A', date made blank.
MSGSTR (DATERR3,WARN) !Conversion error in or text after time field in date string '!A', date made blank.
MSGSTR (DATERR4,WARN) !Conversion error, !L, in date string '!A', date made blank.
MSGSTR (NOGROPRMT,ERROR) !Illegal assignment to a group data item.
MSGSTR (VALIDERR,ERROR) !Validation error for field !A.
MSGSTR (CLANOTPER,ERROR) !!A clause is not permitted in a variable declaration.
MSGSTR (STRTRUN,WARN) !String truncation in conversion or assignment.
MSGSTR (NOGLOVAR,INFO) !No global variables have been declared.
MSGSTR (VARIABLES,INFO) !Global variables:
MSGSTR (TOOMANYVAR,SEVERE) !Don't have enough room to store this many plot variables.
MSGSTR (SHO_FIELD,INFO) !!A!A!A
MSGSTR (ASSNEGUNS,WARN) !Assignment of negative value to unsigned item; absolute value used.
MSGSTR (BADFLDCTX,ERROR) !Invalid context for field '!A'.
MSGSTR (RECERSD,ERROR) !Record has been deleted.
MSGSTR (NORECSEL,WARN) !No record selected, printing whole collection.
MSGSTR (NULPRILIS,ERROR) !Null print list.
MSGSTR (OBJTOOBIG,ERROR) !Print object is too large for line width.
MSGSTR (RMS_ERROR,ERROR) !RMS error !Aing file "!A",!/ !A (ERR: !U),!/ !E (STV: !O).
MSGSTR (FILE_CREATE,INFO) !Creating file !J ...
MSGSTR (FLDSELFREF,ERROR) !Field '!A' contains a self reference and can not be evaluated.
MSGSTR (CLAIGNORE,WARN) !!A clause is ignored when you use a computed by clause
MSGSTR (FUNC_ERR,ERROR) !Function failed giving error code: !U
MSGSTR (DICELTUSE,ERROR) !Dictionary element "!A" already in use.
MSGSTR (ELTNOTDIC,ERROR) !Element "!A" not found in dictionary.
MSGSTR (NOTDICNAM,ERROR) !"!A" is not a "!A" name.
MSGSTR (DICNOTUND,ERROR) !Dictionary element "!A" not understood.
MSGSTR (BADPATHLOG,ERROR) !Logical name "!A" in dictionary path is undefined.
MSGSTR (BADPATHNO,ERROR) !Dictionary path "!A" does not contain an element name.
MSGSTR (BADPATHNAM,ERROR) !Dictionary path "!A" resolves to an invalid file name "!A".
MSGSTR (MULOCCDEP,ERROR) !Multiple OCCURS DEPENDING ON clauses not allowed.
MSGSTR (OCCNOTLAS,ERROR) !OCCURS DEPENDING ON  field is not last item in record definition.
MSGSTR (FLDNOTOCC,ERROR) !Field "!A" not found for OCCURS DEPENDING ON.
MSGSTR (FLDNOTRED,ERROR) !Field "!A" not found for REDEFINES.
MSGSTR (SHOW_DIC,INFO) !The default directory is !A.
MSGSTR (STRING,INFO) !<TAB>!A
MSGSTR (DOMAINS,INFO) !Domains:
MSGSTR (RECORDS,INFO) !Records:
MSGSTR (PLOTS,INFO) !Plots:
MSGSTR (PROCEDURES,INFO) !Procedures:
MSGSTR (TABLES,INFO) !Tables:
MSGSTR (NOLOADTAB,INFO) ! No loaded tables.
MSGSTR (LOADEDTAB,INFO) ! Loaded tables:
MSGSTR (NOTINTAB,ERROR) ! Value not found in table.
MSGSTR (RECLENGTH,INFO) ! [Record is !U !U-bit byte!p long.]
MSGSTR (BADDATTYP,ERROR) ! The usage of field "!A" is invalid in this record.
MSGSTR (BADLENRED,ERROR) ! Bad length for REDEFINES, field "!A".
MSGSTR (BADRECSIZ,WARN) ! Bad record size. Defined: !U  File: !U.
MSGSTR (NOTRDYDOM,ERROR) ! "!A" is not a readied domain.
MSGSTR (EXPCOTAVA,ERROR) ! "!A" is not a collection, loaded table, or global variable.
MSGSTR (NOREADOM,INFO) ! No ready domains.
MSGSTR (READYDOM,INFO) ! Ready domains:
MSGSTR (NOTDOMAIN,ERROR) ! "!A" is not a readied domain, collection, or list.
MSGSTR (NOTLIST,ERROR) ! "!A" is not a list.
MSGSTR (NOREMEXP,ERROR) ! Remote expression is not supported.
MSGSTR (OCCOUTRAN,ERROR) ! Occurs depending on count out of range.
MSGSTR (NOVALFROM,ERROR) ! Value not found from record or table.
MSGSTR (NODOMGLO,INFO) ! No ready domains or global variables.
MSGSTR (FIELDS,INFO) ! Fields of domain !A:
MSGSTR (NOACCCHG,WARN) ! Could not change access to readied domain.
MSGSTR (RERDYFAIL,ERROR) ! Re-ready failed. Domain automatically finished.
MSGSTR (BADKEYDTP,ERROR) ! Key "!A" has an invalid datatype.
MSGSTR (KEYUNDEF,ERROR) ! Key "!A" is not defined in domain "!A".
MSGSTR (CHAOPTINV,ERROR) ! The change option is invalid on the primary key.
MSGSTR (BADIDXSTM,ERROR) ! Keyed files must be fixed or variable, not stream.
MSGSTR (NOREMCROS,ERROR) ! A remote domain may not participate in a CROSS.
MSGSTR (CTXMAGIC,WARN) ! Not enough context. Some field names resolved by Context Searcher.
MSGSTR (MAGICFAIL,WARN) ! Context Searcher failed trying to resolve field.
MSGSTR (NOCOLSOR,ERROR) ! No collection for sort.
MSGSTR (NOCOLSEL,ERROR) ! No collection for select.
MSGSTR (TARRECDRO,WARN) ! Target record has already been dropped.
MSGSTR (NOCOLDROP,ERROR) ! No collection with selected record for DROP.
MSGSTR (RECFOUND,INFO) ! [!U record!p found]
MSGSTR (OUTRANCOL,ERROR) ! Record number out of range for collection.
MSGSTR (SELBADBOO,ERROR) ! Unable to select a record that satisfies the boolean.
MSGSTR (SELNOTFND,ERROR) ! Selected record not found.
MSGSTR (RECPREDRO,ERROR) ! Record has been dropped from the collection.
MSGSTR (SELPURCOL,WARN) ! Parent collection de-selected, collection "!A" automatically released.
MSGSTR (SHOCOLNSR,INFO) ! 	No selected record
MSGSTR (SHOCOLNREC,INFO) ! 	Number of records: !U
MSGSTR (COLLECTIONS,INFO) ! Collections:
MSGSTR (NOESTCOLL,INFO) ! No established collections.
MSGSTR (SHOCOLCOL,INFO) ! Collection !A:
MSGSTR (SHOCOLDOM,INFO) ! 	Domain: !A
MSGSTR (SHOCOLSRNE,INFO) ! 	Selected record: !U (erased)
MSGSTR (SHOCOLSRND,INFO) !	Selected record: !U (dropped)
MSGSTR (SHOCOLSRN,INFO) ! 	Selected record: !U
MSGSTR (SHOCOLSOR,INFO) !	Sort order: !A
MSGSTR (SHOCOLSR2,INFO) !		!A
MSGSTR (ZEROOBJ,WARN) ! Cannot take MAX, MIN, AVERAGE, or STD_DEV of zero objects.
MSGSTR (STAMISDAT,INFO) ! [Function computed using !U of !U values.]
MSGSTR (NOTRGERA,ERROR) ! No target record for ERASE.
MSGSTR (NOERACRO,ERROR) ! Cannot ERASE from a cross.
MSGSTR (WRIACCREQ,ERROR) ! Write access is required for domain "!A".
MSGSTR (NOERASTM,ERROR) ! Cannot ERASE from a stream file in domain "!A".
MSGSTR (NOERALIS,ERROR) ! Cannot ERASE from an occurs list.
MSGSTR (NOVIEWSTO,ERROR) ! Cannot STORE into a view.
MSGSTR (NOSTOREL,ERROR) ! Cannot STORE into a relative file in domain "!A".
MSGSTR (NOTRGMOD,ERROR) ! No target record for MODIFY.
MSGSTR (MODACCREQ,ERROR) ! Modify access is required for domain "!A".
MSGSTR (NOMODSTM,ERROR) ! Cannot MODIFY a stream file in domain "!A".
MSGSTR (OBJNOTDIC,ERROR) ! !A "!A" not found in dictionary.
MSGSTR (ASCIISIXBIT,ERROR) ! Usage clause conflict.
MSGSTR (BADSTM,ERROR) ! Stream files can only contain display_7 and display_7 numeric fields.
MSGSTR (VIEFIEUND,ERROR) ! View field "!A" cannot be found in domain "!A".
MSGSTR (VIEDOMUND,ERROR) ! Domain "!A" was not included in domain list for view.
MSGSTR (WRODOMTYP,ERROR) ! "!A" is not an RMS domain.
MSGSTR (NET_FINISH,INFO) ! FINISH !A; DISPLAY "FINISH";
MSGSTR (REMSYNERR,SEVERE) ! DDMF remote synchronization error at PC=!O.
MSGSTR (NET_READY,INFO) ! READY !A AS !A !A !A; DISPLAY "READY";
MSGSTR (NET_REREADY,INFO) ! READY !A !A !A; DISPLAY "READY";
MSGSTR (PROVERMIS,SEVERE) ! DDMF remote protocol version mismatch
MSGSTR (REMOTEMSG,INFO) ! [DDMF] !A
MSGSTR (RDSTERMIN,ERROR) ! DDMF remote server error.!/ NSP error (!U): !A!/ Last JSYS error: !E
MSGSTR (NOREMANY,ERROR) ! Remote ANY expression may not use another ANY expression in the WITH clause.
MSGSTR (BADHLP,ERROR) ! Error locating help file "!A",!/ !E.
MSGSTR (PMRERR,ERROR) ! DDMF remote server error.!/ NSP error (0): No special error!/ Last JSYS error: !L
MSGSTR (PMRINF,INFO) ! [PMR !A]
MSGSTR (PLBARG,ERROR) ! Too many parameters for plot definition.
MSGSTR (SHOW_PLOT_DIC,INFO) !The default plot directory is !A.
MSGSTR (PLOENTMIS,ERROR) !Plot entry point is not defined.
MSGSTR (PLOLOCRAN,ERROR) !Plot location function out of range. Value: !U.
MSGSTR (PLOIDXRAN,ERROR) !Plot index out of range. Vector: !A, index: !U.
MSGSTR (BADROCKBF,ERROR) ! Bad ROC chain or key buffer.
MSGSTR (NOKEEPNEE,SEVERE) ! No keeplist when one is needed.
MSGSTR (BADSORREC,ERROR) ! Bad sort record length.
MSGSTR (FUNC_JSYS_ERR,ERROR) !Function failed due to JSYS error: !E.
MSGSTR (BADSORT,ERROR) ! Sort failed because:!/!A
MSGSTR (NOMOREMEM,ERROR) ! No more memory available.!/ Use the FINISH or RELEASE commands to free some memory.
MSGSTR (BADADT,ERROR) ! Error locating ADT.EXE file,!/ !E.
MSGSTR (BADEXEC,ERROR) ! Error locating EXEC.EXE file,!/ !E.
MSGSTR (BADEDITOR,ERROR) ! Error locating EDITOR: file,!/ !E.
MSGSTR (UNTERQUO,ERROR) ! Unterminated quoted string.
MSGSTR (REPNOTFIT,ERROR) ! Print object(s) too long to fit on report line.
MSGSTR (MAXLINEXC,ERROR) ! Maximum line count exceeded - report terminated.
MSGSTR (NEWPINBOT,ERROR) ! NEW-PAGE and NEW-SECTION are illegal in AT BOTTOM OF PAGE print list.
MSGSTR (BADQHDR,ERROR) ! Illegal report name.
MSGSTR (MAXPAGEXC,ERROR) ! Maximum report pages exceeded.
MSGSTR (RPODUPAT,WARN) ! Duplicate AT block encountered.
MSGSTR (RPOEXCPRI,ERROR) ! Excessive PRINT statements for REPORT.
MSGSTR (PLOTBIG,ERROR) ! Plot text longer than 255 characters
MSGSTR (RMS_WARN,WARN) !RMS error !Aing file "!A",!/ !A (ERR: !U),!/ !E (STV: !O).
MSGSTR (FUNC_ERR_MSG,ERROR) ! Function error:!/    !A
MSGSTR (FILE_JFN,ERROR) ! Error accessing file !J,!/ !L
MSGSTR (FILE_PTR,ERROR) ! Error accessing file !A,!/ !L
MSGSTR (NOLOADPLT,INFO) ! No loaded plots.
MSGSTR (LOADEDPLT,INFO) ! Loaded plots:
MSGSTR (RELALLPLOTS,INFO) ! [Releasing all plots to conserve memory.]
MSGSTR (FIELD_MATCHS_KEYWORD,ERROR) ! Field "!A" is the same as a Datatrieve keyword. Use another field name.
MSGSTR (PLOTSAT,INFO) ! Plots from !A:
MSGSTR (BADPORTOP,ERROR) ! It is invalid to MODIFY, ERASE or FIND a port.
MSGSTR (BIGATOM,ERROR) ! Item cannot contain more than 255 characters.
MSGSTR (CANREADOM,ERROR) ! Cannot READY domains with same name on different nodes. !/ Use an alias name for "!A".
MSGSTR (BADQUOSTR,ERROR) ! Found an opening quote but no corresponding closing quote.
MSGSTR (LOTOVEFLO,SEVERE) ! Internal error (no more slots available in lock table).
MSGSTR (MEMNOTAVL,SEVERE) ! No dynamic memory available for stream initialization.
MSGSTR (MEMNOTSET,SEVERE) ! Unable to set page accessibility of last stack page.
MSGSTR (MEMNOTFRE,SEVERE) ! Unable to free dynamic memory.
MSGSTR (BADNUMARG,ERROR) ! Invalid number of arguments to DDMF.
MSGSTR (INFBADID,ERROR) ! Bad object id.
MSGSTR (INFBADCOD,ERROR) ! Bad information code.
MSGSTR (BADSTALL,SEVERE) ! Stall point in DAB is invalid.
MSGSTR (EXIT,SUCCESS) ! Exit from Datatrieve requested by operator.
MSGSTR (NOPGETPUT,ERROR) ! Storing and retrieving from ports is not allowed in interactive Datatrieve.
MSGSTR (BADSTRDES,ERROR) ! Invalid string descriptor.
MSGSTR (SELRECCLE,INFO) !SELECT failed due to deadlock.
MSGSTR (SELRECLOS,INFO) !Failed to retrieve a selected record following a re-ready.
MSGSTR (NOMORESEL,INFO) !Collection !A will no longer have a selected record.
MSGSTR (LOCKWAIT,INFO) !Record locked, waiting....

UNDECLARE %QUOTE MSGSTR;