prepsnm_mod.F90 Source File


This file depends on

sourcefile~~prepsnm_mod.f90~~EfferentGraph sourcefile~prepsnm_mod.f90 prepsnm_mod.F90 sourcefile~parkind_ectrans.f90 parkind_ectrans.F90 sourcefile~prepsnm_mod.f90->sourcefile~parkind_ectrans.f90 sourcefile~tpm_dim.f90 tpm_dim.F90 sourcefile~prepsnm_mod.f90->sourcefile~tpm_dim.f90 sourcefile~tpm_distr.f90 tpm_distr.F90 sourcefile~prepsnm_mod.f90->sourcefile~tpm_distr.f90 sourcefile~tpm_fields.f90 tpm_fields.F90 sourcefile~prepsnm_mod.f90->sourcefile~tpm_fields.f90 sourcefile~tpm_gen.f90 tpm_gen.F90 sourcefile~prepsnm_mod.f90->sourcefile~tpm_gen.f90 sourcefile~tpm_fields.f90->sourcefile~parkind_ectrans.f90 sourcefile~tpm_gen.f90->sourcefile~parkind_ectrans.f90

Files dependent on this one

sourcefile~~prepsnm_mod.f90~~AfferentGraph sourcefile~prepsnm_mod.f90 prepsnm_mod.F90 sourcefile~ltdir_mod.f90 ltdir_mod.F90 sourcefile~ltdir_mod.f90->sourcefile~prepsnm_mod.f90 sourcefile~ltdir_mod.f90~2 ltdir_mod.F90 sourcefile~ltdir_mod.f90~2->sourcefile~prepsnm_mod.f90 sourcefile~ltdirad_mod.f90 ltdirad_mod.F90 sourcefile~ltdirad_mod.f90->sourcefile~prepsnm_mod.f90 sourcefile~ltinv_mod.f90~2 ltinv_mod.F90 sourcefile~ltinv_mod.f90~2->sourcefile~prepsnm_mod.f90 sourcefile~ltinvad_mod.f90 ltinvad_mod.F90 sourcefile~ltinvad_mod.f90->sourcefile~prepsnm_mod.f90 sourcefile~setup_trans.f90 setup_trans.F90 sourcefile~setup_trans.f90->sourcefile~prepsnm_mod.f90 sourcefile~suleg_mod.f90 suleg_mod.F90 sourcefile~setup_trans.f90->sourcefile~suleg_mod.f90 sourcefile~suleg_mod.f90->sourcefile~prepsnm_mod.f90 sourcefile~suleg_mod.f90~2 suleg_mod.F90 sourcefile~suleg_mod.f90~2->sourcefile~prepsnm_mod.f90 sourcefile~vd2uv_mod.f90 vd2uv_mod.F90 sourcefile~vd2uv_mod.f90->sourcefile~prepsnm_mod.f90 sourcefile~vd2uv_mod.f90~2 vd2uv_mod.F90 sourcefile~vd2uv_mod.f90~2->sourcefile~prepsnm_mod.f90 sourcefile~dir_trans_ctl_mod.f90 dir_trans_ctl_mod.F90 sourcefile~dir_trans_ctl_mod.f90->sourcefile~ltdir_mod.f90 sourcefile~ltdir_ctl_mod.f90 ltdir_ctl_mod.F90 sourcefile~ltdir_ctl_mod.f90->sourcefile~ltdir_mod.f90 sourcefile~ltdir_ctlad_mod.f90 ltdir_ctlad_mod.F90 sourcefile~ltdir_ctlad_mod.f90->sourcefile~ltdirad_mod.f90 sourcefile~ltinv_ctlad_mod.f90 ltinv_ctlad_mod.F90 sourcefile~ltinv_ctlad_mod.f90->sourcefile~ltinvad_mod.f90 sourcefile~setup_trans.f90~2 setup_trans.F90 sourcefile~setup_trans.f90~2->sourcefile~suleg_mod.f90 sourcefile~vd2uv_ctl_mod.f90 vd2uv_ctl_mod.F90 sourcefile~vd2uv_ctl_mod.f90->sourcefile~vd2uv_mod.f90 sourcefile~vd2uv_ctl_mod.f90~2 vd2uv_ctl_mod.F90 sourcefile~vd2uv_ctl_mod.f90~2->sourcefile~vd2uv_mod.f90 sourcefile~dir_trans.f90 dir_trans.F90 sourcefile~dir_trans.f90->sourcefile~dir_trans_ctl_mod.f90 sourcefile~dir_trans.f90~2 dir_trans.F90 sourcefile~dir_trans.f90~2->sourcefile~dir_trans_ctl_mod.f90 sourcefile~dir_trans_ctl_mod.f90~2 dir_trans_ctl_mod.F90 sourcefile~dir_trans_ctl_mod.f90~2->sourcefile~ltdir_ctl_mod.f90 sourcefile~dir_trans_ctlad_mod.f90 dir_trans_ctlad_mod.F90 sourcefile~dir_trans_ctlad_mod.f90->sourcefile~ltdir_ctlad_mod.f90 sourcefile~inv_trans_ctlad_mod.f90 inv_trans_ctlad_mod.F90 sourcefile~inv_trans_ctlad_mod.f90->sourcefile~ltinv_ctlad_mod.f90 sourcefile~vordiv_to_uv.f90 vordiv_to_uv.F90 sourcefile~vordiv_to_uv.f90->sourcefile~vd2uv_ctl_mod.f90 sourcefile~vordiv_to_uv.f90~2 vordiv_to_uv.F90 sourcefile~vordiv_to_uv.f90~2->sourcefile~vd2uv_ctl_mod.f90 sourcefile~dir_transad.f90~2 dir_transad.F90 sourcefile~dir_transad.f90~2->sourcefile~dir_trans_ctlad_mod.f90 sourcefile~inv_transad.f90~2 inv_transad.F90 sourcefile~inv_transad.f90~2->sourcefile~inv_trans_ctlad_mod.f90

