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

📄 calcmand.asm

📁 frasr200的win 版本源码(18.21),使用make文件,使用的vc版本较低,在我的环境下编译有问题! 很不错的分形程序代码!
💻 ASM
📖 第 1 页 / 共 2 页
字号:
	mov	eax,edi 		; compute (y * x)
	imul	esi			;  ...
	shrd	eax,edx,FUDGEFACTOR-1	;  ( * 2 / fudge)
	add	eax,linity		;  (above) + linity
	mov	edi,eax 		;  save this as y

;	(from the earlier code) 	; compute (x*x - y*y) / fudge
	add	ebx,linitx		;	+ linitx
	mov	esi,ebx 		; save this as x

	mov	ax,oldcolor		; recall the old color
	cmp	ax,k			; check it against this iter
	jge	short chkperiod1
nonmax1:
	dec	k			; while (k < maxit) (dec to 0 is faster)
	jnz	short kloop		; while (k < maxit) ...
kloopend1:
	jmp	short kloopend32	; we done.

chkperiod1:
	mov	eax,esi
	xor	eax,savedx
	test	eax,savedmask
	jnz	short chksave1
	mov	eax,edi
	xor	eax,savedy
	test	eax,savedmask
	jnz	short chksave1
	mov	period,1		; note that we have found periodicity
	mov	k,0			; pretend maxit reached
	jmp	short kloopend1
chksave1:
	mov	ax,k
	test	ax,savedand
	jne	short nonmax1
	mov	savedx,esi
	mov	savedy,edi
	dec	savedincr		; time to change the periodicity?
	jnz	short nonmax1		;  nope.
	shl	savedand,1		; well then, let's try this one!
	inc	savedand		;  (2**n -1)
	mov	savedincr,4		; and reset the increment flag
	jmp	short nonmax1

kloopend32:

.8086					; 386-specific code ends here

kloopend:
	cmp	orbit_ptr,0		; any orbits to clear?
	je	noorbit2		;  nope.
	call	far ptr scrub_orbit	; clear out any old orbits
noorbit2:

	mov	ax,k			; set old color
	sub	ax,10			; minus 10, for safety
	mov	oldcolor,ax		; and save it as the "old" color
	mov	ax,maxit		; compute color
	sub	ax,k			;  (first, re-compute "k")
	sub	kbdcount,ax		; adjust the keyboard count
	cmp	ax,1			; convert any "outlier" region
	jge	short coloradjust1	;  (where abs(x) > 2 or abs(y) > 2)
	mov	ax,1			;   to look like we ran through
coloradjust1:				;    at least one loop.
	mov     realcolor,ax            ; result before adjustments
	cmp     ax,maxit                ; did we max out on iterations?
	jne     short notmax            ;  nope.
	mov     oldcolor,ax             ; set "oldcolor" to maximum
	cmp     inside,0                ; is "inside" >= 0?
	jl      wedone                  ;  nope.  leave it at "maxit"
	mov     ax,inside               ; reset max-out color to default
	cmp     periodicitycheck,0      ; show periodicity matches?
	jge     wedone                  ;  nope.
	mov     al,period               ;  reset color to periodicity flag
	jmp     short wedone

notmax:
	cmp     outside,0               ; is "outside" >= 0?
	jl      wedone                  ;   nope. leave as realcolor
	mov     ax, outside             ; reset to "outside" color

wedone:                                 ;
	mov     color,ax                ; save the color result
	UNFRAME <si,di>                 ; pop stack frame
	ret                             ; and return with color

calcmandasm endp


; ******************** Function code16bit() *****************************
;
;	Performs "short-cut" 16-bit math where we can get away with it.
; CJLT has modified it, mostly by preshifting x and y to fg30 from fg29
; or, since we ignore the lower 16 bits, fg14 from fg13.
; If this shift overflows we are outside x*x+y*y=2, so have escaped.
; Also, he commented out several conditional jumps which he calculated could
; never be taken (e.g. mov ax,si / imul si ;cannot overflow).

code16bit	proc	near

	mov	si,word ptr x+2 	; use SI for X fg13
	mov	di,word ptr y+2 	; use DI for Y fg13

start16bit:
	add	si,si			;CJLT-Convert to fg14
	jo	end16bit		;overflows if <-2 or >2
	mov	ax,si			; compute (x * x)
	imul	si			; Answer is fg14+14-16=fg12
