Google
 

Trailing-Edge - PDP-10 Archives - bb-d868b-bm_tops20_v3a_2020_dist - 3a-sources/lnkerr.mac
There are 38 other files named lnkerr.mac in the archive. Click here to see a list.
TITLE	LNKERR - LINK EXTENDED ERROR MESSAGE SEGMENT
SUBTTL	D.M.NIXON/DMN/JLd/SRM/JBC/JNG	27-Feb-78

;THIS SOFTWARE IS FURNISHED UNDER A LICENSE AND MAY ONLY BE USED
;  OR COPIED IN ACCORDANCE WITH THE TERMS OF SUCH LICENSE.
;
;COPYRIGHT (C) 1973, 1978 BY DIGITAL EQUIPMENT CORPORATION, MAYNARD, MASS.

ENTRY	LNKERR
SEARCH	LNKPAR,LNKLOW,MACTEN,UUOSYM,SCNMAC
EXTERN	LNKLOG,TTYCHK

CUSTVR==0		;CUSTOMER VERSION
DECVER==4		;DEC VERSION
DECMVR==0		;DEC MINOR VERSION
DECEVR==765		;DEC EDIT VERSION

VERSION

SALL
SEGMENT
SUBTTL	REVISION HISTORY

;START OF VERSION 1A
;41	ADD LNKFSI MESSAGE
;46	ADD KLUDGE FEATURE MESSAGE
;71	ADD LNKXIT INFO MESSAGES
;102	ADD NO END BLOCK MESSAGE
;105	ADD ITT MESSAGE (FOR BLOCK TYPE 12)
;107	REPLACE KLUDGE BY MIXFOR

;START OF VERSION 2
;135	ADD OVERLAY FACILITY
;162	ADD ISN MESSAGE
;215	ADD OVERLAY ERROR MESSAGES

;START OF VERSION 2B
;237	(13931) CHANGE RPR ERROR TO NBR
;245	ADD WRONG DEVICE FOR OVERLAY FILE ERROR MESSAGE
;253	Add invalid ASCII text block error (ITB)
;262	Add /LINK switch missing error message (LSM)
;275	ADD SIMULA ERROR MESSAGE
;351	LABEL EDIT 237
;377	Add "Attempt to set relocation counter below origin" (SRB) msg
;404	Re-insert edit 316 (support of the ELN message).
;414	Add the FSN message.
;424	Improve the FSN message.

;START OF VERSION 2C
;442	Add the EOI and EOO messages.
;464	Add the IMM message.
;471	Add messages associated with ALGOL debugging system.
;474	Print the module name on F40 fatal errors.
;531	Add UNS message.
;544	SOUP in LINK version 3 stuff for TOPS-20.
;557	Clean up listing for release.

;START OF VERSION 3
;446	CHANGE SOME OF THE ERROR MESSAGES

;START OF VERSION 3A
;560	Release on both TOPS-10 and TOPS-20 as LINK version 3A(560)

;START OF VERSION 4
;564	Make LINK assemble with MACRO 52.
;611	Support COBOL-74
;624	Add a long message for ?LNKKIA.
;635	Add the %LNKTMA and ?LNKABT messages.
;650	Add the ?LNKPUF message.
;661	Make %LNKMDS be L%W.
;673	Replace all of the messages with the updated versions from
;	the new (reviewed) LINK manual.
;731	SEARCH MACTEN,UUOSYM
;765	Release on both TOPS-10 and TOPS-20 as LINK version 4(765)
SUBTTL	FIND MESSAGE

LNKERR:	JFCL	.+1		;INCASE CCL ENTRY
IFE FTSINGLE,<
	HRRZ	T1,SEGBLK+1	;GET SEGMENT NAME
	CAIE	T1,'ERR'	;IF MULTI-SEGMENTED
	JRST	ERROK		;NO
	MOVE	T1,[SAVEAC+P2,,P2]
	BLT	T1,16		;RESTORE ALL ACCS
	MOVE	P1,SAVEAC+T1	;P1 IS STORED TWICE
ERROK:>;END IFE FTSINGLE
	MOVE	T2,ERRCOD	;GET ASCII ERROR CODE
	TRZ	T2,<BYTE (7) 0,0,0,177,177 (1) 1>
	SETZ	T4,		;PUT SIXBIT IN HERE
	SETZ	T1,		;CLEAR JUNK
	LSHC	T1,7		;GET A CHAR
	SUBI	T1," "		;SIXBITIZE
	LSH	T4,6		;MAKE SPACE
	ADDI	T4,(T1)		;ADD INTO WHATS THERE
	JUMPN	T2,.-5		;LOOP FOR ALL (3) CHARS
				;WE NOW USE T4 AS THE HASH TOTAL (18 BITS)
	MOVE	T1,T4		;GET 18 BITS
	IDIVI	T1,E.PRM	;INITIAL HASH
	JUMPE	T1,[AOJA T1,ERRHS1]	;MAKE SURE T1 NOT ZERO
	CAIGE	T1,E.PRM	;IF QUOTIENT LARGER THAN PRIME
	JRST	ERRHS1		;NO
	SUBI	T1,E.PRM	;STEP DOWN
	JRST	.-4		;TRY AGAIN

ERRHS0:	ADD	T2,T1		;STILL IN TABLE
	CAIL	T2,E.PRM	;STILL IN TABLE
	SUBI	T2,E.PRM	;NO,
ERRHS1:	MOVS	T3,HSHTAB(T2)	;PROBE TABLE
	CAIN	T4,(T3)		;MATCH
	JRST	ERRFND		;YES
	JUMPE	T3,ERRFAI	;FAILED IF ZERO, NOT IN TABLE
	JRST	ERRHS0		;TRY AGAIN

ERRIDX:	HRRZ	T1,ERRCOD	;GET NUMBER
	ANDI	T1,<BYTE (7) 0,0,0,177,177 (1) 1>
	TRNE	T1,<BYTE (7) 0,0,0,100>	;PROPAGATE SIGN
	IOR	T1,[BYTE (7) 177,177,177]
	HLRE	T2,@(T3)	;GET FIRST
	HRRE	T4,@(T3)	;AND LAST
	CAML	T1,T2		;RANGE CHECK
	CAMLE	T1,T4
	JRST	.RPOPJ		;NOT IN RANGE?
	SUB	T1,T2		;ADJUST OFFSET OF TABLE
	ADD	T1,(T3)		;PLUS BASE ADDRESS
	HRRZ	T1,1(T1)	;GET ADDRESS OF MESSAGE
	JRST	ERRFN0
;HERE WHEN THE HASH SEARCH IS SUCCESSFUL. PRINT THE MESSAGE(S).

ERRFND:	MOVS	T3,T3		;ADDRESS IN RIGHT AGAIN
	SKIPGE	(T3)		;INDEXED VAI TABLE?
	JRST	ERRIDX		;YES
	HRRZ	T1,T3		;GET MESSAGE POINTER
ERRFN0:	PUSH	P,T1		;SAVE T1
	OUTVIA	.TCRLF##	;START NEW LINE
	SKIPA	T1,0(P)		;RELOAD T1
ERRFN1:	PUSH	P,T1		;SAVE IT
	ADDI	T1,1		;POINT TO MESSAGE
	OUTVIA	.TSTRG##	;OUTPUT MESSAGE
	POP	P,T1		;GET BACK POINTER
	SKIPN	T1,(T1)		;MORE TO DO?
	JRST	ERRFAI		;NO
	SKIPN	1(T1)		;BUT IS IT A REAL MESSAGE?
	JRST	ERRFN1		;NO, JUST TRANSFER
	JRST	ERRFN0		;YES, NEED A CRLF ALSO

