(git:ccc2433)
fp_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 types used in the flexible partitioning scheme
10 !> \par History
11 !> 04.2006 [Joost VandeVondele]
12 !> \author Joost VandeVondele
13 ! **************************************************************************************************
14 MODULE fp_types
16  cp_logger_type
23  section_vals_type,&
25  USE kinds, ONLY: dp
26 #include "./base/base_uses.f90"
27 
28  IMPLICIT NONE
29  PRIVATE
30 
31  PUBLIC :: fp_type
33 
34  CHARACTER(len=*), PARAMETER, PRIVATE :: moduleN = 'fp_types'
35 
36 ! **************************************************************************************************
37  TYPE fp_type
38 
39  ! input related objects
40  LOGICAL :: use_fp
41 
42  INTEGER :: central_atom
43  INTEGER, DIMENSION(:), POINTER :: inner_atoms, outer_atoms
44  REAL(KIND=dp) :: inner_radius, outer_radius
45  REAL(KIND=dp) :: strength, smooth_width
46  LOGICAL :: bias
47  REAL(KIND=dp) :: temperature
48  TYPE(section_vals_type), POINTER :: print_section
49 
50  ! computed during runs
51  INTEGER :: i1, i2, o1, o2
52  REAL(KIND=dp) :: ri1, ri2, ro1, ro2
53  REAL(KIND=dp) :: weight, comb_weight, bias_weight
54  REAL(KIND=dp) :: energy, bias_energy, restraint_energy
55  END TYPE fp_type
56 
57 CONTAINS
58 
59 ! **************************************************************************************************
60 !> \brief create retain release the flexible partitioning environment
61 !> \param fp_env ...
62 !> \par History
63 !> 04.2006 created [Joost VandeVondele]
64 ! **************************************************************************************************
65  PURE SUBROUTINE fp_env_create(fp_env)
66  TYPE(fp_type), INTENT(OUT) :: fp_env
67 
68  fp_env%use_fp = .false.
69  NULLIFY (fp_env%inner_atoms)
70  NULLIFY (fp_env%outer_atoms)
71  NULLIFY (fp_env%print_section)
72 
73  END SUBROUTINE fp_env_create
74 
75 ! **************************************************************************************************
76 !> \brief ...
77 !> \param fp_env ...
78 ! **************************************************************************************************
79  SUBROUTINE fp_env_release(fp_env)
80  TYPE(fp_type), INTENT(INOUT) :: fp_env
81 
82  IF (ASSOCIATED(fp_env%inner_atoms)) DEALLOCATE (fp_env%inner_atoms)
83  IF (ASSOCIATED(fp_env%outer_atoms)) DEALLOCATE (fp_env%outer_atoms)
84  IF (ASSOCIATED(fp_env%print_section)) CALL section_vals_release(fp_env%print_section)
85  fp_env%use_fp = .false.
86 
87  END SUBROUTINE fp_env_release
88 
89 ! **************************************************************************************************
90 !> \brief reads the corresponding input section and stores it in the fp_env
91 !> \param fp_env ...
92 !> \param fp_section ...
93 !> \par History
94 !> 04.2006 created [Joost VandeVondele]
95 ! **************************************************************************************************
96  SUBROUTINE fp_env_read(fp_env, fp_section)
97  TYPE(fp_type), INTENT(INOUT) :: fp_env
98  TYPE(section_vals_type), POINTER :: fp_section
99 
100  CHARACTER(len=*), PARAMETER :: routinen = 'fp_env_read'
101 
102  INTEGER :: handle
103  INTEGER, DIMENSION(:), POINTER :: tmplist
104 
105  CALL timeset(routinen, handle)
106  CALL section_vals_get(fp_section, explicit=fp_env%use_fp)
107  IF (fp_env%use_fp) THEN
108  CALL section_vals_val_get(fp_section, "CENTRAL_ATOM", i_val=fp_env%central_atom)
109 
110  CALL section_vals_val_get(fp_section, "INNER_ATOMS", i_vals=tmplist)
111  ALLOCATE (fp_env%inner_atoms(SIZE(tmplist, 1)))
112  fp_env%inner_atoms = tmplist
113 
114  CALL section_vals_val_get(fp_section, "OUTER_ATOMS", i_vals=tmplist)
115  ALLOCATE (fp_env%outer_atoms(SIZE(tmplist, 1)))
116  fp_env%outer_atoms = tmplist
117 
118  CALL section_vals_val_get(fp_section, "INNER_RADIUS", r_val=fp_env%inner_radius)
119  CALL section_vals_val_get(fp_section, "OUTER_RADIUS", r_val=fp_env%outer_radius)
120  CALL section_vals_val_get(fp_section, "STRENGTH", r_val=fp_env%strength)
121  CALL section_vals_val_get(fp_section, "SMOOTH_WIDTH", r_val=fp_env%smooth_width)
122  CALL section_vals_val_get(fp_section, "BIAS", l_val=fp_env%bias)
123  CALL section_vals_val_get(fp_section, "TEMPERATURE", r_val=fp_env%temperature)
124 
125  fp_env%print_section => section_vals_get_subs_vals(fp_section, "WEIGHTS")
126  CALL section_vals_retain(fp_env%print_section)
127  END IF
128  CALL timestop(handle)
129 
130  END SUBROUTINE fp_env_read
131 
132 ! **************************************************************************************************
133 !> \brief writes information concerning the fp_env to the output
134 !> \param fp_env ...
135 !> \param fp_section ...
136 !> \par History
137 !> 04.2006 created [Joost VandeVondele]
138 ! **************************************************************************************************
139  SUBROUTINE fp_env_write(fp_env, fp_section)
140  TYPE(fp_type), INTENT(IN) :: fp_env
141  TYPE(section_vals_type), POINTER :: fp_section
142 
143  CHARACTER(len=*), PARAMETER :: routinen = 'fp_env_write'
144 
145  INTEGER :: handle, output_unit
146  TYPE(cp_logger_type), POINTER :: logger
147  TYPE(section_vals_type), POINTER :: print
148 
149  CALL timeset(routinen, handle)
150  logger => cp_get_default_logger()
151 
152  IF (fp_env%use_fp) THEN
153  print => section_vals_get_subs_vals(fp_section, "CONTROL")
154  output_unit = cp_print_key_unit_nr(logger, print, "", extension=".Log")
155  IF (output_unit > 0) THEN
156  WRITE (unit=output_unit, fmt="(T2,A,T79,A)") &
157  "FP| Flexible partitioning is ", "ON"
158  WRITE (unit=output_unit, fmt="(T2,A,T71,I10)") &
159  "FP| Central atom ", fp_env%central_atom
160  WRITE (unit=output_unit, fmt="(T2,A,T71,I10)") &
161  "FP| number of inner atoms", SIZE(fp_env%inner_atoms, 1)
162  WRITE (unit=output_unit, fmt="(1(T2,8I8))") fp_env%inner_atoms
163  WRITE (unit=output_unit, fmt="(T2,A,T71,I10)") &
164  "FP| number of outer atoms", SIZE(fp_env%outer_atoms, 1)
165  WRITE (unit=output_unit, fmt="(1(T2,8I8))") fp_env%outer_atoms
166  WRITE (unit=output_unit, fmt="(T2,A,T61,F20.10)") &
167  "FP| inner radius [a.u.] ", fp_env%inner_radius
168  WRITE (unit=output_unit, fmt="(T2,A,T61,F20.10)") &
169  "FP| outer radius [a.u.] ", fp_env%outer_radius
170  WRITE (unit=output_unit, fmt="(T2,A,T61,F20.10)") &
171  "FP| reflecting restraint strength ", fp_env%strength
172  IF (fp_env%bias) THEN
173  WRITE (unit=output_unit, fmt="(T2,A,T79,A)") &
174  "FP| Flexible partitioning bias is ", "ON"
175  WRITE (unit=output_unit, fmt="(T2,A,T61,F20.10)") &
176  "FP| bias temperature [kT a.u.]", fp_env%temperature
177  WRITE (unit=output_unit, fmt="(T2,A,T61,F20.10)") &
178  "FP| smooth width [a.u.] ", fp_env%smooth_width
179  ELSE
180  WRITE (unit=output_unit, fmt="(T2,A,T78,A)") &
181  "FP| Flexible partitioning bias is", "OFF"
182  END IF
183  END IF
184  CALL cp_print_key_finished_output(output_unit, logger, print, "")
185  END IF
186  CALL timestop(handle)
187 
188  END SUBROUTINE fp_env_write
189 
190 END MODULE fp_types
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,...
types used in the flexible partitioning scheme
Definition: fp_types.F:14
subroutine, public fp_env_write(fp_env, fp_section)
writes information concerning the fp_env to the output
Definition: fp_types.F:140
subroutine, public fp_env_release(fp_env)
...
Definition: fp_types.F:80
subroutine, public fp_env_read(fp_env, fp_section)
reads the corresponding input section and stores it in the fp_env
Definition: fp_types.F:97
pure subroutine, public fp_env_create(fp_env)
create retain release the flexible partitioning environment
Definition: fp_types.F:66
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 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_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
recursive subroutine, public section_vals_release(section_vals)
releases the given object
Defines the basic variable types.
Definition: kinds.F:23
integer, parameter, public dp
Definition: kinds.F:34