boundary Subroutine

public subroutine boundary()

Uses

  • proc~~boundary~~UsesGraph proc~boundary modboundary::boundary module~moddriver moddriver proc~boundary->module~moddriver module~modfields modfields proc~boundary->module~modfields module~modglobal modglobal proc~boundary->module~modglobal module~modinlet modinlet proc~boundary->module~modinlet module~modinletdata modinletdata proc~boundary->module~modinletdata module~modmpi modmpi proc~boundary->module~modmpi module~modsubgriddata modsubgriddata proc~boundary->module~modsubgriddata module~modsurfdata modsurfdata proc~boundary->module~modsurfdata module~moddriver->module~modinletdata module~modinlet->module~modinletdata mpi mpi module~modmpi->mpi

Arguments

None

Calls

proc~~boundary~~CallsGraph proc~boundary modboundary::boundary proc~cyclichi modboundary::cyclichi proc~boundary->proc~cyclichi proc~cyclichj modboundary::cyclichj proc~boundary->proc~cyclichj proc~cyclicmi modboundary::cyclicmi proc~boundary->proc~cyclicmi proc~cyclicmj modboundary::cyclicmj proc~boundary->proc~cyclicmj proc~cyclicqi modboundary::cyclicqi proc~boundary->proc~cyclicqi proc~cyclicqj modboundary::cyclicqj proc~boundary->proc~cyclicqj proc~cyclicsi modboundary::cyclicsi proc~boundary->proc~cyclicsi proc~cyclicsj modboundary::cyclicsj proc~boundary->proc~cyclicsj proc~drivergen moddriver::drivergen proc~boundary->proc~drivergen proc~fluxtop modboundary::fluxtop proc~boundary->proc~fluxtop proc~fluxtopscal modboundary::fluxtopscal proc~boundary->proc~fluxtopscal proc~inletgen modinlet::inletgen proc~boundary->proc~inletgen proc~inletgennotemp modinlet::inletgennotemp proc~boundary->proc~inletgennotemp proc~inlettop modboundary::inlettop proc~boundary->proc~inlettop proc~iohi modboundary::iohi proc~boundary->proc~iohi proc~iolet modboundary::iolet proc~boundary->proc~iolet proc~ioqi modboundary::ioqi proc~boundary->proc~ioqi proc~iosi modboundary::iosi proc~boundary->proc~iosi proc~scalrec modboundary::scalrec proc~boundary->proc~scalrec proc~scalsirane modboundary::scalSIRANE proc~boundary->proc~scalsirane proc~valuetop modboundary::valuetop proc~boundary->proc~valuetop proc~valuetopscal modboundary::valuetopscal proc~boundary->proc~valuetopscal proc~excjs modmpi::excjs proc~cyclichj->proc~excjs proc~cyclicmj->proc~excjs proc~cyclicqj->proc~excjs proc~cyclicsj->proc~excjs proc~writedriverfile moddriver::writedriverfile proc~drivergen->proc~writedriverfile proc~blthicknesst modinlet::blthicknesst proc~inletgen->proc~blthicknesst proc~dispthicknessexp modinlet::dispthicknessexp proc~inletgen->proc~dispthicknessexp proc~enthalpythickness modinlet::enthalpythickness proc~inletgen->proc~enthalpythickness proc~momentumthicknessexp modinlet::momentumthicknessexp proc~inletgen->proc~momentumthicknessexp proc~readinletfile modinlet::readinletfile proc~inletgen->proc~readinletfile proc~slabsum modmpi::slabsum proc~inletgen->proc~slabsum proc~wallawinlet modinlet::wallawinlet proc~inletgen->proc~wallawinlet proc~writeinletfile modinlet::writeinletfile proc~inletgen->proc~writeinletfile proc~writerestartfiles modsave::writerestartfiles proc~inletgen->proc~writerestartfiles proc~inletgennotemp->proc~blthicknesst proc~inletgennotemp->proc~dispthicknessexp proc~inletgennotemp->proc~momentumthicknessexp proc~inletgennotemp->proc~readinletfile proc~inletgennotemp->proc~slabsum proc~inletgennotemp->proc~wallawinlet proc~inletgennotemp->proc~writeinletfile proc~inletgennotemp->proc~writerestartfiles proc~slabsumi modmpi::slabsumi proc~inlettop->proc~slabsumi proc~iolet->proc~slabsum mpi_sendrecv mpi_sendrecv proc~excjs->mpi_sendrecv proc~readinletfile->proc~excjs proc~yinterpolate modinlet::yinterpolate proc~readinletfile->proc~yinterpolate proc~zinterpolate modinlet::zinterpolate proc~readinletfile->proc~zinterpolate proc~zinterpolatet modinlet::zinterpolatet proc~readinletfile->proc~zinterpolatet proc~zinterpolatew modinlet::zinterpolatew proc~readinletfile->proc~zinterpolatew mpi_allreduce mpi_allreduce proc~slabsum->mpi_allreduce proc~slabsumi->mpi_allreduce

