Fortraneries/Fraktalism/mkmandel.f90

126 lines
3.6 KiB
Fortran

!-----------------------------------------------------
! MANDELBROT SET
!-
! refactored Thu 29 Dec 2022 03:21:16 PM CET
!-
!-----------------------------------------------------
!-
subroutine plotsomething(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
print *, "> plotsomething"
width = ubound(pic, 1)
height = ubound(pic, 2)
! print *, " pic size ", width, height
print *, " start ", 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*8, 255)
else
rval = (mod2 + abs(real(start)*aimag(start))) * 666.666
pic(ix, iy)%g = mod(int(rval), 180)
! 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
!-----------------------------------------------------
!
! this is the main programm
!
program mkmandel
use pixrgb
implicit none
interface
subroutine plotsomething (pic, start)
use pixrgb
type(t_pixrgb), intent(inout), dimension (:,:) :: pic
complex, intent(in) :: start
end subroutine plotsomething
end interface
type(t_pixrgb), allocatable :: pic(:,:)
integer :: angle
real :: radangle, radius
real :: stx, sty
character (len=80) :: filename
write(0, *) "-------- making some mandelbrot -------"
allocate(pic(1152, 900))
do angle = 0, 1500
call rgbpix_set_to_zero(pic)
radangle = float(angle) * 0.01664
radius = float(angle) / 1500.0
write (filename, "(a, i5.5, a)") "frames/mandel/", angle, ".pnm"
! filename = trim(filename)
print *, "#### passe ", angle, radangle, trim(filename)
stx = radius * (sin(radangle*3.9) + sin(radangle*5.36))
sty = radius * cos(radangle*3.3)
call plotsomething (pic, complex(stx, sty))
call rgbpix_spit_as_pnm_8 (pic, trim(filename))
print *
enddo
print *, " [DONE]"
end
!-----------------------------------------------------