eset_resol_mod.F90 Source File


This file depends on

sourcefile~~eset_resol_mod.f90~~EfferentGraph sourcefile~eset_resol_mod.f90 eset_resol_mod.F90 sourcefile~abort_trans_mod.f90 abort_trans_mod.F90 sourcefile~eset_resol_mod.f90->sourcefile~abort_trans_mod.f90 sourcefile~tpm_dim.f90 tpm_dim.F90 sourcefile~eset_resol_mod.f90->sourcefile~tpm_dim.f90 sourcefile~tpm_distr.f90 tpm_distr.F90 sourcefile~eset_resol_mod.f90->sourcefile~tpm_distr.f90 sourcefile~tpm_fftw.f90 tpm_fftw.F90 sourcefile~eset_resol_mod.f90->sourcefile~tpm_fftw.f90 sourcefile~tpm_fields.f90 tpm_fields.F90 sourcefile~eset_resol_mod.f90->sourcefile~tpm_fields.f90 sourcefile~tpm_gen.f90 tpm_gen.F90 sourcefile~eset_resol_mod.f90->sourcefile~tpm_gen.f90 sourcefile~tpm_geometry.f90 tpm_geometry.F90 sourcefile~eset_resol_mod.f90->sourcefile~tpm_geometry.f90 sourcefile~tpmald_dim.f90 tpmald_dim.F90 sourcefile~eset_resol_mod.f90->sourcefile~tpmald_dim.f90 sourcefile~tpmald_distr.f90 tpmald_distr.F90 sourcefile~eset_resol_mod.f90->sourcefile~tpmald_distr.f90 sourcefile~tpmald_fields.f90 tpmald_fields.F90 sourcefile~eset_resol_mod.f90->sourcefile~tpmald_fields.f90 sourcefile~tpmald_geo.f90 tpmald_geo.F90 sourcefile~eset_resol_mod.f90->sourcefile~tpmald_geo.f90 sourcefile~abort_trans_mod.f90->sourcefile~tpm_gen.f90

Files dependent on this one

sourcefile~~eset_resol_mod.f90~~AfferentGraph sourcefile~eset_resol_mod.f90 eset_resol_mod.F90 sourcefile~edealloc_resol_mod.f90 edealloc_resol_mod.F90 sourcefile~edealloc_resol_mod.f90->sourcefile~eset_resol_mod.f90 sourcefile~edir_trans.f90 edir_trans.F90 sourcefile~edir_trans.f90->sourcefile~eset_resol_mod.f90 sourcefile~edir_transad.f90 edir_transad.F90 sourcefile~edir_transad.f90->sourcefile~eset_resol_mod.f90 sourcefile~edist_grid.f90 edist_grid.F90 sourcefile~edist_grid.f90->sourcefile~eset_resol_mod.f90 sourcefile~edist_spec.f90 edist_spec.F90 sourcefile~edist_spec.f90->sourcefile~eset_resol_mod.f90 sourcefile~egath_grid.f90 egath_grid.F90 sourcefile~egath_grid.f90->sourcefile~eset_resol_mod.f90 sourcefile~egath_spec.f90 egath_spec.F90 sourcefile~egath_spec.f90->sourcefile~eset_resol_mod.f90 sourcefile~egpnorm_trans.f90 egpnorm_trans.F90 sourcefile~egpnorm_trans.f90->sourcefile~eset_resol_mod.f90 sourcefile~einv_trans.f90 einv_trans.F90 sourcefile~einv_trans.f90->sourcefile~eset_resol_mod.f90 sourcefile~einv_transad.f90 einv_transad.F90 sourcefile~einv_transad.f90->sourcefile~eset_resol_mod.f90 sourcefile~esetup_trans.f90 esetup_trans.F90 sourcefile~esetup_trans.f90->sourcefile~eset_resol_mod.f90 sourcefile~especnorm.f90 especnorm.F90 sourcefile~especnorm.f90->sourcefile~eset_resol_mod.f90 sourcefile~etrans_end.f90 etrans_end.F90 sourcefile~etrans_end.f90->sourcefile~eset_resol_mod.f90 sourcefile~etrans_end.f90->sourcefile~edealloc_resol_mod.f90 sourcefile~etrans_inq.f90 etrans_inq.F90 sourcefile~etrans_inq.f90->sourcefile~eset_resol_mod.f90 sourcefile~etrans_release.f90 etrans_release.F90 sourcefile~etrans_release.f90->sourcefile~edealloc_resol_mod.f90

