program movebloubs use bloubspace use povstuff use mathstuff2 implicit none character(200) :: infile, outfile integer :: inu, outu, errcode, i integer :: compteur, killed type(t_bloubs) :: bloub double precision :: bx, by, bz ! logical :: add_new_bloub = .TRUE. real :: rnd 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) call init_random_seed() open(newunit=inu, & file=trim(infile), form='unformatted', & iostat=errcode, & action='read', status='old') if (0 .ne. errcode) then STOP " : CAN'T OPEN FILE " // trim(infile) endif open(newunit=outu, & file=trim(outfile), form='unformatted', & iostat=errcode, & action='write', status='replace') if (0 .ne. errcode) then STOP " : CAN'T OPEN " // trim(outfile) // "FOR WRITE" endif ! write(0, '("Units: ", 2I5)') inu, outu bx = 0.0; by = 0.0; bz = 0.0 compteur = 0 killed = 0 !- ! begin of bigloop !- do read (unit=inu, iostat=errcode) bloub if (0 .ne. errcode) then ! may be we got an EOF ? exit endif ! moving, morphing and boundingboxing call move_bloub (bloub, 0.185) call bound_a_bloub (bloub) if (bloub%radius .GT. 3.50) then bloub%radius = bloub%radius * 0.999 endif ! if (bloub%radius .LT. 0.00015) then ! bloub%alive = .FALSE. ! endif ! XXX call green_soylent (bloub) ! XXX if (.NOT. bloub%alive) then ! XXX ! write(0, '(A)') " KILL!" ! XXX killed = killed + 1 ! XXX endif ! calcul du barycentre bx = bx + dble(bloub%px) by = by + dble(bloub%py) bz = bz + dble(bloub%pz) if (bloub%alive) then write(outu, iostat=errcode) bloub if (0 .ne. errcode) then STOP " : WRITE ERROR TO " // trim(outfile) endif compteur = compteur + 1 endif enddo ! end of main loop write(0, '(1X,I0,1X,A)') compteur, "bloubs processed" if (killed .GT. 0) then write (0, '(1X,I0,A)') killed, " bloubs killed" endif ! ok, we have read all the bloubs from the input file ! insert some fancy conditional here if (compteur .LT. 50) then call add_more_bloubs(outu, 5, 0.046) endif rnd = rand() ! write(0, *) 'rnd= ', rnd if (rnd .LT. 0.18) then write (0, *) '... random of life ...' call add_more_bloubs(outu, 5, 0.056) endif close(inu) ; close(outu) ! -------------------------------------------------------------- contains subroutine add_more_bloubs(un, nbre, rayon) implicit none integer, intent(in) :: un, nbre real, intent(in) :: rayon type(t_bloubs) :: bloub integer :: foo, count count = nbre+mod(irand(), 2) write(0, '(1X,A,I0,1X,A)') "movebloubs: adding ", count, " bloubs" do foo=1, count bloub%nick = 'newbie ' call make_a_random_bloub(bloub, 10.00) bloub%radius = rayon + (0.11*rand()) bloub%age = 1 bloub%agemax = 160 + (count * 4) bloub%alive = .TRUE. bloub%num = mod(irand(), 42) write(un) bloub ! no error control ? enddo end subroutine ! -------------------------------------------------------------- end program movebloubs