sc_store_fq Subroutine

private subroutine sc_store_fq(self, fq, fqa, fqp, ifl_in, it_in, ig_in)

Store the field equations at row level

Type Bound

supercell_type

Arguments

Type IntentOptional Attributes Name
class(supercell_type), intent(inout) :: self
complex, intent(in), dimension(:, :) :: fq
complex, intent(in), dimension(:, :) :: fqa
complex, intent(in), dimension(:, :) :: fqp
integer, intent(in) :: ifl_in
integer, intent(in) :: it_in
integer, intent(in) :: ig_in

Contents

Source Code


Source Code

  subroutine sc_store_fq(self, fq, fqa, fqp, ifl_in, it_in, ig_in)
    use theta_grid, only: ntgrid
    use run_parameters, only: has_phi, has_apar, has_bpar
    use mp, only: mp_abort, iproc
    implicit none
    class(supercell_type), intent(inout) :: self
    complex, dimension(:, :), intent(in) :: fq, fqa, fqp
    integer, intent(in) :: ifl_in, it_in, ig_in
    integer :: ic, ic_in, irow, ifq, ulim, ir

    !If we don't have anything in this supercell then exit
    if(self%is_empty) return

    !Find out which cell has our it
    ic_in=0
    do ic=1,self%ncell
       if(self%cells(ic)%it_ind.eq.it_in) then
          ic_in=ic
          exit
       endif
    enddo

    !Work out the row we want to put data in
    irow=(ig_in+ntgrid+1)+(ic_in-1)*(2*ntgrid)+(ifl_in-1)*self%nextend

    ! Loop over cells
    do ic=1,self%ncell
       !If we don't have this cell cycle
       if(self%cells(ic)%is_empty) then
          cycle
       endif

       !Check if we have this row, if not cycle
       if(.not.self%cells(ic)%has_row(irow)) then
          cycle
       endif

       !Find upper limit of column
       ulim=self%cells(ic)%ncol
       
       ifq=0
       if(has_phi)then
          !Increment counter
          ifq=ifq+1

          !Convert extended irow to local
          ir=self%cells(ic)%rb(ifq)%irex_to_ir(irow)

          !Store data
          self%cells(ic)%rb(ifq)%data(:,ir) = fq(:ulim, self%cells(ic)%it_ind)
       end if

       if(has_apar)then
          !Increment counter
          ifq=ifq+1

          !Convert extended irow to local
          ir=self%cells(ic)%rb(ifq)%irex_to_ir(irow)

          !Store data
          self%cells(ic)%rb(ifq)%data(:,ir) = fqa(:ulim, self%cells(ic)%it_ind)
       end if

       if(has_bpar)then
          !Increment counter
          ifq=ifq+1

          !Convert extended irow to local
          ir=self%cells(ic)%rb(ifq)%irex_to_ir(irow)

          !Store data
          self%cells(ic)%rb(ifq)%data(:,ir) = fqp(:ulim, self%cells(ic)%it_ind)
       end if
    end do

  end subroutine sc_store_fq