fixuinf1 Subroutine

public subroutine fixuinf1()

Uses

  • proc~~fixuinf1~~UsesGraph proc~fixuinf1 modforces::fixuinf1 module~modfields modfields proc~fixuinf1->module~modfields module~modglobal modglobal proc~fixuinf1->module~modglobal module~modmpi modmpi proc~fixuinf1->module~modmpi mpi mpi module~modmpi->mpi

Arguments

None

Calls

proc~~fixuinf1~~CallsGraph proc~fixuinf1 modforces::fixuinf1 proc~detfreestream modforces::detfreestream proc~fixuinf1->proc~detfreestream mpi_allreduce mpi_allreduce proc~detfreestream->mpi_allreduce

Called by

proc~~fixuinf1~~CalledByGraph proc~fixuinf1 modforces::fixuinf1 program~dalesurban DALESURBAN program~dalesurban->proc~fixuinf1

Contents

Source Code


Source Code

  subroutine fixuinf1
    use modglobal, only : ib,ie,jb,je,kb,ke,kh,dxf,xh,dt,&
                          Uinf,Vinf,ifixuinf,tscale,timee,rk3step,inletav,&
                          freestreamav,lvinf
    use modfields, only : u0,dpdxl,dgdt,dpdx,up,vp
    use modmpi, only    : myid,comm3d,mpierr,mpi_sum,my_real,nprocs
    implicit none

    real  utop,freestream,rk3coef
    integer i,j,k

    utop = 0.


    if ((ifixuinf==1) .and. (rk3step==3)) then

      ! rk3coef = dt / (4. - dble(rk3step))

      ! do j =jb,je
      !   do i =ib,ie
      !     utop = utop + 0.5*(u0(i,j,ke)+u0(i+1,j,ke))*dxf(i)
      !   end do
      ! end do
      ! utop = utop / ( (je-jb+1)*(xh(ie+1)-xh(ib) ) )
      ! call MPI_ALLREDUCE(utop,    freestream,1,MY_REAL,MPI_SUM,comm3d,mpierr)
      ! freestream = freestream / nprocs

      ! Write some statistics to monitoring file
      ! if (myid==0 .and. rk3step==3) then


      ! ! dpdxl(:) = dpdx + (1./rk3coef) * (freestream - Uinf)
      ! dpdxl(:) = dpdx + (1./dt) * (freestream - Uinf)
      call detfreestream(freestream)
      ! write(*,*) "freestream",freestream
      if (lvinf) then
        do k=kb,ke
          do i=ib,ie
            do j=jb,je
              vp(i,j,k) = vp(i,j,k) - (1./dt) * (freestream - Vinf)
            enddo
          enddo
        enddo
      else
        do k=kb,ke
          do j=jb,je
            do i=ib,ie
              up(i,j,k) = up(i,j,k) - (1./dt) * (freestream - Uinf)
            enddo
          enddo
        enddo
      endif
      ! if (myid==0) then
      !   write(*,*), "freestream", freestream
      !   write(*,*), "Uinf", Uinf
      !   open(unit=11,file='freestr.txt',position='append')
      !   write(11,3003) timee,freestream
      !   3003    format (13(6e20.12))
      !   close(11)

      !   open(unit=11,file='dpdx___.txt',position='append')
      !   write(11,3002) timee,dpdxl(kb),dpdxl(kb)-dpdx
      !   3002    format (13(6e20.12))
      !   close(11)
      ! endif
 
    end if

  end subroutine fixuinf1