ERRFAI:	JRST	ER.FIN##	;FINISH OFF MESSAGE

.RPOPJ::			;HERE TO RETURN CPOPJ
	MOVE	T1,UUOTRAP	;GET PC WORD
	TXZ	T1,PC.LIP	;TURN OF LAST INST PUBLIC INCASE EXECUTE ONLY
IFE FTSINGLE,<
	HRRZ	T2,SEGBLK+1	;GET THIS SEGMENT NAME
	CAIE	T2,'ERR'	;IF MULTI-SEGMENTED
>
	JRSTF	@T1		;NO
IFE FTSINGLE,<
	PUSH	P,T1		;STORE RETURN ADDRESS
	JRST	@LSTSEG		;AND RETURN VIA PREV SEGMENT
>
SUBTTL	HASH MACROS

IF1,<			;ALL ON PASS 1
 DEFINE GETSYM (N)<$ER'N==0>
 N==0
	XLIST
 REPEAT E.PRM,<
  GETSYM \N
  N==N+1
 >

 DEFINE HASH (CODE,GOTO,TEXT)<
%ER'CODE:
 IFIDN <GOTO><@>,<
	1B0+CODE'TAB>
 IFDIF <GOTO><@>,<
	GOTO>
	ASCIZ	\TEXT\
  SXB=(<SIXBIT /CODE/>)
  Q=SXB/E.PRM
  R=SXB-Q*E.PRM
  IFGE Q-E.PRM,<Q=Q-Q/E.PRM*E.PRM>
  IFE Q,<Q=1>
  TRY=1
  ITEM Q,\R,CODE
  IFL E.PRM-TRY,<PRINTX HASH FAILURE>
 >

 DEFINE ITEM (QT,RM,CD)<
  IFN $ER'RM,<
   R=R+QT
   IFL E.PRM-R,<R=R-R/E.PRM*E.PRM>
   IFGE E.PRM-<TRY=TRY+1>,<ITEM Q,\R,CD>
  >
  IFE $ER'RM,<
   $ER'RM=SXB,,%ER'CD
>>>

IF2,<
 DEFINE HASH (CODE,GOTO,TEXT)<
  %ER'CODE:
  PURGE %ER'CODE
  IFIDN <GOTO><@>,<
	1B0+CODE'TAB>
  IFDIF <GOTO><@>,<
	GOTO>
	XLIST
	ASCIZ	\TEXT\
	LIST
>>
DEFINE TABLE (CODE,N)<
	EXP	CODE'N
>
DEFINE VIATBL (CODE,FIRST,LAST)<
CODE'TAB:	<FIRST&777777>,,<LAST&777777>
	N=FIRST
 REPEAT LAST-FIRST,<
  M=N&777
  TABLE CODE,\M
  N=N+1
>>

DEFINE INDEX (CODE,IDX,GOTO,TEXT)<
 IRP CODE,<
  N=IDX&777
  LABEL CODE,\N
 >
 EXP	GOTO
	XLIST
	ASCIZ	\TEXT\
	LIST
>

DEFINE LABEL (CODE,NUMBER)<
CODE'NUMBER:
>
SUBTTL	HASH TABLE

HSHTAB:
IF1,<	BLOCK	E.PRM>		;ALLOCATE SPACE ON PASS 1
IF2,<
 DEFINE GETSYM (N)<
	$ER'N
 >
 N==0
	SALL
 REPEAT E.PRM,<
  GETSYM \N
  N==N+1
 >

 DEFINE PRGSYM (N)<
  PURGE $ER'N
 >
 N==0
 REPEAT E.PRM,<
  PRGSYM \N
  N==N+1
 >
 PURGE N,SXB,Q,R,TRY
>
SUBTTL	INDIRECT TABLES

VIATBL	(FEE,-1,32)
VIATBL	(FLE,0,32)
VIATBL	(FRE,0,32)
VIATBL	(GSE,0,32)
.HWFRMT		;SAVE SPACE
COMMENT	\
SHORT LEVEL MESSAGE
THESE ARE INCORE AT ALL TIMES (IN OTHER SEGMENTS)

CODE	LVL	SEV	MESSAGE


ABT	31	31	Load aborted due to %LNKTMA errors, max. /ARSIZE
			needed was  [decimal]
AMP	 8	 8	ALGOL main program not loaded
ANC	31	31	Address not in core
ARL	 8	 8	Ambiguous request in link [decimal] for [symbol]
			defined in links  [decimal]
AZW	31	31	Allocating zero words
B4R	 8	 8	Bad F40 produced .REL file for [name]
CEF	31	31	Core expansion failed
CLF	 1	 1	Closing LOG file, continuing on [file]
CMC	31	31	Cannot mix COBOL-68 and COBOL-74 compiled code
			Error detected in module [module] from	[file]
CMF	31	31	COBOL module must be loaded first
CNW	31	31	Code not yet written at [label]
CSF	 1	 1	Creating saved file
DEB	 *	 1	[name] execution
DLT	 *	 1	Execution deleted
DNA	31	31	DDT not available
DNS	 8	 8	Device not specified for /[switch]
DRC	 8	 8	Decreasing  relocation	counter  [symbol]   from
			[octal] to  [octal]
DSC	31	31	Data store to COMMON [symbol] not in link number
			[decimal] for  [module] in [file]
DSL	31	31	Data store  to	location  [octal]  not	in  link
			number [decimal] for  [module] in [file]
DSO	31	31	Data statement overflow in module [name]
DUZ	31	31	Decreasing undefined symbol count below zero
EAS	31	31	Error creating overflow file for area AS
ECE	31	31	Error creating .EXE file
EHC	31	31	Error creating overflow file for area HC
EID	31	31	Error on input device status [status] for [file]
ELC	31	31	Error creating overflow file for area LC
ELF	 1	 1	End of LOG file
ELN	 7	 1	End of link number [number], name [name]
ELS	31	31	Error creating overflow file for area LS
EMS	 1	 1	End of MAP segment
EOE	31	31	.EXE file output error
EOI	31	31	Error on input status [status] for [file]
EOO	31	31	Error on output status [status] for [file]
EOV	31	31	Error creating overlay file for [file]
ESN	31	31	Extended symbol not expected
EXP	 4	 1	Expanding low segment to [decimal]P
EXS	 1	 1	EXIT segment
FCD	31	31	FORTRAN confused about data statements in module
			[name]
FCF	 1	 1	Final code fixups
FEE	31	31	(Indexed file LOOKUP, ENTER, or RENAME error)
FIN	 1	 1	LINK finished
FLE	31	31	(Indexed file LOOKUP, ENTER, or RENAME error)
FOV	31	31	Cannot overlay F40 compiled code in [module]
FRE	31	31	(Indexed file LOOKUP, ENTER, or RENAME error)
FSF	 8	 8	FORTRAN subroutine [name] not in expected  form,
			MIXFOR fixup not  done
FSI	 8	 8	FORTRAN requires FOROTS, /FORSE switch ignored
FSN	31	31	FUNCT. subroutine not loaded
GSE	31	31	(Indexed file LOOKUP, ENTER, or RENAME error)
HSL	31	31	Attempt to set high segment origin too low
HTL	31	31	Symbol hash table too large
IAS	31	31	Error inputting area AS
I4D	31	31	Illegal F40 DATA code [octal] in module [name]
I4S	31	31	Illegal F40 sub-block [octal] in module [name]
I4T	31	31	Illegal F40 table entry [octal] in module [name]
IBC	31	31	Attempt to increase size of  blank  COMMON  from
			[decimal] to  [decimal]
