SUBROUTINE endrun ! ! Terminate the run ! USE basic USE beam USE fields IMPLICIT NONE INTEGER:: i ! ! Local vars and arrays ! !________________________________________________________________________________ ! IF( nlend ) THEN ! !---------------------------------------------------------------------- ! 1. Normal end of run ! WRITE(*,'(/a)') ' Terminate the run' ! Prepare the particles for writing the restart file ! in case of mpi parallelism, gather the particles on the host DO i=1,nbspecies call bound(partslist(i)) call boundary_loss(partslist(i)) partslist(i)%collected=.false. IF(mpisize .gt. 1) THEN call collectparts(partslist(i),partslist_towrite(i)) else partslist(i)%Nptot=partslist(i)%Nploc end if END DO ! !---------------------------------------------------------------------- ! 2. Abnormal exit ! ELSE WRITE(*,'(/a)') ' Abnormal exit' END IF ! !---------------------------------------------------------------------- ! 9. Epilogue ! ! Create restart file IF(mpirank .eq. 0) then CALL chkrst(1) end if CALL clean_beam(partslist) CALL clean_fields ! ! Closing all files CLOSE(lu_in) END SUBROUTINE endrun