56 lines
1.5 KiB
Fortran
56 lines
1.5 KiB
Fortran
module xperiment
|
|
|
|
implicit none
|
|
contains
|
|
|
|
!===============================================================
|
|
! nouveau 24 mai 2022
|
|
|
|
subroutine parasites_1(pic, cx, cy, maxiter)
|
|
implicit none
|
|
integer, intent(inout), dimension (:,:) :: pic
|
|
|
|
real, intent(in) :: cx, cy
|
|
integer, intent(in) :: maxiter
|
|
|
|
integer :: ix, iy, width, height
|
|
real :: fx, fy, coef
|
|
logical :: burps
|
|
! write(0, *) "subroutine parasites_0" , maxiter
|
|
! write(0, *) "constantes", cx, cy
|
|
|
|
width = ubound(pic, 1) ; height = ubound(pic, 2)
|
|
coef = float(maxiter)
|
|
do ix = 1, width
|
|
fx = cx + (float(ix) / (float(width)/4.0) - 2.0)
|
|
burps = (RAND() .lt. 0.01)
|
|
do iy = 1, height
|
|
fy = cy + (float(iy) / (float(height)/4.0) - 2.0)
|
|
if (burps) then
|
|
pic(ix, iy) = int(fx * fy * coef * 1.005)
|
|
else
|
|
pic(ix, iy) = int(fx * fy * coef)
|
|
endif
|
|
enddo
|
|
enddo
|
|
end subroutine parasites_1
|
|
|
|
!---------------------------------------------------------------
|
|
!
|
|
! aucune idee de l'utilisation de ce truc !
|
|
!
|
|
subroutine loop_of_parasites_1(nbre, mode)
|
|
implicit none
|
|
integer, intent(in) :: nbre, mode
|
|
|
|
integer :: idx
|
|
|
|
if (mode .NE. 0) STOP "BAD MODE"
|
|
do idx = 0, nbre
|
|
write(0, *) "popcorn loop ", idx
|
|
enddo
|
|
end subroutine loop_of_parasites_1
|
|
|
|
!===============================================================
|
|
end module xperiment
|