ICI	31	31	Insufficient core to initialize LINK
IDM	31	31	Illegal data mode for device
IFD	31	31	INIT failure for device [device]
IHC	31	31	Error inputting area HC
ILC	31	31	Error inputting area LC
ILS	31	31	Error inputting area LS
IMA	 8	 8	Incremental maps not yet available
IMM	 *	 1	[number] included  modules  missing  (from  file
			[file])
INS	31	31	I/O data block not set up
IOV	31	31	Input error for overlay file
IPO	31	31	Invalid Polish operator [octal]
IPX	31	31	Invalid PSECT index
IRB	31	31	Illegal REL Block Type [octal] for  [module]  in
			[file]
ISD	 8	 8	Inconsistent symbol definition for [symbol]
ISN	31	31	Illegal symbol name
ISO	31	31	Invalid store operator [octal]
ISP	31	31	Incorrect symbol pointer
ISS	 8	 8	Insufficient space for symbol table (after PSECT
			[name])--table truncated
IST	31	31	Inconsistency in switch table
ITT	 8	 8	Illegal type 12 link number  [octal]  in  module
			[name]
IUU	 *	31	Illegal user UUO at PC [octal]
IVC	31	31	Index validation check failed at [address]
KIA	31	31	Cannot mix KI10 and KA10 compiled code
LDS	 1	 1	LOAD segment
LFC	 1	 1	LOG file continuation
LFI	 1	 1	LOG file initilaization
LII	 8	 1	Library index inconsistent, continuing
LIM	 1	 1	LINK initialization
LMN	 6	 1	Loading module [module]
LNA	 8	 8	Link name [name] already assigned to link number
			[decimal]
LNC	31	31	Link number [decimal] not in core
LNL	 8	 8	Link number [decimal] not loaded
LNN	 8	 8	Link name [name] not assigned
LSM	 8	 8	/LINK switch missing while loading  link  number
			[decimal]  --  /LINK assumed
LSS	 *	 1	Library Search Symbols (Entry points)
MDS	31	 8	Multiply-Defined  Global  symbol   [symbol]   in
			module	[name]	defined  value	= [octal],  this
			value = [octal]
MOV	 1	 1	Moving low segment to expand area [area]
MPS	 1	 1	MAP segment
MRN	 1	 1	Multiple regions not yet implemented
MSN	 8	 8	MAP sorting not yet implemented
MSR	31	31	/MIXFOR switch required to mix F40  and  FORTRAN
			code
MSS	 8	 8	MAXCOR set too small, increasing to [decimal]P
MTB	 8	 8	MAXCOR too big, [decimal]P used
MTS	 8	 8	MAXCOR	too  small,  at  least	 [decimal]P   is
			required
NBR	31	31	Attempt to position to node before root
NCL	 8	 8	Not enough core to load job, saved as [file]
NCX	 8	 1	Not enough core to load and  execute  job,  will
			run from  [file]
NEB	 8	 8	No end block seen for [module]
NED	31	24	Non-existent device
NSA	 *	 1	No start address
OAS	31	31	Error outputting area AS
ODV	31	31	Overlay file must be created on a file structure
OEL	 8	 8	Output error  on  LOG  file,  file  closed,  job
			continuing
OEM	 8	 8	Output error  on  MAP  file,  file  closed,  job
			continuing
OES	 8	 8	Output error on symbol file,  file  closed,  job
			continuing
OEX	 8	 8	Output error  on  XPN  file,  file  closed,  job
			continuing
OFN	31	31	Old FORTRAN (F40) module not available
OHC	31	31	Error outputting area HC
OHN	31	31	Overlay handler not loaded
OLC	31	31	Error outputting area LC
OLS	31	31	Error outputting area LS
OMB	31	31	/OVERLAY switch must be first
ONS	 8	 1	Overlays not supported in this version of LINK
OOV	31	31	Output error for overlay  file	status	[status]
			for [file]
OS2	 1	 1	Overlay segment phase 2
PAS	 1	 1	Area AS overflowing to DSK
PBI	 8	 8	Program break [octal] invalid in [name]
PEF	31	 8	Premature end of file in [file]
PHC	 1	 1	Area HC overflowing to DSK
PLC	 1	 1	Area LC overflowing to DSK
PLS	 1	 1	Area LS overflowing to DSK
POO	 8	 8	PSECT overlay occurred--[name],[name]
PSF	31	31	Polish symbol fixups not yet implemented
PUF	31	31	PAGE. UUO failed, error code was [octal]
RBS	31	31	REL Block Type [octal] too short for [file]
RCU	31	31	Relocation counter [symbol]  undefined,  set  to
			[symbol]
RED	 1	 1	Reducing low segment to [decimal]P
RER	 *	 1	Request External  References  (Inter-Link  Entry
			Points)
RGS	 1	 1	Rehashing Global symbol table from [decimal]  to
			[decimal]
RLC	 *	 1	Reloc ctr.  initial value current value [octal]
RUC	31	31	Returning unavailable core
SFU	 8	 8	Symbol table fouled up
SIF	31	31	Symbol insert failure, non-zero hole found
SLS	 8	 8	Symbols must be in low segment
SMP	 8	 8	SIMULA main program not loaded
SNC	31	31	Symbol [symbol]  already  defined,  but  not  as
			COMMON
SNL	 1	 1	Scanning new command line
SNP	 8	 8	Subroutine [symbol] in link number [decimal] not
			on path for call from link number  [decimal]
SOE	31	31	Saved file output error - status [status]
SRB	 8	 8	Attempt to set relocation counter  [name]  below
			initial value of  [octal]
SSN	 8	 8	Symbol table sorting not yet implemented
SST	 1	 1	Sorting symbol table
STC	 1	 1	Symbol table completed
T13	31	31	LVAR (type 13) code not implemented
TDS	 8	 8	Too late to delete initial symbols
TEC	31	31	Trying to expand COMMON [symbol] from  [decimal]
			to [decimal] in module	[name]
TMA	31	 8	Too many ambiguous requests  in  link  [number],
			use  /ARSIZE:[decimal]
TTF	 8	 8	Too many titles found
UAR	 8	 8	Undefined assign for [symbol] in [file]
UGS	 *	 1	Undefined global symbols
UNS	31	31	Universal files not supported loading [file]
URC	31	 1	Unknown Radix-50 symbol code
USA	 8	 8	Undefined start address [symbol]
USC	31	 8	Undefined subroutine  [name]  called  from  link
			number [decimal]
VAL	 *	 1	[symbol] [value] [type]
XCT	 *	 1	[name] Execution
ZSV	 8	 8	Zero switch value illegal

END OF COMMENT \
SUBTTL	LONG MESSAGES


HASH	ABT,0,<
	You loaded programs containing more  ambiguous	subroutine
	requests than can fit in the tables of one or more overlay
	links.	You received a LNKARL message for  each  ambiguous
	request,  and a LNKTMA message for each link with too many
	requests.  You can solve this problem  in  either  of  two
	ways.	One  is  to  use  the  /ARSIZE	switch	before the
	/OVERLAY switch, thus expanding all the tables.  The other
	is to use the /ARSIZE switch just before each /LINK switch
	to expand the tables separately.>

HASH	AMP,0,<
	You loaded ALGOL procedures, but  no  main  program.   The
	missing start address and undefined symbols will terminate
	execution.>

HASH	ANC,0,<
	LINK expected a particular user address to be  in  memory,
	but  it  is  not  there.   This is an internal LINK error.
	This message is not expected to occur.	If it does, please
	notify	 your  Software  Specialist  or  send  a  Software
	Performance Report (SPR) to DIGITAL.>

