Google
 

Trailing-Edge - PDP-10 Archives - decuslib10-07 - 43,50450/rsxmac.pub
There are no other files named rsxmac.pub in the archive.
00100	.begin "titlepage"
00200	.turn on "{"
00300	.page frame 60 high 80 wide
00400	.title area report!title lines 16 to 25 chars 20 to 57
00500	.title area report!author lines 38 to 60 chars 14 to 63
00600	.place report!title
00700	.begin center
00800	.group skip 3
00900	BLISS-11 Macro Libraries
01000	for Interfacing to RSX-11M
01100	
01200	Reference Manual
01300	.end
01400	.place report!author
01500	.begin center
01600	Keith E. Gorlen
01700	Computer Systems Laboratory
01800	Division of Computer Research and Technology
01900	National Institutes of Health
02000	Bethesda, Maryland 20014
02100	.group skip 4
02200	{date}
02300	.end
02400	.end "titlepage"
     
00100	.REQUIRE "SYS:PUBMAC.DFS" SOURCE!FILE
00200	.!MESSAGES_FALSE;
00300	.SETPAGE(60,69,5,3,2)
00400	.EVERY HEADING({DATE},,BLISS-11/RSX-11M Interface Macros)
00500	.EVERY FOOTING(,{PAGE},)
00600	.STANDARD FRONT(1,1,1,Section,yes,1)
00700	.TURN ON "{"
00800	.DOFOOTNOTE(@@,@,1,YES);
00900	.DOINDEX(&,`);
     
00100	.s(Introduction)
00200	
00300	.ss(Purpose)
00400	
00500	The BLISS-11/RSX-11M Macro Libraries furnish a convenient 
00600	interface to the RSX-11M operating system for programs written in
00700	BLISS-11@@developed by the Computer Science Department,
00800	Carnegie-Mellon University@
00900	in much the same way that the RSX-11M macro
01000	libraries (SY:[1,1]RSXMAC.SML and EXEMC.MLB)
01100	provide an interface for MACRO-11 assembly language programs.
01200	Since a major design goal was to retain as much similarity
01300	in both form and function between the BLISS-11 macros and
01400	their MACRO-11 counterparts, the standard documentation
01500	found in the reference manuals remains the primary source
01600	of information.  This documentation serves mainly to
01700	outline those areas of significant difference
01800	and assumes familiarity with RSX-11M.
01900	
02000	.ss(Problems and Questions)
02100	`problems` `questions`
02200	
02300	Refer any problems or questions concerning the use
02400	of these macro libraries to the &Author&:
02500	
02600	.begin nofill
02700	
02800		Keith E. Gorlen
02900		Rm. 2017, Bg. 12A
03000		Division of Computer Research and Technology
03100		National Institutes of Health
03200		Bethesda, MD 20014
03300		Phone: (301) 496-5361
03400	.end
03500	
03600	{REFER(BUGAPPNDX)} contains a summary of currently
03700	known bugs and limitations.
03800	
03900	.ss(Macro Library Organization)
04000	
04100	Since the macro library is quite large and it is usually
04200	unnecessary to use all of it in any particular
04300	program module, there are a number of library files each
04400	containing a particular class of macro definitions:
04500	`Executive Services macros`
04600	`File Control Services macros`
04700	`File Storage Region macros`
04800	`Utility Conversion Routine macros`
04900	
05000	.begin nofill
05100	
05200		&B11MAC.REQ& -- miscellaneous useful macros
05300		&RSXMAC.REQ& -- Executive Services macros
05400		&FCSMAC.REQ& -- File Control Services macros
05500		&FSRMAC.REQ& -- File Storage Region macros
05600		&EXEMC.REQ&  -- System Data Structures and Symbols
05700		&UTLMAC.REQ& -- Utility Conversion Routine macros
05800	.end
05900	
06000	.ss(Accessing the Macro Libraries)
06100	`macro libraries, accessing`
06200	
06300	The macro definitions are accessed from a BLISS-11
06400	program via the &REQUIRE SOURCE& declaration; for example:
06500	
06600	.begin nofill
06700	
06800		REQUIRE 'RSXMAC.REQ[proj#,prog#]' SOURCE;
06900		REQUIRE 'FCSMAC.REQ[proj#,prog#]' SOURCE;
07000		REQUIRE 'FSRMAC.REQ[proj#,prog#]' SOURCE;
07100		REQUIRE 'EXEMC.REQ[proj#,prog#]' SOURCE;
07200		REQUIRE 'UTLMAC.REQ[proj#,prog#]' SOURCE;
07300	.end
07400	
07500	.ss(Naming Conventions)
07600	`naming conventions`
07700	
07800	.sss(External Names)
07900	`external names`
08000	
08100	BLISS-11 names for all macros and symbols are identical to
08200	their corresponding MACRO-11 names, except that they must
08300	be preceeded by a '?' so that the BLISS compiler will
08400	recognize the characters '.' and '$' as being a part of the
08500	name; for example:
08600	
08700	.begin nofill
08800	
08900		MACRO-11	    BLISS-11
09000	
09100		ABRT$		?ABRT$
09200		ABRT$S		?ABRT$S
09300		A.BTTN		?A.BTTN
09400	.end
09500	
09600	.sss(Internal Names)
09700	`internal names`
09800	
09900	The macros make internal use of names for labels,
10000	OPCODES, macros, etc. which are normally of no
10100	interest to the user.  However, to avoid conflicts
10200	the user should not define names beginning
10300	with '?.'.
10400	
10500	.ss(Accessing Bit Fields)
10600	.LABEL(BITDEF)
10700	`names, bit field`
10800	
10900	The BLISS-11 counterparts to MACRO-11 names for
11000	bit fields are defined as macros which expand
11100	into appropriate &position-size modifier&s (&PSM&s).
11200	The following example illustrates equivalent
11300	BLISS-11 and MACRO-11 code for setting a bit.
11400	
11500	.begin nofill
11600	
11700		MACRO-11
11800	
11900		BISB	#FD.CR,FDB+F.RATT
12000	
12100		BLISS-11
12200	
12300		?F.RATT(FDB)<?FD.CR>=1;
12400	.end
12500	
12600	.ss(Accessing Multi-word Fields)
12700	`multi-word fields`
12800	
12900	Subscript notation is recommended for accessing
13000	multi-word fields; e.g.,
13100	
13200	.begin nofill
13300	
13400		?F.FNAM(FDB)[0]		! Word 0 of file name
13500		?F.FNAM(FDB)[1]		! Word 1 of file name
13600	
13700		?QIO$C(QIODPB);		! Define QIO DPB names
13800		?Q.IOPL[0]=BUFADR;	! Set buffer address
13900		?Q.IOPL[1]=LEN;		! Set byte count
14000	.end
14100	
14200	.ss(Parameter Sublist Notation)
14300	`parameter sublist`
14400	
14500	Several macros require that a list of values be
14600	passed as a single argument.  In MACRO-11 this
14700	is done either by separating the values by '!'
14800	or by enclosing the list of values in angle
14900	brackets.  The latter method is always used by
15000	the equivalent BLISS-11 macros; however,
15100	a &parameter sublist& must either be null or
15200	enclosed in brackets, even if the sublist
15300	contains only one element.  The following
15400	examples illustrate these differences.
15500	
15600	.begin nofill
15700	
15800	.group
15900		MACRO-11
16000	
16100		OPEN$W	#FDB,,,#FD.RWM!FD.RAN!FD.PLC
16200		OPEN$R	#FDB,,,#FD.RWM
16300		OPEN$A	#FDB,,,,#BUF,BUFLEN
16400		QIO$S	#IO.RLB,#1,,,#IOSB,,<#BUF,#72.>
16500	
16600		BLISS-11
16700	
16800		?OPEN$W(FDB,,,<?FD.RWM,?FD.RAN,?FD.PLC>);
16900		?OPEN$R(FDB,,,<?FD.RWM>);
17000		?OPEN$A(FDB,,,,BUF,.BUFLEN);
17100		?QIO$S(?IO.RLB,1,,,IOSB,,<BUF,72>);
17200	.apart
17300	.end
17400	
     
00100	.s(RSXMAC.REQ -- Executive Services Macro Library)
00200	`Executive Services macros` `RSXMAC.REQ`
00300	
00400	This macro library is the BLISS-11 equivalent of the
00500	Executive Services macros described in the
00600	RSX-11M Executive Reference Manual.
00700	Differences from the cited documentation are
00800	described in the following sections.
00900	
01000	.ss(?DIR$ Macro)
01100	`?DIR$`
01200	
01300	The ?$DIR macro is the basic macro for calling RSX-11M
01400	executive services.  It has the following form:
01500	
01600	.begin nofill
01700	
01800		?DIR$(<dpb>[,err])
01900	.end
02000	
02100	The first argument may be either a DPB address expression
02200	or a list of expressions separated by commas which define
02300	the DPB. In either case, this argument must be enclosed
02400	by a bracketing pair@@the pair <> is recommended@.
02500	The ?DIR$ macro will cause the first argument to be
02600	pushed on the stack followed by the execution
02700	of an EMT 377 instruction.
02800	
02900	The second optional argument is a BLISS expression which
03000	will be evaluated if an error condition occurs.
03100	For more information on &error expression&s see
03200	{REFER(ERRORS)}.
03300	
03400	.ss(Error Processing)
03500	`error processing`
03600	.label(ERRORS)
03700	
03800	The &?DIR$& and the &$S-form& macros will accept any
03900	valid BLISS-11 expression@@A BLISS-11 bug currently limits the use
04000	of &EXITLOOP& in &error expression&s.  See {REFER(BUGAPPNDX)}.@
04100	as an optional last argument.
04200	If included, the expression will be evaluated if an error
04300	indication (carry set) is returned by the executive
04400	service call.
04500	
04600	Normally, if no &error expression& is specified then no error
04700	checking is performed; however, a &default error expression&
04800	may be specified by re-defining the macro &?RSXERRDF$&, in
04900	which case the default expression will be evaluated if an
05000	error occurs. The following example illustrates the
05100	possibilities:
05200	
05300	.begin nofill
05400	
05500		?ASTX$S();		! No error processing
05600		?ASTX$S(SIGNAL 1);	! SIGNAL 1 if error
05700		BEGIN
05800		    MACRO $QUOTE ?RSXERRDF$=
05900			TRAP(0)$;	! Define default error exp
06000		    ?ASTX$S();		! TRAP(0) if error
06100		    ?ASTX$S(SIGNAL 2);	! SIGNAL 2 if error
06200		    END;
06300	.end
06400	
06500	Notice that the error parameter for BLISS-11 macros differs
06600	from that of the MACRO-11 macros.  BLISS-11 macros require
06700	an error expression,`error expression`
06800	not a routine address; thus, the BLISS-11 macro call:
06900	
07000	.begin nofill
07100	
07200		?DIR$(<DPB>,ERRSUB());
07300	.end
07400	
07500	will cause ERRSUB to be called if a directive error occurs, and
07600	is equivalent to the MACRO-11 macro call:
07700	
07800	.begin nofill
07900	
08000		DIR$	DPB,ERRSUB
08100	.end
08200	
08300	.ss($-form Macros)
08400	`$-form`
08500	
08600	The BLISS-11 $-form of an RSX-11M macro produces
08700	a &<plit-arg>& which defines the appropriate DPB;
08800	for example:
08900	
09000	.begin nofill
09100	
09200		BIND MRKTDPB=UPLIT(?MRKT$(1,5,2,MTRAP));
09300	
09400		OWN MRKTDPB[?MRKT.DL]=(?MRKT$(1,,2,MTRAP));
09500	
09600		?DIR$(<?MRKT$(1,.TMG,2,MTRAP)>);
09700	.end
09800	
09900	In the second example a &.DL DPB length symbol& is used
10000	to reserve the appropriate number of words of storage
10100	for the DPB (see {REFER(DPBLENGTH)}).
10200	
10300	It is recommended that &PLIT&s or &UPLIT&s be used
10400	for defining pure DPBs `DPB, pure` as in the
10500	first example, and that
10600	impure DPBs `DPB, impure` be defined via OWN or GLOBAL
10700	declarations as in the second example.
10800	
10900	The third example illustrates the use of the &?DIR$& macro
11000	to push the entire DPB on the stack before
11100	executing an EMT 377 instruction.  This is
11200	effectively what is generated by the &$S-form&
11300	macros.
11400	
11500	Task and partition names `task names` `partition names`
11600	used in &$-form& macro calls must be supplied as
11700	six RAD50 characters enclosed in quotes when not
11800	defaulted.  Omitted names are defaulted to
11900	six blanks (two words of zeroes in RAD50).
12000	
12100	.ss($S-form Macros)
12200	`$S-form`
12300	
12400	This form is identical to the MACRO-11 $S-form,
12500	except for the optional <err> parameter as
12600	described in {REFER(ERRORS)}.
12700	Some examples of the use of this macro form are:
12800	
12900	.begin nofill
13000	
13100		?MRKT$S(1,5,2,AST,ERROR());
13200	
13300		?MRKT$S(1,.TMG*10,2,SIGNAL ERROR3);
13400	.end
13500	
13600	In general, task and partition names
13700	`task names` `partition names`
13800	are not defaulted in &$S-form& macros -- the
13900	address of a six character RAD50 string
14000	(usually an &UPLIT&) must be supplied.
14100	Exceptions are the &?ALTP$S& and &?GPRT$S& macros in which the
14200	task name may be left null, causing the name of the
14300	issuing task to be used by default.
14400	
14500	Note that if all arguments to a &$S-form& macro
14600	call are constant at load-time, it is more
14700	economical to use the &$C macro& described in
14800	{REFER(DOLLARC)}.
14900	
15000	.ss($C-form Macros)
15100	`$C-form`
15200	
15300	The $C-form macro simply BINDs names to addresses
15400	within a DPB; for example, to access the word
15500	?M.KTMG in MRKTDPB:
15600	
15700	.begin nofill
15800	
15900		OWN MRKTDPB[?MRKT.DL]=(?MRKT$(1,,2,MTRAP));
16000		?MRKT$C(MRKTDPB);
16100		?M.KTMG=5;
16200	.end
16300	
16400	The names BINDed by the &$C-form& macros are
16500	listed with each macro description in the
16600	RSX-11M Executive Reference Manual.
16700	
16800	The same effect as the MACRO-11 &$C-form& can be
16900	produced by combining the &$C macro& with
17000	the &$-form& macro as described in
17100	{REFER(DOLLARC)}.
17200	
17300	.ss($C Macro)
17400	`$C macro`
17500	.LABEL(DOLLARC)
17600	
17700	The normal function of the MACRO-11 $C-form macros
17800	is to generate code to push a DPB address on the
17900	stack followed by an EMT 377, while generating
18000	the pure DPB `DPB, pure` itself in a separate PSECT.
18100	This function is provided for BLISS-11 programs
18200	by the &$C macro&, which has the following format:
18300	
18400	.begin nofill
18500	
18600		$C(<dpb>[,err]);
18700	.end
18800	The first argument must be a &<plit-arg>& which
18900	defines the desired DPB. This is usually generated
19000	by using a &$-form& macro.  The optional second
19100	argument is an &error expression& as described in
19200	{REFER(ERRORS)}.
19300	
19400	The following example shows a MACRO-11 &$C-form&
19500	macro and its BLISS-11 equivalent:
19600	
19700	.begin nofill
19800	
19900		MACRO-11
20000	
20100		MRKT$C	1,5,2,MTRAP,ERR
20200	
20300		BLISS-11
20400	
20500		$C(<?MRKT$(1,5,2,MTRAP)>,ERR());
20600	.end
20700	
20800	.ss($B-form Macros)
20900	`$B-form`
21000	
21100	The $B-form macros are defined for only those directives
21200	which communicate via a buffer area whose address is
21300	passed in the DPB.  This macro form binds names to
21400	addresses within the buffer.  For example, to access
21500	the partition size returned by the &?GPRT$S& macro:
21600	
21700	.begin nofill
21800	
21900		OWN BUF[?GPRT.BL];
22000		?GPRT$B(BUF);
22100		?GPRT$S(UPLIT RAD50 'ALPHA ',BUF);
22200		PARTITIONSIZE=.?G.PRPS*32;
22300	.end
22400	
22500	This example uses a &.BL buffer length symbol& to allocate the
22600	correct number of words for the buffer area. See
22700	{REFER(BUFLENGTH)} for further information.
22800	
22900	.ss(.DL DPB Length Symbols)
23000	`.DL DPB length symbol`
23100	.LABEL(DPBLENGTH)
23200	
23300	All executive services having a &$-form& macro
23400	also have a .DL DPB length symbol BINDed to
23500	the length (in words) of the DPB generated
23600	by the &$-form& macro.  This is particularly
23700	useful in allocating OWN or GLOBAL storage
23800	for an impure DPB; `DPB, impure` for example:
23900	
24000	.begin nofill
24100	
24200		OWN MRKTDPB[?MRKT.DL]=(?MRKT$(1,5,2,MTRAP));
24300	.end
24400	
24500	.ss(.BL Buffer Length Symbols)
24600	`.BL buffer length symbol`
24700	.LABEL(BUFLENGTH)
24800	
24900	All executive services having a &$B-form& macro
25000	also have a &.BL buffer length symbol& BINDed to the
25100	length (in words) of the buffer whose address
25200	is specified in the DPB.  This is particularly
25300	useful for allocating storage for the buffer; e.g.,
25400	
25500	.begin nofill
25600	
25700		LOCAL BUF[?GPRT.BL];
25800		?GPRT$S(UPLIT RAD50 'ALPHA ',BUF);
25900	.end
26000	
26100	.ss(RDB and WDB Macros)
26200	`RDB` `Region Definition Block`
26300	`WDB` `Window Definition Block`
26400	
26500	When using the &?RDBBK$& and &?WDBBK$& macros to define Region
26600	or Window Definition Blocks, the &?RDBDF$& and &?WDBDF$& macros
26700	must be called before invoking the &?RDBBK$& and &?WDBBK$& macros,
26800	respectively.  The following example illustrates the use of these
26900	macros:
27000	
27100	.begin nofill
27200	
27300		?RDBDF$;			! DEFINE RDB SYMBOLS
27400		OWN RDB[?R.GLGH/2]=(?RDBBK$(102,'ALPHA ','GEN   ',
27500		    <?RS.NDL,?RS.ATT,?RS.WRT,?RS.RED>,#167000));
27600		?CRRG$S(RDB);			! CREATE REGION
27700		IF NOT .?R.GSTS(RDB)<?RS.CRR>	! TEST REGION STATUS
27800		    THEN CRERR();		! IF REGION NOT CREATED
27900	.end
28000	
28100	.ss(?IOERR$ Macro)
28200	.LABEL(IOERROR)
28300	`?IOERR$`
28400	
28500	The &?IE. symbols& defined by the &?IOERR$& macro are
28600	defined as the low-order eight bits of the
28700	corresponding MACRO-11 symbol. This facilitates
28800	comparison of the error byte of an &IOSB& to
28900	the symbol. A BLISS-11 expression such as:
29000	
29100	.begin nofill
29200	
29300		.IOSB<0,8> EQL ?IE.UPN
29400	.end
29500	
29600	would not work as expected if ?IE.UPN were
29700	defined as -1.
29800	
29900	.ss(Other Macros Defined in RSXMAC.REQ)
30000	`RSXMAC.REQ`
30100	
30200	The following sections describe macros available in
30300	the &RSXMAC.REQ& library that are not documented in the
30400	RSX-11M Executive Reference Manual.
30500	
30600	.sss(?IOERR$ -- I/O Error Codes)
30700	`?IOERR$` `I/O Error Codes`
30800	
30900	The I/O error codes described in the
31000	IAS/RSX-11 I/O Operations Reference Manual
31100	may be defined by invoking the &?IOERR$& macro.
31200	See {REFER(IOERROR)} for important information
31300	concerning the use of these symbols.
31400	
31500	.sss(I/O Function Codes)
31600	`I/O function codes`
31700	
31800	The standard, special, and diagnostic
31900	&I/O function codes& described in the
32000	RSX-11M I/O Drivers Reference Manual
32100	may be defined by invoking the &?FILIO$&,
32200	&?SPCIO$&, and &?UMDIO$& macros respectively.
32300	
32400	.sss(?TTSYM$ -- Terminal Driver Symbols)
32500	`Terminal Driver Symbols`
32600	
32700	The terminal driver symbols described in Chapter 2 of the
32800	IAS/RSX-11 I/O Operations Reference Manual
32900	may be defined by invoking the &?TTSYM& macro.
33000	
33100	.sss(Snapshot Dump Macros)
33200	`snapshot dump`
33300	
33400	The snapshot dump macros &?SNPBK$&, &?SNAP$&, and
33500	&?SNPDF$& as described in the
33600	RSX-11M Task Builder Reference Manual
33700	are also available in the &RSXMAC.REQ& macro library.
33800	
     
00100	.s(FCSMAC.REQ -- File Control Services Macro Library)
00200	`File Control Services macros` `FCSMAC.REQ`
00300	
00400	This macro library is the BLISS-11 equivalent of
00500	the File Control Services macros described in the
00600	RSX-11 I/O Operations Reference Manual.
00700	Differences from the cited documentation are
00800	described in the following sections.
00900	
01000	.ss(Error Processing)
01100	`error processing`
01200	
01300	All macros that invoke FCS routines which return
01400	an error indication via the carry bit accept as
01500	their last argument an optional &error expression&
01600	which is evaluated when an error occurs.
01700	Normally, if no error expression is specified then
01800	no error checking is performed; however, a
01900	&default error expression& may be specified by re-
02000	defining the macro &?FCSERRDF$&, in which case the
02100	default expression will be evaluated when an error
02200	occurs. The following example illustrates the
02300	possibilities:
02400	.begin nofill
02500	
02600		?CLOSE$(FDB);		! no error processing
02700		?CLOSE$(FDB,SIGNAL 1);	! SIGNAL 1 if error
02800		BEGIN
02900		    MACRO $QUOTE ?FCSERRDF$=
03000			TRAP(0)$;	! define default error exp.
03100		    ?CLOSE$(FDB);	! TRAP(0) if error
03200		    ?CLOSE$(FDB,SIGNAL 2); ! SIGNAL 2 if error
03300		    END;
03400	.end
03500	
03600	Notice that the error parameter for BLISS-11 macros differs
03700	from that of the MACRO-11 macros.  BLISS-11 macros require
03800	an error expression,`error expression`
03900	not a routine address; thus, the BLISS-11 macro call:
04000	
04100	.begin nofill
04200	
04300		?CLOSE$(FDB,ERRSUB());
04400	.end
04500	
04600	will cause ERRSUB to be called if an FCS error occurs,
04700	and is equivalent to the MACRO-11 macro call:
04800	
04900	.begin nofill
05000	
05100		CLOSE$	FDB,ERRSUB
05200	.end
05300	
05400	.ss(Compile-time FDB Initialization Macros)
05500	`FDB, initialization of`
05600	
05700	Due to the nature of the BLISS-11 compile-time data
05800	initialization facilities, the BLISS-11 macros for
05900	FDB initialization differ greatly from their MACRO-11
06000	counterparts.  The following macros are not
06100	directly implemented:
06200	
06300	.begin nofill
06400	
06500		&FDAT$A&
06600		&FDRC$A&
06700		&FDBK$A&
06800		&FDOP$A&
06900		&FDBF$A&
07000	.end
07100	
07200	These compile-time functions are performed instead by
07300	the BLISS-11 version of the &?FDBDF$& macro:
07400	
07500	.begin nofill
07600	
07700		?FDBDF$(fdbname,m1,m2, ... ,mn);
07800	.end
07900	
08000	This macro call generates (along with a lot of
08100	rubbish):
08200	
08300	.begin nofill
08400	
08500		OWN ?FDB$ fdbname=(?.FDBSYM,24:0);
08600	.end
08700	
08800	&?FDB$& is the name of a structure that defines a
08900	vector of &?S.FDB& bytes for the FDB, and
09000	?.FDBSYM is the name of a macro defined by
09100	the &?FDBDF$& macro which expands into the
09200	constant values necessary to initialize the FDB
09300	appropriately.
09400	These constant values (the compile-time
09500	initialization of the FDB) are determined by
09600	means of the optional parameters m1,m2,m3...
09700	in the &?FDBDF$& macro call.  These parameters
09800	are actually calls to a special set of macros
09900	that are specifically defined for and useful
10000	only in this context.  A summary of these
10100	macros and their MACRO-11 equivalents is
10200	given in
10300	{REFER(FDBDFAPNDX)}.
10400	Calls to these macros may appear in any order
10500	in the ?FDBDF$ argument list.  Note that the
10600	&?FDOFF$& macro must be invoked prior to using
10700	the &?FDBDF$& macro.  The following example
10800	illustrates equivalent BLISS-11 and MACRO-11
10900	code:
11000	
11100	.begin nofill
11200	
11300		BLISS-11
11400	
11500		?FDOFF$;		! Define FDB offsets
11600		?FDBDF$(OUT,
11700		    ?AT$VAR,?AT$CR,	! Attribute Section
11800		    ?RC$URBA(OUTBUF),	! Record Access Section
11900			?RC$URBS(512),
12000		    ?OP$LUN(1),		! File Open Section
12100		    ?BF$EFN(2));	! Block Buffer Section
12200	
12300		MACRO-11
12400	
12500		OUT:	FDBDF$
12600			FDAT$A	R.VAR,FD.CR
12700			FDRC$A	,OUTBUF,512.
12800			FDOP$A	1
12900			FDBF$A	2
13000	.end
13100	
13200	.ss(Compile-time Initialization of the FSR)
13300	`FSR, initialization of` 
13400	`File Storage Region macros`
13500	
13600	Compile-time initialization of the
13700	file storage region (FSR) may be accomplished
13800	with a BLISS-11 module of the following form:
13900	
14000	.begin nofill
14100	
14200		MODULE name=BEGIN
14300		REQUIRE '&FSRMAC.REQ&[proj#,prog#]' SOURCE;
14400		&?FSRSZ$&(files,bufsiz);
14500		END ELUDOM
14600	.end
14700	
14800	The arguments to &?FSRSZ$& are identical to those
14900	of its MACRO-11 counterpart as described in the
15000	RSX-11 I/O Operations Reference Manual.
15100	
15200	.ss(File Control Routines)
15300	`File Control Routines`
15400	
15500	BLISS-11 macros for invoking all file control
15600	routines described in Chapter 4 of the
15700	RSX-11 I/O Operations Reference Manual
15800	are available. Consult the appropriate macro
15900	definitions in &FCSMAC.REQ& for further
16000	information.
16100	
16200	.ss(Command Line Processing Macros)
16300	`command line processing`
16400	
16500	The following command line processing macros are
16600	implemented as described in Chapter 6 of the
16700	RSX-11 I/O Operations Reference Manual:
16800	
16900	.begin nofill
17000	
17100		&?GCMLB$& -- Initialize GCML Control Block
17200		&?GCML$& -- Get Command Line
17300		&?RCML$& -- Reset Indirect Command File Scan
17400		&?CCML$& -- Close Current Command File
17500		&?CSI$& -- Define CSI Control Block Symbols
17600		&?CSI$1& -- Command Syntax Analyzer
17700	.end
17800	
17900	The remaining &command line processing& macros are
18000	implemented with the differences described in the
18100	following sections.
18200	
18300	.sss(?GCMLD$ Macro)
18400	`?GCMLD$`
18500	
18600	The ?GCMLD$ macro, which defines &GCML control block&
18700	offsets and bit values, is implemented as described
18800	in the manual, except that the &?GE. symbols& for
18900	error codes are defined as the low-order eight
19000	bits of the corresponding MACRO-11 symbols.
19100	This facilitates the comparison of &?G.ERR& to the
19200	symbol value. A BLISS-11 expression such as:
19300	
19400	.begin nofill
19500	
19600		.?G.ERR EQL ?GE.IOR
19700	.end
19800	
19900	would not work as expected of ?GE.IOR were
20000	defined as -1.
20100	
20200	.sss(?CSI$2 Macro)
20300	`?CSI$2`
20400	
20500	The ?CSI$2 macro is implemented as described in the
20600	manual, except that the IO parameter in the
20700	macro call must be specified as the character
20800	string 'INP' or 'OUT' for INPUT or OUTPUT,
20900	respectively.
21000	
21100	.sss(?CSI$SW and ?CSI$SV Macros)
21200	`?CSI$SW` `?CSI$SV`
21300	
21400	The ?CSI$SW and ?CSI$SV macros are implemented as
21500	iterated macros which generate &<plit-arg>&s
21600	and permit the definition of an entire switch
21700	descriptor or switch value table within a
21800	single declaration, thus eliminating the need
21900	for an equivalent to the &CSI$ND& macro.
22000	The "compflg" parameter of the &?CSI$SW& macro is not
22100	implemented; thus, only two-character switch names
22200	are permitted.
22300	All other parameters are as described in Section 6.2.4
22400	of the manual, except for keyword parameters
22500	as follows:
22600	
22700	.begin nofill
22800	
22900	.group
23000				BLISS-11	    MACRO-11
23100	
23200		?CSI$SW
23300			CSFLG
23400				'CLR'		CLEAR
23500				'SET'		SET
23600			NFLG
23700				'NEG'		NEG
23800		?CSI$SV
23900			TYPE
24000				'ASC'		ASCII
24100				'NUM'		NUMERIC
24200				'OCT'		OCTAL
24300				'DEC'		DECIMAL
24400	.apart
24500	.end
24600	
24700	The following example illustrates the use of these
24800	macros `?CSI$SW` `?CSI$SV` to
24900	`switch descriptor table` `switch value table`
25000	generate switch descriptor and switch value
25100	tables identical to those in the examples
25200	used in Section 6.2.4 of the manual:
25300	
25400	.begin nofill
25500	
25600		BIND ASMSK=1,NUMSK=2;	! MASK VALUES
25700		OWN MASKX=(0);		! MASK WORD
25800		OWN ASVAL[4];		! ASCII VALUE STORAGE
25900		OWN NUVAL[2];		! NUMERIC VALUE STORAGE
26000		BIND ASSWT=UPLIT(?CSI$SW(
26100		    'AS',ASMSK,MASKX,'SET',,
26200			UPLIT(?CSI$SV('ASC',ASVAL,3,
26300			    'ASC',ASVAL+4,3)),
26400		    'NU',NUMSK,MASKX,'CLR','NEG',
26500			UPLIT(?CSI$SV('OCT',NUVAL,2,
26600			    'DEC',NUVAL+2,2))));
26700	.end
26800	
     
00100	.s(EXEMC.REQ -- System Data Structures and Symbols)
00200	`System Data Structures` `EXEMC.REQ`
00300	
00400	This macro library is the BLISS-11 equivalent of the
00500	&EXEMC.MLB& macro library described in Appendix C of the
00600	RSX-11M Guide to Writing an I/O Driver.
00700	Differences from the cited documentation are described in the
00800	following sections.
00900	
01000	.ss(RSXMC.REQ -- System-Dependent Macro Definitions)
01100	`RSXMC.REQ`
01200	
01300	The file &RSXMC.REQ& is analogous to the &RSXMC.MAC& file
01400	generated by SYSGEN Phase 1 in that it contains information
01500	as to the options present on a particular RSX-11M system.
01600	Since some of the system data structures and symbol values
01700	are dependent upon the presence or absence of certain
01800	options (e.g., memory management), &RSXMC.REQ& is
01900	REQUIREd by &EXEMC.REQ&.
02000	
02100	&RSXMC.REQ& currently contains macros for the following
02200	options:
02300	
02400	.begin nofill
02500	
02600		&?R$$11M& -- &RSX-11M System&
02700		&?R$$11D& -- &RSX-11D System&
02800		&?M$$MGE& -- &Memory Management&
02900		&?L$$DRV& -- &Loadable Device Drivers&
03000		&?P$$LAS& -- &Program Logical Address Space&
03100		&?E$$EAE& -- &Extended Arithmetic Element&
03200	.end
03300	
03400	Each of these options has a macro definition named as indicated.
03500	If the option is present, the macro expands into its argument, if
03600	the option is not present, the macro expansion is null.
03700	The following example shows the macro definitions for an RSX-11M
03800	system without memory management:
03900	
04000	.begin nofill
04100	
04200		MACRO
04300		    ?R$$11M(Y)=Y$,
04400		    ?R$$11D(Y)= $,
04500		    ?M$$MGE(Y)= $;
04600	.end
04700	
04800	Each site should insure that the macros are defined appropriately
04900	for its particular configuration.
05000	
05100	.ss(Arguments to Offset Definition Macros)
05200	.LABEL(SYMBOFFDEF)
05300	`?xxxDF$ macros`
05400	
05500	&EXEMC.REQ& contains macros which define the &symbolic offsets&
05600	for the various blocks which comprise the RSX-11M
05700	system data structure.
05800	These macros have names of the form ?xxxDF$, and require
05900	one argument which is the base address of the block; offsets
06000	relative to the start of a block such as defined by the
06100	corresponding &EXEMC.MLB& macros can be defined by specifying
06200	a base address of zero, i.e. ?xxxDF$(0).
06300	The following example illustrates the use of these
06400	macros:
06500	
06600	.begin nofill
06700	
06800		REQUIRE 'RSXMAC.REQ' SOURCE;
06900		REQUIRE 'EXEMC.REQ' SOURCE;
07000		EXTERNAL $TKTCB;		! POINTER TO TASK TCB
07100		?TCBDF$(.$TKTCB);		! DEFINE TCB OFFSETS
07200		?UCBDF$(.?T.UCB);		! DEFINE TI: UCB OFFSETS
07300		IF NOT .?U.CW2<?U2.PRV>
07400		    THEN ?EXIT$S();		! EXIT IF TI: NOT PRIVILEGED
07500	.end
07600	
07700	.ss(?ADBDF$ -- Attachment Descriptor Block Offset Definitions)
07800	`?ADBDF$` `?PCBDF$` `Attachment Descriptor Blocks`
07900	
08000	The BLISS-11 version of the &?PCBDF$& macro does not define
08100	the symbolic offsets for &Attachment Descriptor Blocks&.
08200	A separate macro, &?ADBDF$&, is provided instead in order
08300	to permit specification of a base address as described in
08400	{REFER(SYMBOFFDEF)}.
08500	
08600	.ss(?WBKDF$ -- Window Block Offset Definitions)
08700	`?WBKDF$` `?HDRDF$` `Window Blocks`
08800	
08900	The BLISS-11 version of the &?HDRDF$& macro does not define
09000	the symbolic offsets for &Window Blocks& in the task header.
09100	A separate macro, &?WBKDF$&, is provided instead in order
09200	to permit specification of a base addres as described in
09300	{REFER(SYMBOFFDEF)}.
     
00100	.s(UTLMAC.REQ -- Utility Conversion Routine Macro Library)
00200	`Utility Conversion Routine macros` `UTLMAC.REQ`
00300	
00400	This macro library provides an interface to some of the
00500	utility conversion routines documented in Appendix A of the
00600	RSX-11M/RSX-11S Release Notes (DEC-11-OMRNA-C-D).
00700	
00800	.ss($CDTB -- Decimal to Binary Conversion)
00900	`$CDTB` `conversion, decimal to binary`
01000	
01100	The $CDTB macro calls a routine to perform conversion
01200	from ASCII decimal to binary.  The calling sequence
01300	is as follows:
01400	
01500	.begin nofill
01600	
01700		[next=]$CDTB(instr,[num],[term]);
01800	
01900		next:	address of next byte in input string
02000		instr:	input string address
02100		num:	address to store converted result
02200		term:	address to return terminal character
02300	.end
02400	
02500	.ss($COTB -- Octal to Binary Conversion)
02600	`$COTB` `conversion, octal to binary`
02700	
02800	The $COTB macro calls a routine to perform conversion
02900	from ASCII octal to binary.  The calling sequence is
03000	as follows:
03100	
03200	.begin nofill
03300	
03400		[next=]$COTB(instr,[num],[term]);
03500	
03600		next:	address of next byte in input string
03700		instr:	input string address
03800		num:	address to store converted result
03900		term:	address to return converted character
04000	.end
04100	
04200	.ss(?.ODCVT -- ASCII to Binary with Octal Default)
04300	`?.ODCVT` `conversion, octal to binary`
04400	
04500	The ?.ODCVT macro calls a routine to perform conversion
04600	from ASCII to binary with octal conversion defaulted.
04700	The default can be overridden by terminating the number
04800	with '.'.  The calling sequence is as follows:
04900	
05000	.begin nofill
05100	
05200		?.ODCVT(result,inlen,instr[,err]);
05300	
05400		result:	address to store converted result
05500		inlen:	length of input string in bytes
05600		instr:	input string address
05700		err:	optional error expression
05800	
05900	.end
06000	
06100	.ss(?.DCCVT -- ASCII to Binary with Decimal Default)
06200	`?.DCCVT` `conversion, decimal to binary`
06300	
06400	The ?.DCCVT macro calls a routine to perform conversion
06500	from ASCII to binary with decimal conversion defaulted.
06600	The default can be overridden by preceeding the number
06700	with '#'.  The calling sequence is as follows:
06800	
06900	.begin nofill
07000	
07100		?.DCCVT(result,inlen,instr[,err]);
07200	
07300		result:	address to store converted result
07400		inlen:	length of input string in bytes
07500		instr:	input string address
07600		err:	optional error expression
07700	.end
07800	
07900	.ss($EDMSG -- Edit Message)
08000	`$EDMSG`
08100	
08200	The $EDMSG macro calls a routine to process an ASCIZ
08300	format string to produce an edited output string.
08400	The format string is scanned looking for &format
08500	directives&.  As each non-format character is
08600	encountered, it is simply copied into the output
08700	string.  If a '%' sign is followed by a 'V' (value),
08800	then the repeat count is taken from the next word
08900	in the argument block.  Else the next 'N' characters
09000	(by context) are converted to binary and this value
09100	is taken as the repeat count.  A repeat count of
09200	zero is defaulted to a repeat count of one in either
09300	case.  The next character in the format string must
09400	be a format directive.
09500	The calling sequence is as follows:
09600	
09700	.begin nofill
09800	
09900		[last=]$EDMSG(outstr,instr,argblk,[outlen],
10000			[nxtarg]);
10100	
10200		last:	address of last byte in output string
10300		instr:	input string address
10400		argblk:	argument block address
10500		outlen:	address to store output string length
10600		nxtarg:	address to store address of next
10700			argument in the argument block.
10800	.end
10900	
11000	The following sections
11100	describe the implemented &format directives&.
11200	
11300	.sss(%A -- ASCII String Conversion)
11400	`conversion, ASCII string`
11500	
11600	The %nA format directive copies 'n' characters to the
11700	output string from the address supplied in the
11800	argument block.
11900	
12000	.sss(%B -- Binary Byte to Octal Conversion)
12100	`conversion, binary byte to octal`
12200	
12300	The %nB format directive converts 'n' bytes beginning
12400	at the address specified in the argument block to ASCII
12500	octal with leading zeros, and places the results in the
12600	output string.  If more than one byte is converted, spaces
12700	are inserted between numbers.
12800	
12900	.sss(%D -- Signed Binary-to-Decimal Conversion)
13000	`conversion, signed binary to decimal`
13100	
13200	The %nD format directive converts the next 'n'
13300	words in the argument block to signed ASCII decimal,
13400	leading zeroes suppressed, and places the results
13500	in the output string.  If more than one number is
13600	converted, tabs are inserted between numbers.
13700	
13800	.sss(%E -- Extended ASCII String Conversion)
13900	`conversion, extended ASCII string`
14000	
14100	The %nE format directive copies 'n' characters to the output
14200	string from the address supplied in the argument block.
14300	The non-printing ASCII codes 0 through 37 (octal) and 177 (octal)
14400	are converted to spaces.
14500	
14600	.sss(%F -- Form Control)
14700	`form control`
14800	
14900	The %nF format directive causes 'n' form feeds
15000	to be inserted in the output string.
15100	
15200	.sss(%M -- Magnitude Binary-to-Decimal Conversion with Zero Suppression)
15300	`conversion, magnitude binary to decimal with zero suppression`
15400	
15500	The %nM format directive converts the next 'n'
15600	words in the argument block to unsigned ASCII decimal,
15700	leading zeroes suppressed, and places the results
15800	in the output string.  If more than one number is
15900	converted, tabs are inserted between numbers.
16000	
16100	.sss(%N -- New Line)
16200	`new line`
16300	
16400	The %nN format directive causes 'n' CR-LF
16500	sequences to be inserted in the output string.
16600	
16700	.sss(%O -- Signed Binary-to-Octal Conversion)
16800	`conversion, signed binary to octal`
16900	
17000	The %nO format directive converts the next 'n'
17100	words in the argument block to ASCII octal,
17200	leading zeroes suppressed, and places the results
17300	in the output string.  If more than one number is
17400	converted, tabs are inserted between numbers.
17500	
17600	.sss(%P -- Magnitude Binary-to-Octal Conversion)
17700	`conversion, magnitude binary to octal`
17800	
17900	The %nP format directive converts the next 'n'
18000	words in the argument block to ASCII octal, and
18100	places the results in the output string.  If
18200	more than one number is converted, tabs are inserted
18300	between numbers.
18400	
18500	.sss(%R -- RAD50-to-ASCII Conversion)
18600	`conversion, RAD50 to ASCII`
18700	
18800	The %nR format directive converts the next 'n'
18900	words in the argument block from RAD50 to ASCII
19000	and places the results in the output string.
19100	
19200	.sss(%S -- Space Generation)
19300	`space generation`
19400	
19500	The %nS format directive inserts 'n' spaces in the
19600	output string.
19700	
19800	.sss(%T -- Double Precision Binary-to-Decimal Conversion)
19900	`conversion, double precision binary to decimal`
20000	
20100	The %nT format directive converts the double-precision
20200	binary numbers stored at the next 'n' addresses specified
20300	in the argument block to unsigned ASCII decimal, leading
20400	zeroes suppressed, and places the results in the output
20500	string.  If more than one number is converted, tabs are
20600	inserted between numbers.  The double-precision numbers
20700	must be stored high-order part first and must be less than
20800	999999999; larger numbers cause a string of five asterisks
20900	to be inserted in the output string.
21000	
21100	.sss(%U -- Magnitude Binary-to-Decimal Conversion without Zero Suppression)
21200	`conversion, magnitude binary to decimal without zero suppression`
21300	
21400	The %nU format directive converts the next 'n'
21500	words in the argument block to unsigned ASCII decimal,
21600	with leading zeroes, and places the results
21700	in the output string.  If more than one number is
21800	converted, tabs are inserted between numbers.
21900	
22000	.sss(%X -- File Name Conversion)
22100	`conversion, file name`
22200	
22300	The %nX format directive converts the next 'n'
22400	file names in the argument block to ASCII and 
22500	stores the results in the output string.
22600	Each file name in the argument block must be
22700	formatted as in an FNB; i.e.,
22800	
22900	.begin nofill
23000	
23100	.group
23200		Word    Contents
23300	
23400		0	RAD50 File Name, 1st 3 characters
23500		1	RAD50 File Name, 2nd 3 characters
23600		2	RAD50 File Name, 3rd 3 characters
23700		3	RAD50 File Type, 3 characters
23800		4	File Version Number, binary integer
23900	.apart
24000	.end
24100	
24200	If more than one file name is converted, tabs are
24300	inserted between names.
24400	
24500	.sss(%Y -- Date Conversion)
24600	`conversion, date`
24700	
24800	The %Y format directive converts the date stored in
24900	the argument block from the standard system format
25000	to an ASCII string of the form
25100	'DD-MMM-YY' and stores the result in the output
25200	string.
25300	The format for the argument block is the same as 
25400	that returned by the &?GTIM$& executive service; i.e.,
25500	
25600	.begin nofill
25700	
25800	.group
25900		Word    Contents
26000	
26100		0	Year-1900
26200		1	Month-of-Year
26300		2	Day-of-Month
26400	.apart
26500	.end
26600	
26700	.sss(%Z -- Time Conversion)
26800	`conversion, time`
26900	
27000	The %nZ format directive converts the time 
27100	stored in the argument block from the
27200	standard system format to an ASCII string of the form
27300	'HH:MM:SS.S' and stores the result in the output
27400	string. The parameter 'n' controls the format
27500	of the output string as follows:
27600	
27700	.begin nofill
27800	
27900		0 or 1	Output: HH
28000		2	Output: HH:MM
28100		3	Output: HH:MM:SS
28200		4	Output: HH:MM:SS.S
28300	.end
28400	
28500	The format for the argument block is the same as
28600	that returned by the &?GTIM$& executive service; i.e,
28700	
28800	.begin nofill
28900	
29000	.group
29100		Word    Contents
29200	
29300		0	Hour-of-Day
29400		1	Minute-of-Hour
29500		2	Second-of-Minute
29600		3	Tick-of-Second
29700		4	Ticks-per-Second
29800	.apart
29900	.end
30000	
30100	.sss(%> -- Fixed Length Field Definition)
30200	`fixed length field definition`
30300	
30400	The %n> format directive inserts 'n' spaces in the output
30500	string, followed by a null.  Upon completion, the output
30600	string pointer is restored to its value before the %>
30700	directive.  This field may then be partially overwritten
30800	with the output from another format directive and the remaining
30900	spaces skipped over by the %< format directive, thus producing
31000	a fixed length output field of 'n' characters.
31100	
31200	.sss(%< -- Locate Field Mark)
31300	`locate field mark`
31400	
31500	The %n< format directive advances the output string pointer
31600	until a field delimiter (null) is located or 'n' characters
31700	are skipped, whichever occurs first.
31800	
31900	.ss(Dynamic Storage Allocation Macros)
32000	`dynamic storage allocation`
32100	
32200	The macros &$RQCB& and &$RLCB& are provided as
32300	an interface to the dynamic storage allocation
32400	routines.  These routines require a data structure
32500	similar to the following:
32600	
32700	.begin nofill
32800	
32900	!
33000	! Free Block List Header:
33100	!
33200		OWN FREEHD[2]=(FREEBK,0);
33300	!
33400	! Free Storage List:
33500	!
33600		OWN FREEBK[size]=(0,size*2);
33700	.end
33800	
33900	.sss($RQCB -- Request Core Block)
34000	`$RQCB`
34100	
34200	The $RQCB macro invokes a routine to allocate a
34300	block from the free storage list.  The calling
34400	sequence is as follows:
34500	
34600	.begin nofill
34700	
34800		blkadr=$RQCB(freehd,blksiz,err);
34900	
35000		blkadr:	address of allocated block
35100		freehd:	address of Free Block List Header
35200		blksiz:	size of block requested in bytes
35300		err:	expression to be executed if block
35400			allocation fails.
35500	.end
35600	
35700	If 'blksiz' is positive then best fit allocation
35800	is used; if negative then first fit allocation is
35900	used.
36000	
36100	.sss($RLCB -- Release Core Block)
36200	`$RLCB`
36300	
36400	The $RLCB macro invokes a routine to return a
36500	block to the free storage list.  The calling 
36600	sequence is as follows:
36700	
36800	.begin nofill
36900	
37000		$RLCB(freehd,blksiz,blkadr);
37100	
37200		freehd:	address of Free Block List Header
37300		blksiz:	size of block to release in bytes
37400		blkadr:	address of block to be released
37500	.end
37600	
     
00100	.s(B11MAC.REQ -- Miscellaneous Useful Macros)
00200	`B11MAC.REQ`
00300	
00400	The macro library file B11MAC.REQ contains a number
00500	of miscellaneous useful macros, some of which are
00600	described in the following sections.  Note that
00700	B11MAC.REQ is REQUIREd by all the other macro
00800	libraries described in this document.
00900	
01000	.ss(?.PACKBYTE -- Pack Bytes for <plit-arg>)
01100	`?.PACKBYTE` `<plit-arg>` `bytes, packing`
01200	
01300	The ?.PACKBYTE macro takes a list of load-time
01400	expressions and expands into a <plit-arg> with
01500	those expression values stored in consecutive
01600	bytes. An additional zero byte is generated
01700	if the number of expressions is odd.
01800	
01900	.ss(?.REVERSE -- Reverse Parameter List)
02000	`?.REVERSE`
02100	
02200	The ?.REVERSE macro takes a list of expressions
02300	and expands into the same list, but in reverse
02400	order.  This macro is sometimes useful when
02500	pushing things on a stack.
02600	
02700	.ss(?.SAVEREG -- Save Registers)
02800	`?.SAVREG` `registers, saving`
02900	
03000	The ?.SAVEREG macro is called with a list of
03100	register names.  It expands into something
03200	that makes the BLISS-11 compiler think it's
03300	necessary to save those registers within a
03400	ROUTINE.
03500	
03600	.ss(Position-Size Modifier Macros)
03700	`PSM` `position-size modifier` `names, bit field`
03800	
03900	As described in {REFER(BITDEF)}, bit fields are
04000	defined by macros which expand into an appropriate
04100	&PSM&.  The following sections describe macros that
04200	are sometimes useful in manipulating PSMs.
04300	
04400	.sss(?.POS -- Extract Position Component of PSM)
04500	
04600	The &?.POS& macro takes a list of position-size pairs
04700	and expands into a list of the positions only; e.g.,
04800	?.POS(0,1,2,3) is 0,2.
04900	
05000	.sss(?.SIZE -- Extract Size Component of PSM)
05100	
05200	The &?.SIZE& macro takes a list of position-size pairs
05300	and expands into a list of the sizes only; e.g,
05400	?.SIZE(0,1,2,3) is 1,3.
05500	
05600	.sss(?.MASK -- Form Mask from PSMs)
05700	
05800	The &?.MASK& macro takes a list of position-size pairs
05900	and expands into a mask word that is the logical OR
06000	of the bit fields defined by the PSM pairs; e.g,
06100	?.MASK(3,3,0,1) is #71.
06200	
06300	.ss(Macro Parameter Handling)
06400	`macro parameters`
06500	
06600	&B11MAC.REQ& contains a number of macros that are
06700	useful in handling macro parameters; these are
06800	described in the following sections.
06900	
07000	.sss(?.SUBLIST -- Extract Parameter Sublist)
07100	
07200	The &?.SUBLIST& macro removes the brackets
07300	surrounding a &parameter sublist&.  Note that
07400	the brackets must be present if the sublist
07500	is not null.
07600	
07700	.sss(?.SELECT -- Selective Expansion)
07800	`expansion, selective`
07900	
08000	The &?.SELECT& macro is called as follows:
08100	
08200	.begin nofill
08300	
08400		?.SELECT(par1,<par2>,<par3>)
08500	.end
08600	
08700	The result is par2 if par1 is not null and
08800	par3 if par1 is null.
08900	
09000	.sss(?.COND -- Conditional Expansion)
09100	`expansion, conditional`
09200	
09300	The &?.COND& macro is called as follows:
09400	
09500	.begin nofill
09600	
09700		?.COND(par1,par2)
09800	.end
09900	
10000	The result is par2 if par1 is not null and
10100	null if par1 is null.
10200	
10300	.sss(?.DEFAULT -- Default Null Parameter)
10400	`expansion, default`
10500	
10600	The &?.DEFAULT& macro is called as follows:
10700	
10800	.begin nofill
10900	
11000		?.DEFAULT(par1,par2)
11100	.end
11200	
11300	The result is par1 if par1 is not null and
11400	par2 if par1 is null.
     
00100	.DOAPPENDIX(A)
     
00100	.s(Summary of Current Known Bugs and Limitations)
00200	.LABEL(BUGAPPNDX)
00300	`bugs` `limitations`
00400	
00500	.ss(Use of EXITLOOP in Error Expressions)
00600	`EXITLOOP` `error expression`
00700	
00800	The code generated for expressions skipped by OPCODE branch
00900	instructions is incorrect if the skipped expressions adjust
01000	the depth of the stack (e.g., to call a routine) due to a
01100	bug in the BLISS-11 compiler.  To avoid this problem, macros
01200	with explicit or default &error expression&s expand as follows:
01300	
01400	.begin nofill
01500	
01600		BEGIN
01700		    SWITCHES UNAMES;
01800		    OPCODE ?.BCC=BCC;
01900		    OPLABEL ?.NOERR;
02000		    ...
02100		    ?.BCC(?.NOERR);
02200		    DO (error expression) WHILE 0;
02300		    ?.NOERR:END;
02400	.end
02500	
02600	Thus, the use of &EXITLOOP& in an &error expression& may
02700	not produce the intended result, as in the following example:
02800	
02900	.begin nofill
03000	
03100		INCR I FROM 1 TO 10 DO
03200		    ?CLEF$S(.I,EXITLOOP);
03300	.end
03400	
03500	The EXITLOOP exits from the innermost loop, which in this
03600	case is the DO ... WHILE 0 loop in the macro expansion of
03700	?CLEF$S instead of the INCR loop.
03800	
03900	.ss(?GCMLB$)
04000	`?GCMLB$`
04100	
04200	A bug in the BLISS-11 compiler causes the offset
04300	location ?F.DFNB in the FDB generated as part of
04400	the GCML control block to be improperly initialized.
04500	To remedy this problem, execute the following
04600	expression prior to calling ?GCML$ for the first
04700	time:
04800	
04900	.begin nofill
05000	
05100		?FDOPR(cmdblk,,,cmdblk+?S.FDB+2*11);
05200	
05300		cmdblk:	address of the GCML control block
05400	.end
     
00100	.s(Compile-time FDB Initialization Macro Summary)
00200	.LABEL(FDBDFAPNDX)
00300	`FDB, initialization of`
00400	
00500	.begin nofill
00600		BLISS-11	    MACRO-11
00700	
00800		?AT$FIX		FDAT$A  R.FIX
00900		?AT$VAR		FDAT$A  R.VAR
01000		?AT$SEQ		FDAT$A	R.SEQ
01100		?AT$FTN		FDAT$A	,FD.FTN
01200		?AT$CR		FDAT$A	,FD.CR
01300		?AT$BLK		FDAT$A	,FD.BLK
01400		?AT$RSIZ(RSIZ)	FDAT$A	,,RSIZ
01500		?AT$CNTG(CNTG)	FDAT$A	,,,CNTG
01600		?AT$ALOC(ALOC)	FDAT$A	,,,,ALOC
01700	
01800		?RC$RWM		FDRC$A	FD.RWM
01900		?RC$RAN		FDRC$A	FD.RAN
02000		?RC$PLC		FDRC$A	FD.PLC
02100		?RC$INS		FDRC$A	FD.INS
02200		?RC$URBA(URBA)	FDRC$A	,URBA
02300		?RC$URBS(URBS)	FDRC$A	,,URBS
02400	
02500		?BK$DA(BKDA)	FDBK$A	BKDA
02600		?BK$DS(BKDS)	FDBK$A	,BKDS
02700		?BK$EF(BKEF)	FDBK$A	,,,BKEF
02800		?BK$ST(BKST)	FDBK$A	,,,,BKST
02900		?BK$DN(BKDN)	FDBK$A	,,,,,BKDN
03000	
03100		?OP$LUN(LUN)	FDOP$A	LUN
03200		?OP$DSPT(DSPT)	FDOP$A	,DSPT
03300		?OP$DFNB(DFNB)	FDOP$A	,,DFNB
03400		?OP$RD		FDOP$A	,,,FA.RD
03500		?OP$WRT		FDOP$A	,,,FA.WRT
03600		?OP$EXT		FDOP$A	,,,FA.EXT
03700		?OP$CRE		FDOP$A	,,,FA.CRE
03800		?OP$TMP		FDOP$A	,,,FA.TMP
03900		?OP$SHR		FDOP$A	,,,FA.SHR
04000		?OP$APD		FDOP$A	,,,FA.APD
04100		?OP$NSP		FDOP$A	,,,FA.NSP
04200	
04300		?BF$EFN(EFN)	FDBF$A	EFN
04400		?BF$OVBS(OVBS)	FDBF$A	,OVBS
04500		?BF$MBCT(MBCT)	FDBF$A	,,MBCT
04600		?BF$RAH		FDBF$A	,,,FD.RAH
04700		?BF$WBH		FDBF$A	,,,FD.WBH
04800	.end
04900	
     
00100	.s(Summary of Implemented Macros)
00200	
00300	The following sections summarize all currently implemented
00400	macros.  Optional parameters are indicated by "[ ]", sublist
00500	parameters are indicated by "< >", and optional sublist
00600	parameters are indicated by "[< >]".
00700	
00800	.ss(RSXMAC.REQ Macro Summary)
00900	`RSXMAC.REQ`
01000	
01100	.begin nofill
01200	
01300	&?ABRT$& (tsk)
01400	&?ABRT$C&(dpb)
01500	&?ABRT$S&(tsk,[err])
01600	&?ALTP$& ([tsk],[pri])
01700	&?ALTP$C&(dpb)
01800	&?ALTP$S&([tsk],[pri],[err])
01900	&?ALUN$& (lun,dev,unt)
02000	&?ALUN$C&(dpb)
02100	&?ALUN$S&(lun,dev,unt,[err])
02200	&?ASTX$S&([err])
02300	&?ATRG$& (rdb)
02400	&?ATRG$C&(dpb)
02500	&?ATRG$S&(rdb,[err])
02600	&?CLEF$& (efn)
02700	&?CLEF$C&(dpb)
02800	&?CLEF$S&(efn,[err])
02900	&?CMKT$S&(,,[err])
03000	&?CRAW$& (wdb)
03100	&?CRAW$C&(dpb)
03200	&?CRAW$S&(wdb,[err])
03300	&?CRRG$& (rdb)
03400	&?CRRG$C&(dpb)
03500	&?CRRG$S&(rdb,[err])
03600	&?CSRQ$& (tsk)
03700	&?CSRQ$C&(dpb)
03800	&?CSRQ$S&(tsk,,[err])
03900	&?DECL$S&(,[err])
04000	&?DIR$&  (<dpb>,[err])
04100	&?DRERR$&
04200	&?DSAR$S&([err])
04300	&?DSCP$S&([err])
04400	&?DTRG$& (rdb)
04500	&?DTRG$C&(dpb)
04600	&?DTRG$S&(rdb,,[err])
04700	&?ELAW$& (wdb)
04800	&?ELAW$C&(dpb)
04900	&?ELAW$S&(wdb,[err])
05000	&?ENAR$S&([err])
05100	&?ENCP$S&([err])
05200	&?EXIF$& (efn)
05300	&?EXIF$C&(dpb)
05400	&?EXIF$S&(efn,[err])
05500	&?EXIT$S&([err])
05600	&?EXTK$& ([inc])
05700	&?EXTK$C&(dpb)
05800	&?EXTK$S&([inc],[err])
05900	&?FILIO$&
06000	&?GLUN$& (lun,buf)
06100	&?GLUN$B&(buf)
06200	&?GLUN$C&(dpb)
06300	&?GLUN$S&(lun,buf,[err])
06400	&?GMCR$&
06500	&?GMCR$C&(dpb)
06600	&?GMCX$& (wvec)
06700	&?GMCX$C&(dpb)
06800	&?GMCX$S&(wvec,[err])
06900	&?GPRT$& ([prt],buf)
07000	&?GPRT$B&(buf)
07100	&?GPRT$C&(dpb)
07200	&?GPRT$S&([prt],buf,[err])
07300	&?GREG$& ([rid],buf)
07400	&?GREG$B&(buf)
07500	&?GREG$C&(dpb)
07600	&?GREG$S&([rid],buf,[err])
07700	&?GSSW$S&([err])
07800	&?GTIM$& (buf)
07900	&?GTIM$B&(buf)
08000	&?GTIM$C&(dpb)
08100	&?GTIM$S&(buf,[err])
08200	&?GTSK$& (buf)
08300	&?GTSK$B&(buf)
08400	&?GTSK$C&(dpb)
08500	&?GTSK$S&(buf,[err])
08600	&?MAP$&  (wdb)
08700	&?MAP$C& (dpb)
08800	&?MAP$S& (wdb)
08900	&?MRKT$& ([efn],tmg,tnt,[ast])
09000	&?MRKT$C&(dpb)
09100	&?MRKT$S&([efn],tmg,tnt,[ast],[err])
09200	&?QIOSY$&
09300	&?QIO$&  (fnc,lun,[efn],[pri],[isb],[ast],[<prl>])
09400	&?QIO$C& (dpb)
09500	&?QIO$S& (fnc,lun,[efn],[pri],[isb],[ast],[<prl>])
09600	&?QIOW$& (fnc,lun,[efn],[pri],[isb],[ast],[<prl>])
09700	&?QIOW$C&(dpb)
09800	&?QIOW$S&(fnc,lun,[efn],[pri],[isb],[ast],[<prl>])
09900	&?RCVD$& (,buf)
10000	&?RCVD$C&(dpb)
10100	&?RCVD$S&(,buf,[err])
10200	&?RCVX$& (,buf)
10300	&?RCVX$C&(dpb)
10400	&?RCVX$S&(,buf,[err])
10500	&?RDAF$& (buf)
10600	&?RDAF$C&(dpb)
10700	&?RDAF$S&(buf,[err])
10800	&?RDBBK$&([siz],[nam],[par],[<sts>],[pro])
10900	&?RDBDF$&
11000	&?RQST$& (tsk,[prt],[pri],[ugc,umc])
11100	&?RQST$C&(dpb)
11200	&?RQST$S&(tsk,[prt],[pri],[ugc,umc],[err])
11300	&?RREF$& (wdb)
11400	&?RREF$C&(dpb)
11500	&?RREF$S&(wdb,[err])
11600	&?RSUM$& (tsk)
11700	&?RSUM$C&(dpb)
11800	&?RSUM$S&(tsk,[err])
11900	&?RUN$&  (tsk,[prt],[pri],[ugc],[umc],[smg],snt,[rmg],[rnt])
12000	&?RUN$C& (dpb)
12100	&?RUN$S& (tsk,[prt],[pri],[ugc],[umc],[smg],snt,[rmg],[rnt],[err])
12200	&?SDAT$& (tsk,buf,[efn])
12300	&?SDAT$C&(dpb)
12400	&?SDAT$S&(tsk,buf,[efn],[err])
12500	&?SETF$& (efn)
12600	&?SETF$C&(dpb)
12700	&?SETF$S&(efn,[err])
12800	&?SFPA$& ([ast])
12900	&?SFPA$C&(dpb)
13000	&?SFPA$S&([ast],[err])
13100	&?SNAP$& (ctl,efn,id,l1,h1,l2,h2,l3,h3,l4,h4)
13200	&?SNPBK$&(dev,unit,ctl,efn,id,l1,h1,l2,h2,l3,h3,l4,h4)
13300	&?SNPDF$&
13400	&?SPCIO$&
13500	&?SPND$S&([err])
13600	&?SPRA$& ([ast])
13700	&?SPRA$C&(dpb)
13800	&?SPRA$S&([ast],[err])
13900	&?SRDA$& ([ast])
14000	&?SRDA$C&(dpb)
14100	&?SRDA$S&([ast],[err])
14200	&?SREF$& (tsk,wdb,[efn])
14300	&?SREF$C&(dpb)
14400	&?SREF$S&(tsk,wdb,[efn],[err])
14500	&?SRRA$& ([ast])
14600	&?SRRA$C&(dpb)
14700	&?SRRA$S&([ast],[err])
14800	&?SVDB$& ([adr],[len])
14900	&?SVDB$C&(dpb)
15000	&?SVDB$S&([adr],[len],[err])
15100	&?SVTK$& ([adr],[len])
15200	&?SVTK$C&(dpb)
15300	&?SVTK$S&([adr],[len],[err])
15400	&?TTSYM$&
15500	&?UMAP$& (wdb)
15600	&?UMAP$C&(dpb)
15700	&?UMAP$S&(wdb,[err])
15800	&?UMDIO$&
15900	&?WDBBK$&([apr],[siz],[rid],[off],[len],[<sts>],[srb])
16000	&?WDBDF$&
16100	&?WSIG$S&([err])
16200	&?WTLO$& (grp,msk)
16300	&?WTLO$C&(dpb)
16400	&?WTLO$S&(grp,msk,[err])
16500	&?WTSE$& (efn)
16600	&?WTSE$C&(dpb)
16700	&?WTSE$S&(efn,[err])
16800	&?$C&    (<dpb>,[err])
16900	.end
     
00100	.ss(FCSMAC.REQ Macro Summary)
00200	`FCSMAC.REQ`
00300	
00400	.begin nofill
00500	
00600	&?ASCPP$&(ascpp,binpp,[err])
00700	&?ASLUN$&(fdb,[fnb],[err])
00800	&?CCML$& (gclblk,[err])
00900	&?CLOSE$&(fdb,[err])
01000	&?CSI$&
01100	&?CSI$SV&(type,adr,len, ... )
01200	&?CSI$SW&(sw,[mk],[mkw],[clr],[neg],[vtab], ... )
01300	&?CSI$1& (csiblk,[buff],[len],[err])
01400	&?CSI$2& (csiblk,[io],[swtab],[err])
01500	&?DELET$&(fdb,[err])
01600	&?DLFNB$&(fdb,[err])
01700	&?ENTER$&(fdb,[fnb],[err])
01800	&?EXTND$&(fdb,lnblks,hnblks,<ext>,[err])
01900	&?FCSBT$&
02000	&?FCSERRDF$&
02100	&?FDAT$R&(fdb,[rtyp],[<ratt>],[rsiz],[cntg],[aloc])
02200	&?FDBDF$&(fdbname,m1,m2, ... ,mn)
02300	&?FDBF$R&(fdb,[efn],[ovbs],[mbct],[<mbfg>])
02400	&?FDBK$R&(fdb,[bkad],[bksz],[bkvb],[bkef],[bkst],[bkdn])
02500	&?FDOFF$&
02600	&?FDOF$L&
02700	&?FDOP$R&(fdb,[lun],[dspt],[dfnb],[<facc>],)
02800	&?FDRC$R&(fdb,[<racc>],[urba],[urbs])
02900	&?FIND$& (fdb,[fnb],[err])
03000	&?FINIT$&
03100	&?GCMLB$&(fdb,[maxd],[prmpt],[ubuf],[lun],[pdl])
03200	&?GCMLD$&
03300	&?GCML$& (gclblk,[adpr],[lnpr],[err])
03400	&?GET$&  (fdb,[urba],[urbs],[err])
03500	&?GET$R& (fdb,[urba],[urbs],[lrcnm],[hrcnm],[err])
03600	&?GET$S& (fdb,[urba],[urbs],[err])
03700	&?GTDID$&(fdb,[fnb],[err])
03800	&?GTDIR$&(fdb,[fnb],[dspt],[err])
03900	&?IOERR$&
04000	&?MARK$& (fdb,lbkvb,hbkvb,bytenum)
04100	&?MRKDL$&(fdb,[err])
04200	&?NBOFF$&
04300	&?NBOF$L&
04400	&?NMBLK$&([fnam],[ftyp],[fver],[dvnm],[unit])
04500	&?OFID$& (fdb,[<facc>],[lun],[dspt],[dfnb],
04600		[<racc>],[urba],[urbs],[err])
04700	&?OFID$A&(fdb,[lun],[dspt],[<racc>],[urba],[urbs],[err])
04800	&?OFID$M&(fdb,[lun],[dspt],[<racc>],[urba],[urbs],[err])
04900	&?OFID$R&(fdb,[lun],[dspt],[<racc>],[urba],[urbs],[err])
05000	&?OFID$U&(fdb,[lun],[dspt],[<racc>],[urba],[urbs],[err])
05100	&?OFID$W&(fdb,[lun],[dspt],[<racc>],[urba],[urbs],[err])
05200	&?OFNB$& (fdb,[<facc>],[lun],[dspt],[dfnb],
05300		[<racc>],[urba],[urbs],[err])
05400	&?OFNB$A&(fdb,[lun],[dspt],[<racc>],[urba],[urbs],[err])
05500	&?OFNB$M&(fdb,[lun],[dspt],[<racc>],[urba],[urbs],[err])
05600	&?OFNB$R&(fdb,[lun],[dspt],[<racc>],[urba],[urbs],[err])
05700	&?OFNB$U&(fdb,[lun],[dspt],[<racc>],[urba],[urbs],[err])
05800	&?OFNB$W&(fdb,[lun],[dspt],[<racc>],[urba],[urbs],[err])
05900	&?OPEN$& (fdb,[<facc>],[lun],[dspt],[dfnb],
06000		[<racc>],[urba],[urbs],[err])
06100	&?OPEN$A&(fdb,[lun],[dspt],[<racc>],[urba],[urbs],[err])
06200	&?OPEN$M&(fdb,[lun],[dspt],[<racc>],[urba],[urbs],[err])
06300	&?OPEN$R&(fdb,[lun],[dspt],[<racc>],[urba],[urbs],[err])
06400	&?OPEN$U&(fdb,[lun],[dspt],[<racc>],[urba],[urbs],[err])
06500	&?OPEN$W&(fdb,[lun],[dspt],[<racc>],[urba],[urbs],[err])
06600	&?OPNS$A&(fdb,[lun],[dspt],[<racc>],[urba],[urbs],[err])
06700	&?OPNS$M&(fdb,[lun],[dspt],[<racc>],[urba],[urbs],[err])
06800	&?OPNS$R&(fdb,[lun],[dspt],[<racc>],[urba],[urbs],[err])
06900	&?OPNS$U&(fdb,[lun],[dspt],[<racc>],[urba],[urbs],[err])
07000	&?OPNS$W&(fdb,[lun],[dspt],[<racc>],[urba],[urbs],[err])
07100	&?OPNT$D&(fdb,[lun],[dspt],[<racc>],[urba],[urbs],[err])
07200	&?OPNT$W&(fdb,[lun],[dspt],[<racc>],[urba],[urbs],[err])
07300	&?PARSE$&(fdb,[fnb],[dspt],[dfnb],[err])
07400	&?POINT$&(fdb,lbkvb,hbkvb,bytenum,[err])
07500	&?POSIT$&(fdb,[lrcnm],[hrcnm],[lbkvb],[hbkvb],[bytenum],[err])
07600	&?POSRC$&(fdb,lrcnm,hrcnm,[err])
07700	&?PPASC$&(ascpp,binpp,zero,sep)
07800	&?PRINT$&(fdb,[err])
07900	&?PRSDV$&(fdb,[fnb],[dspt],[dfnb],[err])
08000	&?PUT$&  (fdb,[nrba],[nrbs],[err])
08100	&?PUT$R& (fdb,[nrba],[nrbs],[lrcnm],[hrcnm],[err])
08200	&?PUT$S& (fdb,[nrba],[nrbs],[err])
08300	&?RCML$& (gclblk,[err])
08400	&?RDFDR$&(size,addr)
08500	&?RDFFP$&
08600	&?READ$& (fdb,[bkda],[bkds],[bkvb],[bkef],[bkst],[bkdn],[err])
08700	&?REMOV$&(fdb,[fnb],[err])
08800	&?RENAM$&(oldfdb,newfdb,[err])
08900	&?RFOWN$&
09000	&?TRUNC$&(fdb,[err])
09100	&?WAIT$& (fdb,[bkef],[bkst],[err])
09200	&?WDFDR$&(size,addr)
09300	&?WDFFP$&(prot)
09400	&?WFOWN$&(pp)
09500	&?WRITE$&(fdb,[bkda],[bkds],[bkvb],[bkef],[bkst],[bkdn],[err])
09600	&?XQIO$& (fdb,fcn,pnum,padr,[err])
09700	.end
     
00100	.ss(FSRMAC.REQ Macro Summary)
00200	`FSRMAC.REQ`
00300	
00400	.begin nofill
00500	
00600	&?BDOFF$&
00700	&?FSRSZ$&(nfiles,[bfspac])
00800	.end
     
00100	.ss(EXEMC.REQ Macro Summary)
00200	`EXEMC.REQ`
00300	
00400	.begin nofill
00500	
00600	&?ADBDF$&(adb)
00700	&?DCBDF$&(dcb)
00800	&?HDRDF$&(hdr)
00900	&?PCBDF$&(pcb)
01000	&?SCBDF$&(scb)
01100	&?TCBDF$&(tcb)
01200	&?UCBDF$&(ucb)
01300	&?WBKDF$&(wbk)
01400	.end
     
00100	.ss(UTLMAC.REQ Macro Summary)
00200	`UTLMAC.REQ`
00300	
00400	.begin nofill
00500	
00600	&?$CDTB& (instr,[num],[term])
00700	&?$COTB& (instr,[num],[term])
00800	&?$EDMSG&(outstr,instr,argblk,[outlen],[nxtarg])
00900	&?$RLCB& (freehd,blksz,blkadr)
01000	&?$RQCB& (freehd,blksz,err)
01100	&?.DCCVT&(result,inlen,instr,[err])
01200	&?.ODCVT&(result,inlen,instr,[err])
01300	.end
     
00100	.ss(B11MAC.REQ Macro Summary)
00200	`B11MAC.REQ`
00300	
00400	.begin nofill
00500	
00600	&?.ASGNC&   (dst,[src])
00700	&?.COMMA&   ([p])
00800	&?.COND&    ([p],nonnull)
00900	&?.DEFAULT& ([p],dflt)
01000	&?.MASK&    (pos1,size1, ... ,posn,sizen)
01100	&?.PACKBYTE&(byte1,byte2, ... ,byten)
01200	&?.POS&     (pos1,size1, ... ,posn,sizen)
01300	&?.REVERSE& (p1,p2, ... ,pn)
01400	&?.SAVEREG& (r1,r2, ... rn)
01500	&?.SELECT&  ([p],nonnull,null)
01600	&?.SET&     (name,value)
01700	&?.SIZE&    (pos1,size1, ... ,posn,sizen)
01800	&?.SUBLIST& (list)
01900	.end
     
00100	.STANDARD BACK