Fortraneries/GravityField/essai.f90

80 lines
2.0 KiB
Fortran
Raw Normal View History

!-----------------------------------------------------------------------
2022-11-30 03:24:24 +01:00
!-
! test program for the project "gravity field"
!-
!-----------------------------------------------------------------------
2022-11-24 00:52:13 +01:00
program essai
2022-11-28 13:47:44 +01:00
use realfield
use spitpgm ! XXX
2022-11-24 00:52:13 +01:00
implicit none
2022-11-30 22:46:44 +01:00
call init_random()
2022-11-24 00:52:13 +01:00
2022-12-12 00:57:00 +01:00
call essai_near_planet(9999, 4096)
2022-11-28 13:47:44 +01:00
2022-11-30 22:46:44 +01:00
STOP 'BECAUSE YOLO'
2022-11-24 00:52:13 +01:00
contains
!-----------------------------------------------------------------------
!-
2022-12-12 00:57:00 +01:00
! computation of thr nearest planet
2022-11-30 22:46:44 +01:00
!-
2022-12-12 00:57:00 +01:00
subroutine essai_near_planet(nbplanets, szfield)
integer, intent(in) :: nbplanets, szfield
integer, dimension(:,:), allocatable :: map
integer :: ix, iy
real :: fx, fy, dx, dy
integer :: near, ipl, errcode
real :: curdist, smalldist
type(massbody) :: planets(nbplanets)
print *, "near planets test", nbplanets, szfield
2022-11-30 22:46:44 +01:00
2022-12-12 00:57:00 +01:00
allocate(map(szfield, szfield), stat=errcode)
map = -1
! create some random bodies
do ipl=1, nbplanets
planets(ipl)%posx = rand() * szfield
planets(ipl)%posy = rand() * szfield
planets(ipl)%serial = ipl
end do
! call save_bodies_to_txt_file(planets, "planets.txt")
! loop over all the location of the field
do ix=1, szfield
fx = real(ix)
do iy=1, szfield
fy = real(iy)
near = -1
smalldist = 1e37
! loop over all the planet's bodies
do ipl=1, nbplanets
! compute the "fake" distance
dx = fx - planets(ipl)%posx
dy = fy - planets(ipl)%posy
curdist = (dx*dx) + (dy*dy)
if (curdist .LT. smalldist) then
near = ipl
smalldist = curdist
endif
end do ! loop on ipl
map(ix, iy) = mod(near, 255)
enddo
write(0, *) "row", ix, " on", szfield
2022-11-30 22:46:44 +01:00
enddo
2022-11-24 00:52:13 +01:00
2022-12-12 00:57:00 +01:00
call spit_as_pgm_8(map, "nearest.pgm")
2022-11-24 00:52:13 +01:00
2022-11-28 13:47:44 +01:00
end subroutine
!-----------------------------------------------------------------------
2022-11-24 00:52:13 +01:00
end program