Chris@10
|
1 @node Calling FFTW from Modern Fortran, Calling FFTW from Legacy Fortran, Distributed-memory FFTW with MPI, Top
|
Chris@10
|
2 @chapter Calling FFTW from Modern Fortran
|
Chris@10
|
3 @cindex Fortran interface
|
Chris@10
|
4
|
Chris@10
|
5 Fortran 2003 standardized ways for Fortran code to call C libraries,
|
Chris@10
|
6 and this allows us to support a direct translation of the FFTW C API
|
Chris@10
|
7 into Fortran. Compared to the legacy Fortran 77 interface
|
Chris@10
|
8 (@pxref{Calling FFTW from Legacy Fortran}), this direct interface
|
Chris@10
|
9 offers many advantages, especially compile-time type-checking and
|
Chris@10
|
10 aligned memory allocation. As of this writing, support for these C
|
Chris@10
|
11 interoperability features seems widespread, having been implemented in
|
Chris@10
|
12 nearly all major Fortran compilers (e.g. GNU, Intel, IBM,
|
Chris@10
|
13 Oracle/Solaris, Portland Group, NAG).
|
Chris@10
|
14 @cindex portability
|
Chris@10
|
15
|
Chris@10
|
16 This chapter documents that interface. For the most part, since this
|
Chris@10
|
17 interface allows Fortran to call the C interface directly, the usage
|
Chris@10
|
18 is identical to C translated to Fortran syntax. However, there are a
|
Chris@10
|
19 few subtle points such as memory allocation, wisdom, and data types
|
Chris@10
|
20 that deserve closer attention.
|
Chris@10
|
21
|
Chris@10
|
22 @menu
|
Chris@10
|
23 * Overview of Fortran interface::
|
Chris@10
|
24 * Reversing array dimensions::
|
Chris@10
|
25 * FFTW Fortran type reference::
|
Chris@10
|
26 * Plan execution in Fortran::
|
Chris@10
|
27 * Allocating aligned memory in Fortran::
|
Chris@10
|
28 * Accessing the wisdom API from Fortran::
|
Chris@10
|
29 * Defining an FFTW module::
|
Chris@10
|
30 @end menu
|
Chris@10
|
31
|
Chris@10
|
32 @c -------------------------------------------------------
|
Chris@10
|
33 @node Overview of Fortran interface, Reversing array dimensions, Calling FFTW from Modern Fortran, Calling FFTW from Modern Fortran
|
Chris@10
|
34 @section Overview of Fortran interface
|
Chris@10
|
35
|
Chris@10
|
36 FFTW provides a file @code{fftw3.f03} that defines Fortran 2003
|
Chris@10
|
37 interfaces for all of its C routines, except for the MPI routines
|
Chris@10
|
38 described elsewhere, which can be found in the same directory as
|
Chris@10
|
39 @code{fftw3.h} (the C header file). In any Fortran subroutine where
|
Chris@10
|
40 you want to use FFTW functions, you should begin with:
|
Chris@10
|
41
|
Chris@10
|
42 @cindex iso_c_binding
|
Chris@10
|
43 @example
|
Chris@10
|
44 use, intrinsic :: iso_c_binding
|
Chris@10
|
45 include 'fftw3.f03'
|
Chris@10
|
46 @end example
|
Chris@10
|
47
|
Chris@10
|
48 This includes the interface definitions and the standard
|
Chris@10
|
49 @code{iso_c_binding} module (which defines the equivalents of C
|
Chris@10
|
50 types). You can also put the FFTW functions into a module if you
|
Chris@10
|
51 prefer (@pxref{Defining an FFTW module}).
|
Chris@10
|
52
|
Chris@10
|
53 At this point, you can now call anything in the FFTW C interface
|
Chris@10
|
54 directly, almost exactly as in C other than minor changes in syntax.
|
Chris@10
|
55 For example:
|
Chris@10
|
56
|
Chris@10
|
57 @findex fftw_plan_dft_2d
|
Chris@10
|
58 @findex fftw_execute_dft
|
Chris@10
|
59 @findex fftw_destroy_plan
|
Chris@10
|
60 @example
|
Chris@10
|
61 type(C_PTR) :: plan
|
Chris@10
|
62 complex(C_DOUBLE_COMPLEX), dimension(1024,1000) :: in, out
|
Chris@10
|
63 plan = fftw_plan_dft_2d(1000,1024, in,out, FFTW_FORWARD,FFTW_ESTIMATE)
|
Chris@10
|
64 ...
|
Chris@10
|
65 call fftw_execute_dft(plan, in, out)
|
Chris@10
|
66 ...
|
Chris@10
|
67 call fftw_destroy_plan(plan)
|
Chris@10
|
68 @end example
|
Chris@10
|
69
|
Chris@10
|
70 A few important things to keep in mind are:
|
Chris@10
|
71
|
Chris@10
|
72 @itemize @bullet
|
Chris@10
|
73
|
Chris@10
|
74 @item
|
Chris@10
|
75 @tindex fftw_complex
|
Chris@10
|
76 @ctindex C_PTR
|
Chris@10
|
77 @ctindex C_INT
|
Chris@10
|
78 @ctindex C_DOUBLE
|
Chris@10
|
79 @ctindex C_DOUBLE_COMPLEX
|
Chris@10
|
80 FFTW plans are @code{type(C_PTR)}. Other C types are mapped in the
|
Chris@10
|
81 obvious way via the @code{iso_c_binding} standard: @code{int} turns
|
Chris@10
|
82 into @code{integer(C_INT)}, @code{fftw_complex} turns into
|
Chris@10
|
83 @code{complex(C_DOUBLE_COMPLEX)}, @code{double} turns into
|
Chris@10
|
84 @code{real(C_DOUBLE)}, and so on. @xref{FFTW Fortran type reference}.
|
Chris@10
|
85
|
Chris@10
|
86 @item
|
Chris@10
|
87 Functions in C become functions in Fortran if they have a return value,
|
Chris@10
|
88 and subroutines in Fortran otherwise.
|
Chris@10
|
89
|
Chris@10
|
90 @item
|
Chris@10
|
91 The ordering of the Fortran array dimensions must be @emph{reversed}
|
Chris@10
|
92 when they are passed to the FFTW plan creation, thanks to differences
|
Chris@10
|
93 in array indexing conventions (@pxref{Multi-dimensional Array
|
Chris@10
|
94 Format}). This is @emph{unlike} the legacy Fortran interface
|
Chris@10
|
95 (@pxref{Fortran-interface routines}), which reversed the dimensions
|
Chris@10
|
96 for you. @xref{Reversing array dimensions}.
|
Chris@10
|
97
|
Chris@10
|
98 @item
|
Chris@10
|
99 @cindex alignment
|
Chris@10
|
100 @cindex SIMD
|
Chris@10
|
101 Using ordinary Fortran array declarations like this works, but may
|
Chris@10
|
102 yield suboptimal performance because the data may not be not aligned
|
Chris@10
|
103 to exploit SIMD instructions on modern proessors (@pxref{SIMD
|
Chris@10
|
104 alignment and fftw_malloc}). Better performance will often be obtained
|
Chris@10
|
105 by allocating with @samp{fftw_alloc}. @xref{Allocating aligned memory
|
Chris@10
|
106 in Fortran}.
|
Chris@10
|
107
|
Chris@10
|
108 @item
|
Chris@10
|
109 @findex fftw_execute
|
Chris@10
|
110 Similar to the legacy Fortran interface (@pxref{FFTW Execution in
|
Chris@10
|
111 Fortran}), we currently recommend @emph{not} using @code{fftw_execute}
|
Chris@10
|
112 but rather using the more specialized functions like
|
Chris@10
|
113 @code{fftw_execute_dft} (@pxref{New-array Execute Functions}).
|
Chris@10
|
114 However, you should execute the plan on the @code{same arrays} as the
|
Chris@10
|
115 ones for which you created the plan, unless you are especially
|
Chris@10
|
116 careful. @xref{Plan execution in Fortran}. To prevent
|
Chris@10
|
117 you from using @code{fftw_execute} by mistake, the @code{fftw3.f03}
|
Chris@10
|
118 file does not provide an @code{fftw_execute} interface declaration.
|
Chris@10
|
119
|
Chris@10
|
120 @item
|
Chris@10
|
121 @cindex flags
|
Chris@10
|
122 Multiple planner flags are combined with @code{ior} (equivalent to @samp{|} in C). e.g. @code{FFTW_MEASURE | FFTW_DESTROY_INPUT} becomes @code{ior(FFTW_MEASURE, FFTW_DESTROY_INPUT)}. (You can also use @samp{+} as long as you don't try to include a given flag more than once.)
|
Chris@10
|
123
|
Chris@10
|
124 @end itemize
|
Chris@10
|
125
|
Chris@10
|
126 @menu
|
Chris@10
|
127 * Extended and quadruple precision in Fortran::
|
Chris@10
|
128 @end menu
|
Chris@10
|
129
|
Chris@10
|
130 @node Extended and quadruple precision in Fortran, , Overview of Fortran interface, Overview of Fortran interface
|
Chris@10
|
131 @subsection Extended and quadruple precision in Fortran
|
Chris@10
|
132 @cindex precision
|
Chris@10
|
133
|
Chris@10
|
134 If FFTW is compiled in @code{long double} (extended) precision
|
Chris@10
|
135 (@pxref{Installation and Customization}), you may be able to call the
|
Chris@10
|
136 resulting @code{fftwl_} routines (@pxref{Precision}) from Fortran if
|
Chris@10
|
137 your compiler supports the @code{C_LONG_DOUBLE_COMPLEX} type code.
|
Chris@10
|
138
|
Chris@10
|
139 Because some Fortran compilers do not support
|
Chris@10
|
140 @code{C_LONG_DOUBLE_COMPLEX}, the @code{fftwl_} declarations are
|
Chris@10
|
141 segregated into a separate interface file @code{fftw3l.f03}, which you
|
Chris@10
|
142 should include @emph{in addition} to @code{fftw3.f03} (which declares
|
Chris@10
|
143 precision-independent @samp{FFTW_} constants):
|
Chris@10
|
144
|
Chris@10
|
145 @cindex iso_c_binding
|
Chris@10
|
146 @example
|
Chris@10
|
147 use, intrinsic :: iso_c_binding
|
Chris@10
|
148 include 'fftw3.f03'
|
Chris@10
|
149 include 'fftw3l.f03'
|
Chris@10
|
150 @end example
|
Chris@10
|
151
|
Chris@10
|
152 We also support using the nonstandard @code{__float128}
|
Chris@10
|
153 quadruple-precision type provided by recent versions of @code{gcc} on
|
Chris@10
|
154 32- and 64-bit x86 hardware (@pxref{Installation and Customization}),
|
Chris@10
|
155 using the corresponding @code{real(16)} and @code{complex(16)} types
|
Chris@10
|
156 supported by @code{gfortran}. The quadruple-precision @samp{fftwq_}
|
Chris@10
|
157 functions (@pxref{Precision}) are declared in a @code{fftw3q.f03}
|
Chris@10
|
158 interface file, which should be included in addition to
|
Chris@10
|
159 @code{fftw3l.f03}, as above. You should also link with
|
Chris@10
|
160 @code{-lfftw3q -lquadmath -lm} as in C.
|
Chris@10
|
161
|
Chris@10
|
162 @c -------------------------------------------------------
|
Chris@10
|
163 @node Reversing array dimensions, FFTW Fortran type reference, Overview of Fortran interface, Calling FFTW from Modern Fortran
|
Chris@10
|
164 @section Reversing array dimensions
|
Chris@10
|
165
|
Chris@10
|
166 @cindex row-major
|
Chris@10
|
167 @cindex column-major
|
Chris@10
|
168 A minor annoyance in calling FFTW from Fortran is that FFTW's array
|
Chris@10
|
169 dimensions are defined in the C convention (row-major order), while
|
Chris@10
|
170 Fortran's array dimensions are the opposite convention (column-major
|
Chris@10
|
171 order). @xref{Multi-dimensional Array Format}. This is just a
|
Chris@10
|
172 bookkeeping difference, with no effect on performance. The only
|
Chris@10
|
173 consequence of this is that, whenever you create an FFTW plan for a
|
Chris@10
|
174 multi-dimensional transform, you must always @emph{reverse the
|
Chris@10
|
175 ordering of the dimensions}.
|
Chris@10
|
176
|
Chris@10
|
177 For example, consider the three-dimensional (@threedims{L,M,N}) arrays:
|
Chris@10
|
178
|
Chris@10
|
179 @example
|
Chris@10
|
180 complex(C_DOUBLE_COMPLEX), dimension(L,M,N) :: in, out
|
Chris@10
|
181 @end example
|
Chris@10
|
182
|
Chris@10
|
183 To plan a DFT for these arrays using @code{fftw_plan_dft_3d}, you could do:
|
Chris@10
|
184
|
Chris@10
|
185 @findex fftw_plan_dft_3d
|
Chris@10
|
186 @example
|
Chris@10
|
187 plan = fftw_plan_dft_3d(N,M,L, in,out, FFTW_FORWARD,FFTW_ESTIMATE)
|
Chris@10
|
188 @end example
|
Chris@10
|
189
|
Chris@10
|
190 That is, from FFTW's perspective this is a @threedims{N,M,L} array.
|
Chris@10
|
191 @emph{No data transposition need occur}, as this is @emph{only
|
Chris@10
|
192 notation}. Similarly, to use the more generic routine
|
Chris@10
|
193 @code{fftw_plan_dft} with the same arrays, you could do:
|
Chris@10
|
194
|
Chris@10
|
195 @example
|
Chris@10
|
196 integer(C_INT), dimension(3) :: n = [N,M,L]
|
Chris@10
|
197 plan = fftw_plan_dft_3d(3, n, in,out, FFTW_FORWARD,FFTW_ESTIMATE)
|
Chris@10
|
198 @end example
|
Chris@10
|
199
|
Chris@10
|
200 Note, by the way, that this is different from the legacy Fortran
|
Chris@10
|
201 interface (@pxref{Fortran-interface routines}), which automatically
|
Chris@10
|
202 reverses the order of the array dimension for you. Here, you are
|
Chris@10
|
203 calling the C interface directly, so there is no ``translation'' layer.
|
Chris@10
|
204
|
Chris@10
|
205 @cindex r2c/c2r multi-dimensional array format
|
Chris@10
|
206 An important thing to keep in mind is the implication of this for
|
Chris@10
|
207 multidimensional real-to-complex transforms (@pxref{Multi-Dimensional
|
Chris@10
|
208 DFTs of Real Data}). In C, a multidimensional real-to-complex DFT
|
Chris@10
|
209 chops the last dimension roughly in half (@threedims{N,M,L} real input
|
Chris@10
|
210 goes to @threedims{N,M,L/2+1} complex output). In Fortran, because
|
Chris@10
|
211 the array dimension notation is reversed, the @emph{first} dimension of
|
Chris@10
|
212 the complex data is chopped roughly in half. For example consider the
|
Chris@10
|
213 @samp{r2c} transform of @threedims{L,M,N} real input in Fortran:
|
Chris@10
|
214
|
Chris@10
|
215 @findex fftw_plan_dft_r2c_3d
|
Chris@10
|
216 @findex fftw_execute_dft_r2c
|
Chris@10
|
217 @example
|
Chris@10
|
218 type(C_PTR) :: plan
|
Chris@10
|
219 real(C_DOUBLE), dimension(L,M,N) :: in
|
Chris@10
|
220 complex(C_DOUBLE_COMPLEX), dimension(L/2+1,M,N) :: out
|
Chris@10
|
221 plan = fftw_plan_dft_r2c_3d(N,M,L, in,out, FFTW_ESTIMATE)
|
Chris@10
|
222 ...
|
Chris@10
|
223 call fftw_execute_dft_r2c(plan, in, out)
|
Chris@10
|
224 @end example
|
Chris@10
|
225
|
Chris@10
|
226 @cindex in-place
|
Chris@10
|
227 @cindex padding
|
Chris@10
|
228 Alternatively, for an in-place r2c transform, as described in the C
|
Chris@10
|
229 documentation we must @emph{pad} the @emph{first} dimension of the
|
Chris@10
|
230 real input with an extra two entries (which are ignored by FFTW) so as
|
Chris@10
|
231 to leave enough space for the complex output. The input is
|
Chris@10
|
232 @emph{allocated} as a @threedims{2[L/2+1],M,N} array, even though only
|
Chris@10
|
233 @threedims{L,M,N} of it is actually used. In this example, we will
|
Chris@10
|
234 allocate the array as a pointer type, using @samp{fftw_alloc} to
|
Chris@10
|
235 ensure aligned memory for maximum performance (@pxref{Allocating
|
Chris@10
|
236 aligned memory in Fortran}); this also makes it easy to reference the
|
Chris@10
|
237 same memory as both a real array and a complex array.
|
Chris@10
|
238
|
Chris@10
|
239 @findex fftw_alloc_complex
|
Chris@10
|
240 @findex c_f_pointer
|
Chris@10
|
241 @example
|
Chris@10
|
242 real(C_DOUBLE), pointer :: in(:,:,:)
|
Chris@10
|
243 complex(C_DOUBLE_COMPLEX), pointer :: out(:,:,:)
|
Chris@10
|
244 type(C_PTR) :: plan, data
|
Chris@10
|
245 data = fftw_alloc_complex(int((L/2+1) * M * N, C_SIZE_T))
|
Chris@10
|
246 call c_f_pointer(data, in, [2*(L/2+1),M,N])
|
Chris@10
|
247 call c_f_pointer(data, out, [L/2+1,M,N])
|
Chris@10
|
248 plan = fftw_plan_dft_r2c_3d(N,M,L, in,out, FFTW_ESTIMATE)
|
Chris@10
|
249 ...
|
Chris@10
|
250 call fftw_execute_dft_r2c(plan, in, out)
|
Chris@10
|
251 ...
|
Chris@10
|
252 call fftw_destroy_plan(plan)
|
Chris@10
|
253 call fftw_free(data)
|
Chris@10
|
254 @end example
|
Chris@10
|
255
|
Chris@10
|
256 @c -------------------------------------------------------
|
Chris@10
|
257 @node FFTW Fortran type reference, Plan execution in Fortran, Reversing array dimensions, Calling FFTW from Modern Fortran
|
Chris@10
|
258 @section FFTW Fortran type reference
|
Chris@10
|
259
|
Chris@10
|
260 The following are the most important type correspondences between the
|
Chris@10
|
261 C interface and Fortran:
|
Chris@10
|
262
|
Chris@10
|
263 @itemize @bullet
|
Chris@10
|
264
|
Chris@10
|
265 @item
|
Chris@10
|
266 @tindex fftw_plan
|
Chris@10
|
267 Plans (@code{fftw_plan} and variants) are @code{type(C_PTR)} (i.e. an
|
Chris@10
|
268 opaque pointer).
|
Chris@10
|
269
|
Chris@10
|
270 @item
|
Chris@10
|
271 @tindex fftw_complex
|
Chris@10
|
272 @cindex precision
|
Chris@10
|
273 @ctindex C_DOUBLE
|
Chris@10
|
274 @ctindex C_FLOAT
|
Chris@10
|
275 @ctindex C_LONG_DOUBLE
|
Chris@10
|
276 @ctindex C_DOUBLE_COMPLEX
|
Chris@10
|
277 @ctindex C_FLOAT_COMPLEX
|
Chris@10
|
278 @ctindex C_LONG_DOUBLE_COMPLEX
|
Chris@10
|
279 The C floating-point types @code{double}, @code{float}, and @code{long
|
Chris@10
|
280 double} correspond to @code{real(C_DOUBLE)}, @code{real(C_FLOAT)}, and
|
Chris@10
|
281 @code{real(C_LONG_DOUBLE)}, respectively. The C complex types
|
Chris@10
|
282 @code{fftw_complex}, @code{fftwf_complex}, and @code{fftwl_complex}
|
Chris@10
|
283 correspond in Fortran to @code{complex(C_DOUBLE_COMPLEX)},
|
Chris@10
|
284 @code{complex(C_FLOAT_COMPLEX)}, and
|
Chris@10
|
285 @code{complex(C_LONG_DOUBLE_COMPLEX)}, respectively.
|
Chris@10
|
286 Just as in C
|
Chris@10
|
287 (@pxref{Precision}), the FFTW subroutines and types are prefixed with
|
Chris@10
|
288 @samp{fftw_}, @code{fftwf_}, and @code{fftwl_} for the different precisions, and link to different libraries (@code{-lfftw3}, @code{-lfftw3f}, and @code{-lfftw3l} on Unix), but use the @emph{same} include file @code{fftw3.f03} and the @emph{same} constants (all of which begin with @samp{FFTW_}). The exception is @code{long double} precision, for which you should @emph{also} include @code{fftw3l.f03} (@pxref{Extended and quadruple precision in Fortran}).
|
Chris@10
|
289
|
Chris@10
|
290 @item
|
Chris@10
|
291 @tindex ptrdiff_t
|
Chris@10
|
292 @ctindex C_INT
|
Chris@10
|
293 @ctindex C_INTPTR_T
|
Chris@10
|
294 @ctindex C_SIZE_T
|
Chris@10
|
295 @findex fftw_malloc
|
Chris@10
|
296 The C integer types @code{int} and @code{unsigned} (used for planner
|
Chris@10
|
297 flags) become @code{integer(C_INT)}. The C integer type @code{ptrdiff_t} (e.g. in the @ref{64-bit Guru Interface}) becomes @code{integer(C_INTPTR_T)}, and @code{size_t} (in @code{fftw_malloc} etc.) becomes @code{integer(C_SIZE_T)}.
|
Chris@10
|
298
|
Chris@10
|
299 @item
|
Chris@10
|
300 @tindex fftw_r2r_kind
|
Chris@10
|
301 @ctindex C_FFTW_R2R_KIND
|
Chris@10
|
302 The @code{fftw_r2r_kind} type (@pxref{Real-to-Real Transform Kinds})
|
Chris@10
|
303 becomes @code{integer(C_FFTW_R2R_KIND)}. The various constant values
|
Chris@10
|
304 of the C enumerated type (@code{FFTW_R2HC} etc.) become simply integer
|
Chris@10
|
305 constants of the same names in Fortran.
|
Chris@10
|
306
|
Chris@10
|
307 @item
|
Chris@10
|
308 @ctindex FFTW_DESTROY_INPUT
|
Chris@10
|
309 @cindex in-place
|
Chris@10
|
310 @findex fftw_flops
|
Chris@10
|
311 Numeric array pointer arguments (e.g. @code{double *})
|
Chris@10
|
312 become @code{dimension(*), intent(out)} arrays of the same type, or
|
Chris@10
|
313 @code{dimension(*), intent(in)} if they are pointers to constant data
|
Chris@10
|
314 (e.g. @code{const int *}). There are a few exceptions where numeric
|
Chris@10
|
315 pointers refer to scalar outputs (e.g. for @code{fftw_flops}), in which
|
Chris@10
|
316 case they are @code{intent(out)} scalar arguments in Fortran too.
|
Chris@10
|
317 For the new-array execute functions (@pxref{New-array Execute Functions}),
|
Chris@10
|
318 the input arrays are declared @code{dimension(*), intent(inout)}, since
|
Chris@10
|
319 they can be modified in the case of in-place or @code{FFTW_DESTROY_INPUT}
|
Chris@10
|
320 transforms.
|
Chris@10
|
321
|
Chris@10
|
322 @item
|
Chris@10
|
323 @findex fftw_alloc_real
|
Chris@10
|
324 @findex c_f_pointer
|
Chris@10
|
325 Pointer @emph{return} values (e.g @code{double *}) become
|
Chris@10
|
326 @code{type(C_PTR)}. (If they are pointers to arrays, as for
|
Chris@10
|
327 @code{fftw_alloc_real}, you can convert them back to Fortran array
|
Chris@10
|
328 pointers with the standard intrinsic function @code{c_f_pointer}.)
|
Chris@10
|
329
|
Chris@10
|
330 @item
|
Chris@10
|
331 @cindex guru interface
|
Chris@10
|
332 @tindex fftw_iodim
|
Chris@10
|
333 @tindex fftw_iodim64
|
Chris@10
|
334 @cindex 64-bit architecture
|
Chris@10
|
335 The @code{fftw_iodim} type in the guru interface (@pxref{Guru vector
|
Chris@10
|
336 and transform sizes}) becomes @code{type(fftw_iodim)} in Fortran, a
|
Chris@10
|
337 derived data type (the Fortran analogue of C's @code{struct}) with
|
Chris@10
|
338 three @code{integer(C_INT)} components: @code{n}, @code{is}, and
|
Chris@10
|
339 @code{os}, with the same meanings as in C. The @code{fftw_iodim64} type in the 64-bit guru interface (@pxref{64-bit Guru Interface}) is the same, except that its components are of type @code{integer(C_INTPTR_T)}.
|
Chris@10
|
340
|
Chris@10
|
341 @item
|
Chris@10
|
342 @ctindex C_FUNPTR
|
Chris@10
|
343 Using the wisdom import/export functions from Fortran is a bit tricky,
|
Chris@10
|
344 and is discussed in @ref{Accessing the wisdom API from Fortran}. In
|
Chris@10
|
345 brief, the @code{FILE *} arguments map to @code{type(C_PTR)}, @code{const char *} to @code{character(C_CHAR), dimension(*), intent(in)} (null-terminated!), and the generic read-char/write-char functions map to @code{type(C_FUNPTR)}.
|
Chris@10
|
346
|
Chris@10
|
347 @end itemize
|
Chris@10
|
348
|
Chris@10
|
349 @cindex portability
|
Chris@10
|
350 You may be wondering if you need to search-and-replace
|
Chris@10
|
351 @code{real(kind(0.0d0))} (or whatever your favorite Fortran spelling
|
Chris@10
|
352 of ``double precision'' is) with @code{real(C_DOUBLE)} everywhere in
|
Chris@10
|
353 your program, and similarly for @code{complex} and @code{integer}
|
Chris@10
|
354 types. The answer is no; you can still use your existing types. As
|
Chris@10
|
355 long as these types match their C counterparts, things should work
|
Chris@10
|
356 without a hitch. The worst that can happen, e.g. in the (unlikely)
|
Chris@10
|
357 event of a system where @code{real(kind(0.0d0))} is different from
|
Chris@10
|
358 @code{real(C_DOUBLE)}, is that the compiler will give you a
|
Chris@10
|
359 type-mismatch error. That is, if you don't use the
|
Chris@10
|
360 @code{iso_c_binding} kinds you need to accept at least the theoretical
|
Chris@10
|
361 possibility of having to change your code in response to compiler
|
Chris@10
|
362 errors on some future machine, but you don't need to worry about
|
Chris@10
|
363 silently compiling incorrect code that yields runtime errors.
|
Chris@10
|
364
|
Chris@10
|
365 @c -------------------------------------------------------
|
Chris@10
|
366 @node Plan execution in Fortran, Allocating aligned memory in Fortran, FFTW Fortran type reference, Calling FFTW from Modern Fortran
|
Chris@10
|
367 @section Plan execution in Fortran
|
Chris@10
|
368
|
Chris@10
|
369 In C, in order to use a plan, one normally calls @code{fftw_execute},
|
Chris@10
|
370 which executes the plan to perform the transform on the input/output
|
Chris@10
|
371 arrays passed when the plan was created (@pxref{Using Plans}). The
|
Chris@10
|
372 corresponding subroutine call in modern Fortran is:
|
Chris@10
|
373 @example
|
Chris@10
|
374 call fftw_execute(plan)
|
Chris@10
|
375 @end example
|
Chris@10
|
376 @findex fftw_execute
|
Chris@10
|
377
|
Chris@10
|
378 However, we have had reports that this causes problems with some
|
Chris@10
|
379 recent optimizing Fortran compilers. The problem is, because the
|
Chris@10
|
380 input/output arrays are not passed as explicit arguments to
|
Chris@10
|
381 @code{fftw_execute}, the semantics of Fortran (unlike C) allow the
|
Chris@10
|
382 compiler to assume that the input/output arrays are not changed by
|
Chris@10
|
383 @code{fftw_execute}. As a consequence, certain compilers end up
|
Chris@10
|
384 repositioning the call to @code{fftw_execute}, assuming incorrectly
|
Chris@10
|
385 that it does nothing to the arrays.
|
Chris@10
|
386
|
Chris@10
|
387 There are various workarounds to this, but the safest and simplest
|
Chris@10
|
388 thing is to not use @code{fftw_execute} in Fortran. Instead, use the
|
Chris@10
|
389 functions described in @ref{New-array Execute Functions}, which take
|
Chris@10
|
390 the input/output arrays as explicit arguments. For example, if the
|
Chris@10
|
391 plan is for a complex-data DFT and was created for the arrays
|
Chris@10
|
392 @code{in} and @code{out}, you would do:
|
Chris@10
|
393 @example
|
Chris@10
|
394 call fftw_execute_dft(plan, in, out)
|
Chris@10
|
395 @end example
|
Chris@10
|
396 @findex fftw_execute_dft
|
Chris@10
|
397
|
Chris@10
|
398 There are a few things to be careful of, however:
|
Chris@10
|
399
|
Chris@10
|
400 @itemize @bullet
|
Chris@10
|
401
|
Chris@10
|
402 @item
|
Chris@10
|
403 @findex fftw_execute_dft_r2c
|
Chris@10
|
404 @findex fftw_execute_dft_c2r
|
Chris@10
|
405 @findex fftw_execute_r2r
|
Chris@10
|
406 You must use the correct type of execute function, matching the way
|
Chris@10
|
407 the plan was created. Complex DFT plans should use
|
Chris@10
|
408 @code{fftw_execute_dft}, Real-input (r2c) DFT plans should use use
|
Chris@10
|
409 @code{fftw_execute_dft_r2c}, and real-output (c2r) DFT plans should
|
Chris@10
|
410 use @code{fftw_execute_dft_c2r}. The various r2r plans should use
|
Chris@10
|
411 @code{fftw_execute_r2r}. Fortunately, if you use the wrong one you
|
Chris@10
|
412 will get a compile-time type-mismatch error (unlike legacy Fortran).
|
Chris@10
|
413
|
Chris@10
|
414 @item
|
Chris@10
|
415 You should normally pass the same input/output arrays that were used when
|
Chris@10
|
416 creating the plan. This is always safe.
|
Chris@10
|
417
|
Chris@10
|
418 @item
|
Chris@10
|
419 @emph{If} you pass @emph{different} input/output arrays compared to
|
Chris@10
|
420 those used when creating the plan, you must abide by all the
|
Chris@10
|
421 restrictions of the new-array execute functions (@pxref{New-array
|
Chris@10
|
422 Execute Functions}). The most tricky of these is the
|
Chris@10
|
423 requirement that the new arrays have the same alignment as the
|
Chris@10
|
424 original arrays; the best (and possibly only) way to guarantee this
|
Chris@10
|
425 is to use the @samp{fftw_alloc} functions to allocate your arrays (@pxref{Allocating aligned memory in Fortran}). Alternatively, you can
|
Chris@10
|
426 use the @code{FFTW_UNALIGNED} flag when creating the
|
Chris@10
|
427 plan, in which case the plan does not depend on the alignment, but
|
Chris@10
|
428 this may sacrifice substantial performance on architectures (like x86)
|
Chris@10
|
429 with SIMD instructions (@pxref{SIMD alignment and fftw_malloc}).
|
Chris@10
|
430 @ctindex FFTW_UNALIGNED
|
Chris@10
|
431
|
Chris@10
|
432 @end itemize
|
Chris@10
|
433
|
Chris@10
|
434 @c -------------------------------------------------------
|
Chris@10
|
435 @node Allocating aligned memory in Fortran, Accessing the wisdom API from Fortran, Plan execution in Fortran, Calling FFTW from Modern Fortran
|
Chris@10
|
436 @section Allocating aligned memory in Fortran
|
Chris@10
|
437
|
Chris@10
|
438 @cindex alignment
|
Chris@10
|
439 @findex fftw_alloc_real
|
Chris@10
|
440 @findex fftw_alloc_complex
|
Chris@10
|
441 In order to obtain maximum performance in FFTW, you should store your
|
Chris@10
|
442 data in arrays that have been specially aligned in memory (@pxref{SIMD
|
Chris@10
|
443 alignment and fftw_malloc}). Enforcing alignment also permits you to
|
Chris@10
|
444 safely use the new-array execute functions (@pxref{New-array Execute
|
Chris@10
|
445 Functions}) to apply a given plan to more than one pair of in/out
|
Chris@10
|
446 arrays. Unfortunately, standard Fortran arrays do @emph{not} provide
|
Chris@10
|
447 any alignment guarantees. The @emph{only} way to allocate aligned
|
Chris@10
|
448 memory in standard Fortran is to allocate it with an external C
|
Chris@10
|
449 function, like the @code{fftw_alloc_real} and
|
Chris@10
|
450 @code{fftw_alloc_complex} functions. Fortunately, Fortran 2003 provides
|
Chris@10
|
451 a simple way to associate such allocated memory with a standard Fortran
|
Chris@10
|
452 array pointer that you can then use normally.
|
Chris@10
|
453
|
Chris@10
|
454 We therefore recommend allocating all your input/output arrays using
|
Chris@10
|
455 the following technique:
|
Chris@10
|
456
|
Chris@10
|
457 @enumerate
|
Chris@10
|
458
|
Chris@10
|
459 @item
|
Chris@10
|
460 Declare a @code{pointer}, @code{arr}, to your array of the desired type
|
Chris@10
|
461 and dimensions. For example, @code{real(C_DOUBLE), pointer :: a(:,:)}
|
Chris@10
|
462 for a 2d real array, or @code{complex(C_DOUBLE_COMPLEX), pointer ::
|
Chris@10
|
463 a(:,:,:)} for a 3d complex array.
|
Chris@10
|
464
|
Chris@10
|
465 @item
|
Chris@10
|
466 The number of elements to allocate must be an
|
Chris@10
|
467 @code{integer(C_SIZE_T)}. You can either declare a variable of this
|
Chris@10
|
468 type, e.g. @code{integer(C_SIZE_T) :: sz}, to store the number of
|
Chris@10
|
469 elements to allocate, or you can use the @code{int(..., C_SIZE_T)}
|
Chris@10
|
470 intrinsic function. e.g. set @code{sz = L * M * N} or use
|
Chris@10
|
471 @code{int(L * M * N, C_SIZE_T)} for an @threedims{L,M,N} array.
|
Chris@10
|
472
|
Chris@10
|
473 @item
|
Chris@10
|
474 Declare a @code{type(C_PTR) :: p} to hold the return value from
|
Chris@10
|
475 FFTW's allocation routine. Set @code{p = fftw_alloc_real(sz)} for a real array, or @code{p = fftw_alloc_complex(sz)} for a complex array.
|
Chris@10
|
476
|
Chris@10
|
477 @item
|
Chris@10
|
478 @findex c_f_pointer
|
Chris@10
|
479 Associate your pointer @code{arr} with the allocated memory @code{p}
|
Chris@10
|
480 using the standard @code{c_f_pointer} subroutine: @code{call
|
Chris@10
|
481 c_f_pointer(p, arr, [...dimensions...])}, where
|
Chris@10
|
482 @code{[...dimensions...])} are an array of the dimensions of the array
|
Chris@10
|
483 (in the usual Fortran order). e.g. @code{call c_f_pointer(p, arr,
|
Chris@10
|
484 [L,M,N])} for an @threedims{L,M,N} array. (Alternatively, you can
|
Chris@10
|
485 omit the dimensions argument if you specified the shape explicitly
|
Chris@10
|
486 when declaring @code{arr}.) You can now use @code{arr} as a usual
|
Chris@10
|
487 multidimensional array.
|
Chris@10
|
488
|
Chris@10
|
489 @item
|
Chris@10
|
490 When you are done using the array, deallocate the memory by @code{call
|
Chris@10
|
491 fftw_free(p)} on @code{p}.
|
Chris@10
|
492
|
Chris@10
|
493 @end enumerate
|
Chris@10
|
494
|
Chris@10
|
495 For example, here is how we would allocate an @twodims{L,M} 2d real array:
|
Chris@10
|
496
|
Chris@10
|
497 @example
|
Chris@10
|
498 real(C_DOUBLE), pointer :: arr(:,:)
|
Chris@10
|
499 type(C_PTR) :: p
|
Chris@10
|
500 p = fftw_alloc_real(int(L * M, C_SIZE_T))
|
Chris@10
|
501 call c_f_pointer(p, arr, [L,M])
|
Chris@10
|
502 @emph{...use arr and arr(i,j) as usual...}
|
Chris@10
|
503 call fftw_free(p)
|
Chris@10
|
504 @end example
|
Chris@10
|
505
|
Chris@10
|
506 and here is an @threedims{L,M,N} 3d complex array:
|
Chris@10
|
507
|
Chris@10
|
508 @example
|
Chris@10
|
509 complex(C_DOUBLE_COMPLEX), pointer :: arr(:,:,:)
|
Chris@10
|
510 type(C_PTR) :: p
|
Chris@10
|
511 p = fftw_alloc_complex(int(L * M * N, C_SIZE_T))
|
Chris@10
|
512 call c_f_pointer(p, arr, [L,M,N])
|
Chris@10
|
513 @emph{...use arr and arr(i,j,k) as usual...}
|
Chris@10
|
514 call fftw_free(p)
|
Chris@10
|
515 @end example
|
Chris@10
|
516
|
Chris@10
|
517 See @ref{Reversing array dimensions} for an example allocating a
|
Chris@10
|
518 single array and associating both real and complex array pointers with
|
Chris@10
|
519 it, for in-place real-to-complex transforms.
|
Chris@10
|
520
|
Chris@10
|
521 @c -------------------------------------------------------
|
Chris@10
|
522 @node Accessing the wisdom API from Fortran, Defining an FFTW module, Allocating aligned memory in Fortran, Calling FFTW from Modern Fortran
|
Chris@10
|
523 @section Accessing the wisdom API from Fortran
|
Chris@10
|
524 @cindex wisdom
|
Chris@10
|
525 @cindex saving plans to disk
|
Chris@10
|
526
|
Chris@10
|
527 As explained in @ref{Words of Wisdom-Saving Plans}, FFTW provides a
|
Chris@10
|
528 ``wisdom'' API for saving plans to disk so that they can be recreated
|
Chris@10
|
529 quickly. The C API for exporting (@pxref{Wisdom Export}) and
|
Chris@10
|
530 importing (@pxref{Wisdom Import}) wisdom is somewhat tricky to use
|
Chris@10
|
531 from Fortran, however, because of differences in file I/O and string
|
Chris@10
|
532 types between C and Fortran.
|
Chris@10
|
533
|
Chris@10
|
534 @menu
|
Chris@10
|
535 * Wisdom File Export/Import from Fortran::
|
Chris@10
|
536 * Wisdom String Export/Import from Fortran::
|
Chris@10
|
537 * Wisdom Generic Export/Import from Fortran::
|
Chris@10
|
538 @end menu
|
Chris@10
|
539
|
Chris@10
|
540 @c =========>
|
Chris@10
|
541 @node Wisdom File Export/Import from Fortran, Wisdom String Export/Import from Fortran, Accessing the wisdom API from Fortran, Accessing the wisdom API from Fortran
|
Chris@10
|
542 @subsection Wisdom File Export/Import from Fortran
|
Chris@10
|
543
|
Chris@10
|
544 @findex fftw_import wisdom_from_filename
|
Chris@10
|
545 @findex fftw_export_wisdom_to_filename
|
Chris@10
|
546 The easiest way to export and import wisdom is to do so using
|
Chris@10
|
547 @code{fftw_export_wisdom_to_filename} and
|
Chris@10
|
548 @code{fftw_wisdom_from_filename}. The only trick is that these
|
Chris@10
|
549 require you to pass a C string, which is an array of type
|
Chris@10
|
550 @code{CHARACTER(C_CHAR)} that is terminated by @code{C_NULL_CHAR}.
|
Chris@10
|
551 You can call them like this:
|
Chris@10
|
552
|
Chris@10
|
553 @example
|
Chris@10
|
554 integer(C_INT) :: ret
|
Chris@10
|
555 ret = fftw_export_wisdom_to_filename(C_CHAR_'my_wisdom.dat' // C_NULL_CHAR)
|
Chris@10
|
556 if (ret .eq. 0) stop 'error exporting wisdom to file'
|
Chris@10
|
557 ret = fftw_import_wisdom_from_filename(C_CHAR_'my_wisdom.dat' // C_NULL_CHAR)
|
Chris@10
|
558 if (ret .eq. 0) stop 'error importing wisdom from file'
|
Chris@10
|
559 @end example
|
Chris@10
|
560
|
Chris@10
|
561 Note that prepending @samp{C_CHAR_} is needed to specify that the
|
Chris@10
|
562 literal string is of kind @code{C_CHAR}, and we null-terminate the
|
Chris@10
|
563 string by appending @samp{// C_NULL_CHAR}. These functions return an
|
Chris@10
|
564 @code{integer(C_INT)} (@code{ret}) which is @code{0} if an error
|
Chris@10
|
565 occurred during export/import and nonzero otherwise.
|
Chris@10
|
566
|
Chris@10
|
567 It is also possible to use the lower-level routines
|
Chris@10
|
568 @code{fftw_export_wisdom_to_file} and
|
Chris@10
|
569 @code{fftw_import_wisdom_from_file}, which accept parameters of the C
|
Chris@10
|
570 type @code{FILE*}, expressed in Fortran as @code{type(C_PTR)}.
|
Chris@10
|
571 However, you are then responsible for creating the @code{FILE*}
|
Chris@10
|
572 yourself. You can do this by using @code{iso_c_binding} to define
|
Chris@10
|
573 Fortran intefaces for the C library functions @code{fopen} and
|
Chris@10
|
574 @code{fclose}, which is a bit strange in Fortran but workable.
|
Chris@10
|
575
|
Chris@10
|
576 @c =========>
|
Chris@10
|
577 @node Wisdom String Export/Import from Fortran, Wisdom Generic Export/Import from Fortran, Wisdom File Export/Import from Fortran, Accessing the wisdom API from Fortran
|
Chris@10
|
578 @subsection Wisdom String Export/Import from Fortran
|
Chris@10
|
579
|
Chris@10
|
580 @findex fftw_export_wisdom_to_string
|
Chris@10
|
581 Dealing with FFTW's C string export/import is a bit more painful. In
|
Chris@10
|
582 particular, the @code{fftw_export_wisdom_to_string} function requires
|
Chris@10
|
583 you to deal with a dynamically allocated C string. To get its length,
|
Chris@10
|
584 you must define an interface to the C @code{strlen} function, and to
|
Chris@10
|
585 deallocate it you must define an interface to C @code{free}:
|
Chris@10
|
586
|
Chris@10
|
587 @example
|
Chris@10
|
588 use, intrinsic :: iso_c_binding
|
Chris@10
|
589 interface
|
Chris@10
|
590 integer(C_INT) function strlen(s) bind(C, name='strlen')
|
Chris@10
|
591 import
|
Chris@10
|
592 type(C_PTR), value :: s
|
Chris@10
|
593 end function strlen
|
Chris@10
|
594 subroutine free(p) bind(C, name='free')
|
Chris@10
|
595 import
|
Chris@10
|
596 type(C_PTR), value :: p
|
Chris@10
|
597 end subroutine free
|
Chris@10
|
598 end interface
|
Chris@10
|
599 @end example
|
Chris@10
|
600
|
Chris@10
|
601 Given these definitions, you can then export wisdom to a Fortran
|
Chris@10
|
602 character array:
|
Chris@10
|
603
|
Chris@10
|
604 @example
|
Chris@10
|
605 character(C_CHAR), pointer :: s(:)
|
Chris@10
|
606 integer(C_SIZE_T) :: slen
|
Chris@10
|
607 type(C_PTR) :: p
|
Chris@10
|
608 p = fftw_export_wisdom_to_string()
|
Chris@10
|
609 if (.not. c_associated(p)) stop 'error exporting wisdom'
|
Chris@10
|
610 slen = strlen(p)
|
Chris@10
|
611 call c_f_pointer(p, s, [slen+1])
|
Chris@10
|
612 ...
|
Chris@10
|
613 call free(p)
|
Chris@10
|
614 @end example
|
Chris@10
|
615 @findex c_associated
|
Chris@10
|
616 @findex c_f_pointer
|
Chris@10
|
617
|
Chris@10
|
618 Note that @code{slen} is the length of the C string, but the length of
|
Chris@10
|
619 the array is @code{slen+1} because it includes the terminating null
|
Chris@10
|
620 character. (You can omit the @samp{+1} if you don't want Fortran to
|
Chris@10
|
621 know about the null character.) The standard @code{c_associated} function
|
Chris@10
|
622 checks whether @code{p} is a null pointer, which is returned by
|
Chris@10
|
623 @code{fftw_export_wisdom_to_string} if there was an error.
|
Chris@10
|
624
|
Chris@10
|
625 @findex fftw_import_wisdom_from_string
|
Chris@10
|
626 To import wisdom from a string, use
|
Chris@10
|
627 @code{fftw_import_wisdom_from_string} as usual; note that the argument
|
Chris@10
|
628 of this function must be a @code{character(C_CHAR)} that is terminated
|
Chris@10
|
629 by the @code{C_NULL_CHAR} character, like the @code{s} array above.
|
Chris@10
|
630
|
Chris@10
|
631 @c =========>
|
Chris@10
|
632 @node Wisdom Generic Export/Import from Fortran, , Wisdom String Export/Import from Fortran, Accessing the wisdom API from Fortran
|
Chris@10
|
633 @subsection Wisdom Generic Export/Import from Fortran
|
Chris@10
|
634
|
Chris@10
|
635 The most generic wisdom export/import functions allow you to provide
|
Chris@10
|
636 an arbitrary callback function to read/write one character at a time
|
Chris@10
|
637 in any way you want. However, your callback function must be written
|
Chris@10
|
638 in a special way, using the @code{bind(C)} attribute to be passed to a
|
Chris@10
|
639 C interface.
|
Chris@10
|
640
|
Chris@10
|
641 @findex fftw_export_wisdom
|
Chris@10
|
642 In particular, to call the generic wisdom export function
|
Chris@10
|
643 @code{fftw_export_wisdom}, you would write a callback subroutine of the form:
|
Chris@10
|
644
|
Chris@10
|
645 @example
|
Chris@10
|
646 subroutine my_write_char(c, p) bind(C)
|
Chris@10
|
647 use, intrinsic :: iso_c_binding
|
Chris@10
|
648 character(C_CHAR), value :: c
|
Chris@10
|
649 type(C_PTR), value :: p
|
Chris@10
|
650 @emph{...write c...}
|
Chris@10
|
651 end subroutine my_write_char
|
Chris@10
|
652 @end example
|
Chris@10
|
653
|
Chris@10
|
654 Given such a subroutine (along with the corresponding interface definition), you could then export wisdom using:
|
Chris@10
|
655
|
Chris@10
|
656 @findex c_funloc
|
Chris@10
|
657 @example
|
Chris@10
|
658 call fftw_export_wisdom(c_funloc(my_write_char), p)
|
Chris@10
|
659 @end example
|
Chris@10
|
660
|
Chris@10
|
661 @findex c_loc
|
Chris@10
|
662 @findex c_f_pointer
|
Chris@10
|
663 The standard @code{c_funloc} intrinsic converts a Fortran
|
Chris@10
|
664 @code{bind(C)} subroutine into a C function pointer. The parameter
|
Chris@10
|
665 @code{p} is a @code{type(C_PTR)} to any arbitrary data that you want
|
Chris@10
|
666 to pass to @code{my_write_char} (or @code{C_NULL_PTR} if none). (Note
|
Chris@10
|
667 that you can get a C pointer to Fortran data using the intrinsic
|
Chris@10
|
668 @code{c_loc}, and convert it back to a Fortran pointer in
|
Chris@10
|
669 @code{my_write_char} using @code{c_f_pointer}.)
|
Chris@10
|
670
|
Chris@10
|
671 Similarly, to use the generic @code{fftw_import_wisdom}, you would
|
Chris@10
|
672 define a callback function of the form:
|
Chris@10
|
673
|
Chris@10
|
674 @findex fftw_import_wisdom
|
Chris@10
|
675 @example
|
Chris@10
|
676 integer(C_INT) function my_read_char(p) bind(C)
|
Chris@10
|
677 use, intrinsic :: iso_c_binding
|
Chris@10
|
678 type(C_PTR), value :: p
|
Chris@10
|
679 character :: c
|
Chris@10
|
680 @emph{...read a character c...}
|
Chris@10
|
681 my_read_char = ichar(c, C_INT)
|
Chris@10
|
682 end function my_read_char
|
Chris@10
|
683
|
Chris@10
|
684 ....
|
Chris@10
|
685
|
Chris@10
|
686 integer(C_INT) :: ret
|
Chris@10
|
687 ret = fftw_import_wisdom(c_funloc(my_read_char), p)
|
Chris@10
|
688 if (ret .eq. 0) stop 'error importing wisdom'
|
Chris@10
|
689 @end example
|
Chris@10
|
690
|
Chris@10
|
691 Your function can return @code{-1} if the end of the input is reached.
|
Chris@10
|
692 Again, @code{p} is an arbitrary @code{type(C_PTR} that is passed
|
Chris@10
|
693 through to your function. @code{fftw_import_wisdom} returns @code{0}
|
Chris@10
|
694 if an error occurred and nonzero otherwise.
|
Chris@10
|
695
|
Chris@10
|
696 @c -------------------------------------------------------
|
Chris@10
|
697 @node Defining an FFTW module, , Accessing the wisdom API from Fortran, Calling FFTW from Modern Fortran
|
Chris@10
|
698 @section Defining an FFTW module
|
Chris@10
|
699
|
Chris@10
|
700 Rather than using the @code{include} statement to include the
|
Chris@10
|
701 @code{fftw3.f03} interface file in any subroutine where you want to
|
Chris@10
|
702 use FFTW, you might prefer to define an FFTW Fortran module. FFTW
|
Chris@10
|
703 does not install itself as a module, primarily because
|
Chris@10
|
704 @code{fftw3.f03} can be shared between different Fortran compilers while
|
Chris@10
|
705 modules (in general) cannot. However, it is trivial to define your
|
Chris@10
|
706 own FFTW module if you want. Just create a file containing:
|
Chris@10
|
707
|
Chris@10
|
708 @example
|
Chris@10
|
709 module FFTW3
|
Chris@10
|
710 use, intrinsic :: iso_c_binding
|
Chris@10
|
711 include 'fftw3.f03'
|
Chris@10
|
712 end module
|
Chris@10
|
713 @end example
|
Chris@10
|
714
|
Chris@10
|
715 Compile this file into a module as usual for your compiler (e.g. with
|
Chris@10
|
716 @code{gfortran -c} you will get a file @code{fftw3.mod}). Now,
|
Chris@10
|
717 instead of @code{include 'fftw3.f03'}, whenever you want to use FFTW
|
Chris@10
|
718 routines you can just do:
|
Chris@10
|
719
|
Chris@10
|
720 @example
|
Chris@10
|
721 use FFTW3
|
Chris@10
|
722 @end example
|
Chris@10
|
723
|
Chris@10
|
724 as usual for Fortran modules. (You still need to link to the FFTW
|
Chris@10
|
725 library, of course.)
|