initinlet Subroutine

public subroutine initinlet()

Uses

  • proc~~initinlet~~UsesGraph proc~initinlet modinlet::initinlet module~modfields modfields proc~initinlet->module~modfields module~modglobal modglobal proc~initinlet->module~modglobal module~modmpi modmpi proc~initinlet->module~modmpi mpi mpi module~modmpi->mpi

Arguments

None

Calls

proc~~initinlet~~CallsGraph proc~initinlet modinlet::initinlet proc~readzincoord modinlet::readzincoord proc~initinlet->proc~readzincoord mpi_bcast mpi_bcast proc~readzincoord->mpi_bcast

Called by

proc~~initinlet~~CalledByGraph proc~initinlet modinlet::initinlet proc~startup modstartup::startup proc~startup->proc~initinlet program~dalesurban DALESURBAN program~dalesurban->proc~startup

Contents

Source Code


Source Code

  subroutine initinlet
    use modglobal, only : ih,ib,ie,jh,jb,je,kb,ke,kh,iinletgen,iplane,xf,lstoreplane,nstore,Uinf,ltempeq,pi,zf,zh
    use modfields, only : um
    use modmpi, only : myid,nprocs
   
    implicit none
    real    :: pfi, epsi
    integer :: k


  if (iinletgen==1) then

  allocate(Utav(ib:ie,kb:ke))
  allocate(Uinl(kb:ke))
  allocate(Winl(kb:ke+1))
  allocate(Urec(kb:ke))
  allocate(Wrec(kb:ke+1))
  allocate(u0inletbc(jb:je,kb:ke))
  allocate(v0inletbc(jb:je,kb:ke))
  allocate(w0inletbc(jb:je,kb:ke+1))
  allocate(u0inletbcold(jb:je,kb:ke))
  allocate(v0inletbcold(jb:je,kb:ke))
  allocate(w0inletbcold(jb:je,kb:ke+1))
  allocate(uminletbc(jb:je,kb:ke))
  allocate(vminletbc(jb:je,kb:ke))
  allocate(wminletbc(jb:je,kb:ke+1))
  allocate(uaver(ib:ie,kb:ke))
  allocate(zirf(kb:ke))
  allocate(ziif(kb:ke))
  allocate(zirh(kb:ke+1))
  allocate(ziih(kb:ke+1))
  allocate(zorf(kb:ke))
  allocate(zoif(kb:ke))
  allocate(zorh(kb:ke+1))
  allocate(zoih(kb:ke+1))
  allocate(loclowif(kb:ke))
  allocate(locupif(kb:ke))
  allocate(loclowih(kb:ke+1))
  allocate(locupih(kb:ke+1))
  allocate(loclowof(kb:ke))
  allocate(locupof(kb:ke))
  allocate(loclowoh(kb:ke+1))
  allocate(locupoh(kb:ke+1))
  allocate(displ(ib:ie))
  allocate(displold(ib:ie))
  allocate(upupavinl(kb:ke))
  allocate(vpvpavinl(kb:ke))
  allocate(wpwpavinl(kb:ke))
  allocate(upwpavinl(kb:ke))
  allocate(thlpthlpavinl(kb:ke))
  allocate(thlpupavinl(kb:ke))
  allocate(thlpwpavinl(kb:ke))
  allocate(heavif(kb:ke))
  allocate(heavih(kb:ke+1))

  if (lstoreplane ) then
    allocate(storeu0inletbc(jb:je,kb:ke,1:nstore))
    allocate(storev0inletbc(jb:je,kb:ke,1:nstore))
    allocate(storew0inletbc(jb:je,kb:ke+1,1:nstore))
  end if 

  epsi = 0.25*di
  do k=kb,ke
    pfi = zf(k) -1.2*di -epsi
    if (pfi < -epsi) then
      heavif(k) = 1.
    elseif(pfi <= epsi) then
      heavif(k) = 0.5* ( 1. - (pfi / epsi) - (1./pi)*sin(pi*pfi/epsi))
    elseif (pfi > epsi) then
      heavif(k) = 0.
    end if  
  end do

  do k=kb,ke+1
    pfi = zh(k) -1.2*di -epsi
    if (pfi < -epsi) then
      heavih(k) = 1.
    elseif(pfi <= epsi) then
      heavih(k) = 0.5* ( 1. - (pfi / epsi) - (1./pi)*sin(pi*pfi/epsi))
    elseif (pfi > epsi) then
      heavih(k) = 0.
    end if
  end do



  if (ltempeq  ) then
    allocate(Ttav(ib:ie,kb:ke))
    allocate(taver(ib:ie,kb:ke))
    allocate(Tinl(kb:ke))
    allocate(Trec(kb:ke))
    allocate(t0inletbc(jb:je,kb:ke))
    allocate(t0inletbcold(jb:je,kb:ke))
    allocate(tminletbc(jb:je,kb:ke))
    allocate(zotr(kb:ke))
    allocate(zoti(kb:ke))
    allocate(loclowot(kb:ke))
    allocate(locupot(kb:ke))
    allocate(heavit(kb:ke))
  
    if (lstoreplane ) then
      allocate(storet0inletbc(jb:je,kb:ke,1:nstore))
    end if
