(git:b279b6b)
gaussian_gridlevels.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 !> Code to return a gridlevel associated with a given gaussian exponent
11 !> \author Joost VandeVondele (27.02.02)
12 ! **************************************************************************************************
15  cp_logger_type
20  section_vals_type
21  USE kinds, ONLY: dp,&
22  int_8
23  USE message_passing, ONLY: mp_comm_type,&
24  mp_para_env_type
25 #include "../base/base_uses.f90"
26 
27  IMPLICIT NONE
28 
29  PRIVATE
30 
31  CHARACTER(len=*), PARAMETER, PRIVATE :: moduleN = 'gaussian_gridlevels'
32 
33 ! **************************************************************************************************
34  TYPE gridlevel_info_type
35  INTEGER :: ngrid_levels = 0
36  REAL(KIND=dp), POINTER, DIMENSION(:) :: cutoff => null()
37  INTEGER(KIND=int_8), POINTER, DIMENSION(:) :: count => null()
38  INTEGER(KIND=int_8) :: total_count = 0_int_8
39  REAL(KIND=dp) :: rel_cutoff = 0.0_dp
40  TYPE(section_vals_type), POINTER :: print_section => null()
41  END TYPE gridlevel_info_type
42 
43  PUBLIC :: gridlevel_info_type
44  PUBLIC :: gaussian_gridlevel
45  PUBLIC :: init_gaussian_gridlevel
47 
48 CONTAINS
49 
50 ! **************************************************************************************************
51 !> \brief ...
52 !> \param gridlevel_info ...
53 !> \param ngrid_levels ...
54 !> \param cutoff ...
55 !> \param rel_cutoff ...
56 !> \param print_section ...
57 ! **************************************************************************************************
58  SUBROUTINE init_gaussian_gridlevel(gridlevel_info, ngrid_levels, cutoff, rel_cutoff, print_section)
59  TYPE(gridlevel_info_type), INTENT(OUT) :: gridlevel_info
60  INTEGER, INTENT(IN) :: ngrid_levels
61  REAL(kind=dp), DIMENSION(ngrid_levels), INTENT(IN) :: cutoff
62  REAL(kind=dp), INTENT(IN) :: rel_cutoff
63  TYPE(section_vals_type), INTENT(IN), TARGET :: print_section
64 
65  INTEGER :: i
66 
67  ALLOCATE (gridlevel_info%cutoff(ngrid_levels))
68  ALLOCATE (gridlevel_info%count(ngrid_levels))
69  gridlevel_info%ngrid_levels = ngrid_levels
70  gridlevel_info%rel_cutoff = rel_cutoff
71  DO i = 1, ngrid_levels
72  gridlevel_info%cutoff(i) = cutoff(i)
73  gridlevel_info%count(i) = 0
74  END DO
75  gridlevel_info%print_section => print_section
76  CALL section_vals_retain(gridlevel_info%print_section)
77  END SUBROUTINE init_gaussian_gridlevel
78 
79 ! **************************************************************************************************
80 !> \brief ...
81 !> \param gridlevel_info ...
82 !> \param para_env ...
83 ! **************************************************************************************************
84  SUBROUTINE destroy_gaussian_gridlevel(gridlevel_info, para_env)
85  TYPE(gridlevel_info_type), INTENT(INOUT) :: gridlevel_info
86  TYPE(mp_para_env_type), INTENT(IN), OPTIONAL :: para_env
87 
88  INTEGER :: i, output_unit
89  LOGICAL :: do_io
90  TYPE(cp_logger_type), POINTER :: logger
91  TYPE(mp_comm_type) :: group
92 
93  NULLIFY (logger)
94  logger => cp_get_default_logger()
95  IF (PRESENT(para_env)) THEN
96  group = para_env
97  do_io = .false. !subgroups completely mess up the output file
98  ELSE
99  group = logger%para_env
100  do_io = .true.
101  END IF
102 
103  IF (do_io) THEN
104 
105  CALL group%sum(gridlevel_info%total_count)
106  CALL group%sum(gridlevel_info%count)
107 
108  output_unit = cp_print_key_unit_nr(logger, gridlevel_info%print_section, &
109  "", extension=".Log")
110 
111  IF (output_unit > 0) THEN
112  WRITE (output_unit, '(/,T2,A,A)') "----------------------------------------", &
113  "---------------------------------------"
114  WRITE (output_unit, '(T2,A,T35,A,T77,A)') "----", "MULTIGRID INFO", "----"
115  WRITE (output_unit, '(T2,A,A)') "----------------------------------------", &
116  "---------------------------------------"
117  IF (gridlevel_info%ngrid_levels > 1) THEN
118  DO i = 1, gridlevel_info%ngrid_levels
119  WRITE (output_unit, '(T2,A,I4,A,I14,9x,A,F12.2)') "count for grid ", i, ": ", &
120  gridlevel_info%count(i), " cutoff [a.u.] ", gridlevel_info%cutoff(i)
121  END DO
122  WRITE (output_unit, '(T2,A,I14)') "total gridlevel count : ", &
123  gridlevel_info%total_count
124  ELSE
125  WRITE (output_unit, '(T2,A,I14,T51,A,F12.2)') "total grid count :", &
126  gridlevel_info%count(1), " cutoff [a.u.] ", gridlevel_info%cutoff(1)
127  END IF
128  END IF
129 
130  CALL cp_print_key_finished_output(output_unit, logger, gridlevel_info%print_section, "")
131  END IF
132 
133  DEALLOCATE (gridlevel_info%cutoff)
134 
135  CALL section_vals_release(gridlevel_info%print_section)
136 
137  DEALLOCATE (gridlevel_info%count)
138 
139  END SUBROUTINE destroy_gaussian_gridlevel
140 
141 ! **************************************************************************************************
142 !> \brief ...
143 !> \param gridlevel_info ...
144 !> \param exponent ...
145 !> \return ...
146 ! **************************************************************************************************
147  FUNCTION gaussian_gridlevel(gridlevel_info, exponent) RESULT(gridlevel)
148  TYPE(gridlevel_info_type), INTENT(INOUT) :: gridlevel_info
149  REAL(kind=dp), INTENT(IN) :: exponent
150  INTEGER :: gridlevel
151 
152  INTEGER :: i
153  REAL(kind=dp) :: needed_cutoff
154 
155  gridlevel = 1
156  needed_cutoff = abs(exponent)*gridlevel_info%rel_cutoff
157  DO i = 1, gridlevel_info%ngrid_levels
158  IF ((gridlevel_info%cutoff(i) + 1e-6_dp) .GE. needed_cutoff) THEN
159  gridlevel = i
160  END IF
161  END DO
162 !$OMP ATOMIC
163  gridlevel_info%total_count = gridlevel_info%total_count + 1
164 !$OMP ATOMIC
165  gridlevel_info%count(gridlevel) = gridlevel_info%count(gridlevel) + 1
166 
167  END FUNCTION gaussian_gridlevel
168 
169 END MODULE gaussian_gridlevels
various routines to log and control the output. The idea is that decisions about where to log should ...
type(cp_logger_type) function, pointer, public cp_get_default_logger()
returns the default logger
routines to handle the output, The idea is to remove the decision of wheter to output and what to out...
integer function, public cp_print_key_unit_nr(logger, basis_section, print_key_path, extension, middle_name, local, log_filename, ignore_should_output, file_form, file_position, file_action, file_status, do_backup, on_file, is_new_file, mpi_io, fout)
...
subroutine, public cp_print_key_finished_output(unit_nr, logger, basis_section, print_key_path, local, ignore_should_output, on_file, mpi_io)
should be called after you finish working with a unit obtained with cp_print_key_unit_nr,...
integer function, public gaussian_gridlevel(gridlevel_info, exponent)
...
subroutine, public destroy_gaussian_gridlevel(gridlevel_info, para_env)
...
subroutine, public init_gaussian_gridlevel(gridlevel_info, ngrid_levels, cutoff, rel_cutoff, print_section)
...
objects that represent the structure of input sections and the data contained in an input section
subroutine, public section_vals_retain(section_vals)
retains the given section values (see doc/ReferenceCounting.html)
recursive subroutine, public section_vals_release(section_vals)
releases the given object
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.