(git:374b731)
Loading...
Searching...
No Matches
cp_realspace_grid_init.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!> Routine to initialize a real space grid from a given input section
11!> \par History
12!> 01.2014 moved routine from realspace_grid_types into separate file.
13!> \author Ole Schuett
14! **************************************************************************************************
22#include "./base/base_uses.f90"
23
24 IMPLICIT NONE
25
26 PRIVATE
27
28 PUBLIC :: init_input_type
29
30 CHARACTER(len=*), PARAMETER, PRIVATE :: moduleN = 'cp_realspace_grid_init'
31
32CONTAINS
33
34! **************************************************************************************************
35!> \brief parses an input section to assign the proper values to the input type
36!> \param input_settings ...
37!> \param nsmax ...
38!> \param rs_grid_section ...
39!> \param ilevel ...
40!> \param higher_grid_layout the layout of a higher level grid. layouts with
41!> negative or zero values are ignored
42!> \par History
43!> 01.2008 created [Joost VandeVondele]
44!> \note
45!> if rs_grid_section is not present we setup for an replicated setup
46! **************************************************************************************************
47 SUBROUTINE init_input_type(input_settings, nsmax, rs_grid_section, ilevel, higher_grid_layout)
48 TYPE(realspace_grid_input_type), INTENT(OUT) :: input_settings
49 INTEGER, INTENT(IN) :: nsmax
50 TYPE(section_vals_type), OPTIONAL, POINTER :: rs_grid_section
51 INTEGER, INTENT(IN) :: ilevel
52 INTEGER, DIMENSION(3), INTENT(IN) :: higher_grid_layout
53
54 INTEGER :: isection, max_distributed_level, nsection
55 INTEGER, DIMENSION(:), POINTER :: tmp
56
57 IF (PRESENT(rs_grid_section)) THEN
58 input_settings%nsmax = nsmax
59 ! we use the section corresponding to the level, or the largest available one
60 ! i.e. the last section defines all following ones
61 CALL section_vals_get(rs_grid_section, n_repetition=nsection)
62 isection = max(1, min(ilevel, nsection))
63 CALL section_vals_val_get(rs_grid_section, "DISTRIBUTION_TYPE", &
64 i_rep_section=isection, &
65 i_val=input_settings%distribution_type)
66 CALL section_vals_val_get(rs_grid_section, "DISTRIBUTION_LAYOUT", &
67 i_rep_section=isection, &
68 i_vals=tmp)
69 input_settings%distribution_layout = tmp
70 CALL section_vals_val_get(rs_grid_section, "MEMORY_FACTOR", &
71 i_rep_section=isection, &
72 r_val=input_settings%memory_factor)
73 CALL section_vals_val_get(rs_grid_section, "HALO_REDUCTION_FACTOR", &
74 i_rep_section=isection, &
75 r_val=input_settings%halo_reduction_factor)
76 CALL section_vals_val_get(rs_grid_section, "LOCK_DISTRIBUTION", &
77 i_rep_section=isection, &
78 l_val=input_settings%lock_distribution)
79 CALL section_vals_val_get(rs_grid_section, "MAX_DISTRIBUTED_LEVEL", &
80 i_rep_section=isection, &
81 i_val=max_distributed_level)
82
83 ! multigrids that are to coarse are not distributed in the automatic scheme
84 IF (input_settings%distribution_type == rsgrid_automatic) THEN
85 IF (ilevel > max_distributed_level) THEN
86 input_settings%distribution_type = rsgrid_replicated
87 END IF
88 END IF
89 END IF
90 IF (input_settings%lock_distribution) THEN
91 IF (all(higher_grid_layout > 0)) input_settings%distribution_layout = higher_grid_layout
92 END IF
93 END SUBROUTINE init_input_type
94
subroutine, public init_input_type(input_settings, nsmax, rs_grid_section, ilevel, higher_grid_layout)
parses an input section to assign the proper values to the input type
objects that represent the structure of input sections and the data contained in an input section
subroutine, public section_vals_get(section_vals, ref_count, n_repetition, n_subs_vals_rep, section, explicit)
returns various attributes about the section_vals
subroutine, public section_vals_val_get(section_vals, keyword_name, i_rep_section, i_rep_val, n_rep_val, val, l_val, i_val, r_val, c_val, l_vals, i_vals, r_vals, c_vals, explicit)
returns the requested value
integer, parameter, public rsgrid_replicated
integer, parameter, public rsgrid_automatic