(git:34ef472)
glbopt_minhop.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 Routines for the Minima Hopping global optimization scheme
10 !> \author Ole Schuett
11 ! **************************************************************************************************
13  USE bibliography, ONLY: goedecker2004,&
14  cite_reference
15  USE glbopt_history, ONLY: history_add,&
19  history_fingerprint_type,&
20  history_init,&
22  history_type
24  section_vals_type,&
26  USE kinds, ONLY: default_string_length,&
27  dp
28  USE physcon, ONLY: kelvin
29  USE swarm_message, ONLY: swarm_message_add,&
30  swarm_message_get,&
31  swarm_message_type
32 #include "../base/base_uses.f90"
33 
34  IMPLICIT NONE
35  PRIVATE
36 
37  CHARACTER(len=*), PARAMETER, PRIVATE :: moduleN = 'glbopt_minhop'
38 
39  PUBLIC :: minhop_type
40  PUBLIC :: minhop_init, minhop_finalize
41  PUBLIC :: minhop_steer
42 
43  TYPE worker_state_type
44  REAL(KIND=dp) :: eaccept = -1.0
45  REAL(KIND=dp) :: temp = -1.0
46  REAL(KIND=dp), DIMENSION(:), ALLOCATABLE :: pos
47  REAL(KIND=dp) :: epot = -1.0
48  TYPE(history_fingerprint_type) :: fp
49  REAL(KIND=dp), DIMENSION(:), ALLOCATABLE :: pos_hop
50  REAL(KIND=dp) :: epot_hop = huge(1.0)
51  TYPE(history_fingerprint_type) :: fp_hop
52  INTEGER :: minima_id = -1
53  INTEGER :: iframe = 1
54  END TYPE worker_state_type
55 
56  TYPE minima_state_type
57  REAL(KIND=dp) :: eaccept = -1.0
58  REAL(KIND=dp) :: temp = -1.0
59  REAL(KIND=dp), DIMENSION(:), ALLOCATABLE :: pos
60  REAL(KIND=dp) :: epot = -1.0
61  TYPE(history_fingerprint_type) :: fp
62  LOGICAL :: disabled = .false.
63  INTEGER :: n_active = 0
64  INTEGER :: n_sampled = 0
65  END TYPE minima_state_type
66 
67  TYPE minhop_type
68  PRIVATE
69  TYPE(history_type), DIMENSION(:), ALLOCATABLE :: history
70  TYPE(worker_state_type), DIMENSION(:), ALLOCATABLE :: worker_state
71  TYPE(minima_state_type), DIMENSION(:), ALLOCATABLE :: minima_state
72  INTEGER :: n_minima = 0
73  REAL(KIND=dp) :: beta1 = 0
74  REAL(KIND=dp) :: beta2 = 0
75  REAL(KIND=dp) :: beta3 = 0
76  REAL(KIND=dp) :: eaccept0 = 0
77  REAL(KIND=dp) :: temp_init = 0
78  REAL(KIND=dp) :: temp_max = 0
79  REAL(KIND=dp) :: temp_min = 0
80  REAL(KIND=dp) :: alpha1 = 0
81  REAL(KIND=dp) :: alpha2 = 0
82  INTEGER :: n_accepted = 0
83  INTEGER :: n_rejected = 0
84  INTEGER :: iw = 0
85  INTEGER :: n_workers = 0
86  LOGICAL :: share_history = .false.
87  END TYPE minhop_type
88 
89 CONTAINS
90 
91 ! **************************************************************************************************
92 !> \brief Initializes master for Minima Hopping
93 !> \param this ...
94 !> \param glbopt_section ...
95 !> \param n_workers ...
96 !> \param iw ...
97 !> \author Ole Schuett
98 ! **************************************************************************************************
99  SUBROUTINE minhop_init(this, glbopt_section, n_workers, iw)
100  TYPE(minhop_type) :: this
101  TYPE(section_vals_type), POINTER :: glbopt_section
102  INTEGER, INTENT(IN) :: n_workers, iw
103 
104  INTEGER :: i, n_histories
105  REAL(kind=dp) :: temp_in_kelvin
106  TYPE(section_vals_type), POINTER :: history_section, minhop_section
107 
108  CALL cite_reference(goedecker2004)
109 
110  ! read input
111  minhop_section => section_vals_get_subs_vals(glbopt_section, "MINIMA_HOPPING")
112  CALL section_vals_val_get(minhop_section, "BETA_1", r_val=this%beta1)
113  CALL section_vals_val_get(minhop_section, "BETA_2", r_val=this%beta2)
114  CALL section_vals_val_get(minhop_section, "BETA_3", r_val=this%beta3)
115  CALL section_vals_val_get(minhop_section, "ALPHA_1", r_val=this%alpha1)
116  CALL section_vals_val_get(minhop_section, "ALPHA_2", r_val=this%alpha2)
117  CALL section_vals_val_get(minhop_section, "E_ACCEPT_INIT", r_val=this%Eaccept0)
118  CALL section_vals_val_get(minhop_section, "TEMPERATURE_INIT", r_val=temp_in_kelvin)
119  this%temp_init = temp_in_kelvin/kelvin
120  CALL section_vals_val_get(minhop_section, "SHARE_HISTORY", l_val=this%share_history)
121 
122  ! allocate history / histories
123  history_section => section_vals_get_subs_vals(glbopt_section, "HISTORY")
124  n_histories = n_workers
125  IF (this%share_history) n_histories = 1
126  ALLOCATE (this%history(n_histories))
127 
128  !only the first history shall write to iw
129  CALL history_init(this%history(1), history_section, iw=iw)
130  DO i = 2, n_histories
131  CALL history_init(this%history(i), history_section, iw=-1)
132  END DO
133 
134  ALLOCATE (this%worker_state(n_workers))
135  this%n_workers = n_workers
136  this%iw = iw
137 
138  IF (this%iw > 0) THEN
139  WRITE (this%iw, '(A,T71,F10.3)') " MINHOP| beta_1", this%beta1
140  WRITE (this%iw, '(A,T71,F10.3)') " MINHOP| beta_2", this%beta2
141  WRITE (this%iw, '(A,T71,F10.3)') " MINHOP| beta_3", this%beta3
142  WRITE (this%iw, '(A,T71,F10.3)') " MINHOP| alpha_1", this%alpha1
143  WRITE (this%iw, '(A,T71,F10.3)') " MINHOP| alpha_2", this%alpha2
144  WRITE (this%iw, '(A,T71,F10.3)') " MINHOP| Initial acceptance energy [Hartree]", this%Eaccept0
145  WRITE (this%iw, '(A,T71,F10.3)') " MINHOP| Initial temperature [Kelvin]", this%temp_init*kelvin
146  WRITE (this%iw, '(A,T71,L10)') " MINHOP| All workers share a single history", this%share_history
147  END IF
148  END SUBROUTINE minhop_init
149 
150 ! **************************************************************************************************
151 !> \brief Central steering routine of Minima Hopping
152 !> \param this ...
153 !> \param report ...
154 !> \param cmd ...
155 !> \author Ole Schuett
156 ! **************************************************************************************************
157  SUBROUTINE minhop_steer(this, report, cmd)
158  TYPE(minhop_type) :: this
159  TYPE(swarm_message_type) :: report, cmd
160 
161  CHARACTER(len=default_string_length) :: status
162  INTEGER :: hid, iframe, wid
163  LOGICAL :: minima_known
164  REAL(kind=dp) :: report_epot
165  REAL(kind=dp), DIMENSION(:), POINTER :: report_positions
166  TYPE(history_fingerprint_type) :: report_fp
167 
168  NULLIFY (report_positions)
169  CALL swarm_message_get(report, "worker_id", wid)
170  CALL swarm_message_get(report, "status", status)
171 
172  IF (trim(status) == "initial_hello") THEN
173  this%worker_state(wid)%temp = this%temp_init
174  this%worker_state(wid)%Eaccept = this%Eaccept0
175  CALL swarm_message_add(cmd, "command", "md_and_gopt")
176  CALL swarm_message_add(cmd, "iframe", 1)
177  CALL swarm_message_add(cmd, "temperature", this%worker_state(wid)%temp)
178  IF (this%iw > 0) WRITE (this%iw, '(1X,A,1X,I10,1X,A,7X,F10.3)') &
179  "MINHOP| Sending worker", wid, &
180  "initial temperature [Kelvin]", this%worker_state(wid)%temp*kelvin
181  RETURN
182  END IF
183 
184  hid = wid ! history_id = worker_id unless ....
185  IF (this%share_history) hid = 1 !...there is ONE shared history.
186 
187  CALL swarm_message_get(report, "Epot", report_epot)
188  CALL swarm_message_get(report, "positions", report_positions)
189 
190  report_fp = history_fingerprint(report_epot, report_positions)
191 
192  IF (.NOT. ALLOCATED(this%worker_state(wid)%pos)) THEN
193  !init (first real report)
194  this%worker_state(wid)%Epot = report_epot
195  ALLOCATE (this%worker_state(wid)%pos(SIZE(report_positions)))
196  this%worker_state(wid)%pos(:) = report_positions
197  this%worker_state(wid)%fp = report_fp
198  END IF
199 
200  IF (history_fingerprint_match(this%history(hid), this%worker_state(wid)%fp, report_fp)) THEN
201  ! not escaped
202  IF (this%iw > 0) WRITE (this%iw, '(A)') " MINHOP| Not escaped"
203  this%worker_state(wid)%temp = this%worker_state(wid)%temp*this%beta1 !increasing temperature
204  ELSE
205  ! escaped
206  CALL history_lookup(this%history(hid), report_fp, minima_known)
207  IF (minima_known) THEN
208  IF (this%iw > 0) WRITE (this%iw, '(A)') " MINHOP| Escaped, old minima"
209  this%worker_state(wid)%temp = this%worker_state(wid)%temp*this%beta2 !increasing temperature
210  ELSE
211  IF (this%iw > 0) WRITE (this%iw, '(A)') " MINHOP| Escaped, new minima"
212  this%worker_state(wid)%temp = this%worker_state(wid)%temp*this%beta3 !decreasing temperature
213  CALL history_add(this%history(hid), report_fp)
214  END IF
215 
216  IF (report_epot < this%worker_state(wid)%Epot_hop) THEN
217  ! new locally lowest
218  IF (this%iw > 0) WRITE (this%iw, '(A)') " MINHOP| New locally lowest"
219  this%worker_state(wid)%Epot_hop = report_epot
220  IF (.NOT. ALLOCATED(this%worker_state(wid)%pos_hop)) &
221  ALLOCATE (this%worker_state(wid)%pos_hop(SIZE(report_positions)))
222  this%worker_state(wid)%pos_hop(:) = report_positions
223  this%worker_state(wid)%fp_hop = report_fp
224  END IF
225 
226  IF (this%worker_state(wid)%Epot_hop - this%worker_state(wid)%Epot < this%worker_state(wid)%Eaccept) THEN
227  ! accept
228  IF (this%iw > 0) WRITE (this%iw, '(A)') " MINHOP| Accept"
229  this%worker_state(wid)%Epot = this%worker_state(wid)%Epot_hop
230  this%worker_state(wid)%pos(:) = this%worker_state(wid)%pos_hop
231  this%worker_state(wid)%fp = this%worker_state(wid)%fp_hop
232  this%worker_state(wid)%Epot_hop = huge(1.0)
233 
234  this%worker_state(wid)%Eaccept = this%worker_state(wid)%Eaccept*this%alpha1 !decreasing Eaccept
235  this%n_accepted = this%n_accepted + 1
236  ELSE
237  ! not accept
238  IF (this%iw > 0) WRITE (this%iw, '(A)') " MINHOP| Reject"
239  this%worker_state(wid)%Eaccept = this%worker_state(wid)%Eaccept*this%alpha2 !increasing Eaccept
240  this%n_rejected = this%n_rejected + 1
241  END IF
242  END IF
243 
244  IF (this%iw > 0) THEN
245  WRITE (this%iw, '(A,15X,E20.10)') &
246  " MINHOP| Worker's acceptance Energy [Hartree]", this%worker_state(wid)%Eaccept
247  WRITE (this%iw, '(A,22X,F20.3)') &
248  " MINHOP| Worker's temperature [Kelvin]", this%worker_state(wid)%temp*kelvin
249  END IF
250 
251  CALL swarm_message_get(report, "iframe", iframe)
252  CALL swarm_message_add(cmd, "iframe", iframe)
253  CALL swarm_message_add(cmd, "command", "md_and_gopt")
254  CALL swarm_message_add(cmd, "positions", this%worker_state(wid)%pos)
255  CALL swarm_message_add(cmd, "temperature", this%worker_state(wid)%temp)
256 
257  IF (this%iw > 0) THEN
258  WRITE (this%iw, '(A,30X,I10)') &
259  " MINHOP| Total number of accepted minima", this%n_accepted
260  WRITE (this%iw, '(A,30X,I10)') &
261  " MINHOP| Total number of rejected minima", this%n_rejected
262  END IF
263 
264  DEALLOCATE (report_positions)
265  END SUBROUTINE minhop_steer
266 
267 ! **************************************************************************************************
268 !> \brief Finalizes master for Minima Hopping
269 !> \param this ...
270 !> \author Ole Schuett
271 ! **************************************************************************************************
272  SUBROUTINE minhop_finalize(this)
273  TYPE(minhop_type) :: this
274 
275  INTEGER :: i
276 
277  DO i = 1, SIZE(this%history)
278  CALL history_finalize(this%history(i))
279  END DO
280  END SUBROUTINE minhop_finalize
281 
282 END MODULE glbopt_minhop
283 
collects all references to literature in CP2K as new algorithms / method are included from literature...
Definition: bibliography.F:28
integer, save, public goedecker2004
Definition: bibliography.F:43
History of minima, calculates, stores and compares fingerprints of minima. Used by Minima Hopping and...
subroutine, public history_init(history, history_section, iw)
Initializes a history.
subroutine, public history_lookup(history, fingerprint, found, id)
Checks if a given fingerprints is contained in the history.
subroutine, public history_finalize(history)
Finalizes a history.
subroutine, public history_add(history, fingerprint, id)
Addes a new fingerprints to the history. Optionally, an abitrary id can be stored alongside the finge...
type(history_fingerprint_type) function, public history_fingerprint(Epot, pos)
Calculates a fingerprint for a given configuration.
logical function, public history_fingerprint_match(history, fp1, fp2)
Checks if two given fingerprints match.
Routines for the Minima Hopping global optimization scheme.
Definition: glbopt_minhop.F:12
subroutine, public minhop_finalize(this)
Finalizes master for Minima Hopping.
subroutine, public minhop_init(this, glbopt_section, n_workers, iw)
Initializes master for Minima Hopping.
subroutine, public minhop_steer(this, report, cmd)
Central steering routine of Minima Hopping.
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
Defines the basic variable types.
Definition: kinds.F:23
integer, parameter, public dp
Definition: kinds.F:34
integer, parameter, public default_string_length
Definition: kinds.F:57
Definition of physical constants:
Definition: physcon.F:68
real(kind=dp), parameter, public kelvin
Definition: physcon.F:165
Swarm-message, a convenient data-container for with build-in serialization.
Definition: swarm_message.F:12