(git:b279b6b)
dbt_tas_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 !> \brief DBT tall-and-skinny base types.
10 !> Mostly wrappers around existing DBM routines.
11 !> \author Patrick Seewald
12 ! **************************************************************************************************
14  USE dbm_api, ONLY: dbm_distribution_obj,&
15  dbm_iterator,&
16  dbm_type
17  USE dbt_tas_global, ONLY: dbt_tas_distribution,&
18  dbt_tas_rowcol_data
19  USE kinds, ONLY: dp,&
20  int_8
21  USE message_passing, ONLY: mp_cart_type
22 #include "../../base/base_uses.f90"
23 
24  IMPLICIT NONE
25  PRIVATE
26 
27  CHARACTER(len=*), PARAMETER, PRIVATE :: moduleN = 'dbt_tas_types'
28 
29  PUBLIC :: &
30  dbt_tas_distribution_type, &
31  dbt_tas_iterator, &
32  dbt_tas_split_info, &
33  dbt_tas_type, &
34  dbt_tas_mm_storage
35 
36 ! **************************************************************************************************
37 !> \brief info on MPI Cartesian grid that is split on MPI subgroups.
38 !> info on distribution of matrix rows / columns to different subgroups.
39 !> \var mp_comm global communicator
40 !> \var pdims dimensions of process grid
41 !> \var igroup which subgroup do I belong to
42 !> \var ngroup how many groups in total
43 !> \var split_rowcol split row or column?
44 !> \var pgrid_split_size how many process rows/cols in subgroups
45 !> \var group_size group size (how many cores) of subgroups
46 !> \var mp_comm_group sub communicator
47 !> \var ngroup_opt optimal number of groups (split factor)
48 !> \var strict_split if .true., split factor should not be modified
49 !> (2 parameters for current and general settings)
50 !> \var refcount lightweight reference counting for communicators
51 ! **************************************************************************************************
52  TYPE dbt_tas_split_info
53  TYPE(mp_cart_type) :: mp_comm
54  INTEGER, DIMENSION(2) :: pdims = [-1, -1]
55  INTEGER :: igroup = -1
56  INTEGER :: ngroup = -1
57  INTEGER :: split_rowcol = -1
58  INTEGER :: pgrid_split_size = -1
59  INTEGER :: group_size = -1
60  TYPE(mp_cart_type) :: mp_comm_group
61  INTEGER, ALLOCATABLE :: ngroup_opt
62  LOGICAL, DIMENSION(2) :: strict_split = [.false., .false.]
63  INTEGER, POINTER :: refcount => null()
64  END TYPE
65 
66  TYPE dbt_tas_distribution_type
67  TYPE(dbt_tas_split_info) :: info
68  TYPE(dbm_distribution_obj) :: dbm_dist
69  CLASS(dbt_tas_distribution), ALLOCATABLE :: row_dist
70  CLASS(dbt_tas_distribution), ALLOCATABLE :: col_dist
71  INTEGER(KIND=int_8), ALLOCATABLE, DIMENSION(:) :: local_rowcols
72  END TYPE
73 
74 ! **************************************************************************************************
75 !> \brief storage for batched matrix multiplication
76 !> \var store_batched intermediate replicated matrix
77 !> \var store_batched_repl intermediate replicated matrix
78 !> \var batched_out whether replicated matrix has been changed in mm...
79 !> and should be copied to actual matrix
80 ! **************************************************************************************************
81  TYPE dbt_tas_mm_storage
82  TYPE(dbt_tas_type), POINTER :: store_batched => null()
83  TYPE(dbt_tas_type), POINTER :: store_batched_repl => null()
84  LOGICAL :: batched_out = .false.
85  LOGICAL :: batched_trans = .false.
86  REAL(dp) :: batched_beta = 1.0_dp
87  END TYPE
88 
89 ! **************************************************************************************************
90 !> \brief type for tall-and-skinny matrices
91 !> \var matrix matrix on subgroup
92 !> \var nblkrows total number of rows
93 !> \var nblkcols total number of columns
94 !> \var nblkrowscols_split nblkrows or nblkcols depending on which is splitted
95 !> \var nfullrows total number of full (not blocked) rows
96 !> \var nfullcols total number of full (not blocked) columns
97 !> \var valid has been created?
98 !> \var do_batched state flag for batched multiplication
99 !> \var mm_storage storage for batched processing of matrix matrix multiplication.
100 !> \var has_opt_pgrid whether pgrid was automatically optimized
101 ! **************************************************************************************************
102  TYPE dbt_tas_type
103  TYPE(dbt_tas_distribution_type) :: dist
104  CLASS(dbt_tas_rowcol_data), ALLOCATABLE :: row_blk_size
105  CLASS(dbt_tas_rowcol_data), ALLOCATABLE :: col_blk_size
106  TYPE(dbm_type) :: matrix
107  INTEGER(KIND=int_8) :: nblkrows = -1
108  INTEGER(KIND=int_8) :: nblkcols = -1
109  INTEGER(KIND=int_8) :: nblkrowscols_split = -1
110  INTEGER(KIND=int_8) :: nfullrows = -1
111  INTEGER(KIND=int_8) :: nfullcols = -1
112  LOGICAL :: valid = .false.
113  INTEGER :: do_batched = 0
114  TYPE(dbt_tas_mm_storage), ALLOCATABLE :: mm_storage
115  LOGICAL :: has_opt_pgrid = .false.
116  END TYPE
117 
118  TYPE dbt_tas_iterator
119  TYPE(dbt_tas_distribution_type), POINTER :: dist => null()
120  TYPE(dbm_iterator) :: iter
121  END TYPE dbt_tas_iterator
122 
123 END MODULE
Definition: dbm_api.F:8
Global data (distribution and block sizes) for tall-and-skinny matrices For very sparse matrices with...
DBT tall-and-skinny base types. Mostly wrappers around existing DBM routines.
Definition: dbt_tas_types.F:13
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.