checkinitvalues Subroutine

public subroutine checkinitvalues()

Uses

  • proc~~checkinitvalues~~UsesGraph proc~checkinitvalues modstartup::checkinitvalues module~modglobal modglobal proc~checkinitvalues->module~modglobal module~modmpi modmpi proc~checkinitvalues->module~modmpi module~modsurfdata modsurfdata proc~checkinitvalues->module~modsurfdata mpi mpi module~modmpi->mpi

Arguments

None

Calls

proc~~checkinitvalues~~CallsGraph proc~checkinitvalues modstartup::checkinitvalues mpi_bcast mpi_bcast proc~checkinitvalues->mpi_bcast mpi_finalize mpi_finalize proc~checkinitvalues->mpi_finalize

Called by

proc~~checkinitvalues~~CalledByGraph proc~checkinitvalues modstartup::checkinitvalues proc~startup modstartup::startup proc~startup->proc~checkinitvalues program~dalesurban DALESURBAN program~dalesurban->proc~startup

Contents

Source Code


Source Code

   subroutine checkinitvalues
      !-----------------------------------------------------------------|
      !                                                                 |
      !      Thijs Heus   TU Delft  9/2/2006                            |
      !                                                                 |
      !     purpose.                                                    |
      !     --------                                                    |
      !                                                                 |
      !      checks whether crucial parameters are set correctly        |
      !                                                                 |
      !     interface.                                                  |
      !     ----------                                                  |
      !                                                                 |
      !     *checkinitvalues* is called from *program*.                 |
      !                                                                 |
      !-----------------------------------------------------------------|

      use modsurfdata, only : wtsurf, wqsurf, qts, ps
      use modglobal, only   : imax,kmax,jtot,ysize,xsize,dxf,ib,ie,&
                              dtmax,runtime,startfile,lwarmstart,lstratstart,&
                              BCxm,BCxT,BCxq,BCxs,BCtopm,BCbotm,&
                              iinletgen,linoutflow,ltempeq,iwalltemp,iwallmom,&
                              ipoiss,POISS_FFT,POISS_CYC
      use modmpi, only      : myid, nprocs, mpierr, comm3d, MPI_INTEGER, MPI_LOGICAL
      use modglobal, only   : idriver
      implicit none
      real :: d(1:imax-1)
      logical :: inequi

      if (mod(jtot, nprocs) /= 0) then
         if (myid == 0) then
            write (0, *) 'STOP ERROR IN NUMBER OF PROCESSORS'
            write (0, *) 'nprocs must divide jtot!!! '
            write (0, *) 'nprocs and jtot are: ', nprocs, jtot
         end if
         call MPI_FINALIZE(mpierr)
         stop 1
      end if

      if (ipoiss==POISS_FFT) then
        if(mod(imax,nprocs)/=0)then
          if(myid==0)then
            write(0,*)'STOP ERROR IN NUMBER OF PROCESSORS'
            write(0,*)'nprocs must divide imax!!! '
            write(0,*)'nprocs and imax are: ',nprocs,imax
          end if
          call MPI_FINALIZE(mpierr)
          stop 1
        end if
      end if

      if (mod(kmax, nprocs) /= 0) then
         if (myid == 0) then
            write (0, *) 'STOP ERROR IN NUMBER OF PROCESSORS'
            write (0, *) 'nprocs must divide kmax!!! '
            write (0, *) 'nprocs and kmax are: ', nprocs, kmax
         end if
         call MPI_FINALIZE(mpierr)
         stop 1
      end if

      !Check Namoptions
      if (runtime < 0) then
         write(0, *) 'ERROR: runtime out of range/not set'
         stop 1
      end if
      if (dtmax < 0) then
         write(0, *) 'ERROR: dtmax out of range/not set'
         stop 1
      end if
      if (ps < 0) then
         write(0, *) 'ERROR: psout of range/not set'
         stop 1
      end if
      if (xsize < 0) then
         write(0, *) 'ERROR: xsize out of range/not set'
         stop 1
      end if
      if (ysize < 0) then
         write(0, *) 'ERROR: ysize out of range/not set'
         stop 1
      end if

      if ((lwarmstart) .or. (lstratstart)) then
         if (startfile == '') then 
            write(0, *) 'ERROR: no restartfile set'
            stop 1
         end if
      end if

      ! Switch to ensure that neutral wall function is called when ltempeq=false and if iwalltemp==1 (constant flux and therefore wall temp is not resolved.
      if ((ltempeq .eqv. .false.) .or. (iwalltemp==1)) then
         iwallmom = 3
         BCbotm = 3
      end if

      ! choosing inoutflow in x requires switches to be set
      ! tg3315 - these could be moved to init boundary
      if (BCxm .eq. 2) then
         write (*, *) "inoutflow conditions, setting appropriate switches (1)"
         iinletgen = 1
         BCxT = 3 !temperature is considered in inletgen & iolet
         BCxq = 3 !humidity is considered in iolet
         BCxs = 3 !scalars are considered in iolet
         BCtopm = 3 !velocity at top determined by topm
         linoutflow = .true.
         call MPI_BCAST(iinletgen, 1, MPI_INTEGER, 0, comm3d, mpierr)
         call MPI_BCAST(BCxT, 1, MPI_INTEGER, 0, comm3d, mpierr)
         call MPI_BCAST(BCxq, 1, MPI_INTEGER, 0, comm3d, mpierr)
         call MPI_BCAST(BCxs, 1, MPI_INTEGER, 0, comm3d, mpierr)
         call MPI_BCAST(BCtopm, 1, MPI_INTEGER, 0, comm3d, mpierr)
         call MPI_BCAST(linoutflow, 1, MPI_LOGICAL, 0, comm3d, mpierr)

      else if (BCxm .eq. 3) then
         write (*, *) "inoutflow conditions, setting appropriate switches (2)"

         iinletgen = 2
         ! see modstartup for conditions that apply with inletgenerators
         ! move to modstartup
         BCxT = 3 !temperature is considered in inletgen & iolet
         BCxq = 3 !humidity is considered in iolet
         BCxs = 3 !scalars are considered in iolet
         BCtopm = 3 !velocity at top determined by topm
         linoutflow = .true.
         call MPI_BCAST(iinletgen, 1, MPI_INTEGER, 0, comm3d, mpierr)
         call MPI_BCAST(BCxT, 1, MPI_INTEGER, 0, comm3d, mpierr)
         call MPI_BCAST(BCxq, 1, MPI_INTEGER, 0, comm3d, mpierr)
         call MPI_BCAST(BCxs, 1, MPI_INTEGER, 0, comm3d, mpierr)
         call MPI_BCAST(BCtopm, 1, MPI_INTEGER, 0, comm3d, mpierr)
         call MPI_BCAST(linoutflow, 1, MPI_LOGICAL, 0, comm3d, mpierr)

      else if (BCxm .eq. 4) then
         write (*, *) "inoutflow conditions, setting appropriate switches (0)"

         iinletgen = 0
         ! see modstartup for conditions that apply with inletgenerators
         ! move to modstartup
         BCxT = 3 !temperature is considered in inletgen & iolet
         BCxq = 3 !humidity is considered in iolet
         BCxs = 3 !scalars are considered in iolet
         BCtopm = 3 !velocity at top determined by topm
         linoutflow = .true.
         call MPI_BCAST(iinletgen, 1, MPI_INTEGER, 0, comm3d, mpierr)
         call MPI_BCAST(BCxT, 1, MPI_INTEGER, 0, comm3d, mpierr)
         call MPI_BCAST(BCxq, 1, MPI_INTEGER, 0, comm3d, mpierr)
         call MPI_BCAST(BCxs, 1, MPI_INTEGER, 0, comm3d, mpierr)
         call MPI_BCAST(BCtopm, 1, MPI_INTEGER, 0, comm3d, mpierr)
         call MPI_BCAST(linoutflow, 1, MPI_LOGICAL, 0, comm3d, mpierr)

      else if (BCxm .eq. 5) then

         write (*, *) "inoutflow conditions and idriver, setting appropriate switches (0)"

         iinletgen = 0
         idriver = 2
         BCxT = 3 !temperature is considered in inletgen & iolet
         BCxq = 3 !humidity is considered in iolet
         BCxs = 3 !scalars are considered in iolet
         BCtopm = 3 !velocity at top determined by topm
         linoutflow = .true.
         call MPI_BCAST(iinletgen, 1, MPI_INTEGER, 0, comm3d, mpierr)
         call MPI_BCAST(idriver, 1, MPI_INTEGER, 0, comm3d, mpierr)
         call MPI_BCAST(BCxT, 1, MPI_INTEGER, 0, comm3d, mpierr)
         call MPI_BCAST(BCxq, 1, MPI_INTEGER, 0, comm3d, mpierr)
         call MPI_BCAST(BCxs, 1, MPI_INTEGER, 0, comm3d, mpierr)
         call MPI_BCAST(BCtopm, 1, MPI_INTEGER, 0, comm3d, mpierr)
         call MPI_BCAST(linoutflow, 1, MPI_LOGICAL, 0, comm3d, mpierr)

      end if

      ! check the Poisson solver setting w.r.t. x-grid
      d(1:imax-1) = dxf(ib+1:ie) - dxf(ib:ie-1)
      inequi = any(abs(d)>dxf(ib)*1e-5)

      if ((.not. inequi) .and. (ipoiss == POISS_CYC) .and. (.not. linoutflow)) then
         write(*, *) "WARNING: consider using FFT poisson solver for better performance!"
      end if

      if ((ipoiss == POISS_FFT) .and. (inequi)) then
         write(*, *) "ERROR: POISS_FFT requires equidistant grid. Aborting..."
         call MPI_FINALIZE(mpierr)
         stop 1
      end if

   end subroutine checkinitvalues