Called by

proc~~boundary~~CalledByGraph proc~boundary modboundary::boundary proc~readinitfiles modstartup::readinitfiles proc~readinitfiles->proc~boundary program~dalesurban DALESURBAN program~dalesurban->proc~boundary proc~startup modstartup::startup program~dalesurban->proc~startup proc~startup->proc~readinitfiles

Contents

Source Code


Source Code

   subroutine boundary

      use modglobal, only:ib, ie, ih, jb, je, jgb, jge, jh, kb, ke, kh, linoutflow, dzf, zh, dy, &
         timee, ltempeq, lmoist, BCxm, BCym, BCxT, BCyT, BCxq, BCyq, BCxs, BCys, BCtopm, BCtopT,&
         BCtopq, BCtops, e12min, idriver, luvolflowr, luoutflowr
      use modfields, only:u0, v0, w0, um, vm, wm, thl0, thlm, qt0, qtm, uout, uouttot, e120, e12m,&
                          u0av
      use modsubgriddata, only:ekh, ekm
      use modsurfdata, only:thl_top, qt_top, sv_top, wttop, wqtop, wsvtop
      use modmpi, only:myid, slabsum
      use modinlet, only:inletgen, inletgennotemp
      use moddriver, only : drivergen
      use modinletdata, only:irecy, ubulk, iangle
