SUBROUTINE start ! ! Start or restart the run ! USE basic,ONLY: mpirank, nlmaxwellsource, time, lu_in, Zbounds, nbspecies, cstep, nlres Use maxwsrce Use geometry Use neutcol Use beam Use fields use mpi use psupply IMPLICIT NONE ! ! Local vars and arrays INTEGER:: i, nbbounds !________________________________________________________________________________ IF(mpirank.eq.0) WRITE(*,'(a/)') '=== Start or restart the run ===' !________________________________________________________________________________ ! IF (cstep .eq. 0) THEN CALL partdiagnostics Do i=1,nbspecies if(.not. partslist(i)%calc_moments) CYCLE CALL momentsdiag(partslist(i)) End do END IF ! Initialize electron neutral collisions CALL neutcol_init(lu_in, partslist(1)) ! resize nblost array to adapt for correct number of boundaries nbbounds=2 if(the_domain%nbsplines .gt. 0) nbbounds=the_domain%nbsplines Do i=1,nbspecies if( allocated(partslist(i)%nblost)) deallocate(partslist(i)%nblost) allocate(partslist(i)%nblost(4+nbbounds)) partslist(i)%nblost=0 end do ! Initialize the external power supply if(nlres .and. the_ps%active)then write(*,*) "the_ps is active" call psupply_init(lu_in, cstep, nbbounds, neutdens, the_ps%bias) else write(*,*) "use default psupply init" call psupply_init(lu_in, cstep, nbbounds, neutdens) end if ! Activate the source if present IF (nlmaxwellsource) CALL maxwsrce_init(lu_in, time, Zbounds) END SUBROUTINE start