Ignore:
Timestamp:
Jun 11, 2020 8:51:48 AM (4 years ago)
Author:
raasch
Message:

files re-formatted to follow the PALM coding standard

File:
1 edited

Legend:

Unmodified
Added
Removed
  • palm/trunk/SOURCE/cuda_fft_interfaces.f90

    r4360 r4559  
    11!> @file cuda_fft_interfaces.f90
    2 !--------------------------------------------------------------------------------!
    3 ! This file is part of PALM.
     2!--------------------------------------------------------------------------------------------------!
     3! This file is part of the PALM model system.
    44!
    5 ! PALM is free software: you can redistribute it and/or modify it under the terms
    6 ! of the GNU General Public License as published by the Free Software Foundation,
    7 ! either version 3 of the License, or (at your option) any later version.
     5! PALM is free software: you can redistribute it and/or modify it under the terms of the GNU General
     6! Public License as published by the Free Software Foundation, either version 3 of the License, or
     7! (at your option) any later version.
    88!
    9 ! PALM is distributed in the hope that it will be useful, but WITHOUT ANY
    10 ! WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS FOR
    11 ! A PARTICULAR PURPOSE.  See the GNU General Public License for more details.
     9! PALM is distributed in the hope that it will be useful, but WITHOUT ANY WARRANTY; without even the
     10! implied warranty of MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU General
     11! Public License for more details.
    1212!
    13 ! You should have received a copy of the GNU General Public License along with
    14 ! PALM. If not, see <http://www.gnu.org/licenses/>.
     13! You should have received a copy of the GNU General Public License along with PALM. If not, see
     14! <http://www.gnu.org/licenses/>.
    1515!
    1616! Copyright 1997-2020 Leibniz Universitaet Hannover
    17 !--------------------------------------------------------------------------------!
     17!--------------------------------------------------------------------------------------------------!
    1818!
    1919! Current revisions:
     
    2424! -----------------
    2525! $Id$
     26! file re-formatted to follow the PALM coding standard
     27!
     28! 4360 2020-01-07 11:25:50Z suehring
    2629! Corrected "Former revisions" section
    27 ! 
     30!
    2831! 3655 2019-01-07 16:51:22Z knoop
    2932! 1683 2015-10-07 23:57:51Z knoop
     
    3437!> FORTRAN interfaces for the CUDA fft
    3538!> Routines for the fft along x and y (forward/backward) using the CUDA fft
    36 !--------------------------------------------------------------------------------!
     39!--------------------------------------------------------------------------------------------------!
    3740 MODULE cuda_fft_interfaces
    38  
     41
    3942
    4043#if defined ( __cuda_fft )
     
    4245    USE kinds
    4346
     47    INTEGER(iwp) ::  CUFFT_C2C = Z'29'    !< Complex to Complex, interleaved
     48    INTEGER(iwp) ::  CUFFT_C2R = Z'2c'    !< Complex (interleaved) to Real
     49    INTEGER(iwp) ::  CUFFT_D2Z = Z'6a'    !< Double to Double-Complex
    4450    INTEGER(iwp) ::  CUFFT_FORWARD = -1   !<
    4551    INTEGER(iwp) ::  CUFFT_INVERSE =  1   !<
    4652    INTEGER(iwp) ::  CUFFT_R2C = Z'2a'    !< Real to Complex (interleaved)
    47     INTEGER(iwp) ::  CUFFT_C2R = Z'2c'    !< Complex (interleaved) to Real
    48     INTEGER(iwp) ::  CUFFT_C2C = Z'29'    !< Complex to Complex, interleaved
    49     INTEGER(iwp) ::  CUFFT_D2Z = Z'6a'    !< Double to Double-Complex
    5053    INTEGER(iwp) ::  CUFFT_Z2D = Z'6c'    !< Double-Complex to Double
    5154    INTEGER(iwp) ::  CUFFT_Z2Z = Z'69'    !< Double-Complex to Double-Complex
     
    5861    INTERFACE CUFFTPLAN1D
    5962
    60 !------------------------------------------------------------------------------!
     63!--------------------------------------------------------------------------------------------------!
    6164! Description:
    6265! ------------
    6366!> @todo Missing subroutine description.
    64 !------------------------------------------------------------------------------!
    65        SUBROUTINE CUFFTPLAN1D( plan, nx, type, batch ) bind( C, name='cufftPlan1d' )
     67!--------------------------------------------------------------------------------------------------!
     68       SUBROUTINE CUFFTPLAN1D( plan, nx, type, batch ) BIND( C, name='cufftPlan1d' )
    6669
    6770          USE ISO_C_BINDING
    6871
    69           INTEGER(C_INT)        ::  plan   !< 
    70           INTEGER(C_INT), value ::  batch  !<
    71           INTEGER(C_INT), value ::  nx     !<
    72           INTEGER(C_INT), value ::  type   !<
     72          INTEGER(C_INT)        ::  plan   !<
     73          INTEGER(C_INT), VALUE ::  batch  !<
     74          INTEGER(C_INT), VALUE ::  nx     !<
     75          INTEGER(C_INT), VALUE ::  type   !<
    7376       END SUBROUTINE CUFFTPLAN1D
    7477
     
    7982    INTERFACE CUFFTDESTROY
    8083
    81 !------------------------------------------------------------------------------!
     84!--------------------------------------------------------------------------------------------------!
    8285! Description:
    8386! ------------
    8487!> @todo Missing subroutine description.
    85 !------------------------------------------------------------------------------!
    86        SUBROUTINE CUFFTDESTROY( plan ) bind( C, name='cufftDestroy' )
     88!--------------------------------------------------------------------------------------------------!
     89       SUBROUTINE CUFFTDESTROY( plan ) BIND( C, name='cufftDestroy' )
    8790
    8891          USE ISO_C_BINDING
     
    97100    INTERFACE CUFFTEXECZ2D
    98101
    99 !------------------------------------------------------------------------------!
     102!--------------------------------------------------------------------------------------------------!
    100103! Description:
    101104! ------------
    102105!> @todo Missing subroutine description.
    103 !------------------------------------------------------------------------------!
    104        SUBROUTINE CUFFTEXECZ2D( plan, idata, odata ) bind( C, name='cufftExecZ2D' )
     106!--------------------------------------------------------------------------------------------------!
     107       SUBROUTINE CUFFTEXECZ2D( plan, idata, odata ) BIND( C, name='cufftExecZ2D' )
    105108
    106109          USE ISO_C_BINDING
    107110          USE kinds
    108111
     112          COMPLEX(dp), DEVICE   ::  idata(:,:,:)  !<
     113
    109114          INTEGER(C_INT), VALUE ::  plan          !<
    110           COMPLEX(dp), DEVICE   ::  idata(:,:,:)  !<
     115
    111116          REAL(dp), DEVICE      ::  odata(:,:,:)  !<
    112117
     
    118123    INTERFACE CUFFTEXECD2Z
    119124
    120 !------------------------------------------------------------------------------!
     125!--------------------------------------------------------------------------------------------------!
    121126! Description:
    122127! ------------
    123128!> @todo Missing subroutine description.
    124 !------------------------------------------------------------------------------!
     129!--------------------------------------------------------------------------------------------------!
    125130       SUBROUTINE CUFFTEXECD2Z( plan, idata, odata ) bind( C, name='cufftExecD2Z' )
    126131
    127132          USE ISO_C_BINDING
    128          
     133
    129134          USE kinds
    130135
     136          COMPLEX(dp), DEVICE   ::  odata(:,:,:)  !<
     137
    131138          INTEGER(C_INT), VALUE ::  plan          !<
     139
    132140          REAL(dp), DEVICE      ::  idata(:,:,:)  !<
    133           COMPLEX(dp), DEVICE   ::  odata(:,:,:)  !<
    134141
    135142       END SUBROUTINE CUFFTEXECD2Z
     
    141148    INTERFACE CUFFTdummy
    142149
    143 !------------------------------------------------------------------------------!
     150!--------------------------------------------------------------------------------------------------!
    144151! Description:
    145152! ------------
    146 !> Dummy interface to avoid compiler warnings in case of no bublic objects
    147 !> declared.
    148 !------------------------------------------------------------------------------!
     153!> Dummy interface to avoid compiler warnings in case of no bublic objects declared.
     154!--------------------------------------------------------------------------------------------------!
    149155       SUBROUTINE CUFFTdummy( dummy )
    150        
     156
    151157          USE kinds
    152158
Note: See TracChangeset for help on using the changeset viewer.