ftdir_mod.F90 Source File


This file depends on

sourcefile~~ftdir_mod.f90~~EfferentGraph sourcefile~ftdir_mod.f90 ftdir_mod.F90 sourcefile~buffered_allocator_mod.f90 buffered_allocator_mod.F90 sourcefile~ftdir_mod.f90->sourcefile~buffered_allocator_mod.f90 sourcefile~parkind_ectrans.f90 parkind_ectrans.F90 sourcefile~ftdir_mod.f90->sourcefile~parkind_ectrans.f90 sourcefile~tpm_distr.f90 tpm_distr.F90 sourcefile~ftdir_mod.f90->sourcefile~tpm_distr.f90 sourcefile~tpm_gen.f90 tpm_gen.F90 sourcefile~ftdir_mod.f90->sourcefile~tpm_gen.f90 sourcefile~tpm_geometry.f90 tpm_geometry.F90 sourcefile~ftdir_mod.f90->sourcefile~tpm_geometry.f90 sourcefile~tpm_hicfft.f90 tpm_hicfft.F90 sourcefile~ftdir_mod.f90->sourcefile~tpm_hicfft.f90 sourcefile~tpm_stats.f90 tpm_stats.F90 sourcefile~ftdir_mod.f90->sourcefile~tpm_stats.f90 sourcefile~buffered_allocator_mod.f90->sourcefile~parkind_ectrans.f90 sourcefile~abort_trans_mod.f90 abort_trans_mod.F90 sourcefile~buffered_allocator_mod.f90->sourcefile~abort_trans_mod.f90 sourcefile~growing_allocator_mod.f90 growing_allocator_mod.F90 sourcefile~buffered_allocator_mod.f90->sourcefile~growing_allocator_mod.f90 sourcefile~tpm_gen.f90->sourcefile~parkind_ectrans.f90 sourcefile~tpm_geometry.f90->sourcefile~parkind_ectrans.f90 sourcefile~tpm_hicfft.f90->sourcefile~parkind_ectrans.f90 sourcefile~tpm_hicfft.f90->sourcefile~growing_allocator_mod.f90 sourcefile~tpm_stats.f90->sourcefile~parkind_ectrans.f90 sourcefile~abort_trans_mod.f90->sourcefile~tpm_distr.f90 sourcefile~abort_trans_mod.f90->sourcefile~tpm_gen.f90

Files dependent on this one

sourcefile~~ftdir_mod.f90~~AfferentGraph sourcefile~ftdir_mod.f90 ftdir_mod.F90 sourcefile~dir_trans_ctl_mod.f90 dir_trans_ctl_mod.F90 sourcefile~dir_trans_ctl_mod.f90->sourcefile~ftdir_mod.f90 sourcefile~ftdir_ctl_mod.f90 ftdir_ctl_mod.F90 sourcefile~ftdir_ctl_mod.f90->sourcefile~ftdir_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~ftdir_ctl_mod.f90

Source Code

! (C) Copyright 2000- ECMWF.
! (C) Copyright 2000- Meteo-France.
! (C) Copyright 2022- NVIDIA.
!
! 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 FTDIR_MOD
  USE BUFFERED_ALLOCATOR_MOD
  IMPLICIT NONE

  PRIVATE
  PUBLIC :: FTDIR, FTDIR_HANDLE, PREPARE_FTDIR

  TYPE FTDIR_HANDLE
  END TYPE
CONTAINS

  FUNCTION PREPARE_FTDIR() RESULT(HFTDIR)
    IMPLICIT NONE
    TYPE(FTDIR_HANDLE) :: HFTDIR
  END FUNCTION

  SUBROUTINE FTDIR(ALLOCATOR,HFTDIR,PREEL_REAL,PREEL_COMPLEX,KFIELD)
    !**** *FTDIR - Direct Fourier transform

    !     Purpose. Routine for Grid-point to Fourier transform
    !     --------

    !**   Interface.
    !     ----------
    !        CALL FTDIR(..)

    !        Explicit arguments :  PREEL   - Fourier/grid-point array
    !        --------------------  KFIELD   - number of fields

    !     Method.
    !     -------

    !     Externals.  FFT992 - FFT routine
    !     ----------
    !

    !     Author.
    !     -------
    !        Mats Hamrud *ECMWF*

    !     Modifications.
    !     --------------
    !        Original : 00-03-03
    !        G. Radnoti 01-04-24 2D model (NLOEN=1)
    !        D. Degrauwe  (Feb 2012): Alternative extension zone (E')
    !        G. Mozdzynski (Oct 2014): support for FFTW transforms
    !        G. Mozdzynski (Jun 2015): Support alternative FFTs to FFTW
    !     ------------------------------------------------------------------

    USE TPM_GEN         ,ONLY : LSYNC_TRANS
    USE PARKIND_ECTRANS ,ONLY : JPIM, JPRBT

    USE TPM_DISTR       ,ONLY : MYSETW, MYPROC, NPROC, D_NSTAGT0B, D_NSTAGTF,D_NPTRLS, D_NPNTGTB0, D_NPROCM, D_NDGL_FS
    USE TPM_GEOMETRY    ,ONLY : G_NMEN, G_NLOEN
    USE TPM_HICFFT      ,ONLY : EXECUTE_DIR_FFT
    USE MPL_MODULE      ,ONLY : MPL_BARRIER
    USE TPM_STATS, ONLY : GSTATS => GSTATS_NVTX

    IMPLICIT NONE

    INTEGER(KIND=JPIM),INTENT(IN)  :: KFIELD
    REAL(KIND=JPRBT), INTENT(INOUT), POINTER :: PREEL_REAL(:)
    REAL(KIND=JPRBT), INTENT(OUT), POINTER :: PREEL_COMPLEX(:)
    TYPE(BUFFERED_ALLOCATOR), INTENT(IN) :: ALLOCATOR
    TYPE(FTDIR_HANDLE) :: HFTDIR

    INTEGER(KIND=JPIM) :: KGL

    PREEL_COMPLEX => PREEL_REAL

#ifdef ACCGPU
    !$ACC DATA PRESENT(PREEL_REAL, PREEL_COMPLEX, &
    !$ACC&             D_NSTAGTF,D_NSTAGT0B,D_NPTRLS,D_NPROCM,D_NPNTGTB0,G_NMEN,G_NLOEN)
#endif
#ifdef OMPGPU
    !$OMP TARGET DATA MAP(ALLOC:PREEL_COMPLEX)
#endif

    IF (LSYNC_TRANS) THEN
      CALL GSTATS(430,0)
      CALL MPL_BARRIER(CDSTRING='')
      CALL GSTATS(430,1)
    ENDIF
    CALL GSTATS(413,0)
    CALL EXECUTE_DIR_FFT(PREEL_REAL(:),PREEL_COMPLEX(:),KFIELD, &
        & LOENS=G_NLOEN(D_NPTRLS(MYSETW):D_NPTRLS(MYSETW)+D_NDGL_FS-1), &
        & OFFSETS=D_NSTAGTF(1:D_NDGL_FS+1),ALLOC=ALLOCATOR%PTR)

    IF (LSYNC_TRANS) THEN
      CALL GSTATS(433,0)
      CALL MPL_BARRIER(CDSTRING='')
      CALL GSTATS(433,1)
    ENDIF
    CALL GSTATS(413,1)

#ifdef ACCGPU
    !$ACC END DATA
#endif
#ifdef OMPGPU
    !$OMP END TARGET DATA
#endif

    NULLIFY(PREEL_REAL)

    !     ------------------------------------------------------------------
  END SUBROUTINE FTDIR
END MODULE FTDIR_MOD