;	cmp	dx,0			;CJLT commented out-
;	jl	end16bit		;CJLT-  imul CANNOT overflow
;	mov	cx,32-FUDGEFACTOR	;CJLT. FUDGEFACTOR=29 is hard coded
loop16bit1:
	shl	ax,1			;  ...
	rcl	dx,1			;  ...
	jo	end16bit		;  (oops.  overflow)
;	loop	loop16bit1		;CJLT...do it once only. dx now fg13.
	mov	bx,dx			; save this for a tad

;ditto for y*y...

	add	di,di			;CJLT-Convert to fg14
	jo	end16bit		;overflows if <-2 or >2
	mov	ax,di			; compute (y * y)
	imul	di			;  ...
;	cmp	dx,0			; say, did we overflow? <V20-compat>
;	jl	end16bit		;  (oops.  We done.)
;	mov	cx,32-FUDGEFACTOR	; ( / fudge)
;loop16bit2:
	shl	ax,1			;  ...
	rcl	dx,1			;  ...
	jo	end16bit		;  (oops.  overflow)
;	loop	loop16bit2		;  ...

	mov	cx,bx			; compute (x*x - y*y) / fudge
	sub	bx,dx			;  for the next iteration

	add	cx,dx			; compute (x*x + y*y) / fudge
	jo	end16bit		; bail out if too high
;	js	end16bit		;  ...

	cmp	cx,word ptr lm+2	; while (xx+yy < lm)
	jae	end16bit		;  ...
	dec	k			; while (k < maxit)
	jz	end16bit		;  we done.

	mov	ax,di			; compute (y * x) fg14+14=fg28
	imul	si			;  ...
;	mov	cx,33-FUDGEFACTOR-2	; ( * 2 / fudge)
;loop16bit3:
	shl	ax,1			;  ...
	rcl	dx,1			;  ...
	shl	ax,1			;  shift two bits
	rcl	dx,1			;  cannot overflow as |x|<=2, |y|<=2
;	loop	loop16bit3		;  ...
	add	dx,word ptr linity+2	; (2*y*x) / fudge + linity
	jo	end16bit		; bail out if too high
	mov	di,dx			; save as y

	add	bx,word ptr linitx+2	; (from above) (x*x - y*y)/fudge + linitx
	jo	end16bit		; bail out if too high
	mov	si,bx			; save as x

	mov	ax,oldcolor		; recall the old color
	cmp	ax,k			; check it against this iter
	jle	short nonmax3		;  nope.  bypass periodicity check.
	mov	word ptr x+2,si 	; save x for periodicity check
	mov	word ptr y+2,di 	; save y for periodicity check
	call	checkperiod		; check for periodicity
nonmax3:
	jmp	start16bit		; try, try again.

end16bit:				; we done.
	ret
code16bit	endp


;	The following routine checks for periodic loops (a known
;	method of decay inside "Mandelbrot Lake", and an easy way to
;	bail out of "lake" points quickly).  For speed, only the
;	high-order sixteen bits of X and Y are checked for periodicity.
;	For accuracy, this routine is only fired up if the previous pixel
;	was in the lake (which means that the FIRST "wet" pixel was
;	detected by the dull-normal maximum iteration process).

checkperiod	proc near		; periodicity check
	mov	ax,k			; set up to test for save-time
	test	ax,savedand		; save on 0, check on anything else
	jz	checksave		;  time to save a new "old" value
	mov	dx,word ptr x+2 	; load up x
	and	dx,word ptr savedmask+2 ;  truncate to appropriate precision
	cmp	dx,word ptr savedx+2	; does X match?
	jne	checkdone		;  nope.  forget it.
	mov	ax,word ptr x		; load up x
	and	ax,word ptr savedmask	;  truncate to appropriate precision
	cmp	ax,word ptr savedx	; does X match?
	jne	checkdone		;  nope.  forget it.
	mov	dx,word ptr y+2 	; now test y
	and	dx,word ptr savedmask+2 ;  truncate to appropriate precision
	cmp	dx,word ptr savedy+2	; does Y match?
	jne	checkdone		;  nope.  forget it.
	mov	ax,word ptr y		; load up y
	and	ax,word ptr savedmask	;  truncate to appropriate precision
	cmp	ax,word ptr savedy	; does Y match?
	jne	checkdone		;  nope.  forget it.
	mov	period,1		; note that we have found periodicity
	mov	k,1			; pretend maxit reached