HASH	ARL,0,<
	More than one successor link can satisfy a  call  from	an
	ancestor  link.  The ancestor link requests an entry point
	that is contained in two or more of its  successors.   You
	should	 revise  your  overlay	structure  to  remove  the
	ambiguity.

	If you execute the current load, one of the following will
	occur when the ambiguous call is executed:

	1.  If only  one  module  satisfying  the  request  is	in
	    memory, that module will be called.

	2.  If two or more modules satisfying the request  are	in
	    memory,  the  one  with  the most links of its path in
	    memory will be called.

	3.  If no modules satisfying the request  are  in  memory,
	    the one with the most links of its path in memory will
	    be called.

	If a module cannot be selected	by  the  methods  2  or  3
	above, one of the modules will be called at random.>

HASH	AZW,0,<
	LINK's memory manager was called  with	a  request  for  0
	words.	 This  is an internal LINK error.  This message is
	not expected to occur.	If it  does,  please  notify  your
	Software  Specialist or send a Software Performance Report
	(SPR) to DIGITAL.>

HASH	B4R,0,<
	Either the compiler produced incorrect code  or  the  .REL
	file  was  incorrectly	modified.  Two possible causes for
	the error are:	a  table  is  too  long  (more	than  2^18
	words);   or  a table that should have paired words has an
	odd length.  LNKB4R is usually followed by a fatal error.>

HASH	CEF,0,<
	LINK cannot expand core further.  All permitted  overflows
	to  disk  have	been  tried, but your program is still too
	large for available memory.  A probable cause is  a  large
	global symbol table, which cannot be overflowed to disk.>

HASH	CLF,0,<
	You have changed the log file device.  The old log file is
	closed;   further  log	entries are written in the new log
	file.>

HASH	CMC,0,<
	You cannot use COBOL-68 and COBOL-74  files  in  the  same
	load.	Compile  all COBOL programs with the same compiler
	and reload.>

HASH	CMF,0,<
	You are loading a  mixture  of	COBOL-compiled	files  and
	other files.  Load one of the COBOL-compiled files first.>

HASH	CNW,0,<
	You attempted to use an unimplemented feature.	This is an
	internal  LINK	error.	 This  message	is not expected to
	occur.	If it does, please notify your Software Specialist
	or send a Software Performance Report (SPR) to DIGITAL.>

HASH	CSF,0,<
	LINK is generating your .EXE file.>

;(There is no long text for the DEB message.)

;(There is no long text for the DLT message.)

HASH	DNA,0,<
	A monitor call for SYS:UDDT.EXE failed.>

HASH	DNS,0,<
	You  used  a  device   switch	(for   example,   /REWIND,
	/BACKSPACE),  but  LINK cannot associate a device with the
	switch.  Neither LINK's default device nor any device  you
	gave  with the /DEFAULT switch can apply.  Give the device
	with or before the switch (in the same command line).>

HASH	DRC,0,<
	You are using the /SET switch to reduce the  value  of	an
	already  defined  relocation  counter.	 Unless  you  know
	exactly  where	each  module  is  loaded,  code   may	be
	overwritten.>

HASH	DSC,0,<
	You loaded a FORTRAN-compiled  file  with  DATA  statement
	assignments  to a COMMON area.	The COMMON area is already
	defined in an ancestor link.>

HASH	DSL,0,<
	You have a data store for an absolute location outside the
	specified link.  Load the module into the root link.


				   NOTE

	    If [octal] is less	than  140,  this  message  has
	    level 8 and severity 8.


	>

HASH	DSO,0,<
	Incorrect code has been generated  by  the  F40  compiler.
	This message is not expected to occur.	If it does, please
	notify	your  Software	Specialist  or	send  a   Software
	Performance Report (SPR) to DIGITAL.>

HASH	DUZ,0,<
	LINK's undefined symbol count has become  negative.   This
	message  is  not  expected  to	occur.	If it does, please
	notify	your  Software	Specialist  or	send  a   Software
	Performance Report (SPR) to DIGITAL.>

HASH	EAS,0,<
	LINK could not make the ALGOL symbol table  on	the  disk.
	You  could  be	over your disk quota, or the disk could be
	full or have errors.>

HASH	ECE,0,<
	LINK could not write the saved	file  on  the  disk.   You
	could  be  over your disk quota, or the disk could be full
	or have errors.>

HASH	EHC,0,<
	LINK could not write your high-segment code on	the  disk.
	You  could  be	over your disk quota, or the disk could be
	full or have errors.>

IFE TOPS20,<
HASH	EID,0,<
	A read error has occurred on the input device.	Use of the
	device is terminated and the file is released.	The status
	is represented by the right half of the file status  word.
	Refer	to   the   DECsystem-10   Monitor  Calls  for  the
	explanation of the file status bits.>
> ;END IFE TOPS20

IFN TOPS20,<
HASH	EID,0,<
	A read error has occurred on the input device.	Use of the
	device is terminated and the file is released.>
> ;END IFN TOPS20

HASH	ELC,0,<
	LINK could not write your low-segment code  on	the  disk.
	You  could  be	over your disk quota, or the disk could be
	full or have errors.>

;(There is no long text for the ELF message.)

HASH	ELN,0,<
	The link is loaded.>

HASH	ELS,0,<
	LINK could not write your local symbol table on the  disk.
	You  could  be	over your disk quota, or the disk could be
	full or have errors.>

HASH	EMS,0,<
	The map file is completed and closed.>

HASH	EOE,0,<
	LINK could not write the saved	file  on  the  disk.   You
	could  be  over your disk quota, or the disk could be full
	or have errors.>

IFE TOPS20,<
HASH	EOI,0,<
	An error has been detected while reading the  named  file.
	The  status  is  represented by the right half of the file
	status word.  Refer to the DECsystem-10 Monitor Calls  for
	the explanation of the file status bits.>
> ;END IFE TOPS20

IFN TOPS20,<
HASH	EOI,0,<
	An error has been detected while reading the named file.>
> ;END IFN TOPS20

IFE TOPS20,<
HASH	EOO,0,<
	An error has been detected while writing the  named  file.
	The  status  is  represented by the right half of the file
	status word.  Refer to the DECsystem-10 Monitor Calls  for
	the explanation of the file status bits.>
> ;END IFE TOPS20

IFN TOPS20,<
HASH	EOO,0,<
	An error has been detected while writing the named file.>
> ;END IFN TOPS20

HASH	EOV,0,<
	LINK cannot write the overlay file on disk.   You  may	be
	over  your disk quota;	the disk may be full;  or the disk
	may have errors.>

HASH	ESN,0,<
	Long symbol names  (more  than	six  characters)  are  not
	implemented.   This  message is not expected to occur.	If
	it does, please notify your Software Specialist or send  a
	Software Performance Report (SPR) to DIGITAL.>

HASH	EXP,0,<
	LINK is expanding memory to the specified amount.  You can
	speed  up  future loads of this program by using the /CORE
	switch to allocate the required core.>

HASH	EXS,0,<
	LINK is in the last stages of loading  your  program  (for
	example,  creating  .EXE  and  symbol files, preparing for
	execution if requested).>

HASH	FCD,0,<
	You are loading incorrect F40-compiled code  caused  by  a
	source statement of the form

	     DATA A(I),I=1,4/1,2,3,4/

	instead of the form

	     DATA (A(I),I=1,4)/1,2,3,4/

	This message is not expected to occur.	If it does, please
	notify	 your  Software  Specialist  or  send  a  Software
	Performance Report (SPR) to DIGITAL.>

HASH	FCF,0,<
	LINK  is  reading  one	or  both  segment  overflow  files
	backwards  to  perform	any  needed code fixups.  This may
	cause considerable disk overhead, but occurs only if  your
	program is too big for memory.>

HASH	FEE,@

HASH	FIN,0,<
	LINK is finished.  Control is passed to the monitor, or to
	the loaded program for execution.>