Source Code

! (C) Copyright 2001- ECMWF.
! (C) Copyright 2001- 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 ESET_RESOL_MOD
CONTAINS
SUBROUTINE ESET_RESOL(KRESOL)
USE PARKIND1  ,ONLY : JPIM     ,JPRB
USE YOMHOOK   ,ONLY : LHOOK,   DR_HOOK, JPHOOK

USE TPM_GEN         ,ONLY : NOUT, MSETUP0, NCUR_RESOL, NMAX_RESOL
USE TPM_DIM         ,ONLY : R, DIM_RESOL
!USE TPM_TRANS
USE TPM_DISTR       ,ONLY : D, DISTR_RESOL
USE TPM_GEOMETRY    ,ONLY : G, GEOM_RESOL
USE TPM_FIELDS      ,ONLY : F, FIELDS_RESOL
#ifdef WITH_FFT992
USE TPM_FFT         ,ONLY : T, FFT_RESOL
#endif
USE TPM_FFTW        ,ONLY : TW, FFTW_RESOL

USE ABORT_TRANS_MOD ,ONLY : ABORT_TRANS

USE TPMALD_DIM      ,ONLY : RALD, ALDDIM_RESOL
USE TPMALD_DISTR    ,ONLY : DALD, ALDDISTR_RESOL
#ifdef WITH_FFT992
USE TPMALD_FFT      ,ONLY : TALD, ALDFFT_RESOL
#endif
USE TPMALD_FIELDS   ,ONLY : FALD, ALDFIELDS_RESOL
USE TPMALD_GEO      ,ONLY : GALD, ALDGEO_RESOL
!

IMPLICIT NONE

! Declaration of arguments

INTEGER(KIND=JPIM) ,OPTIONAL, INTENT(IN) :: KRESOL

! Local varaibles
INTEGER(KIND=JPIM) :: IRESOL
REAL(KIND=JPHOOK) :: ZHOOK_HANDLE

!     ------------------------------------------------------------------

IF (LHOOK) CALL DR_HOOK('ESET_RESOL_MOD:ESET_RESOL',0,ZHOOK_HANDLE)
IF(MSETUP0 == 0) CALL ABORT_TRANS('ESET_RESOL:TRANS NOT SETUP')
IRESOL = 1
IF(PRESENT(KRESOL)) THEN
  IRESOL = KRESOL
 IF(KRESOL < 1 .OR. KRESOL > NMAX_RESOL) THEN
    WRITE(NOUT,*)'ESET_RESOL: UNKNOWN RESOLUTION ',KRESOL,NMAX_RESOL
    CALL ABORT_TRANS('ESET_RESOL:KRESOL < 1 .OR. KRESOL > NMAX_RESOL')
 ENDIF
ENDIF
IF(IRESOL /= NCUR_RESOL) THEN
  NCUR_RESOL = IRESOL
  R => DIM_RESOL(NCUR_RESOL)
  F => FIELDS_RESOL(NCUR_RESOL)
  G => GEOM_RESOL(NCUR_RESOL)
  D => DISTR_RESOL(NCUR_RESOL)
#ifdef WITH_FFT992
  T => FFT_RESOL(NCUR_RESOL)
#endif
  TW => FFTW_RESOL(NCUR_RESOL)

  RALD => ALDDIM_RESOL(NCUR_RESOL)
  DALD => ALDDISTR_RESOL(NCUR_RESOL)
#ifdef WITH_FFT992
  TALD => ALDFFT_RESOL(NCUR_RESOL)
#endif
  FALD => ALDFIELDS_RESOL(NCUR_RESOL)
  GALD => ALDGEO_RESOL(NCUR_RESOL)

ENDIF
IF (LHOOK) CALL DR_HOOK('ESET_RESOL_MOD:ESET_RESOL',1,ZHOOK_HANDLE)

END SUBROUTINE ESET_RESOL
END MODULE ESET_RESOL_MOD