checksave:
	mov	dx,word ptr x+2 	; load up x
	and	dx,word ptr savedmask+2 ;  truncate to appropriate precision
	mov	word ptr savedx+2,dx	;  and save it
	mov	ax,word ptr x		; load up x
	and	ax,word ptr savedmask	;  truncate to appropriate precision
	mov	word ptr savedx,ax	;  and save it
	mov	dx,word ptr y+2 	; load up y
	and	dx,word ptr savedmask+2 ;  truncate to appropriate precision
	mov	word ptr savedy+2,dx	;  and save it
	mov	ax,word ptr y		; load up y
	and	ax,word ptr savedmask	;  truncate to appropriate precision
	mov	word ptr savedy,ax	;  and save it
	dec	savedincr		; time to change the periodicity?
	jnz	checkdone		;  nope.
	shl	savedand,1		; well then, let's try this one!
	inc	savedand		;  (2**n -1)
	mov	savedincr,4		; and reset the increment flag
checkdone:
	ret				; we done.
checkperiod	endp


; ******************** Function code32bit() *****************************
;
;	Perform the 32-bit logic required using 16-bit logic
;
;	New twice as fast logic,
;	   Courtesy of Bill Townsend and Mike Gelvin (CIS:73337,520)
;	Even newer, faster still by Chris Lusby Taylor
;	 who noted that we needn't square the low word if we first multiply
;	 by 4, since we only need 29 places after the point and this will
;	 give 30. (We divide answer by two to give 29 bit shift in answer)
;	Also, he removed all testing for special cases where a word of operand
;	happens to be 0, since testing 65536 times costs more than the saving
;	1 time out of 65536! (I benchmarked it. Just removing the tests speeds
;	us up by 3%.)
;
;Note that square returns DI,AX squared in DX,AX now.
; DI,AX is first converted to unsigned fg31 form.
; (For its square to be representable in fg29 (range -4..+3.999)
; DI:AX must be in the range 0..+1.999 which fits neatly into unsigned fg31.)
; This allows us to ignore the part of the answer corresponding to AX*AX as it
; is less than half a least significant bit of the final answer.
; I thought you'd like that.
;
; As we prescaled DI:AX, we need to shift the answer 1 bit to the right to
; end up in fg29 form since 29=(29+2)+(29+2)-32-1
; However, the mid term AX*DI is needed twice, so the shifts cancel.
;
; Since abs(x) and abs(y) in fg31 form will be needed in calculating 2*X*Y
; we push them onto the stack for later use.

; Note that square does nor affect bl,si,bp
; and leaves highword of argument in di
; but destroys bh,cx
square	MACRO	donepops
	LOCAL	notneg
	shl	ax,1		;Multiply by 2 to convert to fg30
	rcl	di,1		;If this overflows DI:AX was negative
	jnc	notneg
	not	ax			; so negate it
	not	di			; ...
	add	ax,1			; ...
	adc	di,0			; ...
	not	bl			; change negswt
notneg:	shl	ax,1		;Multiply by 2 again to give fg31
	rcl	di,1		;If this gives a carry then DI:AX was >=2.0
				;If its high bit is set then DI:AX was >=1.0
				;This is OK, but note that this means that
				;DI:AX must now be treated as unsigned.
	jc	donepops
	push	di		; save y or x (in fg31 form) on stack
	push	ax		; ...
	mul	di		;GET MIDDLE PART - 2*A*B
	mov	bh,ah		;Miraculously, it needs no shifting!
	mov	cx,dx
	mov	ax,di
	mul	ax		;SQUARE HIGH HWORD - A*A
	shl	bh,1		;See if we round up
	adc	ax,1		;Anyway, add 1 to round up/down accurately
	adc	dx,0
	shr	dx,1		;This needs shifting one bit
	rcr	ax,1
	add	ax,cx		;Add in the 2*A*B term
	adc	dx,0
	ENDM	;#EM


code32bit	proc near
;
; BL IS USED FOR THE "NEGSWT" FLAG
;   NEGSWT IS ONE IF EITHER "X" OR "Y" ARE NEGATIVE, BUT NOT BOTH NEGATIVE
;

	push	bp
	xor	bl,bl			; NEGSWT STARTS OFF ZERO

