trans_release.F90 Source File


This file depends on

sourcefile~~trans_release.f90~2~~EfferentGraph sourcefile~trans_release.f90~2 trans_release.F90 sourcefile~dealloc_resol_mod.f90 dealloc_resol_mod.F90 sourcefile~trans_release.f90~2->sourcefile~dealloc_resol_mod.f90 sourcefile~seefmm_mix.f90 seefmm_mix.F90 sourcefile~dealloc_resol_mod.f90->sourcefile~seefmm_mix.f90 sourcefile~set_resol_mod.f90 set_resol_mod.F90 sourcefile~dealloc_resol_mod.f90->sourcefile~set_resol_mod.f90 sourcefile~tpm_ctl.f90 tpm_ctl.F90 sourcefile~dealloc_resol_mod.f90->sourcefile~tpm_ctl.f90 sourcefile~tpm_dim.f90 tpm_dim.F90 sourcefile~dealloc_resol_mod.f90->sourcefile~tpm_dim.f90 sourcefile~tpm_distr.f90 tpm_distr.F90 sourcefile~dealloc_resol_mod.f90->sourcefile~tpm_distr.f90 sourcefile~tpm_fft.f90 tpm_fft.F90 sourcefile~dealloc_resol_mod.f90->sourcefile~tpm_fft.f90 sourcefile~tpm_fields.f90 tpm_fields.F90 sourcefile~dealloc_resol_mod.f90->sourcefile~tpm_fields.f90 sourcefile~tpm_flt.f90 tpm_flt.F90 sourcefile~dealloc_resol_mod.f90->sourcefile~tpm_flt.f90 sourcefile~tpm_gen.f90 tpm_gen.F90 sourcefile~dealloc_resol_mod.f90->sourcefile~tpm_gen.f90 sourcefile~tpm_geometry.f90 tpm_geometry.F90 sourcefile~dealloc_resol_mod.f90->sourcefile~tpm_geometry.f90 sourcefile~tpm_hicfft.f90 tpm_hicfft.F90 sourcefile~dealloc_resol_mod.f90->sourcefile~tpm_hicfft.f90 sourcefile~parkind_ectrans.f90 parkind_ectrans.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~set_resol_mod.f90->sourcefile~tpm_ctl.f90 sourcefile~set_resol_mod.f90->sourcefile~tpm_dim.f90 sourcefile~set_resol_mod.f90->sourcefile~tpm_distr.f90 sourcefile~set_resol_mod.f90->sourcefile~tpm_fft.f90 sourcefile~set_resol_mod.f90->sourcefile~tpm_fields.f90 sourcefile~set_resol_mod.f90->sourcefile~tpm_flt.f90 sourcefile~set_resol_mod.f90->sourcefile~tpm_gen.f90 sourcefile~set_resol_mod.f90->sourcefile~tpm_geometry.f90 sourcefile~set_resol_mod.f90->sourcefile~tpm_hicfft.f90 sourcefile~abort_trans_mod.f90 abort_trans_mod.F90 sourcefile~set_resol_mod.f90->sourcefile~abort_trans_mod.f90 sourcefile~sharedmem_mod.f90 sharedmem_mod.F90 sourcefile~tpm_ctl.f90->sourcefile~sharedmem_mod.f90 sourcefile~tpm_fft.f90->sourcefile~parkind_ectrans.f90 sourcefile~tpm_fields.f90->sourcefile~parkind_ectrans.f90 sourcefile~tpm_flt.f90->sourcefile~seefmm_mix.f90 sourcefile~tpm_flt.f90->sourcefile~parkind_ectrans.f90 sourcefile~tpm_gen.f90->sourcefile~parkind_ectrans.f90 sourcefile~tpm_geometry.f90->sourcefile~parkind_ectrans.f90 sourcefile~growing_allocator_mod.f90 growing_allocator_mod.F90 sourcefile~tpm_hicfft.f90->sourcefile~growing_allocator_mod.f90 sourcefile~tpm_hicfft.f90->sourcefile~parkind_ectrans.f90 sourcefile~abort_trans_mod.f90->sourcefile~tpm_distr.f90 sourcefile~abort_trans_mod.f90->sourcefile~tpm_gen.f90 sourcefile~wts500_mod.f90->sourcefile~parkind_ectrans.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.
!

SUBROUTINE TRANS_RELEASE(KRESOL)

!**** *TRANS_RELEASE* - release a spectral resolution

!     Purpose.
!     --------
!      Release all arrays related to a given resolution tag

!**   Interface.
!     ----------
!     CALL TRANS_RELEASE

!     Explicit arguments : KRESOL : resolution tag
!     --------------------

!     Method.
!     -------

!     Externals.  None
!     ----------

!     Author.
!     -------
!        R. El Khatib *METEO-FRANCE*

!     Modifications.
!     --------------
!        Original : 09-Jul-2013

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

USE PARKIND1  ,ONLY : JPIM

!ifndef INTERFACE

USE DEALLOC_RESOL_MOD   ,ONLY : DEALLOC_RESOL
!

IMPLICIT NONE

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

!endif INTERFACE

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

CALL DEALLOC_RESOL(KRESOL)

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

END SUBROUTINE TRANS_RELEASE