(git:ccc2433)
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-2024 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
17  USE message_passing, ONLY: mp_cart_type,&
18  mp_comm_null,&
19  mp_comm_type
20 #include "../base/base_uses.f90"
21 
22  IMPLICIT NONE
23 
24  PRIVATE
25  PUBLIC :: pw_grid_type, map_pn
26 
27  ! (only for reciprocal grid:) fill in half or full space
28  INTEGER, PARAMETER, PUBLIC :: halfspace = 211, fullspace = 212
29  INTEGER, PARAMETER, PUBLIC :: pw_mode_local = 0, pw_mode_distributed = 1
30 
31  ! maps to positive and negative g-vectors
32 ! **************************************************************************************************
33  TYPE map_pn
34  INTEGER, DIMENSION(:), ALLOCATABLE :: pos, neg
35  END TYPE map_pn
36 
37 ! info on parallelisation
38  ! contains only significant information if mode == PW_MODE_DISTRIBUTED
39 ! **************************************************************************************************
40  TYPE pw_para_type
41  INTEGER :: mode = pw_mode_local ! 0 = local = PW_MODE_LOCAL ; 1 = distributed = PW_MODE_DISTRIBUTED
42  LOGICAL :: ray_distribution = .false. ! block or pencil distribution
43  LOGICAL :: blocked = .false. ! block or pencil distribution
44  TYPE(mp_comm_type) :: group = mp_comm_null ! MPI group
45  INTEGER :: my_pos = -1! Position within group
46  INTEGER :: group_size = -1! # of Processors in group
47  LOGICAL :: group_head = .false. ! Master process within group
48  INTEGER :: group_head_id = 0 ! Id of group_head
49  INTEGER, DIMENSION(:, :, :), ALLOCATABLE :: yzp ! g-space rays (xy,k,pe)
50  INTEGER, DIMENSION(:, :), ALLOCATABLE :: yzq ! local inverse pointer of yzp
51  INTEGER, DIMENSION(:), ALLOCATABLE :: nyzray ! number of g-space rays (pe)
52  TYPE(mp_cart_type) :: rs_group = mp_cart_type() ! real space group (2-dim cart)
53  INTEGER :: rs_mpo = -1 ! real space group position
54  INTEGER, DIMENSION(2) :: rs_dims = 0 ! real space group dimensions
55  INTEGER, DIMENSION(2) :: rs_pos = -1 ! real space group positions in grid
56  INTEGER, DIMENSION(:, :, :, :), ALLOCATABLE :: bo ! list of axis distribution
57  INTEGER, DIMENSION(:), ALLOCATABLE :: pos_of_x ! what my_pos holds a given x plane....should go: hard-codes to plane distributed
58  END TYPE pw_para_type
59 
60  ! all you always wanted to know about grids, but were...
61 ! **************************************************************************************************
62  TYPE pw_grid_type
63  INTEGER(int_8) :: ngpts = 0_int_8 ! # grid points
64  INTEGER(int_8) :: ngpts_cut = 0_int_8 ! # grid points within cutoff
65  INTEGER, DIMENSION(2, 3) :: bounds = 0 ! lower and upper bounds
66  INTEGER, DIMENSION(3) :: npts = 0 ! # point in all directions
67  INTEGER :: ngpts_local = 0 ! # grid points
68  INTEGER :: ngpts_cut_local = 0 ! # grid points within cutoff
69  INTEGER, DIMENSION(2, 3) :: bounds_local = 0 ! bounds on local process
70  INTEGER, DIMENSION(3) :: npts_local = 0 ! local version of npts
71  REAL(kind=dp), DIMENSION(3) :: dr = 0.0_dp ! grid spacing
72  REAL(kind=dp), DIMENSION(3, 3) :: dh = 0.0_dp ! incremental cell matrix
73  REAL(kind=dp), DIMENSION(3, 3) :: dh_inv = 0.0_dp ! inverse incremental cell matrix
74  LOGICAL :: orthorhombic = .true. ! cell symmetry
75  REAL(kind=dp) :: dvol = 0.0_dp, vol = 0.0_dp ! volume element, volume
76  REAL(kind=dp) :: cutoff = 0.0_dp ! cutoff in a.u.
77  TYPE(map_pn) :: mapl = map_pn(), mapm = map_pn(), mapn = map_pn() ! mapping 1D => 3D
78  TYPE(pw_para_type) :: para = pw_para_type() ! information on parallelisation
79  REAL(kind=dp), DIMENSION(:, :), POINTER, CONTIGUOUS :: g => null() ! grid point vectors
80  REAL(kind=dp), DIMENSION(:), POINTER, CONTIGUOUS :: gsq => null() ! squared vector lengths
81  INTEGER, DIMENSION(:, :), ALLOCATABLE :: g_hat ! grid point indices (Miller)
82  INTEGER, DIMENSION(:, :), POINTER, CONTIGUOUS :: g_hatmap => null() ! mapped grid point indices (Miller) [CUDA]
83  INTEGER :: grid_span = fullspace ! type HALFSPACE/FULLSPACE
84  LOGICAL :: have_g0 = .true. ! whether I have G = [0,0,0]
85  INTEGER :: first_gne0 = 0 ! first g index /= 0 [1/2]
86  INTEGER :: id_nr = -1 ! tag of this grid
87  INTEGER :: reference = 0 ! reference grid identifier
88  INTEGER, DIMENSION(:), POINTER :: gidx => null() ! ref grid index
89  INTEGER :: ref_count = 0 ! reference count
90  LOGICAL :: spherical = .false. ! spherical cutoff?
91  COMPLEX(KIND=dp), DIMENSION(:, :), CONTIGUOUS, POINTER :: grays => null() ! used by parallel 3D FFT routine
92  END TYPE pw_grid_type
93 
94 END MODULE pw_grid_types
95 
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.
type(mp_comm_type), parameter, public mp_comm_null
integer, parameter, public halfspace
Definition: pw_grid_types.F:28
integer, parameter, public pw_mode_local
Definition: pw_grid_types.F:29
integer, parameter, public fullspace
Definition: pw_grid_types.F:28
integer, parameter, public pw_mode_distributed
Definition: pw_grid_types.F:29