62 lines
1.8 KiB
Fortran
62 lines
1.8 KiB
Fortran
!-----------------------------------------------------------------------
|
|
!-
|
|
! test program for the project "gravity field"
|
|
!-
|
|
!-----------------------------------------------------------------------
|
|
program essai
|
|
use realfield
|
|
use spitpgm ! XXX
|
|
|
|
implicit none
|
|
|
|
! some configuration constants
|
|
integer, parameter :: S_WIDTH = 800
|
|
integer, parameter :: S_HEIGHT = 600
|
|
integer, parameter :: NB_BODY = 51
|
|
|
|
type(massbody) :: planets(NB_BODY)
|
|
integer :: foo
|
|
character(len=100) :: filename
|
|
|
|
call init_random()
|
|
call create_some_planets(planets, 45e5, S_WIDTH, S_HEIGHT)
|
|
|
|
do foo=0, 1999
|
|
write (filename, "(a, i5.5, a)") 'WS/field/', foo, '.pgm'
|
|
call build_and_write_a_field(S_WIDTH, S_HEIGHT, planets, filename)
|
|
! print *, trim(filename)
|
|
! OMG! two magic numbers, wtf?
|
|
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)
|
|
|
|
enddo
|
|
|
|
STOP 'BECAUSE YOLO'
|
|
|
|
contains
|
|
!-----------------------------------------------------------------------
|
|
!-
|
|
! Et si on bougeait un peu tous ces corps planétaires ?
|
|
!-
|
|
subroutine boulegue_les_astres(astres, factor)
|
|
type(massbody), intent(inout) :: astres(:)
|
|
real, intent(in) :: factor
|
|
|
|
integer :: foo
|
|
|
|
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)
|
|
enddo
|
|
|
|
|
|
end subroutine
|
|
!-----------------------------------------------------------------------
|
|
!-----------------------------------------------------------------------
|
|
|
|
end program
|