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

📄 circle.asm

📁 [随书类]Dos6.0源代码
💻 ASM
📖 第 1 页 / 共 2 页
字号:
	PUSH	DX		;SAVE INTEGER COUNT
	MOV	DX,-1		;DEFAULT END COUNT = INFINITY
OGCircle2:			

	FLD	DWORD PTR B$A_END 

	JMP	SHORT ENDFND	;Use user specified end angle
NOEND:				;Provide end angle default
	mov	ax,-1		;integer end count = infinity
	mov	bl,0		;polarity is always counterclockwise
	JMP	SHORT cstplt	;go plot the circle
ENDFND:
	MOV	CL,128		;SET HI BIT IN B$CLINEF FOR LINE TO CNTR
	CALL	ANGLE_CALC	;GO DO ANGLE CALCULATIONS - result in AX



	;AX = integer end count
	POP	DX		;Restore integer start count
	CMP	AX,DX
	MOV	BL,0
	JAE	CSTPLT		;PLOT POINTS BETWEEN STRT & END if end >= start

	MOV	BL,B$CLINEF	;fetch center line flag byte
	OR	BL,BL		;was either flag set ?
	JZ	CIRREV		;no, just reverse polarity
	XOR	BL,129		;yes, were they both set ?
	JZ	CIRREV		;yes, just reverse polarity
	MOV	B$CLINEF,BL	;no, reverse center line flags also
CIRREV:
	MOV	BL,-1		;PLOT POINTS ABOVE & BELOW
	XCHG	DX,AX		;SWAP START AND END SO START .LT. END
CSTPLT:
	MOV	B$CPLOTF,BL	;SET UP PLOT POLARITY FLAG
	MOV	B$CSTCNT,DX	;STORE START COUNT
	MOV	B$CENCNT,AX	;AND END COUNT
	CMP	AX,DX		;Does START .EQ. END?
	JNE	CIRCPL		;No: GO PLOT CIRCLE
	MOV	AL,B$CLINEF	;Yes: check for special case
	TEST	AL,129		;   if either center line flag set then
	JZ	CIRCPL		;(BOTH FLAGS ALREADY SET)
	OR	AL,129		;set the BOTH flags so order of checks
	MOV	B$CLINEF,AL	;in CPLOT4 won't miss a center line needed
CIRCPL: 			;PLOT THE CIRCLE
	JMP	B$DrawCircle	;NOW DRAW THE CIRCLE


;***
;B$ClipCheck
;
;Purpose:
;	Detect if the circle must be clipped.
;
;Entry:
;	([B$VXMIN],[B$VYMIN]) = left upper window boundary
;	([B$VXMAX],[B$VYMAX]) = right lower window boundary
;	[b$ASPECTR] = integer aspect ratio
;	[B$COPTFL] = circle option flag
;	  bit 0 set means scale x axis by aspect ratio
;	  bit 0 clear means scale y axis by aspect ratio
;	[B$GRPACX] = center X
;	[B$GRPACY] = center Y
;	[B$GXPOS] = radius
;
;Exit:
;      [B$CLIPF] = FF indicates clipping will be required.
;
;Modifies:
;	none
;****

cProc	B$ClipCheck,<NEAR>,<AX,CX,DX>	
cBegin
	mov	dx,B$GXPOS	;move radius to dx for cplscx
	call	cplscx
	MOV	AX,B$GRPACX	;Get the X center
	ADD	AX,CX		;Radius
	SUB	AX,B$VXMAX	;Test for off to the right
	NEG	AX
	JS	CLPCLP		;Clipping required
	MOV	AX,B$GRPACX
	SUB	AX,CX		;Radius
	SUB	AX,B$VXMIN	;Test for off to the left
	JS	CLPCLP		;Clipping required
	MOV	AX,B$GRPACY	;Now check for the Y direction
	ADD	ax,dx		
	SUB	AX,B$VYMAX	;Test for off the bottom
	NEG	AX
	JS	CLPCLP		;Clipping required
	MOV	AX,B$GRPACY
	sub	ax,dx		
	SUB	AX,B$VYMIN	;Test for off the top

