⭐ 欢迎来到虫虫下载站! | 📦 资源下载 📁 资源专辑 ℹ️ 关于我们
⭐ 虫虫下载站

📄 gwplays.asm

📁 [随书类]Dos6.0源代码
💻 ASM
📖 第 1 页 / 共 2 页
字号:
	TITLE	GWPLAYS - GW BASIC 2.0 Multi Voice Play
;***
; GWPLAYS - GW BASIC 2.0 Multi Voice Play
;
;	Copyright <C> 1986 - 1988, Microsoft Corporation
;
;Purpose:
;	Multi Voice Play statement processor
;
; BASIC Syntax mapping to included runtime entry points:
;
; - PLAY Statement:
;
;      PLAY string
;	 |
;      B$SPLY
;
;    NOTE: the more advanced syntax of 'PLAY string, string, ...' (i.e.
;    multi-voiced PLAY) will be accepted by the compiler. For all but the
;    last parameter (which is passed to B$SPLY), defaulted parameters will
;    generate a call to B$PL1, and specified parameters get passed to B$PL0
;    both of these, in turn, just generate an Advanced Feature error.
;    NOTE 2: the above comment doesn't apply to bascom 30.  The compiler
;	will not generate calls to B$PL0 and B$PL1.  They will be flagged as
;	syntax errors.	B$PL0 and B$PL1 will not be present for BASCOM 30.
;	The code to support multivoice play will be left for future reference,
;	but it will need to be changed to the new style interface (stack based)
;	if a multi voice version is ever produced.
;
;******************************************************************************

	INCLUDE switch.inc	; switch file [new]
	INCLUDE rmacros.inc	; Runtime Macro Defintions

	USESEG	_DATA		
	USESEG	_BSS		
	USESEG	SN_TEXT 	

	INCLUDE seg.inc 	
	INCLUDE	ibmunv.inc	
	INCLUDE	rtps.inc	
	INCLUDE idmac.inc	
	INCLUDE string.inc	

	.RADIX	10

;	Two new macros Alloc & DeclareB/DeclareW are defined here.
;	The main purpose of Declare macro is to allocate given number of
;	bytes (static variable) and initialize it to the specified value.
;	Additionally, it declares an EQUate for the specified variable
;	for automatic indexing if FS_MVOICE is TRUE. The index register
;	assumed is SI. Actually, the variable defined has a trailing underscore
;	and the indexed EQUate is identical to the name supplied to this macro.
;	Alloc is just a helper macro.

Alloc	MACRO	v,nm,init,siz	
static&v	<nm&_>,<init>,<siz>

nm	EQU	nm&_		
	ENDM

DeclareB	MACRO	nm,init,siz	
Alloc	B,<nm>,<init>,<siz>
	ENDM			

DeclareW	MACRO	nm,init,siz	
Alloc	W,<nm>,<init>,<siz>
	ENDM			


sBegin	_DATA			

externW	B$AC			

sEnd				

sBegin	_BSS			

	externW B$MCLTAB 	;defined in GWDATA.ASM
	externW B$MCLLEN 	;defined in GWDATA.ASM
	externW B$MCLPTR 	;defined in GWDATA.ASM

	externB B$MMODE		;defined in GWINI.ASM
	externB B$BEATS		;defined in GWINI.ASM
	externB B$NOTE1L 	;defined in GWINI.ASM
	externB B$NOTELN 	;defined in GWINI.ASM
	externB B$NOTFLG 	;defined in GWINI.ASM
	externB B$MSCALE 	;defined in GWINI.ASM
	externB B$OCTAVE 	;defined in GWINI.ASM
	externB b$VTYP		
	externW b$curlevel	;current program level



DeclareB MQUEFL,?,1		
DeclareB PLYPRS,?,1		
DeclareW STRDSC,?,NUM_VOICES	
DeclareW VSTACK,?,<NUM_VOICES*NUM_VSTACK> 
DeclareW VSTBAS,?,NUM_VOICES	
DeclareW VSTOFF,?,NUM_VOICES	

sEnd	_BSS			

assumes CS,SN_TEXT		
sBegin	SN_TEXT 		