;	iteration loop

nextit:	mov	ax,word ptr y		; ax=low(y)
	mov	di,word ptr y+2 	; di=high(y)
	square done0	;square y and quit via done0 if it overflows
	mov	si,ax		; square returns results in dx,ax
	mov	bp,dx		; save y*y in bp,si
	mov	ax,word ptr x
	mov	di,word ptr x+2
	square	done2		; square x and quit via done2 if it overflows
	mov	cx,ax		; Save low answer in cx.
	ADD	ax,si		; calc y*y + x*x
	mov	ax,bp
	ADC	ax,dx		;  ...
	jno	nextxy		; overflow?
				;NOTE: The original code tests against lm
				;here, but as lm=4<<29 this is the same
				;as testing for signed overflow
done4:	add	sp,4			; discard saved value of |x| fg 31
done2:	add	sp,4			; discard saved value of |y| fg 31
done0: pop	bp			; restore saved bp
	ret

;---------------------------------------------------------------------------

nextxy:	dec	k		; while (k < maxit)
	jz	done4		;  we done.
	sub	cx,si			; subtract y*y from x*x
	sbb	dx,bp			;  ...
	add	cx,word ptr linitx	; add "A"
	adc	dx,word ptr linitx+2	;  ...
	jo	done4			;CJLT-Must detect overflow here
					; but increment loop count first
	mov	word ptr x,cx		; store new x = x*x-y*y+a
	mov	word ptr x+2,dx 	;  ...

; now calculate x*y
;
;More CJLT tricks here. We use the pushed abs(x) and abs(y) in fg31 form
;which, when multiplied, give x*y in fg30, which, luckily, is the same as...
;2*x*y fg29.
;As with squaring, we can ignore the product of the low order words, and still
;be more accurate than the original algorithm.
;
	pop	bp		;Xlow
	pop	di		;Xhigh (already there, actually)
	pop	ax		;Ylow
	mul	di		;Xhigh * Ylow
	mov	bh,ah		;Discard lowest 8 bits of answer
	mov	cx,dx
	pop	ax		;Yhigh
	mov	si,ax		; copy it
	mul	bp		;Xlow * Yhigh
	xor	bp,bp		;Clear answer
	add	bh,ah
	adc	cx,dx
	adc	bp,0
	mov	ax,si		;Yhigh
	mul	di		;Xhigh * Yhigh
	shl	bh,1		;round up/down
	adc	ax,cx		;Answer-low
	adc	dx,bp		;Answer-high
				;NOTE: The answer is 0..3.9999 in fg29
	js	done0		;Overflow if high bit set
	or	bl,bl		; ZERO IF NONE OR BOTH X , Y NEG
	jz	signok		; ONE IF ONLY ONE OF X OR Y IS NEG
	not	ax		; negate result
	not	dx		;  ...
	add	ax,1		;  ...
	adc	dx,0		;  ...
	xor	bl,bl		;Clear negswt
signok:
	add	ax,word ptr linity
	adc	dx,word ptr linity+2	; dx,ax = 2(X*Y)+B
	jo	done0
	mov	word ptr y,ax		; save the new value of y
	mov	word ptr y+2,dx 	;  ...
	mov	ax,oldcolor		; recall the old color
	cmp	ax,k			; check it against this iter
	jle	short chkmaxit		;  nope.  bypass periodicity check.
	call	checkperiod		; check for periodicity

chkmaxit:
	cmp	show_orbit,0		; orbiting on?
	jne	horbit			;  yep.
	jmp	nextit			;go around again

jmpdone0:
	jmp	done0			; DOES [(X*X)-(Y*Y)+P] BEFORE THE DEC.

horbit: push	bx			; save my flags
	mov	ax,-1			; color for plot orbit
	push	ax			;  ...
	push	word ptr y+2		; co-ordinates for plot orbit
	push	word ptr y		;  ...
	push	word ptr x+2		;  ...
	push	word ptr x		;  ...
	call	far ptr iplot_orbit	; display the orbit
	add	sp,5*2			; clear out the parameters
	pop	bx			; restore flags
	jmp	nextit			; go around again

code32bit	endp

	   end

⌨️ 快捷键说明

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