CLPCLP:
	RCL	AX,1		;Rotate sign bit to PSW.C
	SBB	AL,AL		;Map PSW.C to 0 or FF
	MOV	B$CLIPF,AL	;Store the new flag
cEnd


;*** 
; ANGLE_CALC
;
;Purpose:
;
;Entry:
; [ST0] = angle
; [CL]	= LO or HI bit set for line to cntr
;
;Exit:
; [AX]	= result of calculation
;
;Uses:
;
;Preserves: (optional)
;
;Exceptions:
;
;******************************************************************************
;
; Note:  This routine may exit by jumping to CGETXY
;

DbPub ANGLE_CALC
cProc ANGLE_CALC,<NEAR>
cBegin

;
; check sign of angle - make positive if not
;
	PUSH	CX		
	CALL	B$fcompz	; see if zero
	POP	CX		; restore input
	JZ	CHKCONT 	; brif angle = 0.0
	JC	CHKCONT 	; brif angle > 0.0

	MOV	BX,OFFSET DGROUP:B$CLINEF ; SET BIT IN [C] IN B$CLINEF
	OR	[BX],CL 	
	FCHS			; change sign of angle to positive
CHKCONT:			

	FLD	FP_2PI		; [ST0] = 2*PI
	CALL	B$fcomp	; Ensure angle within range
	JC	AngleBad	; Jump if > 2*PI


	FLD	ST(0)		; duplicate input angle on numeric stack
	FMUL	FP_4OPI 	; [ST0] = 4/PI * input angle
	CALL	B$FIX8		; MUST be truncated towards zero
	CALL	B$ftolrnd	; AX = trunc(octant(angle))  (0-7)
	INC	AX		; convert to 1-8
	SHR	AL,1		; AL = octant/2
	RCR	AL,1		; set up flags
	PUSHF			; PSW.V: 1=+,0=-; PSW.C: 1=COS,0=SIN
	RCL	AL,1		; restore octant/2, then multiply by 2:
	SHL	AL,1		; 0,2,2,4,4,6,6,8 = octant base index
	MUL	WORD PTR [B$CNPNTS] ; AX = (2 * INT((OCT+1)/2)) * CNPNTS
	POPF			; get flags: PSW.C: 1=COS, 0=SIN
	PUSH	AX		; save scaled count base
	PUSHF			; save PSW.V
	JC	UseCOS		; brif PSW.C = 1, use COSINE
	CALL	B$SIN4		; [ST0] = SIN(input angle)
	JMP	SHORT FixSign	; skip the COS stuff
UseCOS:				
	CALL	B$COS4		; [ST0] = COS(input angle)
FixSign:			
	FABS			; [ST0]=ABS(f(angle)), where f = SIN or COS
	POPF			; retrieve PSW.V
	JO	SignOK		; brif PSW.V set, otherwise simulate SUB
	FCHS			; NEGATE [ST0]
