Fortraneries/GravityField/essai.f90

62 lines
1.8 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-12-03 02:25:37 +01:00
! some configuration constants
integer, parameter :: S_WIDTH = 800
integer, parameter :: S_HEIGHT = 600
integer, parameter :: NB_BODY = 51
type(massbody) :: planets(NB_BODY)
2022-11-28 13:47:44 +01:00
integer :: foo
2022-11-30 03:24:24 +01:00
character(len=100) :: filename
2022-11-30 22:46:44 +01:00
call init_random()
2022-12-03 02:25:37 +01:00
call create_some_planets(planets, 45e5, S_WIDTH, S_HEIGHT)
2022-11-24 00:52:13 +01:00
2022-12-03 02:25:37 +01:00
do foo=0, 1999
write (filename, "(a, i5.5, a)") 'WS/', foo, '.pgm'
call build_and_write_a_field(S_WIDTH, S_HEIGHT, planets, filename)
! print *, trim(filename)
2022-11-30 22:46:44 +01:00
! OMG! two magic numbers, wtf?
2022-12-03 02:25:37 +01:00
planets(1)%posx = planets(1)%posx + 3 + (4.5*rand())
planets(1)%posy = planets(1)%posy + 3 + (2.1*rand())
if (planets(1)%posx .GT. S_WIDTH) planets(1)%posx = 0.0
if (planets(1)%posy .GT. S_HEIGHT) planets(1)%posy = 0.0
call boulegue_les_astres(planets, 2.21)
2022-11-28 13:47:44 +01:00
enddo
2022-11-30 22:46:44 +01:00
STOP 'BECAUSE YOLO'
2022-11-24 00:52:13 +01:00
contains
!-----------------------------------------------------------------------
!-
2022-12-03 02:25:37 +01:00
! Et si on bougeait un peu tous ces corps planétaires ?
2022-11-30 22:46:44 +01:00
!-
2022-12-03 02:25:37 +01:00
subroutine boulegue_les_astres(astres, factor)
type(massbody), intent(inout) :: astres(:)
real, intent(in) :: factor
2022-11-30 22:46:44 +01:00
integer :: foo
2022-12-03 02:25:37 +01:00
do foo = 2, ubound(astres, 1)
astres(foo)%posx = astres(foo)%posx + factor*(rand() - 0.5)
astres(foo)%posy = astres(foo)%posy + factor*(rand() - 0.5)
2022-11-30 22:46:44 +01:00
enddo
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