Fortraneries/GravityField/essai.f90

55 lines
1.2 KiB
Fortran
Raw Normal View History

2022-11-28 13:47:44 +01:00
!
! project "gravity field"
!
2022-11-24 00:52:13 +01:00
program essai
2022-11-28 13:47:44 +01:00
use realfield
2022-11-24 00:52:13 +01:00
implicit none
2022-11-28 13:47:44 +01:00
type(massbody) :: planet
integer :: foo
planet%posx = 1337.314
planet%posy = 1664.666
planet%mass = 1e4
2022-11-24 00:52:13 +01:00
2022-11-28 13:47:44 +01:00
do foo=1, 10
call build_a_field(800, 600, planet)
planet%posy = planet%posy + 51.45
enddo
STOP 'YOLO'
2022-11-24 00:52:13 +01:00
2022-11-28 13:47:44 +01:00
contains !------------------------------------------
!
subroutine build_a_field(szx, szy, moon)
integer, intent(in) :: szx, szy
type(massbody), intent(in) :: moon
integer :: ix, iy
real :: fx, fy
real :: grav, maxi, mini
integer :: errcode
real, dimension(:,:), allocatable :: field
allocate(field(szx, szy), stat=errcode)
do ix=1, szx
2022-11-24 00:52:13 +01:00
fx = real(ix)
2022-11-28 13:47:44 +01:00
do iy=1, szy
2022-11-24 00:52:13 +01:00
fy = real(iy)
2022-11-28 13:47:44 +01:00
grav = compute_gravity(ix, iy, moon) / 2180800.0
field(ix,iy) = grav
2022-11-24 00:52:13 +01:00
enddo
enddo
2022-11-28 13:47:44 +01:00
maxi = maxval(field)
mini = minval(field)
print *, "field: ", mini, maxi, maxi-mini
2022-11-24 00:52:13 +01:00
2022-11-28 13:47:44 +01:00
deallocate(field)
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