2022-02-06 23:45:08 +01:00
|
|
|
program movebloubs
|
|
|
|
|
|
|
|
use bloubspace
|
|
|
|
use povstuff
|
2022-02-08 18:56:51 +01:00
|
|
|
use mathstuff
|
2022-02-06 23:45:08 +01:00
|
|
|
|
|
|
|
implicit none
|
|
|
|
|
|
|
|
character(200) :: infile, outfile
|
|
|
|
integer :: inu, outu, errcode, i
|
2022-02-08 18:56:51 +01:00
|
|
|
integer :: compteur, killed
|
2022-02-06 23:45:08 +01:00
|
|
|
type(t_bloubs) :: bloub
|
|
|
|
double precision :: bx, by, bz
|
2022-02-16 15:59:42 +01:00
|
|
|
! logical :: add_new_bloub = .TRUE.
|
2022-02-08 18:56:51 +01:00
|
|
|
! real :: rnd
|
|
|
|
|
|
|
|
call init_random_seed()
|
2022-02-06 23:45:08 +01:00
|
|
|
|
|
|
|
i = IARGC()
|
|
|
|
if (i .ne. 2) then
|
|
|
|
STOP ": BAD ARGS ON COMMAND LINE"
|
|
|
|
endif
|
|
|
|
call getarg(1, infile)
|
|
|
|
call getarg(2, outfile)
|
|
|
|
|
|
|
|
write (0, '(A)') &
|
|
|
|
"*** moving bloubs from "//trim(infile)//" to "//trim(outfile)
|
|
|
|
|
2022-02-08 18:56:51 +01:00
|
|
|
open(newunit=inu, &
|
|
|
|
file=trim(infile), form='unformatted', &
|
2022-02-06 23:45:08 +01:00
|
|
|
iostat=errcode, &
|
|
|
|
action='read', status='old')
|
|
|
|
if (0 .ne. errcode) then
|
|
|
|
STOP " : CAN'T OPEN FILE " // trim(infile)
|
|
|
|
endif
|
|
|
|
|
2022-02-08 18:56:51 +01:00
|
|
|
open(newunit=outu, &
|
|
|
|
file=trim(outfile), form='unformatted', &
|
|
|
|
iostat=errcode, &
|
2022-02-06 23:45:08 +01:00
|
|
|
action='write', status='replace')
|
|
|
|
if (0 .ne. errcode) then
|
2022-02-08 02:53:49 +01:00
|
|
|
STOP " : CAN'T OPEN " // trim(outfile) // "FOR WRITE"
|
2022-02-06 23:45:08 +01:00
|
|
|
endif
|
|
|
|
|
|
|
|
bx = 0.0; by = 0.0; bz = 0.0
|
2022-02-08 18:56:51 +01:00
|
|
|
compteur = 0
|
|
|
|
killed = 0
|
2022-02-06 23:45:08 +01:00
|
|
|
|
|
|
|
do
|
|
|
|
read (unit=inu, iostat=errcode) bloub
|
|
|
|
if (0 .ne. errcode) then
|
2022-02-08 18:56:51 +01:00
|
|
|
! may be we got an EOF ?
|
2022-02-06 23:45:08 +01:00
|
|
|
exit
|
|
|
|
endif
|
|
|
|
|
2022-02-08 02:53:49 +01:00
|
|
|
! moving and boundingboxing
|
2022-02-08 18:56:51 +01:00
|
|
|
call move_bloub (bloub, 0.15)
|
|
|
|
call bound_a_blob (bloub)
|
|
|
|
call green_soylent (bloub)
|
|
|
|
if (.NOT. bloub%alive) then
|
2022-02-09 00:42:32 +01:00
|
|
|
! write(0, '(A)') " KILL!"
|
2022-02-08 18:56:51 +01:00
|
|
|
killed = killed + 1
|
|
|
|
cycle
|
|
|
|
endif
|
2022-02-08 02:53:49 +01:00
|
|
|
! calcul du barycentre
|
2022-02-08 18:56:51 +01:00
|
|
|
bx = bx + dble(bloub%px)
|
|
|
|
by = by + dble(bloub%py)
|
|
|
|
bz = bz + dble(bloub%pz)
|
2022-02-06 23:45:08 +01:00
|
|
|
|
2022-02-08 02:53:49 +01:00
|
|
|
write(outu, iostat=errcode) bloub ! no error control ?
|
|
|
|
if (0 .ne. errcode) then
|
|
|
|
STOP " : WRITE ERROR TO " // trim(outfile)
|
2022-02-07 02:08:17 +01:00
|
|
|
endif
|
2022-02-08 18:56:51 +01:00
|
|
|
compteur = compteur + 1
|
2022-02-06 23:45:08 +01:00
|
|
|
|
|
|
|
enddo
|
|
|
|
|
2022-02-11 15:26:52 +01:00
|
|
|
! ok, we have read all the bloubs in the input file
|
|
|
|
|
|
|
|
! insert some fancy conditional here
|
2022-02-16 15:59:42 +01:00
|
|
|
if (compteur .LT. 1500) then
|
2022-02-08 18:56:51 +01:00
|
|
|
|
2022-02-16 15:59:42 +01:00
|
|
|
call add_more_bloubs(outu, 8, 0.075)
|
2022-02-11 15:26:52 +01:00
|
|
|
|
2022-02-08 02:53:49 +01:00
|
|
|
endif
|
2022-02-06 23:45:08 +01:00
|
|
|
|
|
|
|
close(inu) ; close(outu)
|
|
|
|
|
2022-02-09 00:42:32 +01:00
|
|
|
if (killed .GT. 0) then
|
|
|
|
write (0, '(I5, A)') killed, " bloubs killed"
|
|
|
|
endif
|
|
|
|
|
2022-02-08 18:56:51 +01:00
|
|
|
bx = bx / dble(compteur)
|
|
|
|
by = by / dble(compteur)
|
|
|
|
bz = bz / dble(compteur)
|
|
|
|
write (0, '(A,3(F12.6,3X))') "barycentre : ", bx, by, bz
|
|
|
|
|
2022-02-11 15:26:52 +01:00
|
|
|
! --------------------------------------------------------------
|
|
|
|
contains
|
|
|
|
|
|
|
|
subroutine add_more_bloubs(un, nbre, wtf)
|
|
|
|
integer, intent(in) :: un, nbre
|
|
|
|
real, intent(in) :: wtf
|
|
|
|
type(t_bloubs) :: bloub
|
|
|
|
integer :: foo
|
|
|
|
|
|
|
|
do foo=1, nbre
|
|
|
|
|
|
|
|
bloub%nick = 'newbie '
|
|
|
|
bloub%alive = .TRUE.
|
|
|
|
call random_pv(bloub)
|
|
|
|
bloub%radius = wtf
|
|
|
|
bloub%seq = foo
|
2022-02-16 15:59:42 +01:00
|
|
|
! call display_bloub (bloub, "new bloub")
|
2022-02-11 15:26:52 +01:00
|
|
|
write(un) bloub ! no error control ?
|
|
|
|
|
|
|
|
enddo
|
|
|
|
|
|
|
|
end subroutine
|
|
|
|
|
|
|
|
! --------------------------------------------------------------
|
2022-02-08 18:56:51 +01:00
|
|
|
|
2022-02-11 15:26:52 +01:00
|
|
|
end program movebloubs
|