Source Code

! (C) Copyright 2000- ECMWF.
! (C) Copyright 2000- Meteo-France.
! 
! This software is licensed under the terms of the Apache Licence Version 2.0
! which can be obtained at http://www.apache.org/licenses/LICENSE-2.0.
! In applying this licence, ECMWF does not waive the privileges and immunities
! granted to it by virtue of its status as an intergovernmental organisation
! nor does it submit to any jurisdiction.
!

MODULE PREPSNM_MOD
  CONTAINS
  SUBROUTINE PREPSNM
  
  
  !**** *PREPSNM* - Prepare REPSNM for wavenumber KM
  
  !     Purpose.
  !     --------
  !        Copy the REPSNM values for specific zonal wavenumber M
  !        to work array
  
  !**   Interface.
  !     ----------
  !        CALL PREPSNM(...)
  
  !        Explicit arguments :  KM - zonal wavenumber
  !        -------------------   KMLOC - local zonal wavenumber
  !                              PEPSNM - REPSNM for zonal
  !                                      wavenumber KM
  
  !        Implicit arguments :
  !        --------------------
  
  !     Method.
  !     -------
  
  
  !     Reference.
  !     ----------
  
  
  !     Author.
  !     -------
  !        Lars Isaksen *ECMWF*
  
  !     Modifications.
  !     --------------
  !        Original : 00-02-01 From LTINV in IFS CY22R1
  
  !     ------------------------------------------------------------------
 
  USE PARKIND_ECTRANS ,ONLY : JPIM     ,JPRBT
 
  USE TPM_DIM         ,ONLY : R
  USE TPM_FIELDS      ,ONLY : F, ZEPSNM
  USE TPM_DISTR       ,ONLY : D
  USE TPM_GEN         ,ONLY : NOUT
  !
 
  IMPLICIT NONE
  
  INTEGER(KIND=JPIM)  :: KM,KMLOC
  !!REAL(KIND=JPRB),    INTENT(INOUT) :: PEPSNM(:,:)
 
  !     LOCAL INTEGER SCALARS
  INTEGER(KIND=JPIM) :: JN
  INTEGER(KIND=JPIM) :: R_NTMAX
 
 
  !     ------------------------------------------------------------------
 
  !*       1.       COPY REPSNM.
  !                 ------------
 
 
 
 
  !!!$OMP TARGET TEAMS DISTRIBUTE PARALLEL DO
  !!!$ACC parallel loop
  DO KMLOC=1,D%NUMP
     KM = D%MYMS(KMLOC)
 
     IF (KM > 0) THEN
#ifdef ACCGPU
        !$ACC loop
#endif
        DO JN=0,KM-1
           ZEPSNM(KMLOC,JN) = 0.0_JPRBT
        ENDDO
     ENDIF
 
     DO JN=KM,R%NTMAX+2
        ZEPSNM(KMLOC,JN) = F%REPSNM(D%NPMT(KM)+KMLOC-KM+JN)
     ENDDO
     ! end loop over wavenumber
  ENDDO
  !!!!$OMP END TARGET DATA
  !!!!$ACC end data
 
  !     ------------------------------------------------------------------
 
  END SUBROUTINE PREPSNM
 
 END MODULE PREPSNM_MOD