setup_dims_mod.F90 Source File


This file depends on

sourcefile~~setup_dims_mod.f90~~EfferentGraph sourcefile~setup_dims_mod.f90 setup_dims_mod.F90 sourcefile~tpm_dim.f90 tpm_dim.F90 sourcefile~setup_dims_mod.f90->sourcefile~tpm_dim.f90 sourcefile~tpm_flt.f90 tpm_flt.F90 sourcefile~setup_dims_mod.f90->sourcefile~tpm_flt.f90 sourcefile~parkind_ectrans.f90 parkind_ectrans.F90 sourcefile~tpm_flt.f90->sourcefile~parkind_ectrans.f90 sourcefile~seefmm_mix.f90 seefmm_mix.F90 sourcefile~tpm_flt.f90->sourcefile~seefmm_mix.f90 sourcefile~seefmm_mix.f90->sourcefile~parkind_ectrans.f90 sourcefile~wts500_mod.f90 wts500_mod.F90 sourcefile~seefmm_mix.f90->sourcefile~wts500_mod.f90 sourcefile~wts500_mod.f90->sourcefile~parkind_ectrans.f90

Files dependent on this one

sourcefile~~setup_dims_mod.f90~~AfferentGraph sourcefile~setup_dims_mod.f90 setup_dims_mod.F90 sourcefile~setup_trans.f90 setup_trans.F90 sourcefile~setup_trans.f90->sourcefile~setup_dims_mod.f90 sourcefile~setup_trans.f90~2 setup_trans.F90 sourcefile~setup_trans.f90~2->sourcefile~setup_dims_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 SETUP_DIMS_MOD
CONTAINS
SUBROUTINE SETUP_DIMS

USE PARKIND1  ,ONLY : JPIM

USE TPM_DIM   ,ONLY : R
USE TPM_FLT   ,ONLY : S
!

IMPLICIT NONE

INTEGER(KIND=JPIM) :: JM,JN,ISPOLEG

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

ISPOLEG = 0
DO JM=0,R%NSMAX
  DO JN=JM,R%NTMAX+1
    ISPOLEG = ISPOLEG+1
  ENDDO
ENDDO
R%NSPOLEG = ISPOLEG

R%NSPEC_G = (R%NSMAX+1)*(R%NSMAX+2)/2
R%NSPEC2_G = R%NSPEC_G*2

R%NDGNH = (R%NDGL+1)/2

R%NLEI1 = R%NSMAX+4+MOD(R%NSMAX+4+1,2)
R%NLEI3 = R%NDGNH+MOD(R%NDGNH+2,2)
IF (S%LSOUTHPNM) R%NLEI3=2*R%NLEI3 

R%NLED3 = R%NTMAX+2+MOD(R%NTMAX+3,2)
R%NLED4 = R%NTMAX+3+MOD(R%NTMAX+4,2)

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

END SUBROUTINE SETUP_DIMS
END MODULE SETUP_DIMS_MOD