HASH	FLE,@

HASH	FOV,0,<
	You cannot load F40-compiled code in an overlay structure.
	Recompile with the FORTRAN compiler.>

HASH	FRE,@

HASH	FSF,0,<
	LINK  cannot  find  a  return	from   this   F40-compiled
	subroutine.>

HASH	FSI,0,<
	You gave the /FORSE switch while loading  FORTRAN-compiled
	code.>

HASH	FSN,0,<
	During final processing of your root link, LINK found that
	the FUNCT. subroutine was not loaded.  This would cause an
	infinite recursion if your  program  were  executed.   The
	FUNCT. subroutine is requested by the overlay handler, and
	is usually loaded from a default system  library.   Either
	you  prevented	searching  of system libraries, or you did
	not  load  a  main  program  from  an	overlay-supporting
	compiler into the root link.>

HASH	GSE,@

IFE TOPS20,<
HASH	HSL,0,<
	You have set the high-segment counter to a page containing
	low-segment code.  Reload, using the /SET:.HIGH.:n switch,
	or (for MACRO programs)  reassemble  after  changing  your
	TWOSEG	 pseudo-op.    Note   that   you  cannot  set  the
	high-segment counter  below  400000  for  a  KI10  monitor
	before 5.07, or for any KA10 monitor.>
> ;END IFE TOPS20

IFN TOPS20,<
HASH	HSL,0,<
	You have set the high-segment counter to a page containing
	low-segment code.  Reload, using the /SET:.HIGH.:n switch,
	or (for MACRO programs)  reassemble  after  changing  your
	TWOSEG pseudo-op.>
> ;END IFN TOPS20

HASH	HTL,0,<
	Your symbol hash table is larger than the maximum LINK can
	generate  (about  50P).   This	table  size is an assembly
	parameter.  This message is not expected to occur.  If	it
	does,  please  notify  your  Software Specialist or send a
	Software Performance Report (SPR) to DIGITAL.>

HASH	IAS,0,<
	An error  occurred  while  reading  in	the  ALGOL  symbol
	table.>

HASH	I4D,0,<
	Incorrect code has been generated  by  the  F40  compiler.
	This message is not expected to occur.	If it does, please
	notify	your  Software	Specialist  or	send  a   Software
	Performance Report (SPR) to DIGITAL.>

HASH	I4S,0,<
	Incorrect code has been generated  by  the  F40  compiler.
	This message is not expected to occur.	If it does, please
	notify	your  Software	Specialist  or	send  a   Software
	Performance Report (SPR) to DIGITAL.>

HASH	I4T,0,<
	Incorrect code has been generated  by  the  F40  compiler.
	This message is not expected to occur.	If it does, please
	notify	your  Software	Specialist  or	send  a   Software
	Performance Report (SPR) to DIGITAL.>

HASH	IBC,0,<
	A blank COMMON	area  cannot  be  expanded  once  defined.
	Either	load the module with the largest definition first,
	or use the /COMMON switch to reserve the needed space.>

HASH	ICI,0,<
	LINK needs more memory than is available.>

HASH	IDM,0,<
	You specified an illegal combination of  device  and  data
	mode  (for  example, terminal and dump mode).  Respecify a
	legal device.>

HASH	IFD,0,<
	An OPEN or INIT monitor  call  for  the  specified  device
	failed.  The device may be under another user's control.>

HASH	IHC,0,<
	An error  occurred  while  reading  in	your  high-segment
	code.>

HASH	ILC,0,<
	An error occurred while reading in your low-segment code.>

HASH	ILS,0,<
	An error occurred  while  reading  in  your  local  symbol
	table.>

HASH	IMA,0,<
	The INCREMENTAL keyword for /MAP is not implemented.   The
	switch is ignored.>

;(There is no long text for the IMM message.)

HASH	INS,0,<
	LINK attempted a monitor call (for example, LOOKUP, ENTER)
	for  a	channel  that  is not set up.  This is an internal
	LINK error.  This message is not expected to occur.  If it
	does,  please  notify  your  Software Specialist or send a
	Software Performance Report (SPR) to DIGITAL.>

IFE TOPS20,<
HASH	IOV,0,<
	An error occurred when	reading  the  overlay  file.   The
	status is represented by the right half of the file status
	word.  Refer to the DECsystem-10  Monitor  Calls  for  the
	explanation of the file status bits.>
> ;END IFE TOPS20

IFN TOPS20,<
HASH	IOV,0,<
	An error occurred when reading the overlay file.>
> ;END IFN TOPS20

HASH	IPO,0,<
	You are attempting to load a file  containing  an  invalid
	REL  Block  Type  11  (POLISH).   This is an internal LINK
	error.	This message is not  expected  to  occur.   If	it
	does,  please  notify  your  Software Specialist or send a
	Software Performance Report (SPR) to DIGITAL.>

HASH	IPX,0,<
	A REL block contains a reference to a  nonexistent  PSECT.
	This  error  is probably caused by a fault in the language
	translator used for the program.>

HASH	IRB,0,<
	The file is not in the proper binary format.  It may  have
	been   generated  by  a  translator  that  LINK  does  not
	recognize, or it may be an ASCII or .EXE file.>

HASH	ISD,0,<
	The named symbol either has a partial  definition  and	an
	explicit  definition,  or  has	two  partial  definitions.
	Later resolution of partial definitions may  result  in  a
	multiply-defined global symbol.

	A partial definition is one in which a symbol  is  defined
	in  terms  of  other  undefined symbols.  If your code has
	A=:B##+3 and A=:7, then either B## will have to be 4 or  A
	will be multiply-defined.>

HASH	ISN,0,<
	The LINK symbol table routine was called  with	the  blank
	symbol.   This is an internal LINK error.  This message is
	not expected to occur.	If it  does,  please  notify  your
	Software  Specialist or send a Software Performance Report
	(SPR) to DIGITAL.>

HASH	ISO,0,<
	You are attempting to load a file  containing  an  invalid
	REL  Block  Type  11  (POLISH).   This is an internal LINK
	error.	This message is not  expected  to  occur.   If	it
	does,  please  notify  your  Software Specialist or send a
	Software Performance Report (SPR) to DIGITAL.>

HASH	ISP,0,<
	There is an  error  in	the  global  symbol  table.   This
	message  is  not  expected  to	occur.	If it does, please
	notify	your  Software	Specialist  or	send  a   Software
	Performance Report (SPR) to DIGITAL.>

;(There is no long text for the ISS message.)

HASH	IST,0,<
	LINK has found errors in the switch table passed from  the
	SCAN  module.	This message is not expected to occur.	If
	it does, please notify your Software Specialist or send  a
	Software Performance Report (SPR) to DIGITAL.>

HASH	ITT,0,<
	REL Block Type 12 (CHAIN) must contain a number from 1	to
	100 (octal) in its first word.>

;(There is no long text for the IUU message.)

HASH	IVC,0,<
	The range checking of LINK's internal  tables  and  arrays
	failed.   The address given is the point in a LINK segment
	at which failure occurred.  This message is  not  expected
	to  occur.   If  it  does,  please  notify  your  Software
	Specialist or send a Software Performance Report (SPR)	to
	DIGITAL.>

HASH	KIA,0,<
	Some modules loaded were compiled for the KA10	processor,
	and  some  for	the KI10 processor.  Recompile so that all
	modules are compiled for the same processor.>

HASH	LDS,0,<
	The LINK module LNKLOD is beginning its processing.>

;(There is no long text for the LFC message.)

;(There is no long text for the LFI message.)

HASH	LII,0,<
	A REL Block Type 14 (INDEX) for a MAKLIB or FUDGE2 library
	file  is  inconsistent.   The library is searched, but the
	index is ignored.>

