(git:d18deda)
Loading...
Searching...
No Matches
pw_grid_types.F
Go to the documentation of this file.
1!--------------------------------------------------------------------------------------------------!
2! CP2K: A general program to perform molecular dynamics simulations !
3! Copyright 2000-2025 CP2K developers group <https://cp2k.org> !
4! !
5! SPDX-License-Identifier: GPL-2.0-or-later !
6!--------------------------------------------------------------------------------------------------!
7
8! **************************************************************************************************
9!> \par History
10!> JGH (20-12-2000) : Parallel data layout
11!> \author APSI
12! **************************************************************************************************
14
15 USE kinds, ONLY: dp,&
16 int_8
18#include "../base/base_uses.f90"
19
20 IMPLICIT NONE
21
22 PRIVATE
23 PUBLIC :: pw_grid_type, map_pn
24
25 ! (only for reciprocal grid:) fill in half or full space
26 INTEGER, PARAMETER, PUBLIC :: halfspace = 211, fullspace = 212
27 INTEGER, PARAMETER, PUBLIC :: pw_mode_local = 0, pw_mode_distributed = 1
28
29 ! maps to positive and negative g-vectors
30! **************************************************************************************************
31 TYPE map_pn
32 INTEGER, DIMENSION(:), ALLOCATABLE :: pos, neg
33 END TYPE map_pn
34
35! info on parallelisation
36 ! contains only significant information if mode == PW_MODE_DISTRIBUTED
37! **************************************************************************************************
38 TYPE pw_para_type
39 INTEGER :: mode = pw_mode_local ! 0 = local = PW_MODE_LOCAL ; 1 = distributed = PW_MODE_DISTRIBUTED
40 LOGICAL :: ray_distribution = .false. ! block or pencil distribution
41 LOGICAL :: blocked = .false. ! block or pencil distribution
42 INTEGER, DIMENSION(:, :, :), ALLOCATABLE :: yzp ! g-space rays (xy,k,pe)
43 INTEGER, DIMENSION(:, :), ALLOCATABLE :: yzq ! local inverse pointer of yzp
44 INTEGER, DIMENSION(:), ALLOCATABLE :: nyzray ! number of g-space rays (pe)
45 TYPE(mp_cart_type) :: group = mp_cart_type() ! real space group (2-dim cart)
46 INTEGER, DIMENSION(:, :, :, :), ALLOCATABLE :: bo ! list of axis distribution
47 INTEGER, DIMENSION(:), ALLOCATABLE :: pos_of_x ! what my_pos holds a given x plane....should go: hard-codes to plane distributed
48 END TYPE pw_para_type
49
50 ! all you always wanted to know about grids, but were...
51! **************************************************************************************************
53 INTEGER(int_8) :: ngpts = 0_int_8 ! # grid points
54 INTEGER(int_8) :: ngpts_cut = 0_int_8 ! # grid points within cutoff
55 INTEGER, DIMENSION(2, 3) :: bounds = 0 ! lower and upper bounds
56 INTEGER, DIMENSION(3) :: npts = 0 ! # point in all directions
57 INTEGER :: ngpts_local = 0 ! # grid points
58 INTEGER :: ngpts_cut_local = 0 ! # grid points within cutoff
59 INTEGER, DIMENSION(2, 3) :: bounds_local = 0 ! bounds on local process
60 INTEGER, DIMENSION(3) :: npts_local = 0 ! local version of npts
61 REAL(kind=dp), DIMENSION(3) :: dr = 0.0_dp ! grid spacing
62 REAL(kind=dp), DIMENSION(3, 3) :: dh = 0.0_dp ! incremental cell matrix
63 REAL(kind=dp), DIMENSION(3, 3) :: dh_inv = 0.0_dp ! inverse incremental cell matrix
64 LOGICAL :: orthorhombic = .true. ! cell symmetry
65 REAL(kind=dp) :: dvol = 0.0_dp, vol = 0.0_dp ! volume element, volume
66 REAL(kind=dp) :: cutoff = 0.0_dp ! cutoff in a.u.
67 TYPE(map_pn) :: mapl = map_pn(), mapm = map_pn(), mapn = map_pn() ! mapping 1D => 3D
68 TYPE(pw_para_type) :: para = pw_para_type() ! information on parallelisation
69 REAL(kind=dp), DIMENSION(:, :), POINTER, CONTIGUOUS :: g => null() ! grid point vectors
70 REAL(kind=dp), DIMENSION(:), POINTER, CONTIGUOUS :: gsq => null() ! squared vector lengths
71 INTEGER, DIMENSION(:, :), ALLOCATABLE :: g_hat ! grid point indices (Miller)
72 INTEGER, DIMENSION(:, :), POINTER, CONTIGUOUS :: g_hatmap => null() ! mapped grid point indices (Miller) [CUDA]
73 INTEGER :: grid_span = fullspace ! type HALFSPACE/FULLSPACE
74 LOGICAL :: have_g0 = .true. ! whether I have G = [0,0,0]
75 INTEGER :: first_gne0 = 0 ! first g index /= 0 [1/2]
76 INTEGER :: id_nr = -1 ! tag of this grid
77 INTEGER :: reference = 0 ! reference grid identifier
78 INTEGER, DIMENSION(:), POINTER :: gidx => null() ! ref grid index
79 INTEGER :: ref_count = 0 ! reference count
80 LOGICAL :: spherical = .false. ! spherical cutoff?
81 COMPLEX(KIND=dp), DIMENSION(:, :), CONTIGUOUS, POINTER :: grays => null() ! used by parallel 3D FFT routine
82 END TYPE pw_grid_type
83
84END MODULE pw_grid_types
85
Defines the basic variable types.
Definition kinds.F:23
integer, parameter, public int_8
Definition kinds.F:54
integer, parameter, public dp
Definition kinds.F:34
Interface to the message passing library MPI.
integer, parameter, public halfspace
integer, parameter, public pw_mode_local
integer, parameter, public fullspace
integer, parameter, public pw_mode_distributed