130 lines
3.6 KiB
Fortran
130 lines
3.6 KiB
Fortran
!-----------------------------------------------------------------------
|
|
!-
|
|
! test program for the project "gravity field"
|
|
!-
|
|
!-----------------------------------------------------------------------
|
|
program essai
|
|
use realfield
|
|
use spitpgm ! XXX
|
|
|
|
implicit none
|
|
|
|
type(massbody) :: planets(60)
|
|
integer :: foo
|
|
character(len=100) :: filename
|
|
|
|
call init_random()
|
|
|
|
call create_some_planets(planets, 45e5)
|
|
|
|
do foo=0, 72
|
|
write (filename, "(a, i5.5, a)") 'WS/A', foo, '.pgm'
|
|
call build_and_write_a_field(640, 480, planets, filename)
|
|
print *, trim(filename)
|
|
! OMG! two magic numbers, wtf?
|
|
planets(1)%posx = planets(1)%posx + 8.08
|
|
planets(1)%posy = planets(1)%posy + 6.42
|
|
enddo
|
|
|
|
STOP 'BECAUSE YOLO'
|
|
|
|
contains
|
|
!-----------------------------------------------------------------------
|
|
!-
|
|
! Yes, I know, this is a disturbing kluge, but I like it :}
|
|
! May be, it's time to read the doc of modern Fortran
|
|
!-
|
|
subroutine init_random()
|
|
|
|
integer, dimension(3) :: tarray
|
|
integer :: t3
|
|
real :: dummy
|
|
call itime(tarray)
|
|
t3 = 8971*tarray(1) + 443*tarray(2) + tarray(3)
|
|
write(0, '(A,3I3,A,I6)') "sranding: ", tarray, " --> ", t3
|
|
call srand(t3)
|
|
! after initializing the random generator engine,
|
|
! you MUST use it for initializing the initializer
|
|
dummy = rand()
|
|
write(0, *) 'dummy was ', dummy
|
|
|
|
end subroutine
|
|
!-----------------------------------------------------------------------
|
|
!-
|
|
! make a few solid body to play with...
|
|
!-
|
|
subroutine create_some_planets(planets, coef)
|
|
type(massbody), intent(inout) :: planets(:)
|
|
real, intent(in) :: coef
|
|
integer :: foo
|
|
! real :: quux, quuy
|
|
character(100) :: fmt
|
|
|
|
fmt = "(I4, ' : ', 2(F9.2, ' '), e11.3, I7)"
|
|
|
|
do foo=1, ubound(planets, 1)
|
|
if (foo .EQ. 1) then
|
|
planets(1)%posx = 20
|
|
planets(1)%posy = 20
|
|
planets(1)%mass = 9e8
|
|
planets(1)%serial = 1337
|
|
else
|
|
planets(foo)%posx = rand() * 639.999
|
|
planets(foo)%posy = rand() * 479.999
|
|
planets(foo)%mass = 7e6 + coef*foo
|
|
planets(foo)%serial = foo
|
|
endif
|
|
write (*, fmt) foo, planets(foo)
|
|
enddo
|
|
|
|
! STOP 'ABEND'
|
|
|
|
end subroutine
|
|
!-----------------------------------------------------------------------
|
|
!-
|
|
! compute a field with only one body; and write pic file
|
|
!-
|
|
subroutine build_and_write_a_field(szx, szy, moons, fname)
|
|
integer, intent(in) :: szx, szy
|
|
type(massbody), intent(in) :: moons(:)
|
|
character(len=*), intent(in) :: fname
|
|
|
|
real :: maxi, mini
|
|
integer :: errcode, foo
|
|
real, dimension(:,:), allocatable :: field, tmpf
|
|
integer, dimension(:,:), allocatable :: greymap
|
|
|
|
allocate(field(szx, szy), stat=errcode)
|
|
allocate(tmpf(szx, szy), stat=errcode)
|
|
|
|
field = 0.0
|
|
do foo=1, ubound(moons, 1)
|
|
call compute_a_field(tmpf, moons(foo))
|
|
tmpf = tmpf * 0.019
|
|
field = field + tmpf
|
|
enddo
|
|
|
|
maxi = maxval(field)
|
|
mini = minval(field)
|
|
! print *, "field: ", mini, maxi, maxi-mini
|
|
|
|
allocate(greymap(szx, szy), stat=errcode)
|
|
greymap = 0
|
|
! convert from real value to 16 bits int values
|
|
where (field < 65530.0)
|
|
greymap = int(field)
|
|
end where
|
|
|
|
call spit_as_pgm_16(greymap, trim(fname))
|
|
|
|
! make valgrind happy
|
|
deallocate(field)
|
|
deallocate(greymap)
|
|
|
|
end subroutine
|
|
|
|
!-----------------------------------------------------------------------
|
|
!-----------------------------------------------------------------------
|
|
|
|
end program
|