HASH	LIM,0,<
	LINK is ready for your input.>

HASH	LMN,0,<
	LINK is loading the named module.>

HASH	LNA,0,<
	You used this name for another link.  Specify a  different
	name for this link.>

HASH	LNC,0,<
	LINK cannot find the named link in memory.   This  message
	is  not expected to occur.  If it does, please notify your
	Software Specialist or send a Software Performance  Report
	(SPR) to DIGITAL.>

HASH	LNL,0,<
	The link with this number has not yet  been  loaded.   The
	/NODE  switch  is  ignored.  If you have used link numbers
	instead of link names with the /NODE switch, you may  have
	confused  the  link  numbers.	To  avoid  this,  use link
	names.>

HASH	LNN,0,<
	The name you gave with the /NODE switch is not the name of
	any loaded link.  The switch is ignored.>

HASH	LSM,0,<
	Your use of the /NODE switch shows that you want to  begin
	a  new	overlay  link,	but  the  current  link is not yet
	completely  loaded.    LINK   assumes	a   /LINK   switch
	immediately preceding the /NODE switch, and loads the link
	(without a link name).>

;(There is no long text for the LSS message.)

HASH	MDS,0,<
	The named module contains a new definition of  an  already
	defined  global symbol.  The new definition is used.  Make
	the definitions consistent and reload.>

HASH	MOV,0,<
	LINK is rearranging the low segment to make more room  for
	the  specified	area.	area  is  one  of  the	following:
	AS=ALGOL symbol table, BG=bound global symbols, DY=dynamic
	free  core, FX=fixup area, GS=global symbol table, HC=your
	high-segment  code,  LC=your  low-segment  code,  LS=local
	symbol tables, RT=relocation tables.>

HASH	MPS,0,<
	The LINK module LNKMAP is writing a map file.>

HASH	MRN,0,<
	Overlay structures consisting of more than one region  are
	not supported.>

HASH	MSN,0,<
	Alphabetical or numerical sorting of the map file  is  not
	implemented.   The  symbols  in the map file appear in the
	order they are found in the .REL files.>

HASH	MSR,0,<
	You must use the /MIXFOR  switch  to  load  a  mixture	of
	modules  compiled  by F40 and FORTRAN.	The /MIXFOR switch
	must precede any module names or filenames.>

HASH	MSS,0,<
	The current value of MAXCOR  is  too  small  for  LINK	to
	operate.  You can speed up future loads of this program by
	setting the /MAXCOR switch to this expanded  size  at  the
	beginning of the load.>

HASH	MTB,0,<
	You are attempting to set MAXCOR so  large  that  the  low
	segment cannot fit before the high segment.  LINK will use
	only the core indicated.>

HASH	MTS,0,<
	LINK needs more space  than  you  gave	with  the  /MAXCOR
	switch.   Give	a  new	/MAXCOR  switch  with at least the
	required size.>

HASH	NBR,0,<
	The argument you gave for the /NODE switch would  indicate
	a  link  before  the  root  link.   (For  example,  from a
	position after the third link in a path, you  cannot  give
	/NODE:-4.)>

HASH	NCL,0,<
	Your program is too large to load  from  LINK.	 LINK  has
	saved  it  as  an  .EXE file on disk and cleared your user
	memory.  You can use a GET or RUN command to load the .EXE
	file.	If  it	is still too large:  use a larger machine;
	obtain	a  larger  core  limit;   or  define  an   overlay
	structure for your program.>

HASH	NCX,0,<
	Your program is too large to load into memory;	LINK saved
	it  as	an  .EXE  file	on  disk.  LINK will automatically
	execute the program with a RUN monitor call, but the  .EXE
	file will not be deleted.>

HASH	NEB,0,<
	No REL Block Type 5 (END) was found in the  named  module.
	This  will  happen  if LINK finds two Type 6 Blocks (NAME)
	without an intervening END, or if an end-of-file is  found
	before	the  END.   Fatal  messages  usually  follow  this
	message.>

HASH	NED,0,<
	You gave a device that does  not  exist  on  this  system.
	Correct your input files and reload.>

;(There is no long text for the NSA message.)

HASH	OAS,0,<
	An error occurred  while  writing  out	the  ALGOL  symbol
	table.>

HASH	ODV,0,<
	Specify a disk device for the overlay file.>

IFE TOPS20,<
HASH	OEL,0,<
	An error has occurred on the output file.  The output file
	is closed at the end of the last data successfully output.
	The status is represented by the right half  of  the  file
	status	word.  Refer to the DECsystem-10 Monitor Calls for
	the explanation of the file status bits.>
> ;END IFE TOPS20

IFN TOPS20,<
HASH	OEL,0,<
	An error has occurred on the output file.  The output file
	is  closed  at	the  end  of  the  last  data successfully
	output.>
> ;END IFN TOPS20

IFE TOPS20,<
HASH	OEM,0,<
	An error has occurred on the output file.  The output file
	is closed at the end of the last data successfully output.
	The status is represented by the right half  of  the  file
	status	word.  Refer to the DECsystem-10 Monitor Calls for
	the explanation of the file status bits.>
> ;END IFE TOPS20

IFN TOPS20,<
HASH	OEM,0,<
	An error has occurred on the output file.  The output file
	is  closed  at	the  end  of  the  last  data successfully
	output.>
> ;END IFN TOPS20

IFE TOPS20,<
HASH	OES,0,<
	An error has occurred on the output file.  The output file
	is closed at the end of the last data successfully output.
	The status is represented by the right half  of  the  file
	status	word.  Refer to the DECsystem-10 Monitor Calls for
	the explanation of the file status bits.>
> ;END IFE TOPS20

IFN TOPS20,<
HASH	OES,0,<
	An error has occurred on the output file.  The output file
	is  closed  at	the  end  of  the  last  data successfully
	output.>
> ;END IFN TOPS20

HASH	OEX,0,<
	An error has occurred on the output file.  The output file
	is closed at the end of the last data successfully output.
	The status is represented by the right half  of  the  file
	status	word.  Refer to the DECsystem-10 Monitor Calls for
	the explanation of the file status bits.>

IFE TOPS20,<
HASH	OFN,0,<
	LINK handles F40-compiled code	with  its  LNKF40  module.
	Your  installation  has  substituted  a  dummy	version of
	LNKF40.   You  can  either  recompile  with  the   FORTRAN
	compiler, or request your installation to reload LINK with
	the real LNKF40 module.>
> ;END IFE TOPS20

IFN TOPS20,<
HASH	OFN,0,<
	The standard released version of LINK does not support F40
	code.>
> ;END IFN TOPS20

HASH	OHC,0,<
	An error occurred  while  writing  out	your  high-segment
	code.>

HASH	OHN,0,<
	Internal symbols in  the  overlay  handler  could  not	be
	referenced.   If  you  are using your own overlay handler,
	this is a user error;  if not, it is  an  internal  error.
	This message is not expected to occur.	If it does, please
	notify	your  Software	Specialist  or	send  a   Software
	Performance Report (SPR) to DIGITAL.>

HASH	OLC,0,<
	An error  occurred  while  writing  out  your  low-segment
	code.>

HASH	OLS,0,<
	An error occurred while  writing  out  your  local  symbol
	table.>

HASH	OMB,0,<
	The /OVERLAY switch must appear before you can use any	of
	the  following	switches:   /ARSIZE,  /LINK, /NODE, /PLOT,
	/SPACE.  (It is sufficient that the /OVERLAY switch appear
	on the same line as the first of these switches you use.)>

;(There is no long text for the ONS message.)

