SUBROUTINE inital ! USE basic USE beam USE fields USE mpihelper USE maxwsrce Use geometry Use neutcol ! ! Set initial conditions ! IMPLICIT NONE INTEGER:: i, nbbounds ! !________________________________________________________________________________ IF(mpirank .eq. 0) WRITE(*,'(a/)') '=== Set initial conditions ===' !________________________________________________________________________________ ! ! Init Electric and Magnetic Fields ALLOCATE(partslist(nbspecies)) CALL fields_init call timera(0, "read_geom") call read_geom(lu_in, rnorm, splrz, Potinn, Potout) call timera(1, "read_geom") call mag_init ! 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 CALL load_parts ! will call the localisation qnorm=abs(partslist(1)%weight*partslist(1)%q) IF(mpisize .gt. 1) THEN CALL calc_Zbounds(partslist(1), Zbounds, femorder) END IF Do i=1,size(partslist) CALL keep_mpi_self_parts(partslist(i), Zbounds) END DO call fields_start CALL fields_comm_init(Zbounds) CALL rhscon(partslist) CALL poisson(splrz) CALL EFieldscompatparts(partslist(1)) CALL adapt_vinit(partslist(1)) !________________________________________________________________________________ END SUBROUTINE inital