(git:ed6f26b)
Loading...
Searching...
No Matches
arnoldi_types.F
Go to the documentation of this file.
1!--------------------------------------------------------------------------------------------------!
2! CP2K: A general program to perform molecular dynamics simulations !
3! Copyright 2000-2025 CP2K developers group <https://cp2k.org> !
4! !
5! SPDX-License-Identifier: GPL-2.0-or-later !
6!--------------------------------------------------------------------------------------------------!
7
8! **************************************************************************************************
9!> \brief collection of types used in arnoldi
10!> \par History
11!> 2014.09 created [Florian Schiffmann]
12!> 2023.12 Removed support for single-precision [Ole Schuett]
13!> 2024.12 Removed support for complex input matrices [Ole Schuett]
14!> \author Florian Schiffmann
15! **************************************************************************************************
17 USE cp_dbcsr_api, ONLY: dbcsr_type
18 USE kinds, ONLY: dp
20
21 IMPLICIT NONE
22
23! Type that gets created during the arnoldi procedure and contains basically everything
24! As it is not quite clear what the user will request, this is the most general way to satisfy all needs:
25! Give him everything we have and create some easy to use routines to post process externally
27 LOGICAL :: local_comp = .false., converged = .false.
28 INTEGER :: myproc = -1
29 TYPE(mp_comm_type) :: mp_group = mp_comm_type(), pcol_group = mp_comm_type()
30 INTEGER :: max_iter = -1 ! Maximum number of iterations
31 INTEGER :: current_step = -1 ! In case subspace converged early contains last iteration
32 INTEGER :: nval_req = -1
33 INTEGER :: selection_crit = -1
34 INTEGER :: nval_out = -1
35 INTEGER :: nrestart = -1
36 REAL(dp) :: threshold = 0.0_dp
37 LOGICAL :: symmetric = .false.
38 LOGICAL :: generalized_ev = .false.
39 LOGICAL :: iram = .false.
40 LOGICAL :: has_initial_vector = .false.
41 INTEGER, DIMENSION(:), POINTER :: selected_ind => null() ! list of indices matching the selection criterion
43
45 REAL(kind=dp), POINTER, DIMENSION(:) :: f_vec => null() ! the local parts of the residual vector
46 REAL(kind=dp), POINTER, DIMENSION(:, :) :: hessenberg => null() ! the Hessenberg matrix
47 REAL(kind=dp), POINTER, DIMENSION(:, :) :: local_history => null() ! the complete set of orthonormal vectors (local part)
48 COMPLEX(dp), POINTER, DIMENSION(:) :: evals => null() ! the real part of the eigenvalues (if complex both)
49 COMPLEX(dp), POINTER, DIMENSION(:, :) :: revec => null() ! the right eigenvectors
50 REAL(kind=dp) :: rho_scale = 0.0_dp ! scling factor for general eig arnoldi
51 REAL(kind=dp), POINTER, DIMENSION(:) :: x_vec => null() ! eigenvector for genreal eig arnoldi
52 END TYPE arnoldi_data_type
53
55 TYPE(arnoldi_data_type), POINTER, PRIVATE :: data => null()
56 TYPE(arnoldi_control_type), POINTER, PRIVATE :: control => null()
57 END TYPE arnoldi_env_type
58
60 TYPE(dbcsr_type) :: input_vec
61 TYPE(dbcsr_type) :: result_vec
62 TYPE(dbcsr_type) :: rep_col_vec
63 TYPE(dbcsr_type) :: rep_row_vec
64 END TYPE m_x_v_vectors_type
65
66 PRIVATE
67
68 CHARACTER(len=*), PARAMETER, PRIVATE :: modulen = 'arnoldi_types'
69
73CONTAINS
74
75! **************************************************************************************************
76!> \brief ...
77!> \param arnoldi_env ...
78!> \param control ...
79! **************************************************************************************************
80 SUBROUTINE set_control(arnoldi_env, control)
81 TYPE(arnoldi_env_type), INTENT(INOUT) :: arnoldi_env
82 TYPE(arnoldi_control_type), INTENT(IN), POINTER :: control
83
84 arnoldi_env%control => control
85 END SUBROUTINE set_control
86
87! **************************************************************************************************
88!> \brief ...
89!> \param arnoldi_env ...
90!> \return ...
91! **************************************************************************************************
92 FUNCTION get_sel_ind(arnoldi_env) RESULT(selected_ind)
93 TYPE(arnoldi_env_type), INTENT(IN) :: arnoldi_env
94 INTEGER, DIMENSION(:), POINTER :: selected_ind
95
96 selected_ind => arnoldi_env%control%selected_ind
97
98 END FUNCTION get_sel_ind
99
100! **************************************************************************************************
101!> \brief ...
102!> \param arnoldi_env ...
103!> \return ...
104! **************************************************************************************************
105 FUNCTION get_data(arnoldi_env) RESULT(ar_data)
106 TYPE(arnoldi_env_type), INTENT(IN) :: arnoldi_env
107 TYPE(arnoldi_data_type), POINTER :: ar_data
108
109 ar_data => arnoldi_env%data
110
111 END FUNCTION get_data
112
113! **************************************************************************************************
114!> \brief ...
115!> \param arnoldi_env ...
116!> \param ar_data ...
117! **************************************************************************************************
118 SUBROUTINE set_data(arnoldi_env, ar_data)
119 TYPE(arnoldi_env_type), INTENT(INOUT) :: arnoldi_env
120 TYPE(arnoldi_data_type), INTENT(IN), POINTER :: ar_data
121
122 arnoldi_env%data => ar_data
123
124 END SUBROUTINE set_data
125
126! **************************************************************************************************
127!> \brief ...
128!> \param arnoldi_env ...
129!> \return ...
130! **************************************************************************************************
131 FUNCTION get_control(arnoldi_env) RESULT(control)
132 TYPE(arnoldi_env_type), INTENT(INOUT) :: arnoldi_env
133 TYPE(arnoldi_control_type), POINTER :: control
134
135 control => arnoldi_env%control
136
137 END FUNCTION get_control
138
139! **************************************************************************************************
140!> \brief ...
141!> \param arnoldi_env ...
142!> \return ...
143! **************************************************************************************************
144 FUNCTION get_evals(arnoldi_env) RESULT(evals)
145 TYPE(arnoldi_env_type), INTENT(IN) :: arnoldi_env
146 COMPLEX(dp), DIMENSION(:), POINTER :: evals
147
148 evals => arnoldi_env%data%evals
149
150 END FUNCTION get_evals
151
152END MODULE arnoldi_types
collection of types used in arnoldi
complex(dp) function, dimension(:), pointer, public get_evals(arnoldi_env)
...
type(arnoldi_data_type) function, pointer, public get_data(arnoldi_env)
...
type(arnoldi_control_type) function, pointer, public get_control(arnoldi_env)
...
subroutine, public set_control(arnoldi_env, control)
...
subroutine, public set_data(arnoldi_env, ar_data)
...
integer function, dimension(:), pointer, public get_sel_ind(arnoldi_env)
...
Defines the basic variable types.
Definition kinds.F:23
integer, parameter, public dp
Definition kinds.F:34
Interface to the message passing library MPI.