SignOK:				
	FIMUL	WORD PTR [B$GXPOS] ; [ST0] = Radius * ABS(f(angle)
	MOV	BX,SP		; [BX] points to scaled count base
	FIADD	WORD PTR [BX]	; Add octant base value for point count
	CALL	B$ftolrnd	; put integer equivalent in AX
	POP	BX		; remove count base from stack


cEnd				

AngleBad:
	JMP	B$ERR_FC	;angle too big




;
cProc	CPLSCX,<NEAR>		
cBegin				
	mov	cx,dx		;save unscaled value
	mov	ax,[b$ASPECTR]	;get 256*aspect ratio
	mul	dx		;dx:ax = dx * aspect *256
	add	ax,128D 	
	ADC	DH,DL		;(DH was 0 after mul)
	mov	dl,ah		;result is in dx
tstxchg:
	TEST	B$COPTFL,1	;SEE WHETHER ASPECT WAS .GT. 1
	JZ	CPLRET		;DON'T SWAP IF ZERO
	XCHG	cx,DX		;Greater, use 1/Aspect
CPLRET:
cEnd				

;***
;
;	CIRCLE ALGORITHM
;
;   [SI] = X = RADIUS
;   [DI] = Y = 0
;   SUM  = 1 - RADIUS
;   LOOP
;	plot 8 reflections of the point around the circle's center
;	IF Y >= X THEN
;	    EXIT LOOP
;	IF SUM > 0
;	    SUM = SUM - 2*X + 2
;	    X = X - 1
;	SUM = SUM + 2*Y + 3
;	Y = Y + 1
;
; 26-Jan-87 Major revision for speed
;
;****

cProc	B$DrawCircle,<NEAR>,<DI,SI,ES>   
cBegin
	CALL	[b$SetPixFirstC] ;low-level circle initialization
	XOR	DI,DI		;INIT Y = 0
	MOV	SI,B$GXPOS	;X = RADIUS
	MOV	AX,1		;SUM = 1-RADIUS
	SUB	AX,SI		
	MOV	B$CRCSUM,AX	
CIRCLP: 			
	PUSH	DI		;save X,Y
	PUSH	SI		
	CALL	CPLOT8		;reflect the point 8 ways
	POP	SI		;restore X,Y
	POP	DI		
	CMP	DI,SI		;finished when Y >= X
	JAE	CRCLPX		;go if done
	MOV	AX,B$CRCSUM	
	OR	AX,AX		;check sum for whether to move X too
	JS	CNODEX		;go, no X change this time, only Y
	SUB	AX,SI		;SUM = SUM - 2*X + 2
	SUB	AX,SI		
	ADD	AX,2		
	DEC	SI		;X = X - 1
CNODEX: 			;always move Y
	ADD	AX,DI		;SUM = SUM + 2*Y + 3
	ADD	AX,DI		
	ADD	AX,3		
	INC	DI		;Y = Y + 1
	MOV	B$CRCSUM,AX	;update sum
	JMP	SHORT CIRCLP	;loop

CRCLPX: 			;circle finished
	CALL	[b$SetPixLastC] ;low-level circle termination
cEnd				

TestClip:			;check point for clipping
	CALL	B$INVIEW 	;See if point outside of viewport
	JNC	CPLFIN		;go if pt not visible (carry reset)
	JMP	SHORT NoClip	;go if pt visible (carry set)

;
; REFLECT THE POINTS AROUND CENTER
; [SI] = X OFFSET FROM CENTER, [DI] = Y OFFSET FROM CENTER
;
cProc	CPLOT8,<NEAR>		
cBegin				
	MOV	B$CPCNT,DI	;octant point count is Y
	MOV	B$CPCNT8,0	;circle point count is 0

	MOV	AX,b$ASPECTR	;BX = round(Y * (aspect*256) / 256)
	MOV	CX,AX		
	MUL	DI		
	ADD	AX,128D 	
	ADC	DH,DL		;(DH was 0 after mul)
	MOV	DL,AH		
	MOV	BX,DX		

	MOV	AX,CX		;DX = round(X * (aspect*256) / 256)
	MUL	SI		
	ADD	AX,128D 	
	ADC	DH,DL		;(DH was 0 after mul)
	MOV	DL,AH		

	TEST	B$COPTFL,1	;which axis is being scaled?
	JNZ	NoSwap		;go if scaling X
	XCHG	BX,DI		;swap scaled/unscaled values
	XCHG	DX,SI		
NoSwap: 			
	MOV	B$CXOFF,BX	; B$CXOFF = scaled(unscaled) Y
				; DI     = unscaled(scaled) Y
	MOV	B$CYOFF,SI	; B$CYOFF = unscaled(scaled) X
	MOV	SI,DX		; SI     = scaled(unscaled) X

	NEG	DI		;negate Y to start
	CALL	CPLOT4		;plot (X,-SY) (-Y,-SX) (-X,SY) (Y,-SX)

	MOV	AX,B$CNPNTS	;odd octant counts start at end of octant
	MOV	B$CPCNT8,AX	
	SUB	AX,B$CPCNT	;later calculate point count in odd octant
	MOV	B$CPCNT,AX	;  as PNTCNT = PNTS/OCT - PNTCNT
	NEG	B$CXOFF		;negate B$CXOFF and Y to start
	NEG	DI		
cEnd	<nogen> 		

	; fall through to plot (Y,-SX) (-X,-SY) (-Y,SX) (X,SY)

;

cProc	CPLOT4,<NEAR>		
cBegin				
	MOV	AX,4		;plotting four points
CPLOT:
	PUSH	AX		;save count
	MOV	CX,SI		;get X,Y from saved values
	MOV	DX,DI		
	ADD	CX,B$GRPACX	;actual points are offset from
	ADD	DX,B$GRPACY	;  the circle's center
	test	B$COPTFL,6	;start or end angles specified?
	JNZ	TestAng 	;go if so
CPLTIT:
	CMP	B$CLIPF,0	;is clipping required?
	JNZ	TestClip	;go if so to check point
NoClip: 			;point gets plotted here
	CALL	[b$MapXYC]	;convert X,Y to address and mask
	CALL	[b$SetPixC]	;plot it
CPLFIN:
	POP	AX		;restore count
	DEC	AX		;finished?
	JZ	CIRRET		;go if so
	XCHG	SI,B$CXOFF	;swap values for next octant
	NEG	SI		
	XCHG	DI,B$CYOFF	
	NEG	DI		
	JMP	SHORT CPLOT	;loop for four octants/points
CIRRET:
cEnd				

TestAng:			;check point against start/end angles
	MOV	BX,B$CPCNT8	;current octant point count
	MOV	AX,B$CNPNTS	;update for next octant/point
	SAL	AX,1		
	ADD	AX,BX		
	MOV	B$CPCNT8,AX	
	ADD	BX,B$CPCNT	;BX = current point's count
	CMP	BX,B$CSTCNT	;at start point?
	JZ	CLINSC		;go if so
	JB	CNBTWN		;if less then point is not between
	CMP	BX,B$CENCNT	;at end point?
	JZ	CLINEC		;go if so
	JB	CBTWEN		;if less then point is between
CNBTWN:
	CMP	B$CPLOTF,0	;SEE WHETHER TO PLOT OR NOT
	JNZ	CPLTIT		;NEED TO PLOT NOT-BETWEEN POINTS
	JMP	SHORT CPLFIN	;DON'T PLOT - FIX UP STACK & RETURN
CLINEC:
	MOV	al,B$CLINEF	;get ptr to center line flag byte
	test	al,128
	JZ	CPLTIT		;NO LINE REQUIRED - JUST PLOT POINT
	test	al,64
	jnz	CPLFIN		;Don't draw line or point on arc.
	or	[B$CLINEF],64	;don't plot the line twice
	jmp	short CLINE	;plot the line from end angle to ctr

CLINSC:
	MOV	al,B$CLINEF	;get ptr to center line flag byte
	test	al,1
	JZ	CPLTIT		;NO LINE REQUIRED - JUST PLOT POINT
	test	al,2
	jnz	CPLFIN		;Don't draw line or point on arc.
	or	[B$CLINEF],2	;don't plot the line twice
CLINE:
	PUSH	SI		;save X,Y
	PUSH	DI		
	CALL	B$CLINE2 	;DRAW LINE FROM [CX],[DX] TO CENTER
	CALL	[b$SetPixFirstC] ;re-initialize for circle (EGA)
	POP	DI		;restore X,Y
	POP	SI		
GOCPLFIN:			
	JMP	SHORT CPLFIN

CBTWEN:
	CMP	B$CPLOTF,0	;SEE WHETHER PLOTTING BETWEENS OR NOT
	JNZ	GOCPLFIN	;relative jump out of range
	JMP	CPLTIT		;IF Z, THEN DOING BETWEENS


sEnd	GR_TEXT 		
	END

⌨️ 快捷键说明

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