source: palm/trunk/SOURCE/cuda_fft_interfaces.f90 @ 4132

Last change on this file since 4132 was 3655, checked in by knoop, 5 years ago

Bugfix: made "unit" and "found" intend INOUT in module interface subroutines + automatic copyright update

  • Property svn:keywords set to Id
File size: 4.8 KB
Line 
1!> @file cuda_fft_interfaces.f90
2!--------------------------------------------------------------------------------!
3! This file is part of PALM.
4!
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.
8!
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.
12!
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/>.
15!
16! Copyright 1997-2019 Leibniz Universitaet Hannover
17!--------------------------------------------------------------------------------!
18!
19! Current revisions:
20! -----------------
21!
22!
23! Former revisions:
24! -----------------
25! $Id: cuda_fft_interfaces.f90 3655 2019-01-07 16:51:22Z suehring $
26! Initial revision ( OpenACC port for SPEC )
27!
28! 1683 2015-10-07 23:57:51Z knoop
29!
30!
31! Description:
32! ------------
33!> FORTRAN interfaces for the CUDA fft
34!> Routines for the fft along x and y (forward/backward) using the CUDA fft
35!--------------------------------------------------------------------------------!
36 MODULE cuda_fft_interfaces
37 
38
39#if defined ( __cuda_fft )
40
41    USE kinds
42
43    INTEGER(iwp) ::  CUFFT_FORWARD = -1   !<
44    INTEGER(iwp) ::  CUFFT_INVERSE =  1   !<
45    INTEGER(iwp) ::  CUFFT_R2C = Z'2a'    !< Real to Complex (interleaved)
46    INTEGER(iwp) ::  CUFFT_C2R = Z'2c'    !< Complex (interleaved) to Real
47    INTEGER(iwp) ::  CUFFT_C2C = Z'29'    !< Complex to Complex, interleaved
48    INTEGER(iwp) ::  CUFFT_D2Z = Z'6a'    !< Double to Double-Complex
49    INTEGER(iwp) ::  CUFFT_Z2D = Z'6c'    !< Double-Complex to Double
50    INTEGER(iwp) ::  CUFFT_Z2Z = Z'69'    !< Double-Complex to Double-Complex
51
52    PUBLIC
53
54
55!
56!-- cufftPlan1d( cufftHandle *plan, int nx, cufftType type, int batch )
57    INTERFACE CUFFTPLAN1D
58
59!------------------------------------------------------------------------------!
60! Description:
61! ------------
62!> @todo Missing subroutine description.
63!------------------------------------------------------------------------------!
64       SUBROUTINE CUFFTPLAN1D( plan, nx, type, batch ) bind( C, name='cufftPlan1d' )
65
66          USE ISO_C_BINDING
67
68          INTEGER(C_INT)        ::  plan   !<
69          INTEGER(C_INT), value ::  batch  !<
70          INTEGER(C_INT), value ::  nx     !<
71          INTEGER(C_INT), value ::  type   !<
72       END SUBROUTINE CUFFTPLAN1D
73
74    END INTERFACE CUFFTPLAN1D
75
76!
77!-- cufftDestroy( cufftHandle plan )  !!! remove later if not really needed !!!
78    INTERFACE CUFFTDESTROY
79
80!------------------------------------------------------------------------------!
81! Description:
82! ------------
83!> @todo Missing subroutine description.
84!------------------------------------------------------------------------------!
85       SUBROUTINE CUFFTDESTROY( plan ) bind( C, name='cufftDestroy' )
86
87          USE ISO_C_BINDING
88
89          INTEGER(C_INT), VALUE ::  plan
90
91       END SUBROUTINE CUFFTDESTROY
92
93    END INTERFACE CUFFTDESTROY
94
95
96    INTERFACE CUFFTEXECZ2D
97
98!------------------------------------------------------------------------------!
99! Description:
100! ------------
101!> @todo Missing subroutine description.
102!------------------------------------------------------------------------------!
103       SUBROUTINE CUFFTEXECZ2D( plan, idata, odata ) bind( C, name='cufftExecZ2D' )
104
105          USE ISO_C_BINDING
106          USE kinds
107
108          INTEGER(C_INT), VALUE ::  plan          !<
109          COMPLEX(dp), DEVICE   ::  idata(:,:,:)  !<
110          REAL(dp), DEVICE      ::  odata(:,:,:)  !<
111
112       END SUBROUTINE CUFFTEXECZ2D
113
114    END INTERFACE CUFFTEXECZ2D
115
116
117    INTERFACE CUFFTEXECD2Z
118
119!------------------------------------------------------------------------------!
120! Description:
121! ------------
122!> @todo Missing subroutine description.
123!------------------------------------------------------------------------------!
124       SUBROUTINE CUFFTEXECD2Z( plan, idata, odata ) bind( C, name='cufftExecD2Z' )
125
126          USE ISO_C_BINDING
127         
128          USE kinds
129
130          INTEGER(C_INT), VALUE ::  plan          !<
131          REAL(dp), DEVICE      ::  idata(:,:,:)  !<
132          COMPLEX(dp), DEVICE   ::  odata(:,:,:)  !<
133
134       END SUBROUTINE CUFFTEXECD2Z
135
136    END INTERFACE CUFFTEXECD2Z
137
138#else
139
140    INTERFACE CUFFTdummy
141
142!------------------------------------------------------------------------------!
143! Description:
144! ------------
145!> Dummy interface to avoid compiler warnings in case of no bublic objects
146!> declared.
147!------------------------------------------------------------------------------!
148       SUBROUTINE CUFFTdummy( dummy )
149       
150          USE kinds
151
152          REAL(wp) ::  dummy  !<
153
154       END SUBROUTINE CUFFTdummy
155
156    END INTERFACE CUFFTdummy
157
158#endif
159
160 END MODULE cuda_fft_interfaces
Note: See TracBrowser for help on using the repository browser.