;	externNP B$MCLXEQ	;execute substring routine

	externNP B$DONOTE	;oem routine
	externNP B$STRTSD	
	externNP B$SNDWAT	

	externNP B$ERR_FC	
	externNP B$ERR_OM	
	externNP B$ERR_TM	; Type mismatch error

	externNP B$SETMCL	
	externNP B$MACCMD	
	externNP B$FETCHR	
	externNP B$DECFET	
	externNP B$FETCHZ	
	externNP B$VALSC2	
	externNP B$BREAK_CHK	
	externNP B$GETSTKC	; Check stack
	externNP B$SCNVAR	; get descriptor from VARPTR$

	externNP B$STDALCALLTMP ; **** liberate temporaries ****

;PLAY Statement
;Syntax:
;   PLAY ON
;   PLAY OFF
;   PLAY STOP
;   PLAY [A$] [, [B$] [, [C$]]]   - multi-voice play

;PLAY is made up of a forground task and a background task.  A queue exists
;for each voice through which the forground task passes the background task
;Commands and Syncronization information.  One SYNC byte is placed in each
;voice queue at the start of each PLAY statement.  All commands which are
;produced by the PLAY statement follow the SYNC byte in the queue.
;When the background task encounters the SYNC byte, it disables that voice
;until it has received a SYNC byte for each voice and PLYBGC .GT. 0.  This
;mechanism insures that all voices for a play statement will begin at
;the same time, even if one of the voices in the previous play statement
;was shorter than the rest.

;A String-Pointer stack is associated with each voice to allow each voice
;string to include (nest) other voice strings via the X macro-language
;command.

;PLAY Algorithm:
;    Initialize a str-ptr stack for every voice.
;    Parse n strings (saving ptrs to string temps in STRDSC(i)).
;    For each voice,
;      Put SYNC byte at start of each voice queue
;      Release Temp string desc and push str ptr&len to voice's str-ptr stack.
;    For each voice,
;1)    Fill each queue as far as possible (till end-of-string or end-of-queue)
;      if 1st pass
;	 B$STRTSD (start clock int routine, all voices)
;      if no voices active and all strings are not empty, B$STRTSD(all voices)
;	 (This is a safety valve to insure BASIC will never hang during PLAY)
;    If all strings have not been completely consumed,
;      goto step 1
;  If Music Forground, wait till all voice activity halts



PLAYS:
; Entry point for the PLAY statement.  Test to see which of the
; allowed forms has been specified.

;***
; B$PL0, B$PL1, B$SPLY - Play   <sexp>... statement
;
; Purpose:
;	Runtime Entry Points.
;	B$PL0 and B$PL1 are alternate PLAY Statement preamble entry points
;		B$SPLY is called with the last parm, and it actually executes
;		the statement.
;	B$PL0   called if a parm is specified
;	B$PL1   called if a parm is defaulted
;	B$SPLY   called for last parm (may be the only parm as well)
;
;	 Parse the strings from the program statement, and set up the pointers
;	 in the string stacks.
;
; Input:
;	sdPlay == string descriptor of a single argument (B$PL0 & B$SPLY only -
;		no input is given for B$PL1)
; Output:
;	NONE
; Modifies:
;	NONE
;****


cProc	B$SPLY,<PUBLIC,FAR>,<SI> 
parmSD	sdPlay			
cBegin				
	cCALL	B$CHKINI
	GetpSD	BX,sdPlay	;BX = psd for play string
	MOV	STRDSC,BX	; save str desc for B$PARSER.
	cCALL	B$PARSE0	; Go process everything
	MOV	AX,b$curlevel	;deallocate all temps >= current level
	cCALL	B$STDALCALLTMP	
cEnd				

;***
;B$CHKINI
;
;PURPOSE:
;	Initialize runtime variables related to music if starting play statement
;
;ENTRY:
;
;EXIT:
;
;MODIFIES:
;	AX,CX,SI
;
;****

cProc	B$CHKINI,<NEAR>		
cBegin				

				;exit -- bx is preserved

	XOR	AX,AX		

	MOV	[B$MCLTAB],OFFSET PLYTAB ;B$MCLTAB points to play command table
				; for B$MACCMD
	MOV	[MQUEFL],AL	; indicates no music cmds have been queued

; Initialize the string stacks for use while parsing the play strings.
; These stacks are used to support the X music command which functions
; like a subroutine call.

	MOV	CX,OFFSET DGROUP:VSTACK ; *cx = string stack for voice 1
inistl:
	MOV	VSTOFF,AX	; reset offset for voice si
	MOV	VSTBAS,CX	; set stack base ptr for voice si
	MOV	STRDSC,AX	; reset string desr ptr for voice si
