tstep_integrate Subroutine

subroutine tstep_integrate()

Uses

  • proc~~tstep_integrate~~UsesGraph proc~tstep_integrate tstep.f90::tstep_integrate module~modchem modchem proc~tstep_integrate->module~modchem module~modfields modfields proc~tstep_integrate->module~modfields module~modglobal modglobal proc~tstep_integrate->module~modglobal module~modinletdata modinletdata proc~tstep_integrate->module~modinletdata module~modmpi modmpi proc~tstep_integrate->module~modmpi module~modsubgriddata modsubgriddata proc~tstep_integrate->module~modsubgriddata mpi mpi module~modmpi->mpi

Arguments

None

Calls

proc~~tstep_integrate~~CallsGraph proc~tstep_integrate tstep.f90::tstep_integrate proc~chem modchem::chem proc~tstep_integrate->proc~chem

Called by

proc~~tstep_integrate~~CalledByGraph proc~tstep_integrate tstep.f90::tstep_integrate program~dalesurban DALESURBAN program~dalesurban->proc~tstep_integrate

Contents

Source Code


Source Code

subroutine tstep_integrate


  use modglobal, only : ib,ie,jb,jgb,je,kb,ke,nsv,dt,rk3step,e12min,lmoist,timee,ntrun,&
                        linoutflow, iinletgen,ltempeq,idriver,&
                        dzf,dzhi,dzf,dxhi,dxf,ifixuinf,thlsrc,lchem
  use modmpi, only    : cmyid,myid,nprocs
  use modfields, only : u0,um,up,v0,vm,vp,w0,wm,wp,&
                        thl0,thlm,thlp,qt0,qtm,qtp,e120,e12m,e12p,sv0,svm,svp,uouttot,&
                        wouttot,dpdxl,dgdt,momfluxb,tfluxb,qfluxb
  use modinletdata, only: totalu,di_test,dr,thetar,thetai,displ,irecy, &
                          dti_test,dtr,thetati,thetatr,q0,lmoi,lmor,utaui,utaur,&
                          storetdriver, nstepread, nstepreaddriver, irecydriver
  use modsubgriddata, only : loneeqn,ekm,ekh
  use modchem, only : chem

  implicit none

  integer i,j,k,n,m
  real rk3coef,rk3coefi

  rk3coef = dt / (4. - dble(rk3step))
  rk3coefi = 1./rk3coef

  if(ifixuinf==2) then
    dpdxl(:) = dpdxl(:) + dgdt*rk3coef 
!    if(ltempeq) then
!      thlsrc = thlsrc + thlsrcdt*rk3coef
!    end if
!    write(6,*) 'dpdx = ', dpdxl(kb)
  end if

  if (loneeqn) then
    do k=kb,ke
      do j=jb,je
        do i=ib,ie
          u0(i,j,k)   = um(i,j,k)   + rk3coef * up(i,j,k)
          v0(i,j,k)   = vm(i,j,k)   + rk3coef * vp(i,j,k)
          w0(i,j,k)   = wm(i,j,k)   + rk3coef * wp(i,j,k)
          e120(i,j,k) = e12m(i,j,k) + rk3coef * e12p(i,j,k)
          e120(i,j,k) = max(e12min,e120(i,j,k))
          e12m(i,j,k) = max(e12min,e12m(i,j,k))
          do n=1,nsv
            sv0(i,j,k,n) = svm(i,j,k,n) + rk3coef * svp(i,j,k,n)
          enddo
        enddo
      enddo
    end do
  else
    do k=kb,ke
      do j=jb,je
        do i=ib,ie
          u0(i,j,k)   = um(i,j,k)   + rk3coef * up(i,j,k)
          v0(i,j,k)   = vm(i,j,k)   + rk3coef * vp(i,j,k)
          w0(i,j,k)   = wm(i,j,k)   + rk3coef * wp(i,j,k) 
          do n=1,nsv
            sv0(i,j,k,n) = svm(i,j,k,n) + rk3coef * svp(i,j,k,n)
          enddo
        enddo 
      enddo
    enddo
  end if

  if (lchem .and. rk3coef == dt) then
    call chem
  end if

  if (ltempeq) then
 ! if (myid==0) then
 ! write(*,*) "thlp(20,1,46)",thlp(20,1,46)  
 ! end if
  do k=kb,ke
      do j=jb,je
        do i=ib,ie
          thl0(i,j,k) = thlm(i,j,k) + rk3coef * thlp(i,j,k)
        enddo 
      enddo 
    enddo
  end if
  if (lmoist) then
   do k=kb,ke
     do j=jb,je
       do i=ib,ie
         qt0(i,j,k) = qtm(i,j,k) + rk3coef * qtp(i,j,k)
       enddo 
      enddo
    enddo
  end if

  
  if (linoutflow) then
    if ((iinletgen == 0) .and. (idriver /= 2)) then
      u0(ie+1,jb:je,kb:ke) = um(ie+1,jb:je,kb:ke)  + rk3coef * up(ie+1,jb:je,kb:ke)
    else
      u0(ib-1,jb:je,kb:ke) = um(ib-1,jb:je,kb:ke)  + rk3coef * up(ib-1,jb:je,kb:ke)
      u0(ie+1,jb:je,kb:ke) = um(ie+1,jb:je,kb:ke)  + rk3coef * up(ie+1,jb:je,kb:ke)
    end if
  end if

!up to here

!  Write some statistics to monitoring file 
      if ((myid==0) .and. (rk3step==3)) then
        open(unit=11,file='monitor'//cmyid//'.txt',position='append')
        if (iinletgen == 1) then 
          write(11,3001) timee
        elseif (idriver == 1) then
          write(11, '(I4)') nstepreaddriver
          write(11, 3001) timee, u0(irecydriver,1,32)
        ! elseif (idriver == 2) then
          ! write(11, '(I4)') nstepreaddriver
          ! write(11, 3001) timee, storetdriver(nstepreaddriver), u0(irecydriver, 1, 32)              
        else
          write(11,3001) timee
        end if
3001    format (13(6e14.6))
        close(11)

        if (ifixuinf == 2) then
          open(unit=11,file='dpdx___.txt',position='append')
          write(11,3002) timee,dpdxl(kb)
3002      format (13(6e20.12))
          close(11)
          
          if (ltempeq) then
            open(unit=11,file='thlsrc.txt',position='append')
            write(11,3002) timee,thlsrc
3003        format (13(6e20.12))
            close(11)
          end if


        end if
      endif

  up=0.
  vp=0.
  wp=0.
  thlp=0.
  svp=0.
  e12p=0.
  qtp=0.

  if(rk3step == 3) then
    um = u0
    vm = v0
    wm = w0
    thlm = thl0
    e12m = e120
    svm = sv0
    qtm = qt0
  end if
end subroutine tstep_integrate