IFE TOPS20,<
HASH	OOV,0,<
	An error has occurred while writing the overlay file.  The
	status is represented by the right half of the file status
	word.  Refer to the DECsystem-10  Monitor  Calls  for  the
	explanation of the file status bits.>
> ;END IFE TOPS20

IFN TOPS20,<
HASH	OOV,0,<
	An error has occurred while writing the overlay file.>
> ;END IFN TOPS20

HASH	OS2,0,<
	LINK's module LNKOV2 is writing your overlay file.>

HASH	PAS,0,<
	The job is too large to fit into the  allowed  memory  and
	the ALGOL symbol table is being moved to disk.>

HASH	PBI,0,<
	The highest address  allocated	in  the  named	module	is
	greater than 512P.  This is usually caused by dimensioning
	large arrays.  Modify your programs or load list to reduce
	the size of the load.>

HASH	PEF,0,<
	LINK found an end-of-file inside a REL Block (that is, the
	word   count   for   the   block   extended   beyond   the
	end-of-file).>

HASH	PHC,0,<
	The job is too large to fit into the  allowed  memory  and
	your high-segment code is being moved to disk.>

HASH	PLC,0,<
	The job is too large to fit into the  allowed  memory  and
	your low-segment code is being moved to disk.>

HASH	PLS,0,<
	The job is too large to fit into the  allowed  memory  and
	your local symbol tables are being moved to disk.>

;(There is no long text for the POO message.)

HASH	PSF,0,<
	The feature you requested is not available.>

HASH	PUF,0,<
	A PAGE. UUO to rearrange LINK's address space has  failed,
	and  returned  the  error  code given.	You may be able to
	avoid this problem by varying  the  physical  and  virtual
	limits	for  the  job, or by varying the values given with
	the /CORE and /MAXCOR switches.  This is an internal  LINK
	error.	 This  message	is  not  expected to occur.  If it
	does, please notify your Software  Specialist  or  send  a
	Software Performance Report (SPR) to DIGITAL.>

HASH	RBS,0,<
	The REL Block is inconsistent.	 This  may  be	caused	by
	incorrect  output  from a translator (for example, missing
	argument for an END  block).   Recompile  the  module  and
	reload.>

HASH	RCU,0,<
	The global symbol you gave with the  /SET  switch  is  not
	defined.  Load a module that defines the symbol.>

HASH	RED,0,<
	LINK  is  reclaiming  memory  by  deleting  its   internal
	tables.>

;(There is no long text for the RER message.)

HASH	RGS,0,<
	LINK is expanding the global  symbol  table  either  to  a
	prime  number larger than your /HASHSIZE switch requested,
	or by about 50 percent.  You can speed up future loads	of
	this  program  by  setting  /HASHSIZE  this  large  at the
	beginning of the load.>

;(There is no long text for the RLC message.)

HASH	RUC,0,<
	LINK attempted to return memory to the memory manager, but
	the  specified	memory	was  never  allocated to this job.
	This message is not expected to occur.	If it does, please
	notify	 your  Software  Specialist  or  send  a  Software
	Performance Report (SPR) to DIGITAL.>

HASH	SFU,0,<
	There are errors  in  the  local  symbol  table.   Loading
	continues,  but  any  maps  you  request  will not contain
	control section lengths.  This message is not expected	to
	occur.	If it does, please notify your Software Specialist
	or send a Software Performance Report (SPR) to DIGITAL.>

HASH	SIF,0,<
	LINK's hashing algorithms  failed;   they  are	trying	to
	write  a  new  symbol over an old one.	You may be able to
	load your files in a different order.  This message is not
	expected  to  occur.   If  it  does,  please  notify  your
	Software Specialist or send a Software Performance  Report
	(SPR) to DIGITAL.>

HASH	SLS,0,<
	You have  specified  /SYMSEG:HIGH  or  /SYMSEG:PSECT  when
	loading  an  overlay  structure.   Specify  /SYMSEG:LOW or
	/SYMSEG:DEFAULT.>

HASH	SMP,0,<
	You loaded some SIMULA procedures or classes, but no  main
	program.  Missing start address and undefined symbols will
	terminate execution.>

HASH	SNC,0,<
	You defined a COMMON  symbol  with  the  same  name  as  a
	non-COMMON  symbol.   You must decide which definition you
	want.  If you want the COMMON definition, load the  COMMON
	area first.>

HASH	SNL,0,<
	LINK is ready to process the next command line.>

HASH	SNP,0,<
	The named subroutine is  in  a	different  path  from  the
	calling link.  Redefine your overlay structure so that the
	subroutine is in the correct path.>

IFE TOPS20,<
HASH	SOE,0,<
	An error occurred in outputting the .EXE file.	 The  file
	was  closed  after the last successful output.	The status
	is represented by the right half of the file status  word.
	Refer	to   the   DECsystem-10   Monitor  Calls  for  the
	explanation of the file status bits.>
> ;END IFE TOPS20

IFN TOPS20,<
HASH	SOE,0,<
	An error occurred in outputting the .EXE file.	 The  file
	was closed after the last successful output.>
> ;END IFN TOPS20

HASH	SRB,0,<
	You cannot /SET the named  relocation  counter	below  its
	initial value.	The attempt is ignored.>

HASH	SSN,0,<
	Alphabetical or numerical sorting of the symbol  table	is
	not implemented.  The symbols appear in the order they are
	found.>

HASH	SST,0,<
	LINK is rearranging the symbol table, and if required,	is
	converting  the  symbols  from	the  new  to old format as
	indicated on the /SYMSEG, /SYMBOL, or /DEBUG switch.>

HASH	STC,0,<
	The symbol table has been sorted and  moved  according	to
	the /SYMSEG, /SYMBOL, or /DEBUG switch.>

HASH	T13,0,<
	REL Block Type 13  (LVAR)  is  obsolete.   Use	the  MACRO
	pseudo-op TWOSEG.>

HASH	TDS,0,<
	LINK has already loaded  the  initial  symbol  table.	To
	prevent  this  loading, place the /NOINITIAL switch before
	the first file specification.>

HASH	TEC,0,<
	You cannot expand an already defined  COMMON  area.   Load
	the  largest  definition of a given named COMMON first, or
	use the /COMMON switch to reserve space for it.   You  can
	define a new COMMON area with a new name any time.>

HASH	TMA,0,<
	You have more ambiguous subroutine requests (indicated	by
	LNKARL messages) than will fit in the table for this link.
	Continue loading.  Your load will abort at the end with  a
	LNKABT	message;   if  you  have  loaded  all modules, the
	message will give the size of the  needed  /ARSIZE  switch
	for a reload.>

HASH	TTF,0,<
	In producing the index for a map  file,  LINK  found  more
	program  names	than there are programs.  The symbol table
	is in error.  This message is not expected to  occur.	If
	it  does, please notify your Software Specialist or send a
	Software Performance Report (SPR) to DIGITAL.>

HASH	UAR,0,<
	The named symbol was referenced in an  .ASSIGN	pseudo-op,
	but  the  symbol  is  undefined.  The .ASSIGN pseudo-op is
	ignored.  You  should  load  a	module	that  defines  the
	symbol.>

;(There is no long text for the UGS message.)

HASH	UNS,0,<
	Extraction of symbols from a MACRO universal file  is  not
	implemented.>

HASH	URC,0,<
	In a REL Block Type 2 (SYMBOLS), the first 4 bits of  each
	word  pair  contain  the Radix-50 symbol code.	LINK found
	one or more invalid codes in the block.>

HASH	USA,0,<
	You gave an undefined global symbol as the start  address.
	Load a module that defines the symbol.>

HASH	USC,0,<
	The named link contains a call for a subroutine  you  have
	not  loaded.  If the subroutine is required for execution,
	you must reload, including  the  required  module  in  the
	link.>

