84 lines
2.5 KiB
Fortran
84 lines
2.5 KiB
Fortran
!-----------------------------------------------------
|
|
! MANDELBROT SET
|
|
!-
|
|
! refactored Thu 29 Dec 2022 03:21:16 PM CET
|
|
! refactored Sat 31 Dec 2022 12:37:03 PM CET
|
|
!-
|
|
!-----------------------------------------------------
|
|
!-
|
|
module mandelbrots
|
|
implicit none
|
|
contains
|
|
!-----------------------------------------------------------------------
|
|
|
|
subroutine mandelbrot_one(pic, start)
|
|
! use cmplxmath
|
|
! use imagetools
|
|
use pixrgb
|
|
|
|
implicit none
|
|
|
|
type(t_pixrgb), intent(inout), dimension (:,:) :: pic
|
|
complex, intent(in) :: start
|
|
! type (CenterMag), intent(in) :: cz
|
|
|
|
integer :: ix, iy, width, height
|
|
real :: fx, fy, mod2, rval
|
|
complex :: za, zb, cste
|
|
integer :: iter, maxiter
|
|
logical :: escape
|
|
|
|
write(0,*) "> plotsomething"
|
|
|
|
width = ubound(pic, 1)
|
|
height = ubound(pic, 2)
|
|
! print *, " pic size ", width, height
|
|
print *, real(start), aimag(start)
|
|
|
|
! initialise constants
|
|
!
|
|
maxiter = 1984
|
|
|
|
! enter megaloop
|
|
!
|
|
do iy = 1, height
|
|
fy = (float(iy) / float(height/3)) - 1.5
|
|
!! print *, "line ", iy, fy
|
|
do ix = 1, width
|
|
fx = (float(ix) / float(width/3)) - 2.0
|
|
!-------------------------------------
|
|
! working on the current pixel
|
|
za = start
|
|
cste = complex ( fx, fy )
|
|
iter = 0
|
|
escape = .FALSE.
|
|
do while (iter .lt. maxiter)
|
|
zb = (za * za) + cste
|
|
mod2 = real(zb)*real(zb) + aimag(zb)*aimag(zb)
|
|
!! print *, "mod2 ", mod2
|
|
if (mod2 .GT. 4.0) then
|
|
escape = .TRUE.
|
|
exit
|
|
endif
|
|
za = zb
|
|
iter = iter + 1
|
|
!! print *, "ZA ITER ESCAPE", za, iter, escape
|
|
enddo
|
|
if (escape) then
|
|
pic(ix, iy)%r = mod(iter*12, 255)
|
|
pic(ix, iy)%b = mod(iter*7, 255)
|
|
else
|
|
rval = (sqrt(mod2) + abs(real(start)*aimag(start))) * 9e2
|
|
pic(ix, iy)%g = mod(int(rval), 210)
|
|
! pic(ix, iy)%g = mod(iter, 255)
|
|
! pic(ix, iy)%b = mod(iter*11, 255)
|
|
endif
|
|
!-------------------------------------
|
|
end do ! fin boucle sur X
|
|
end do
|
|
|
|
end subroutine
|
|
!-----------------------------------------------------
|
|
end module
|
|
!-----------------------------------------------------
|