(git:374b731)
Loading...
Searching...
No Matches
rel_control_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 parameters that control a relativistic calculation
10!> \par History
11!> 09.2002 created [fawzi] (as scf_control_types.F)
12!> 10.2008 modified for relativistic control types (Jens Thar)
13!> \author Fawzi Mohamed
14! **************************************************************************************************
16
17 USE input_constants, ONLY: rel_none,&
24#include "./base/base_uses.f90"
25
26 IMPLICIT NONE
27
28 PRIVATE
29
30 CHARACTER(len=*), PARAMETER, PRIVATE :: moduleN = 'rel_control_types'
31 LOGICAL, PRIVATE, PARAMETER :: debug_this_module = .true.
32
33 ! Public data types
34
35 PUBLIC :: rel_control_type
36
37 ! Public subroutines
38
39 PUBLIC :: rel_c_create, &
42
43! **************************************************************************************************
44!> \brief contains the parameters needed by a relativistic calculation
45!> \param method used relativistic method (NONE, DKH)
46!> \param DKH_order order of the DKH transformation (2,3)
47!> \param transformation used blocks of the full matrix (FULL, MOLECULE, ATOM)
48!> \param z_cutoff considered range of the Coulomb interaction
49!> \param potential nuclear electron Coulomb potential (FULL, ERFC)
50!> \par History
51!> 09.2002 created [fawzi] for scf_control_type
52!> 10.2008 copied to rel_control_type [JT]
53!> \author Fawzi Mohamed
54! **************************************************************************************************
56 INTEGER :: rel_method
57 INTEGER :: rel_dkh_order
58 INTEGER :: rel_zora_type
59 INTEGER :: rel_transformation
60 INTEGER :: rel_z_cutoff
61 INTEGER :: rel_potential
62 END TYPE rel_control_type
63
64CONTAINS
65
66! **************************************************************************************************
67!> \brief allocates and initializes an rel control object with the default values
68!> \param rel_control the object to initialize
69!> \par History
70!> 09.2002 created [fawzi] for scf_control_type
71!> 10.2008 copied to rel_control_type [JT]
72!> \author Fawzi Mohamed
73! **************************************************************************************************
74 SUBROUTINE rel_c_create(rel_control)
75
76 TYPE(rel_control_type), INTENT(OUT) :: rel_control
77
78 ! Load the default values
79
80 rel_control%rel_method = rel_none
81 rel_control%rel_DKH_order = 2
82 rel_control%rel_ZORA_type = rel_zora_full
83 rel_control%rel_transformation = rel_trans_full
84 rel_control%rel_z_cutoff = 1
85 rel_control%rel_potential = rel_pot_full
86
87 END SUBROUTINE rel_c_create
88
89! **************************************************************************************************
90!> \brief releases the given rel_control (see cp2k/doc/ReferenceCounting.html)
91!> \param rel_control the object to free
92!> \par History
93!> 09.2002 created [fawzi] for scf_control_type
94!> 10.2008 copied to rel_control_type [JT]
95!> \author Fawzi Mohamed
96!> \note
97!> at the moment does nothing
98! **************************************************************************************************
99 SUBROUTINE rel_c_release(rel_control)
100
101 TYPE(rel_control_type), INTENT(IN) :: rel_control
102
103 mark_used(rel_control)
104
105 END SUBROUTINE rel_c_release
106
107! **************************************************************************************************
108!> \brief reads the parameters of the relativistic section into the given rel_control
109!> \param rel_control the object that wil contain the values read
110!> \param dft_section ...
111!> \par History
112!> 05.2001 created [Matthias] for scf_control_type
113!> 09.2002 created separated scf_control type [fawzi]
114!> 10.2008 copied to rel_control_type [JT]
115!> \author Matthias Krack
116! **************************************************************************************************
117 SUBROUTINE rel_c_read_parameters(rel_control, dft_section)
118
119 TYPE(rel_control_type), INTENT(INOUT) :: rel_control
120 TYPE(section_vals_type), POINTER :: dft_section
121
122 TYPE(section_vals_type), POINTER :: rel_section
123
124 cpassert(ASSOCIATED(dft_section))
125
126 rel_section => section_vals_get_subs_vals(dft_section, "RELATIVISTIC")
127 CALL section_vals_val_get(rel_section, "method", &
128 i_val=rel_control%rel_method)
129 CALL section_vals_val_get(rel_section, "DKH_order", &
130 i_val=rel_control%rel_DKH_order)
131 CALL section_vals_val_get(rel_section, "ZORA_TYPE", &
132 i_val=rel_control%rel_zora_type)
133 CALL section_vals_val_get(rel_section, "transformation", &
134 i_val=rel_control%rel_transformation)
135 CALL section_vals_val_get(rel_section, "z_cutoff", &
136 i_val=rel_control%rel_z_cutoff)
137 CALL section_vals_val_get(rel_section, "potential", &
138 i_val=rel_control%rel_potential)
139
140 END SUBROUTINE rel_c_read_parameters
141
142END MODULE rel_control_types
collects all constants needed in input so that they can be used without circular dependencies
integer, parameter, public rel_zora_full
integer, parameter, public rel_pot_full
integer, parameter, public rel_trans_full
integer, parameter, public rel_none
objects that represent the structure of input sections and the data contained in an input section
recursive type(section_vals_type) function, pointer, public section_vals_get_subs_vals(section_vals, subsection_name, i_rep_section, can_return_null)
returns the values of the requested subsection
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
parameters that control a relativistic calculation
subroutine, public rel_c_create(rel_control)
allocates and initializes an rel control object with the default values
subroutine, public rel_c_read_parameters(rel_control, dft_section)
reads the parameters of the relativistic section into the given rel_control
subroutine, public rel_c_release(rel_control)
releases the given rel_control (see cp2k/doc/ReferenceCounting.html)
contains the parameters needed by a relativistic calculation