;(There is no long text for the VAL message.)

;(There is no long text for the XCT message.)

HASH	ZSV,0,<
	You omitted required arguments for a switch (for  example,
	/REQUIRE with no symbols).  Respecify the switch.>
SUBTTL	INDEXED MESSAGES

INDEX	<FEE,FRE>,0,0,<
	One of the following conditions occurred:

	1.  The filename given was illegal.

	2.  When updating a file, the filename given did not match
	    the file to be updated.

	3.  The RENAME monitor call following a LOOKUP monitor call
	    failed.>

INDEX	<FLE,GSE>,0,0,<
	The file requested by the user was not  found.   The  user
	should respecify the correct filename.>

INDEX	<FEE,FLE,FRE,GSE>,1,0,<
	The directory does not exist on the named file  structure,
	or the project-programmer number given was incorrect.>

INDEX	<FEE,FLE,FRE,GSE>,2,0,<
	The user does not have the correct  privileges  to  access
	the named file.>

INDEX	FEE,-1,0,<
	The directory on the DECtape has no room for the file.>

INDEX	<FEE,FLE,FRE,GSE>,3,0,<
	Another user is currently modifying the named  file.   The
	user should try accessing the file later.>

INDEX	<FEE,FLE,FRE,GSE>,4,0,<
	The specified filename  already  exists,  or  a  different
	filename was given  on  the ENTER monitor call following a
	LOOKUP monitor call.>

INDEX	<FEE,FLE,FRE,GSE>,5,%SPR,<
	The user specified an illegal sequence  of  monitor  calls
	(e.g., a RENAME without a preceding LOOKUP or ENTER, or  a
	LOOKUP after an ENTER).>

INDEX	<FEE,FLE,FRE,GSE>,6,0,<
	One of the following conditions occurred:

	1.  Transmission, device, or  data  error  occurred  while
	    attempting to read the UFD or RIB.

	2.  A hardware-detected device or data error was  detected
	    while reading the UFD RIB or UFD data block.

	3.  A  software-detected  data  inconsistency  error   was
	    detected while reading the UFD RIB or file RIB.>

INDEX	<FEE,FLE,FRE,GSE>,7,%NPOS,<
	The named file is not a saved file.>

INDEX	<FEE,FLE,FRE,GSE>,10,%NPOS,<
	The system cannot supply enough memory to use  as  buffers
	or to read in a program.>

INDEX	<FEE,FLE,FRE,GSE>,11,%NPOS,<
	The  device  indicated  by  the  user  is  currently   not
	available.>

INDEX	<FEE,FLE,FRE,GSE>,12,%NPOS,<
	The device specified by the user  does  not  exist.>

INDEX	<FEE,FLE,FRE,GSE>,13,%NPOS,<
	The  machine  does  not  have  a  two-register  relocation
	capability.>

INDEX	<FEE,FLE,FRE,GSE>,14,0,<
	There is no room on the file structure for the named file,
	or  the  user's  quota  on  the  file  structure  would be
	exceeded if the file were placed on the structure.>

INDEX	<FEE,FLE,FRE,GSE>,15,0,<
	The user cannot write on the specified device  because  it
	is write-locked.>

INDEX	<FEE,FLE,FRE,GSE>,16,0,<
	There is not enough table space in  the  monitor's  4-WOrd
	blocks for the specified file. The user should try running
	the job at a later time.>

INDEX	<FEE,FLE,FRE,GSE>,17,0,<
	Because of the user's quota or the available space on  the
	device,  the total number of blocks requested could not be
	allocated and a partial allocation was given.>

INDEX	<FEE,FLE,FRE,GSE>,20,%NPOS,<
	The block required by LINK is not available for allocation.>

INDEX	<FEE,FLE,FRE,GSE>,21,0,<
	The user attempted to  supersede  an  existing  directory.>

INDEX	<FEE,FLE,FRE,GSE>,22,%NPOS,<
	The user attempted to delete  a  directory  that  was  not
	empty.>

INDEX	<FEE,FLE,FRE,GSE>,23,0,<
	The required sub-file directory in the specified path  was
	not found.>

INDEX	<FEE,FLE,FRE,GSE>,24,0,<
	A LOOKUP and ENTER monitor call was performed  on  generic
	device DSK and the search list is empty.>

INDEX	<FEE,FLE,FRE,GSE>,25,0,<
	An attempt was made to create a subfile  directory  nested
	deeper  than  the maximum level allowed.>

INDEX	<FEE,FLE,FRE,GSE>,26,0,<
	No file structure in the job's search list  has  both  the
	no-create bit and the write-lock bit equal to zero and has
	the UFD or SFD specified by the default or explicit path.>

INDEX	<FEE,FLE,FRE,GSE>,27,%NPOS,<
	A GETSEG monitor call was issued from a locked low segment
	to a high segment which is not a  dormant, active, or idle
	segment.>

INDEX	<FEE,FLE,FRE,GSE>,30,0,<
	A LOOKUP and ENTER monitor call  was  given  to  update  a
	file, but the file  cannot  be  updated  for  some  reason
	(e.g., another user is superseding  it  or  the  file  was
	deleted between the time of the LOOKUP and the ENTER).>

INDEX	<FEE,FLE,FRE,GSE>,31,0,<
	The end of the low segment is above the beginning  of  the
	high segment.>

INDEX	<FEE,FLE,FRE,GSE>,32,%SPR,<
	This message indicates that a  LOOKUP,  ENTER,  or  RENAME
	error  occurred which was larger in number than the errors
	LINK knows about.>

IF2,<	PURGE N,M>
SUBTTL	COMMON MESSAGES

REPEAT 0,<		;NO LONGER USED
			;SHOULD BE REIMPLEMENTED IN COOPERATION
			;WITH THE DOCUMENTATION GROUP
%L10:	%SPR
.ASCIZ	<
	This is an internal LINK error.>

%F40:	%SPR
.ASCIZ	<
	Incorrect code has been generated by the F40 compiler.>

%E$$:	0
.ASCIZ	<
	LINK could not make the named file on the disk  (LC=user's
	low  segment code,  HC=user's high segment code,  LS=local
	symbol table).  The user could be over quota, or the  disk
	could be full or have errors.>

%I$$:	%AREA
.ASCIZ	<
	An error  occurred  while  reading  in  the  named   area.>

%O$$:	%AREA
.ASCIZ	<
	An error  occurred  while  writing  out  the  named  area.>

%OE$:	%STS
.ASCIZ	<
	An error has occurred on the output file.  The output file
	is   closed   at  the  end  of  the  last  data  that  was
	successfully output.>


%P$$:	0
.ASCIZ	<
	the job is too large to fit into the  allowed  memory  and
	the named area is being moved to disk (LC=user low segment
	code, HC=user high segment code,  LS=local symbol  table).>

IFE TOPS20,<
%STS:	0
.ASCIZ	<
	The status is represented by the right half  of  the  file
	status  word.  Refer to DECsystem-10 Monitor Calls for the
	explanation of the file status bits.>
>
IFN TOPS20,<
%STS:	0
	0
>

%AREA:	%STS
.ASCIZ	<
	(LC=user's  low segment code, HC=user's high segment code,
	LS=local symbol table, and GS=global symbol table).>

> ;END REPEAT 0

%NPOS:	%SPR
.ASCIZ	<
	This  message  can  never  occur  and is included only for
	completeness of the LOOKUP, ENTER, and RENAME error codes.>

%SPR:	0
.ASCIZ	<
	This message is not expected to occur.  If it does, please
	notify   your  Software  Specialist  or  send  a  Software
	Performance Report (SPR) to DEC.>


ERRLIT:
END	LNKERR