!    use modsurface, only : getobl
      implicit none
      real, dimension(kb:ke) :: uaverage
      integer i, k

     ! if not using massflowrate need to set outflow velocity
     if (luoutflowr) then
        ! do nothing - calculated in modforces
     elseif (.not. luvolflowr) then
        !ubulk = sum(u0av)/(ke-kb+1)
        do k = kb, ke
           uaverage(k) = u0av(k)*dzf(k)                                                        
        end do
        ! need a method to know if we have all blocks at lowest cell kb
        ! assuming this for now (hence kb+1)
        uouttot = sum(uaverage(kb:ke))/(zh(ke + 1) - zh(kb+1)) 
     else
        uouttot = ubulk
     end if

     !BCxm!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
     !periodic or inflow/outflow conditions for momentum
      if (BCxm .eq. 1) then  !periodic
         call cyclicmi

         if (idriver == 1) then ! write driver files
           call drivergen
         end if

      else if (BCxm .eq. 2) then !previously iinletgen 1
         uouttot = cos(iangle)*ubulk
         if (ltempeq) then
            call inletgen
         else
            call inletgennotemp
         end if

         ! iolet - called due to BCtopm = 3

      else if (BCxm .eq. 3) then ! previously iinletgen 2
         uouttot = cos(iangle)*ubulk
         if (ltempeq) then
            call inletgen
         else
            call inletgennotemp
         end if

         ! iolet - called due to BCtopm = 3

      else if (BCxm .eq. 4) then !previously (inoutflow without iinlet)
         uouttot = cos(iangle)*ubulk
         if (ltempeq) then
            call inletgen
         else
            call inletgennotemp
         end if

         ! iolet - called due to BCtopm = 3

      else if (BCxm .eq. 5) then ! driver from drivergen (idriver == 2)

         uouttot = ubulk ! does this hold for all forcings of precursor simulations? tg3315

         call drivergen

         ! iolet - called due to BCtopm = 3

      else
         write(0, *) "ERROR: lateral boundary type for veloctiy in x-direciton undefined"
         stop 1
      end if

      !BCym!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
      !currently BC in y is always periodic for momentum
      if (BCym .eq. 1) then
         call cyclicmj
      else
         write(0, *) "ERROR: lateral boundary type for velocity in y-direction undefined"
         stop 1
      end if

      !BCxT!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
      if (BCxT .eq. 1) then
         call cyclichi

      else if (BCxT .eq. 2) then !inoutflow - will be overwritten unless BCxm == 1
         call iohi    ! make sure uouttot is known and realistic
      else if (BCxT .eq. 3) then
         !do nothing, temperature is considered in iolet
      else
         write(0, *) "ERROR: lateral boundary type for temperature in x-direction undefined"
         stop 1
      end if

      !BCyT!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
      if (BCyT .eq. 1) then
         call cyclichj
      else
         write(0, *) "ERROR: lateral boundary type for temperature in y-direction undefined"
         stop 1
      end if

      !BCxq!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
      if (BCxq .eq. 1) then
         call cyclicqi
      else if (BCxq .eq. 2) then !inoutflow  - will be overwritten unless BCxm == 1
        call ioqi ! tg3315 - make sure uouttot is known and realistic
      elseif (BCxq .eq. 3) then 
        !do nothing, temperature is considered in iolet
      else
         write(0, *) "ERROR: lateral boundary type for humidity in x-direction undefined"
         stop 1
      end if

      !BCyq!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
      if (BCyq .eq. 1) then
         call cyclicqj
      else
         write(0, *) "ERROR: lateral boundary type for humidity in y-direction undefined"
         stop 1
      end if

      !BCys!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
      if (BCys .eq. 1) then
         call cyclicsj
      elseif (BCys .eq. 5) then
         ! done in scalSIRANE
      else
         write(0, *) "ERROR: lateral boundary type for scalars in y-direction undefined"
         stop 1
      end if

      !BCxs!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
      if (BCxs .eq. 1) then
         call cyclicsi
      else if (BCxs .eq. 2) then !inoutflow  - will be overwritten unless BCxm == 1
         call iosi ! make sure uouttot is known and correct for the running set-up
      else if (BCxs .eq. 3) then
         ! do nothing - considered in iolet

      else if (BCxs .eq. 4) then !scalrec - will be overwritten unless BCxm == 1
         call scalrec

      else if (BCxs .eq. 5) then !previously SIRANE - will be overwritten unless BCxm == 1
         call scalSIRANE !  make sure uouttot/ vouttot is known and realistic

      else
         write(0, *) "ERROR: lateral boundary type for scalars in x-direction undefined"
         stop 1
      end if

      !BCtopm!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
      if (BCtopm .eq. 1) then
         !free-slip = zero-flux
         call fluxtop(um, ekm, 0.0)
         call fluxtop(u0, ekm, 0.0)
         call fluxtop(vm, ekm, 0.0)
         call fluxtop(v0, ekm, 0.0)
         e120(:, :, ke + 1) = e12min ! free slip top wall
         e12m(:, :, ke + 1) = e12min
         w0(:, :, ke + 1) = 0.0
         wm(:, :, ke + 1) = 0.0
      else if (BCtopm .eq. 2) then
         !no-slip = zero velocity at wall
         call valuetop(um, 0.0)
         call valuetop(u0, 0.0)
         call valuetop(vm, 0.0)
         call valuetop(v0, 0.0)
         w0(:, :, ke + 1) = 0.0
         wm(:, :, ke + 1) = 0.0
      else if (BCtopm .eq. 3) then
         call fluxtop(um, ekm, 0.0)
         call fluxtop(u0, ekm, 0.0)
         call fluxtop(vm, ekm, 0.0)
         call fluxtop(v0, ekm, 0.0)
         e120(:, :, ke + 1) = e12min ! free slip top wall
         e12m(:, :, ke + 1) = e12min
         if (idriver==2) then ! does not use ddispdx, Uinf etc.
           w0(:, :, ke + 1) = 0.0
           wm(:, :, ke + 1) = 0.0
         else
           call inlettop ! for iinletgen...
         end if
         call iolet  !ils13, 13.8.18: iolet also deals with lateral boundaries!!
      else
         write(0, *) "ERROR: top boundary type for velocity undefined"
         stop 1
      end if

      !BCtopT!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
      if (BCtopT .eq. 1) then
         call fluxtop(thlm, ekh, wttop)
         call fluxtop(thl0, ekh, wttop)
      else if (BCtopT .eq. 2) then
         call valuetop(thlm, thl_top)
         call valuetop(thl0, thl_top)
      else
         write(0, *) "ERROR: top boundary type for temperature undefined"
         stop 1
      end if

      !BCtopq!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
      if (BCtopq .eq. 1) then
         call fluxtop(qtm, ekh, wqtop)
         call fluxtop(qt0, ekh, wqtop)
      else if (BCtopq .eq. 2) then
         call valuetop(qtm, qt_top)
         call valuetop(qt0, qt_top)
      else
         write(0, *) "ERROR: top boundary type for humidity undefined"
         stop 1
      end if

      !BCtops!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
      if (BCtops .eq. 1) then
         call fluxtopscal(wsvtop)
         call fluxtopscal(wsvtop)
      else if (BCtops .eq. 2) then
         call valuetopscal(sv_top)
         call valuetopscal(sv_top)
      else
         write(0, *) "ERROR: top boundary type for scalars undefined"
         stop 1
      end if

   end subroutine boundary