SUBROUTINE resume ! ! Resume from previous run ! Use beam Use basic Use fields Use sort Use maxwsrce Use geometry Use neutcol IMPLICIT NONE ! ! Local vars and arrays INTEGER:: i !________________________________________________________________________________ WRITE(*,'(a)') ' Resume from previous run' !________________________________________________________________________________ ! ! Open and read initial conditions from restart file CALL chkrst(0) ! If we want to start a new run with a new file IF (newres) THEN ! we start time and step from 0 cstep=0 time=0 END IF CALL fields_init call timera(0, "read_geom") call read_geom(lu_in, rnorm, splrz, Potinn, Potout) call timera(1, "read_geom") ! Initialize the magnetic field and the electric field solver call init_mag CALL fields_start call localisation(partslist(1)) ! Add the requested test particles and read them from input files IF (nbaddtestspecies .gt. 0) THEN Do i=1,nbaddtestspecies CALL load_part_file(partslist(nbspecies+i),addedtestspecfile(i)) call localisation(partslist(nbspecies+i)) END DO nbspecies=nbspecies+nbaddtestspecies END IF IF(mpisize .gt. 1) THEN CALL calc_Zbounds(partslist(1), Zbounds, femorder) DO i=1,nbspecies CALL keep_mpi_self_parts(partslist(i),Zbounds) call collectparts(partslist(i)) END DO END IF CALL bound(partslist(1)) CALL localisation(partslist(1)) ! Allocate the variables for MPI communications CALL fields_comm_init(Zbounds) ! Solve Poisson for the initial conditions CALL rhscon(partslist) CALL poisson(splrz) ! Compute the fields at the particles positions CALL EFieldscompatparts(partslist(1)) if(mpirank .eq. 0) WRITE(*,*) "Initial forces computed" ! END SUBROUTINE resume