📄 mirrors.asm
字号:
fsqrt ; SQRT(delta_X**2 + delta_Y**2)
fsub circles.Radius ; Subtract base circle radius to get P
; Now calculate the radius of the orthogonal circle, using the equation
;
; R(n) = SQRT( P*(D(b) + P) )
; where D(b) is the diameter of the base circle. = 2*R(b)
fld base_circle_diameter
fadd st,st(1) ; Add P to the base circle diam'
fmul ; Multiply result by P
fsqrt
fstp circles.Radius[ebx] ; Save integer radius
;--------------------------------------
; Draw the 1st orthog circle
;--------------------------------------
CIRCLE circles.X_Coord[ebx],circles.Y_Coord[ebx],circles.Radius[ebx],circles.Colour[ebx]
;---------------------------------------------
; Draw remaining NOC orthogonal circles
;---------------------------------------------
mov ebx,2*16 ; Start creating with 3rd circle, (we
; have base and 1st orthog already)
.WHILE ebx <= NOC*16 ; Complete creation of NOC orthogonal circles
fld circles.Radius[16] ; Use 1st orthog circ radius for all
fstp circles.Radius[ebx] ; orthog circles around the base
; Rotate orthogonal circle centre by theta degrees to the next pos'n
; -------------------------------------------------------------------
fld circles.X_Coord[ebx-16] ; Get X coord of last circles centre
fsub circles.X_Coord ; Translate coords into math space
fstp math_X_Coord
fld circles.Y_Coord[ebx-16] ; Get Y coord of last circles centre
fsub circles.Y_Coord
fstp math_Y_Coord
call rotate ; Rotate theta degrees to get new centre coords
fadd circles.Y_Coord ; Translate coords back into real space
fstp circles.Y_Coord[ebx] ; Adding new coordinates to list
fadd circles.X_Coord ;
fstp circles.X_Coord[ebx] ;
CIRCLE circles.X_Coord[bx],circles.Y_Coord[bx],circles.Radius[bx],circles.Colour[bx]
add ebx,16 ; Increment the circle index
.ENDW
;***************************************************************;
; Now invert all orthogonal circles, using the first as ;
; a mirror; the process is then repeated choosing the ;
; next as a mirror until all orthogonal circles have been ;
; inverted in all possible mirror circles. ;
;***************************************************************;
mov last,ebx ; bx is the index to ALL circles
sub last,16
.WHILE count <= NoLevels ; Check against the inversion level
mov edi,first ; Set to first mirror circle
.WHILE edi <= last ; Loop for all possible mirrors
mov esi,first ; Set index to 1st orthogonal circle
.WHILE esi <= last ; Loop until all targets are inverted
cmp esi,edi
je skip_circle ; Don't invert the mirror circle
;-------------------------------------------------------------------------;
; Calculate the angle beta between the line joining the centres of the ;
; inversion circle & the target circle to be inverted, & the horizontal ;
; also evaluate the sine and cosine. ;
;-------------------------------------------------------------------------;
fld circles[edi].Y_Coord ; Y coord for mirror circle
fsub circles[esi].Y_Coord ; Get delta_Y into st
fld circles[edi].X_Coord
fsub circles[esi].X_Coord ; Now st = delta_X, st1 = delta_y
fpatan ; Get the angle in radians
fsincos ; Get sine & cosine
fxch ; Swap sine & cosine
fstp sin_beta ; save sin(beta) & pop
fst cos_beta ; save cos(beta)
;-------------------------------------------------------------------------;
; Calculate distance "SL" between the centre "S" of the invertion circle ;
; and the most distant point "L" on the circumference of target circle ;
; which is coincident with the line joining the 2 centres. ;
; ;
; We use the equation:- ;
; ;
; SL = SQRT( (X(m) - X(t) + R(t)*cos(beta) )**2 + ;
; (Y(m) - Y(t) + R(t)*sin(beta) )**2 ) ;
; ;
; where X(m),Y(m) are the coordinates for centre of the invertion circle;
; X(t),Y(t) " " " " target " ;
; R(t) is the radius of the target circle ;
;-------------------------------------------------------------------------;
fmul circles[esi].Radius ; Times radius of the target circle
fst radius_cos_beta ; st = R*cos(beta)
fld circles[edi].X_Coord ; Get invertion circles X coordinate
fsub circles[esi].X_Coord ; Minus target circles X coordinate
; Gives X(m) - X(t)
; st = delta_X, st(1) = R*cos(beta)
fst delta_X ; Save for use again
fadd ; st = X(m) - X(t) + R(t)*cos(beta)
fld st ; Take a copy into st(1)
fmul ; Square=(X(m)-X(t)+R(t)*cos(beta))^2
fld sin_beta ; st = sin(beta),st(1)=term1^2
fmul circles[esi].Radius
fst radius_sin_beta ; Save for use again
fld circles[edi].Y_Coord ; Get invertion circle Y coordinate
fsub circles[esi].Y_Coord ; Minus target circles Y coordinate
; Gives Y(m) - Y(t)
; st=delta_Y, st(1)=R*sin(beta), st(2)=term1^2
fst delta_Y
fadd ; st=Y(m)-Y(t)+R(t)*sin(beta), st(1)=term1^2
fld st ; Take a copy into st(1)
fmul ; and form the square
; st=term2^2, st(1)=term1^2
fadd ; Add the 2 squares togeter
fsqrt ; Now have SL in st(0)
;--------------------------------------------------------------------------;
; In circle inversion we have the relationship:- ;
; ;
; SQ * SQ' = R**2 ;
; ;
; where SQ is the distance from the centre of the base circle to ;
; any radial point within it. ;
; SQ' is the distance from the centre of the base circle to ;
; the inverted point on the same radial line. ;
; R is the radius of the mirror circle. ;
; ;
; We therefore calculate the distance SL' using the equation:- ;
; ;
; SL' = R(m)**2/SL ;
;--------------------------------------------------------------------------;
fld circles[edi].Radius ; Load radius of invertion circle
fld st ; Take a copy
fmul ; Square it to give st=R^2,st(1)=SL
fld st ; Take a copy; R^2, R^2, SL
fdiv st,st(2) ; Divide by SL; SL', R^2, SL
fstp SL_prime ; Store SL'; R^2, SL
fxch ; Swap; st=SL, st(1)=R^2
fstp st ; Flush st st=R^2
;--------------------------------------------------------------------------;
; Calculate distance "SM" between the centre of the invertion circle and ;
; the nearest point "M" on the circumference of the target circle, which ;
; is coincident with the line joining the 2 centres. We use equation:- ;
; ;
; SM = SQRT( (X(m) - X(t) - R(t)*cos(beta) )**2 + ;
; (Y(m) - Y(t) - R(t)*sin(beta) )**2 ) ;
; ;
; where X(m),Y(m) are the coordinates for centre of the invertion circle ;
; X(t),Y(t) " " " " target " ;
; R(t) is the radius of the target circle ;
;--------------------------------------------------------------------------;
fld delta_X ; st = delta_X, st(1) = R^2
fsub radius_cos_beta ; st = X(m)-X(t)-R(t)*cos(beta), st(1)=R^2
fld st ; Take a copy
fmul ; Square; term1^2, R^2
fld delta_Y ; st = delta_Y, st(1)=term1^2, st(2)=R^2
fsub radius_sin_beta ; Y(m)-Y(t)-R(t)*sin(beta), term1^2,R^2
fld st ; Take a copy
fmul ; Square; term2^2, term1^2, R^2
fadd ; Add the 2 squares togeter
fsqrt ; Now have SM in st(0) & R^2 in st(1)
; Calculate the distance SM' using the equation: SM' = R(m)**2/SM
fdiv ; Divide R**2 by SM to give SM'
fst SM_prime
fld st ; Take a copy; SM', SM'
; The radius of the inverted circle is then given by (SM' - SL')/2
fsub SL_prime ; st = (SM' - SL'), st(1) = SM'
fabs ; Make sure it's never negative
fdiv two
fstp circles[ebx].Radius ; Store new inverted circle radius; now st = SM'
;------------------------------------------------------------------------;
; Now calculate the location of the centre of the inverted circle using ;
; the equations:- ;
; ;
; X(i) = X(m) - (SL' + SM')*cos(beta)/2 ;
; Y(i) = Y(m) - (SL' + SM')*sin(beta)/2 ;
; ;
; where X(i),Y(i) are the coords of the inverted circles centre ;
; ;
;------------------------------------------------------------------------;
fadd SL_prime ; st = (SL' + SM')
fld st ; Take a copy into st(1)
fmul cos_beta ; st=(SL'+SM')*cos(beta), st(1)=(SL'+SM')
fld circles[edi].X_Coord
fadd st,st ; Double invertion circles X coordinate
;
fsubr ; X(m)*2-(SL'+SM')*cos(beta),(SL'+SM')
fdiv two
fstp circles.X_Coord[ebx] ; Save X coord for possible future
; inversion of the created circle
fmul sin_beta ; st = (SL' + SM')*sin(beta)
fld circles[edi].Y_Coord ; Get invertion circles Y coordinate
fadd st,st ; Double, st = Y(m)*2, st1=(SL'+SM')..
fsubr ; Y(m)*2 - (SL' + SM')*sin(beta)
fdiv two
fstp circles.Y_Coord[ebx] ; Save Y coordinate
; Set colour of new inversion circle
mov eax,circles[esi].Colour ; Get colour of target circle
mov circles.Colour[ebx],eax ; and set inverted circle to have the same
add ebx,16 ; Bump index up for next circle
add circles_made,16 ; Add 16 for each circle
; Check size of inverted circle
fld circles[ebx-16].Radius
fistp temp
cmp temp,2 ; Min circle diameter set to 4 pixels
jle skip_circle
; cmp temp,80 ; Limit size of drawn circle <160 OK
; jg skip_circle
; Fill new circle with colour ;
CIRCLE circles.X_Coord[bx-16],circles.Y_Coord[bx-16],circles.Radius[bx-16],circles.Colour[bx-16]
skip_circle:
add esi,16
.ENDW
add edi,16 ; Change index for next mirror circle
.ENDW
mov eax,circles_made ; Get no of circles made * 16
add last,eax ; New limit for last circle to invert
mov first,esi ; Reset index to 1st of new inverted
inc count ; Flag its a new set
.ENDW
;-------End of circle inversion code-----------
invoke EndPaint,hWnd, ADDR ps
.ELSEIF eax==WM_DESTROY
invoke DeleteObject, bluepen
invoke PostQuitMessage,NULL
.ELSE
invoke DefWindowProc,hWnd,uMsg,wParam,lParam
ret
.ENDIF
xor eax,eax
ret
WndProc endp
;---------------------------------------------------------------;
; This routine finds new values for cartesian coordinates X & Y ;
; when the point is rotated by theta radians. ;
; ;
; X1 = X * cos(theta) + Y * sin(theta) ;
; Y1 = -X * sin(theta) + Y * cos(theta) ;
; ;
; Return ST & ST(1) contain Y1 & X1 respectively. ;
;---------------------------------------------------------------;
rotate PROC
fld theta ; Put the rotation in degrees into st(0)
fmul deg2rad ; st=radians
fsincos ; st=cos, st(1)=sin
fld st ; st=cos, st(1)=cos, st(2)=sin
fmul math_X_Coord ; st=X*cos, st(1)=cos, st(2)=sin
fxch ; st=cos, st(1)=X*cos, st(2)=sin
fmul math_Y_Coord ; st=Y*cos, st(1)=X*cos, st(2)=sin
fxch st(2) ; st=sin, st(1)=X*cos, st(2)=Y*cos
fld st ; st=sin, st1=sin, st2=X*cos, st3=Y*cos ;now X, X, Y*sin, Y*cos, cos, sin
fmul math_X_Coord ; X*sin, sin, X*cos, Y*cos
fxch ; sin, X*sin, X*cos, Y*cos
fmul math_Y_Coord ; Y*sin, X*sin, X*cos, Y*cos
fadd st,st(2) ; X1, X*sin, X*cos, Y*cos
fxch st(3) ; Y*cos, X*sin, X*cos, X1
fxch st(2) ; X*cos, X*sin, Y*cos, X1
fstp st ; X*sin, Y*cos, X1
fsub st(1),st ; X*sin, -(X*sin)+(Y*cos), X1
fstp st ; -(X*sin)+(Y*cos), X1
RET
rotate ENDP
end start
⌨️ 快捷键说明
复制代码
Ctrl + C
搜索代码
Ctrl + F
全屏模式
F11
切换主题
Ctrl + Shift + D
显示快捷键
?
增大字号
Ctrl + =
减小字号
Ctrl + -