(git:374b731)
Loading...
Searching...
No Matches
pw_types.F
Go to the documentation of this file.
1!--------------------------------------------------------------------------------------------------!
2! CP2K: A general program to perform molecular dynamics simulations !
3! Copyright 2000-2024 CP2K developers group <https://cp2k.org> !
4! !
5! SPDX-License-Identifier: GPL-2.0-or-later !
6!--------------------------------------------------------------------------------------------------!
7
8! **************************************************************************************************
9!> \note
10!> If parallel mode is distributed certain combination of
11!> "in_use" and "in_space" can not be used.
12!> For performance reasons it would be better to have the loops
13!> over g-vectros in the gather/scatter routines in new subprograms
14!> with the actual arrays (also the addressing) in the parameter list
15!> \par History
16!> JGH (29-Dec-2000) : Changes for parallel use
17!> JGH (13-Mar-2001) : added timing calls
18!> JGH (26-Feb-2003) : OpenMP enabled
19!> JGH (17-Nov-2007) : Removed mass arrays
20!> JGH (01-Dec-2007) : Removed and renamed routines
21!> 03.2008 [tlaino] : Splitting pw_types into pw_types and pw_methods
22!> \author apsi
23! **************************************************************************************************
25
27 USE kinds, ONLY: dp
29 USE pw_grids, ONLY: pw_grid_release, &
31#include "../base/base_uses.f90"
32
33 IMPLICIT NONE
34
35
36
37
38 PRIVATE
47
48! **************************************************************************************************
50 REAL(kind=dp), DIMENSION(:), CONTIGUOUS, POINTER :: array => null()
51 TYPE(pw_grid_type), POINTER :: pw_grid => null()
52 CONTAINS
53 PROCEDURE, PUBLIC, non_overridable :: create => pw_create_r1d_rs
54 PROCEDURE, PUBLIC, non_overridable :: release => pw_release_r1d_rs
55 END TYPE pw_r1d_rs_type
56
57! **************************************************************************************************
59 TYPE(pw_r1d_rs_type), POINTER :: pw => null()
60 END TYPE pw_r1d_rs_p_type
61! **************************************************************************************************
63 REAL(kind=dp), DIMENSION(:, :, :), CONTIGUOUS, POINTER :: array => null()
64 TYPE(pw_grid_type), POINTER :: pw_grid => null()
65 CONTAINS
66 PROCEDURE, PUBLIC, non_overridable :: create => pw_create_r3d_rs
67 PROCEDURE, PUBLIC, non_overridable :: release => pw_release_r3d_rs
68 END TYPE pw_r3d_rs_type
69
70! **************************************************************************************************
72 TYPE(pw_r3d_rs_type), POINTER :: pw => null()
73 END TYPE pw_r3d_rs_p_type
74! **************************************************************************************************
76 COMPLEX(KIND=dp), DIMENSION(:), CONTIGUOUS, POINTER :: array => null()
77 TYPE(pw_grid_type), POINTER :: pw_grid => null()
78 CONTAINS
79 PROCEDURE, PUBLIC, non_overridable :: create => pw_create_c1d_rs
80 PROCEDURE, PUBLIC, non_overridable :: release => pw_release_c1d_rs
81 END TYPE pw_c1d_rs_type
82
83! **************************************************************************************************
85 TYPE(pw_c1d_rs_type), POINTER :: pw => null()
86 END TYPE pw_c1d_rs_p_type
87! **************************************************************************************************
89 COMPLEX(KIND=dp), DIMENSION(:, :, :), CONTIGUOUS, POINTER :: array => null()
90 TYPE(pw_grid_type), POINTER :: pw_grid => null()
91 CONTAINS
92 PROCEDURE, PUBLIC, non_overridable :: create => pw_create_c3d_rs
93 PROCEDURE, PUBLIC, non_overridable :: release => pw_release_c3d_rs
94 END TYPE pw_c3d_rs_type
95
96! **************************************************************************************************
98 TYPE(pw_c3d_rs_type), POINTER :: pw => null()
99 END TYPE pw_c3d_rs_p_type
100! **************************************************************************************************
102 REAL(kind=dp), DIMENSION(:), CONTIGUOUS, POINTER :: array => null()
103 TYPE(pw_grid_type), POINTER :: pw_grid => null()
104 CONTAINS
105 PROCEDURE, PUBLIC, non_overridable :: create => pw_create_r1d_gs
106 PROCEDURE, PUBLIC, non_overridable :: release => pw_release_r1d_gs
107 END TYPE pw_r1d_gs_type
108
109! **************************************************************************************************
111 TYPE(pw_r1d_gs_type), POINTER :: pw => null()
112 END TYPE pw_r1d_gs_p_type
113! **************************************************************************************************
115 REAL(kind=dp), DIMENSION(:, :, :), CONTIGUOUS, POINTER :: array => null()
116 TYPE(pw_grid_type), POINTER :: pw_grid => null()
117 CONTAINS
118 PROCEDURE, PUBLIC, non_overridable :: create => pw_create_r3d_gs
119 PROCEDURE, PUBLIC, non_overridable :: release => pw_release_r3d_gs
120 END TYPE pw_r3d_gs_type
121
122! **************************************************************************************************
124 TYPE(pw_r3d_gs_type), POINTER :: pw => null()
125 END TYPE pw_r3d_gs_p_type
126! **************************************************************************************************
128 COMPLEX(KIND=dp), DIMENSION(:), CONTIGUOUS, POINTER :: array => null()
129 TYPE(pw_grid_type), POINTER :: pw_grid => null()
130 CONTAINS
131 PROCEDURE, PUBLIC, non_overridable :: create => pw_create_c1d_gs
132 PROCEDURE, PUBLIC, non_overridable :: release => pw_release_c1d_gs
133 END TYPE pw_c1d_gs_type
134
135! **************************************************************************************************
137 TYPE(pw_c1d_gs_type), POINTER :: pw => null()
138 END TYPE pw_c1d_gs_p_type
139! **************************************************************************************************
141 COMPLEX(KIND=dp), DIMENSION(:, :, :), CONTIGUOUS, POINTER :: array => null()
142 TYPE(pw_grid_type), POINTER :: pw_grid => null()
143 CONTAINS
144 PROCEDURE, PUBLIC, non_overridable :: create => pw_create_c3d_gs
145 PROCEDURE, PUBLIC, non_overridable :: release => pw_release_c3d_gs
146 END TYPE pw_c3d_gs_type
147
148! **************************************************************************************************
150 TYPE(pw_c3d_gs_type), POINTER :: pw => null()
151 END TYPE pw_c3d_gs_p_type
152
153 CHARACTER(len=*), PARAMETER, PRIVATE :: modulen = 'pw_types'
154 LOGICAL, PARAMETER, PRIVATE :: debug_this_module = .false.
155
156CONTAINS
157! **************************************************************************************************
158!> \brief releases the given pw
159!> \param pw the pw to release
160!> \par History
161!> 04.2003 created [fawzi]
162!> \author fawzi
163!> \note
164!> see doc/ReferenceCounting.html
165! **************************************************************************************************
166 SUBROUTINE pw_release_r1d_rs (pw)
167 CLASS(pw_r1d_rs_type), INTENT(INOUT) :: pw
168
169 IF (ASSOCIATED(pw%array)) DEALLOCATE (pw%array)
170 CALL pw_grid_release(pw%pw_grid)
171 END SUBROUTINE pw_release_r1d_rs
172
173! **************************************************************************************************
174!> \brief allocates and initializes pw_r3d_rs_type
175!> \param pw the type that will bw allocated and initialized
176!> \param pw_grid ...
177!> \param array_ptr pointer with to data
178!> \par History
179!> 11.2003 created [fawzi]
180!> \author fawzi
181! **************************************************************************************************
182 SUBROUTINE pw_create_r1d_rs (pw, pw_grid, array_ptr)
183 CLASS(pw_r1d_rs_type), INTENT(INOUT) :: pw
184 TYPE(pw_grid_type), INTENT(IN), POINTER :: pw_grid
185 REAL(kind=dp), DIMENSION(:), CONTIGUOUS, INTENT(IN), OPTIONAL, POINTER :: array_ptr
186
187 CHARACTER(len=*), PARAMETER :: routinen = 'pw_create_r1d'
188
189 INTEGER :: handle
190
191 CALL timeset(routinen, handle)
192
193 ! Ensure a clean grid to prevent memory leaks
194 CALL pw%release()
195
196 pw%pw_grid => pw_grid
197 CALL pw_grid_retain(pw%pw_grid)
198
199 IF (PRESENT(array_ptr)) THEN
200 IF (ASSOCIATED(array_ptr)) THEN
201 cpassert(SIZE(array_ptr) == pw%pw_grid%ngpts_cut_local)
202 pw%array(1:pw%pw_grid%ngpts_cut_local) => array_ptr
203 END IF
204 END IF
205 IF (.NOT. ASSOCIATED(pw%array)) ALLOCATE (pw%array(pw%pw_grid%ngpts_cut_local))
206 CALL timestop(handle)
207 END SUBROUTINE pw_create_r1d_rs
208! **************************************************************************************************
209!> \brief releases the given pw
210!> \param pw the pw to release
211!> \par History
212!> 04.2003 created [fawzi]
213!> \author fawzi
214!> \note
215!> see doc/ReferenceCounting.html
216! **************************************************************************************************
217 SUBROUTINE pw_release_r3d_rs (pw)
218 CLASS(pw_r3d_rs_type), INTENT(INOUT) :: pw
219
220 IF (ASSOCIATED(pw%array)) DEALLOCATE (pw%array)
221 CALL pw_grid_release(pw%pw_grid)
222 END SUBROUTINE pw_release_r3d_rs
223
224! **************************************************************************************************
225!> \brief allocates and initializes pw_r3d_rs_type
226!> \param pw the type that will bw allocated and initialized
227!> \param pw_grid ...
228!> \param array_ptr pointer with to data
229!> \par History
230!> 11.2003 created [fawzi]
231!> \author fawzi
232! **************************************************************************************************
233 SUBROUTINE pw_create_r3d_rs (pw, pw_grid, array_ptr)
234 CLASS(pw_r3d_rs_type), INTENT(INOUT) :: pw
235 TYPE(pw_grid_type), INTENT(IN), POINTER :: pw_grid
236 REAL(kind=dp), DIMENSION(:, :, :), CONTIGUOUS, INTENT(IN), OPTIONAL, POINTER :: array_ptr
237
238 CHARACTER(len=*), PARAMETER :: routinen = 'pw_create_r3d'
239
240 INTEGER :: handle
241
242 CALL timeset(routinen, handle)
243
244 ! Ensure a clean grid to prevent memory leaks
245 CALL pw%release()
246
247 pw%pw_grid => pw_grid
248 CALL pw_grid_retain(pw%pw_grid)
249
250 associate(bounds => pw%pw_grid%bounds_local)
251 IF (PRESENT(array_ptr)) THEN
252 IF (ASSOCIATED(array_ptr)) THEN
253 IF (all(bounds(1, :) <= bounds(2, :))) THEN
254 cpassert(all(lbound(array_ptr) == bounds(1, :)))
255 cpassert(all(ubound(array_ptr) == bounds(2, :)))
256 END IF
257 pw%array => array_ptr
258 END IF
259 END IF
260 IF (.NOT. ASSOCIATED(pw%array)) THEN
261 ALLOCATE (pw%array( &
262 bounds(1, 1):bounds(2, 1), &
263 bounds(1, 2):bounds(2, 2), &
264 bounds(1, 3):bounds(2, 3)))
265 END IF
266 END associate
267 CALL timestop(handle)
268 END SUBROUTINE pw_create_r3d_rs
269! **************************************************************************************************
270!> \brief releases the given pw
271!> \param pw the pw to release
272!> \par History
273!> 04.2003 created [fawzi]
274!> \author fawzi
275!> \note
276!> see doc/ReferenceCounting.html
277! **************************************************************************************************
278 SUBROUTINE pw_release_c1d_rs (pw)
279 CLASS(pw_c1d_rs_type), INTENT(INOUT) :: pw
280
281 IF (ASSOCIATED(pw%array)) DEALLOCATE (pw%array)
282 CALL pw_grid_release(pw%pw_grid)
283 END SUBROUTINE pw_release_c1d_rs
284
285! **************************************************************************************************
286!> \brief allocates and initializes pw_r3d_rs_type
287!> \param pw the type that will bw allocated and initialized
288!> \param pw_grid ...
289!> \param array_ptr pointer with to data
290!> \par History
291!> 11.2003 created [fawzi]
292!> \author fawzi
293! **************************************************************************************************
294 SUBROUTINE pw_create_c1d_rs (pw, pw_grid, array_ptr)
295 CLASS(pw_c1d_rs_type), INTENT(INOUT) :: pw
296 TYPE(pw_grid_type), INTENT(IN), POINTER :: pw_grid
297 COMPLEX(KIND=dp), DIMENSION(:), CONTIGUOUS, INTENT(IN), OPTIONAL, POINTER :: array_ptr
298
299 CHARACTER(len=*), PARAMETER :: routinen = 'pw_create_c1d'
300
301 INTEGER :: handle
302
303 CALL timeset(routinen, handle)
304
305 ! Ensure a clean grid to prevent memory leaks
306 CALL pw%release()
307
308 pw%pw_grid => pw_grid
309 CALL pw_grid_retain(pw%pw_grid)
310
311 IF (PRESENT(array_ptr)) THEN
312 IF (ASSOCIATED(array_ptr)) THEN
313 cpassert(SIZE(array_ptr) == pw%pw_grid%ngpts_cut_local)
314 pw%array(1:pw%pw_grid%ngpts_cut_local) => array_ptr
315 END IF
316 END IF
317 IF (.NOT. ASSOCIATED(pw%array)) ALLOCATE (pw%array(pw%pw_grid%ngpts_cut_local))
318 CALL timestop(handle)
319 END SUBROUTINE pw_create_c1d_rs
320! **************************************************************************************************
321!> \brief releases the given pw
322!> \param pw the pw to release
323!> \par History
324!> 04.2003 created [fawzi]
325!> \author fawzi
326!> \note
327!> see doc/ReferenceCounting.html
328! **************************************************************************************************
329 SUBROUTINE pw_release_c3d_rs (pw)
330 CLASS(pw_c3d_rs_type), INTENT(INOUT) :: pw
331
332 IF (ASSOCIATED(pw%array)) DEALLOCATE (pw%array)
333 CALL pw_grid_release(pw%pw_grid)
334 END SUBROUTINE pw_release_c3d_rs
335
336! **************************************************************************************************
337!> \brief allocates and initializes pw_r3d_rs_type
338!> \param pw the type that will bw allocated and initialized
339!> \param pw_grid ...
340!> \param array_ptr pointer with to data
341!> \par History
342!> 11.2003 created [fawzi]
343!> \author fawzi
344! **************************************************************************************************
345 SUBROUTINE pw_create_c3d_rs (pw, pw_grid, array_ptr)
346 CLASS(pw_c3d_rs_type), INTENT(INOUT) :: pw
347 TYPE(pw_grid_type), INTENT(IN), POINTER :: pw_grid
348 COMPLEX(KIND=dp), DIMENSION(:, :, :), CONTIGUOUS, INTENT(IN), OPTIONAL, POINTER :: array_ptr
349
350 CHARACTER(len=*), PARAMETER :: routinen = 'pw_create_c3d'
351
352 INTEGER :: handle
353
354 CALL timeset(routinen, handle)
355
356 ! Ensure a clean grid to prevent memory leaks
357 CALL pw%release()
358
359 pw%pw_grid => pw_grid
360 CALL pw_grid_retain(pw%pw_grid)
361
362 associate(bounds => pw%pw_grid%bounds_local)
363 IF (PRESENT(array_ptr)) THEN
364 IF (ASSOCIATED(array_ptr)) THEN
365 IF (all(bounds(1, :) <= bounds(2, :))) THEN
366 cpassert(all(lbound(array_ptr) == bounds(1, :)))
367 cpassert(all(ubound(array_ptr) == bounds(2, :)))
368 END IF
369 pw%array => array_ptr
370 END IF
371 END IF
372 IF (.NOT. ASSOCIATED(pw%array)) THEN
373 ALLOCATE (pw%array( &
374 bounds(1, 1):bounds(2, 1), &
375 bounds(1, 2):bounds(2, 2), &
376 bounds(1, 3):bounds(2, 3)))
377 END IF
378 END associate
379 CALL timestop(handle)
380 END SUBROUTINE pw_create_c3d_rs
381! **************************************************************************************************
382!> \brief releases the given pw
383!> \param pw the pw to release
384!> \par History
385!> 04.2003 created [fawzi]
386!> \author fawzi
387!> \note
388!> see doc/ReferenceCounting.html
389! **************************************************************************************************
390 SUBROUTINE pw_release_r1d_gs (pw)
391 CLASS(pw_r1d_gs_type), INTENT(INOUT) :: pw
392
393 IF (ASSOCIATED(pw%array)) DEALLOCATE (pw%array)
394 CALL pw_grid_release(pw%pw_grid)
395 END SUBROUTINE pw_release_r1d_gs
396
397! **************************************************************************************************
398!> \brief allocates and initializes pw_r3d_rs_type
399!> \param pw the type that will bw allocated and initialized
400!> \param pw_grid ...
401!> \param array_ptr pointer with to data
402!> \par History
403!> 11.2003 created [fawzi]
404!> \author fawzi
405! **************************************************************************************************
406 SUBROUTINE pw_create_r1d_gs (pw, pw_grid, array_ptr)
407 CLASS(pw_r1d_gs_type), INTENT(INOUT) :: pw
408 TYPE(pw_grid_type), INTENT(IN), POINTER :: pw_grid
409 REAL(kind=dp), DIMENSION(:), CONTIGUOUS, INTENT(IN), OPTIONAL, POINTER :: array_ptr
410
411 CHARACTER(len=*), PARAMETER :: routinen = 'pw_create_r1d'
412
413 INTEGER :: handle
414
415 CALL timeset(routinen, handle)
416
417 ! Ensure a clean grid to prevent memory leaks
418 CALL pw%release()
419
420 pw%pw_grid => pw_grid
421 CALL pw_grid_retain(pw%pw_grid)
422
423 IF (PRESENT(array_ptr)) THEN
424 IF (ASSOCIATED(array_ptr)) THEN
425 cpassert(SIZE(array_ptr) == pw%pw_grid%ngpts_cut_local)
426 pw%array(1:pw%pw_grid%ngpts_cut_local) => array_ptr
427 END IF
428 END IF
429 IF (.NOT. ASSOCIATED(pw%array)) ALLOCATE (pw%array(pw%pw_grid%ngpts_cut_local))
430 CALL timestop(handle)
431 END SUBROUTINE pw_create_r1d_gs
432! **************************************************************************************************
433!> \brief releases the given pw
434!> \param pw the pw to release
435!> \par History
436!> 04.2003 created [fawzi]
437!> \author fawzi
438!> \note
439!> see doc/ReferenceCounting.html
440! **************************************************************************************************
441 SUBROUTINE pw_release_r3d_gs (pw)
442 CLASS(pw_r3d_gs_type), INTENT(INOUT) :: pw
443
444 IF (ASSOCIATED(pw%array)) DEALLOCATE (pw%array)
445 CALL pw_grid_release(pw%pw_grid)
446 END SUBROUTINE pw_release_r3d_gs
447
448! **************************************************************************************************
449!> \brief allocates and initializes pw_r3d_rs_type
450!> \param pw the type that will bw allocated and initialized
451!> \param pw_grid ...
452!> \param array_ptr pointer with to data
453!> \par History
454!> 11.2003 created [fawzi]
455!> \author fawzi
456! **************************************************************************************************
457 SUBROUTINE pw_create_r3d_gs (pw, pw_grid, array_ptr)
458 CLASS(pw_r3d_gs_type), INTENT(INOUT) :: pw
459 TYPE(pw_grid_type), INTENT(IN), POINTER :: pw_grid
460 REAL(kind=dp), DIMENSION(:, :, :), CONTIGUOUS, INTENT(IN), OPTIONAL, POINTER :: array_ptr
461
462 CHARACTER(len=*), PARAMETER :: routinen = 'pw_create_r3d'
463
464 INTEGER :: handle
465
466 CALL timeset(routinen, handle)
467
468 ! Ensure a clean grid to prevent memory leaks
469 CALL pw%release()
470
471 pw%pw_grid => pw_grid
472 CALL pw_grid_retain(pw%pw_grid)
473
474 associate(bounds => pw%pw_grid%bounds_local)
475 IF (PRESENT(array_ptr)) THEN
476 IF (ASSOCIATED(array_ptr)) THEN
477 IF (all(bounds(1, :) <= bounds(2, :))) THEN
478 cpassert(all(lbound(array_ptr) == bounds(1, :)))
479 cpassert(all(ubound(array_ptr) == bounds(2, :)))
480 END IF
481 pw%array => array_ptr
482 END IF
483 END IF
484 IF (.NOT. ASSOCIATED(pw%array)) THEN
485 ALLOCATE (pw%array( &
486 bounds(1, 1):bounds(2, 1), &
487 bounds(1, 2):bounds(2, 2), &
488 bounds(1, 3):bounds(2, 3)))
489 END IF
490 END associate
491 CALL timestop(handle)
492 END SUBROUTINE pw_create_r3d_gs
493! **************************************************************************************************
494!> \brief releases the given pw
495!> \param pw the pw to release
496!> \par History
497!> 04.2003 created [fawzi]
498!> \author fawzi
499!> \note
500!> see doc/ReferenceCounting.html
501! **************************************************************************************************
502 SUBROUTINE pw_release_c1d_gs (pw)
503 CLASS(pw_c1d_gs_type), INTENT(INOUT) :: pw
504
505 IF (ASSOCIATED(pw%array)) DEALLOCATE (pw%array)
506 CALL pw_grid_release(pw%pw_grid)
507 END SUBROUTINE pw_release_c1d_gs
508
509! **************************************************************************************************
510!> \brief allocates and initializes pw_r3d_rs_type
511!> \param pw the type that will bw allocated and initialized
512!> \param pw_grid ...
513!> \param array_ptr pointer with to data
514!> \par History
515!> 11.2003 created [fawzi]
516!> \author fawzi
517! **************************************************************************************************
518 SUBROUTINE pw_create_c1d_gs (pw, pw_grid, array_ptr)
519 CLASS(pw_c1d_gs_type), INTENT(INOUT) :: pw
520 TYPE(pw_grid_type), INTENT(IN), POINTER :: pw_grid
521 COMPLEX(KIND=dp), DIMENSION(:), CONTIGUOUS, INTENT(IN), OPTIONAL, POINTER :: array_ptr
522
523 CHARACTER(len=*), PARAMETER :: routinen = 'pw_create_c1d'
524
525 INTEGER :: handle
526
527 CALL timeset(routinen, handle)
528
529 ! Ensure a clean grid to prevent memory leaks
530 CALL pw%release()
531
532 pw%pw_grid => pw_grid
533 CALL pw_grid_retain(pw%pw_grid)
534
535 IF (PRESENT(array_ptr)) THEN
536 IF (ASSOCIATED(array_ptr)) THEN
537 cpassert(SIZE(array_ptr) == pw%pw_grid%ngpts_cut_local)
538 pw%array(1:pw%pw_grid%ngpts_cut_local) => array_ptr
539 END IF
540 END IF
541 IF (.NOT. ASSOCIATED(pw%array)) ALLOCATE (pw%array(pw%pw_grid%ngpts_cut_local))
542 CALL timestop(handle)
543 END SUBROUTINE pw_create_c1d_gs
544! **************************************************************************************************
545!> \brief releases the given pw
546!> \param pw the pw to release
547!> \par History
548!> 04.2003 created [fawzi]
549!> \author fawzi
550!> \note
551!> see doc/ReferenceCounting.html
552! **************************************************************************************************
553 SUBROUTINE pw_release_c3d_gs (pw)
554 CLASS(pw_c3d_gs_type), INTENT(INOUT) :: pw
555
556 IF (ASSOCIATED(pw%array)) DEALLOCATE (pw%array)
557 CALL pw_grid_release(pw%pw_grid)
558 END SUBROUTINE pw_release_c3d_gs
559
560! **************************************************************************************************
561!> \brief allocates and initializes pw_r3d_rs_type
562!> \param pw the type that will bw allocated and initialized
563!> \param pw_grid ...
564!> \param array_ptr pointer with to data
565!> \par History
566!> 11.2003 created [fawzi]
567!> \author fawzi
568! **************************************************************************************************
569 SUBROUTINE pw_create_c3d_gs (pw, pw_grid, array_ptr)
570 CLASS(pw_c3d_gs_type), INTENT(INOUT) :: pw
571 TYPE(pw_grid_type), INTENT(IN), POINTER :: pw_grid
572 COMPLEX(KIND=dp), DIMENSION(:, :, :), CONTIGUOUS, INTENT(IN), OPTIONAL, POINTER :: array_ptr
573
574 CHARACTER(len=*), PARAMETER :: routinen = 'pw_create_c3d'
575
576 INTEGER :: handle
577
578 CALL timeset(routinen, handle)
579
580 ! Ensure a clean grid to prevent memory leaks
581 CALL pw%release()
582
583 pw%pw_grid => pw_grid
584 CALL pw_grid_retain(pw%pw_grid)
585
586 associate(bounds => pw%pw_grid%bounds_local)
587 IF (PRESENT(array_ptr)) THEN
588 IF (ASSOCIATED(array_ptr)) THEN
589 IF (all(bounds(1, :) <= bounds(2, :))) THEN
590 cpassert(all(lbound(array_ptr) == bounds(1, :)))
591 cpassert(all(ubound(array_ptr) == bounds(2, :)))
592 END IF
593 pw%array => array_ptr
594 END IF
595 END IF
596 IF (.NOT. ASSOCIATED(pw%array)) THEN
597 ALLOCATE (pw%array( &
598 bounds(1, 1):bounds(2, 1), &
599 bounds(1, 2):bounds(2, 2), &
600 bounds(1, 3):bounds(2, 3)))
601 END IF
602 END associate
603 CALL timestop(handle)
604 END SUBROUTINE pw_create_c3d_gs
605
606END MODULE pw_types
various routines to log and control the output. The idea is that decisions about where to log should ...
Defines the basic variable types.
Definition kinds.F:23
integer, parameter, public dp
Definition kinds.F:34
This module defines the grid data type and some basic operations on it.
Definition pw_grids.F:36
subroutine, public pw_grid_release(pw_grid)
releases the given pw grid
Definition pw_grids.F:2133
subroutine, public pw_grid_retain(pw_grid)
retains the given pw grid
Definition pw_grids.F:2117