! Heaviside function for temperature
    epsi = 0.25*dti
    do k=kb,ke
      pfi = zf(k) -1.2*dti -epsi
      if (pfi < -epsi) then
        heavit(k) = 1.
      elseif(pfi <= epsi) then
        heavit(k) = 0.5* ( 1. - (pfi / epsi) - (1./pi)*sin(pi*pfi/epsi))
      elseif (pfi > epsi) then
        heavit(k) = 0.
      end if
    end do

 
  end if

  displ=0.
  displold =0.

  irecy = ib+iplane        ! index of recycle plane equals iplane (read from namoptions)


  xfm  = sum(xf(ib:ie))/(ie-ib+1)            ! mean(xf) 
  xf2m = sum(xf(ib:ie)**2.)/(ie-ib+1)        ! mean(xf^2)
!  btime = timee                              ! this is done to make sure btime is set when avint is computed correctly at startup (only for RA) 

  
  else if (iinletgen == 2) then
    allocate(storeu0inletbc(jb:je,kb:ke,1:nstore))
    allocate(storev0inletbc(jb:je,kb:ke,1:nstore))
    allocate(storew0inletbc(jb:je,kb:ke+1,1:nstore))
    allocate(u0rot(1:nstore,jb-jh:je+jh,kb:ke))
    allocate(v0rot(1:nstore,jb-jh:je+jh,kb:ke))
    allocate(u0inletbc(jb:je,kb:ke))
    allocate(v0inletbc(jb:je,kb:ke))
    allocate(w0inletbc(jb:je,kb:ke+1))
    allocate(u0inletbcold(jb:je,kb:ke))
    allocate(v0inletbcold(jb:je,kb:ke))
    allocate(w0inletbcold(jb:je,kb:ke+1))
    allocate(uminletbc(jb:je,kb:ke))
    allocate(vminletbc(jb:je,kb:ke))
    allocate(wminletbc(jb:je,kb:ke+1))
    if (ltempeq ) then
      allocate(storet0inletbc(jb:je,kb:ke,1:nstore))
      allocate(t0inletbc(jb:je,kb:ke))
      allocate(t0inletbcold(jb:je,kb:ke))
      allocate(tminletbc(jb:je,kb:ke))
    end if
    !iangle = iangledeg * pi / 180.  ! convert degrees to radians
    irecy = ib+iplane
  ! read coordinates of inletprofile  
    call readzincoord
!    ddispdx      = 0.00038/Uinf        ! this value should becomputed from the w0 computed in the inletgenerator
    ddispdx      = wtop/Uinf            ! wtop is read from zgrid.inf 
    ddispdxold   = ddispdx              ! this value should becomputed from the w0 computed in the inletgenerator
!    inlfactor    = nprocs/nprocsinl     ! nprocs should be larger or equal to nprocsin!
!    write(6,*) 'inlfactor= ',inlfactor
  else
   return
  end if
 
  end subroutine initinlet