fm_update_fields Subroutine

private subroutine fm_update_fields(self, phi, apar, bpar)

Update the fields using calculated update

Type Bound

fieldmat_type

Arguments

Type IntentOptional Attributes Name
class(fieldmat_type), intent(in) :: self
complex, intent(inout), dimension(:,:,:) :: phi
complex, intent(inout), dimension(:,:,:) :: apar
complex, intent(inout), dimension(:,:,:) :: bpar

Contents

Source Code


Source Code

  subroutine fm_update_fields(self,phi,apar,bpar)
    use fields_arrays, only: orig_phi=>phi, orig_apar=>apar, orig_bpar=>bpar
    use run_parameters, only: has_phi, has_apar, has_bpar
    use kt_grids, only: kwork_filter
    use mp, only: proc0
    implicit none
    class(fieldmat_type), intent(in) ::  self
    complex,dimension(:,:,:),intent(inout) :: phi,apar,bpar
    integer :: ik,it,is,ic

    !If we're proc0 then we need to do full array (for diagnostics)
    if(proc0) then
       if(has_phi) phi=phi+orig_phi
       if(has_apar) apar=apar+orig_apar
       if(has_bpar) bpar=bpar+orig_bpar
       return
    endif

    !Now loop over cells and calculate field equation as required
    !$OMP PARALLEL DO DEFAULT(none) &
    !$OMP PRIVATE(ik, is, ic, it) &
    !$OMP SHARED(self, kwork_filter, has_phi, has_apar, has_bpar, &
    !$OMP phi, apar, bpar, orig_phi, orig_apar, orig_bpar) &
    !$OMP SCHEDULE(static)
    do ik=1,self%naky
       !Skip not local cells
       if(.not.self%kyb(ik)%is_local) cycle
       do is=1,self%kyb(ik)%nsupercell
          if(.not.self%kyb(ik)%supercells(is)%is_local) cycle
          do ic=1,self%kyb(ik)%supercells(is)%ncell
             if(.not.self%kyb(ik)%supercells(is)%cells(ic)%is_local) cycle

             it=self%kyb(ik)%supercells(is)%cells(ic)%it_ind

             if(kwork_filter(it,ik)) cycle

             !Increment fields
             if(has_phi) phi(:,it,ik)=phi(:,it,ik)+orig_phi(:,it,ik)
             if(has_apar) apar(:,it,ik)=apar(:,it,ik)+orig_apar(:,it,ik)
             if(has_bpar) bpar(:,it,ik)=bpar(:,it,ik)+orig_bpar(:,it,ik)
          enddo
       enddo
    enddo
    !$OMP END PARALLEL DO

  end subroutine fm_update_fields