chkret:

cEnd				; End of B$CHKINI

;
;***
;B$PARSE0
;
;PURPOSE:
;	Pre-PARSER for play string
;
;ENTRY:
;
;EXIT:
;
;USES:
;	per convention
;
;****

cProc	B$PARSE0,<NEAR>	
cBegin				; **** HERE AFTER LAST PARM ****

; Release string temps in reverse order (because its a stack)

	MOV	[PLYPRS],NUM_VOICES ;NUM_VOICES strings have been parsed


SETSTL:

	MOV	BX,STRDSC	; *bx = temp str desc for voice(si)
	OR	BX,BX
	JE	EMPTYS		;branch if no string was parsed
	CALL	B$SETMCL 	;set B$MCLPTR, B$MCLLEN to str @bx
	cCALL	B$PUTSTR	;save B$MCLPTR, B$MCLLEN on voicen's stack
	DEC	[PLYPRS]	;one less string has been parsed
emptys:
	JMP	SHORT B$PARSER	

cEnd	<nogen>			; End of B$PARSE0

;***
;B$PARSER fills the background-music queues as follows:
; Repeat
;   For Each voice
;     while (input string is not empty) and
;	    (room exists in voice's queue for 1 command)
;	Call B$MACCMD to process next command in string.
;	(This causes some routine in PLYTAB to be called which may try to
;	 queue information for the background task into that voice's queue.
;   If 1st pass, DI, bump PLYBGC, cCALL	B$STRTSD(7) to initiate background task
; Until all voice strings are empty
; If music-forground, wait until PLYMSK=0
;****

cProc	B$PARSER,<NEAR>	
cBegin				

PARSER_BEGIN:			


; Get music macro commands from the string for this voice until the
; queue for this voice fills or we hit the end of the string.

PRSL10:
	cCALL	B$GETSTR		;Get B$MCLPTR, B$MCLLEN for [voicen]


	CMP	[B$MCLLEN],0	; Check if end of string
	JNE	PRSCONT		; Brif more in string, process it
	CMP	VSTOFF,0	; Test if string was nested by X command
	JNE	PRSL10		; Brif so, jump to return to next string up
	JMP	SHORT PRSLPX	; Else, the top level string s done 
PRSCONT:			; Continue with parsing
	PUSH	[B$MCLPTR]	;SAve the current string pointers
	PUSH	[B$MCLLEN]	;  in case the queue overflows

	CALL	B$MACCMD 	;Parse one command from this string
	JB	PRSL20		;Quit this loop if the queue overflowed
	POP	AX		;Clear old pointers from stack
	POP	AX
	cCALL	B$PUTSTR		;save new B$MCLPTR, B$MCLLEN for [voicen]
	JMP	SHORT PRSL10	;continue trying to fill this queue

; Had a queue overflow on the last call to B$MACCMD.  Restore the original
; string pointers so that the command which caused the overflow can be
; reprocessed the next time.
PRSL20:
	POP	[B$MCLLEN]	;RESTORE the old pointers
	POP	[B$MCLPTR]
	cCALL	B$PUTSTR		;And  put them back on the local stack

PRSLPX:


; Test if the user wants to break
	CALL	B$BREAK_CHK	;CTRL-BREAK?

; Have made a pass through the strings.  If this is pass 1 and there
; is data in any of the queues, then start the music playing.

	TEST	PLYPRS,LOW 128D
	JNZ	NOTPS1		;Brif not Pass 1
	OR	PLYPRS,LOW 128D ;Set parsed once flag
	CMP	MQUEFL,LOW 0
	JE	NOTPS1		;branch if no cmds have been queued for
				; this PLAY statement (no need to start
				; background task
	cCALL	B$STRTSD	;Start sounds

NOTPS1:

; Test if we are all done.  This occurs when the count of voice strings
; completely parsed (contained in PLYPRS) equals the number of voices.

	CMP	[PLYPRS],LOW 200O+NUM_VOICES
	JE	PRSDON		;Brif all NUM_VOICES strings parsed
	MOV	AL,LOW TSTVOC	;Ask the OEM if any voices are active
	cCALL	B$DONOTE	
	OR	AL,AL		;See what they had to say about it
	JNE	PARSER_BEGIN	; If there are active voices, then the
				;queue's are emptying, so go try to
				;parse the rest of the strings.

; If we get here, then it means that we are not done parsing the PLAY
; strings, the queues are full, but none of the voices are active.
; This should never occur, but IF it did, BASIC would be hung indefinitely.
; This simple safeguard ensures this will never happen.

	MOV	AL,LOW STRSND	;Function code to start music
	cCALL	B$DONOTE 	; Tell OEM to start playing the music
	JMP	PARSER_BEGIN	; and go parse the rest of the strings

; We are all done parsing the input strings.  If the music mode is
; Background, then we are done.  If mode is Foreground, we need to
; wait around until the sound stops.

PRSDON:
	cCALL	B$SNDWAT	;wait if Music Foreground

cEnd				; End of B$PARSER


;***
;B$PUTSTR
;Purpose:
;	Save B$MCLPTR, B$MCLLEN on Voice Stack for voice [VOICEN]
;Input:
;	[VOICEN] = voice id (0..2)
;	[B$MCLLEN]=number of bytes left in current string for this voice
;	[B$MCLPTR]=pointer to next byte in current string for this voice
;Output:
;	If stack overflows, an Out of Memory error is issued
;Modifies:
;	AX
;****

cProc	B$PUTSTR,<NEAR>,<BX,SI,DI>	
cBegin				

; Get the stack pointer for this string and check for stack overflow


	MOV	DI,VSTBAS	; di points to stack base for voice si
	MOV	BX,VSTOFF	; bx = offset for current top of stack
	CMP	BX,NUM_VSTACK	;Check if the stack is full
	JB	STKOK		;branch if still room on stack
	JMP	B$ERR_OM	;NO room, so signal out of memory error

				; Save the current data on the stack
STKOK:
	MOV	AX,[B$MCLPTR]
	MOV	[BX+DI],AX	;save string pointer on stack
	MOV	AX,[B$MCLLEN]
	MOV	[BX+DI]+2,AX	;save string length on stack
; Update the stack pointer to account for new stack size
	ADD	BX,4
	MOV	VSTOFF,BX	; save offset to top of stack

cEnd				; End of B$PUTSTR

;***
;B$GETSTR
;Purpose:
;	Set B$MCLPTR, B$MCLLEN for Voice [VOICEN]
;Input:
;	[VOICEN] = voice id (0..2)
;Output:
;	[B$MCLLEN]=number of bytes left in current string for this voice
;	[B$MCLPTR]=pointer to next byte in current string for this voice
;	If this voice's string has been completely consumed then
;	  PLYPRS is incremented and B$MCLLEN=0
;Modifies:
;	AX
;****

cProc	B$GETSTR,<NEAR>,<BX,SI,DI>	
cBegin				

; Get the stack pointer for this voice, and test if stack is empty

	MOV	BX,VSTOFF	; bx = offset for current top of stack
	MOV	[B$MCLLEN],BX	;length=0 if no more strings stacked
	OR	BX,BX
	JE	GETSTX		;brif no entries exist on voice's stack
	MOV	DI,VSTBAS	; DI points to stack base for voice SI

; Get the next set of entries from the stack.
GETSTL:
	SUB	BX,4		;Adjust stack pointer to next entry
	MOV	AX,[BX+DI]	;get string pointer from stack
	MOV	[B$MCLPTR],AX
	MOV	AX,[BX+DI]+2	;get string length from stack
	MOV	[B$MCLLEN],AX
	OR	AX,AX
	JNE	GETSTX		;exit if this string is not empty
	OR	BX,BX
	JNE	GETSTL		;brif more entries on voice's stack
	INC	[PLYPRS]	;Bump number of strings consumed

; Update the stack pointer, restore the registers, and get out
GETSTX:
	MOV	VSTOFF,BX	; save offset to top of stack

cEnd				; End of B$GETSTR

;--------------------------------------------------------------------------
; Music Macro Language command table
; This table contains all of the command characters allowed in the music
; language strings, and the entry points of the routines to process them

PLYTAB	LABEL	BYTE		

	DB	"A"		;The notes A-G
	DW	OFFSET PLYNOT
	DB	"B"
	DW	OFFSET PLYNOT

⌨️ 快捷键说明

复制代码 Ctrl + C
搜索代码 Ctrl + F
全屏模式 F11
切换主题 Ctrl + Shift + D
显示快捷键 ?
增大字号 Ctrl + =
减小字号 Ctrl + -