Line data Source code
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 Contains type used for a Simulation Cell Optimization
10 : !> \par History
11 : !> none
12 : !> \author Teodoro Laino - created [tlaino] - 03.2008 - Zurich University
13 : ! **************************************************************************************************
14 : MODULE cell_opt_types
15 :
16 : USE cell_methods, ONLY: cell_create
17 : USE cell_opt_utils, ONLY: read_external_press_tensor
18 : USE cell_types, ONLY: cell_clone,&
19 : cell_release,&
20 : cell_type
21 : USE cp_log_handling, ONLY: cp_get_default_logger,&
22 : cp_logger_type
23 : USE cp_output_handling, ONLY: cp_print_key_finished_output,&
24 : cp_print_key_unit_nr
25 : USE cp_subsys_types, ONLY: cp_subsys_get,&
26 : cp_subsys_type
27 : USE cp_units, ONLY: cp_unit_from_cp2k
28 : USE force_env_types, ONLY: force_env_get,&
29 : force_env_type
30 : USE input_constants, ONLY: fix_none,&
31 : fix_x,&
32 : fix_xy,&
33 : fix_xz,&
34 : fix_y,&
35 : fix_yz,&
36 : fix_z
37 : USE input_section_types, ONLY: section_vals_type,&
38 : section_vals_val_get
39 : USE kinds, ONLY: dp
40 : USE particle_list_types, ONLY: particle_list_type
41 : #include "../base/base_uses.f90"
42 :
43 : IMPLICIT NONE
44 : PRIVATE
45 :
46 : LOGICAL, PRIVATE, PARAMETER :: debug_this_module = .FALSE.
47 : CHARACTER(len=*), PARAMETER, PRIVATE :: moduleN = 'cell_opt_types'
48 :
49 : PUBLIC :: cell_opt_env_type, &
50 : cell_opt_env_create, &
51 : cell_opt_env_release
52 :
53 : ! **************************************************************************************************
54 : !> \brief Type containing all informations abour the simulation cell optimization
55 : !> \par History
56 : !> none
57 : !> \author Teodoro Laino - created [tlaino] - 03.2008 - Zurich University
58 : ! **************************************************************************************************
59 : TYPE cell_opt_env_type
60 : ! Simulation cell optimization parameters
61 : INTEGER :: constraint_id = fix_none
62 : LOGICAL :: keep_angles = .FALSE., &
63 : keep_symmetry = .FALSE.
64 : REAL(KIND=dp) :: pres_ext = 0.0_dp, pres_int = 0.0_dp, pres_tol = 0.0_dp, pres_constr = 0.0_dp
65 : REAL(KIND=dp), DIMENSION(3, 3) :: mtrx = 0.0_dp
66 : REAL(KIND=dp), DIMENSION(3, 3) :: rot_matrix = 0.0_dp
67 : TYPE(cell_type), POINTER :: ref_cell => NULL()
68 : END TYPE cell_opt_env_type
69 :
70 : CONTAINS
71 :
72 : ! **************************************************************************************************
73 : !> \brief ...
74 : !> \param cell_env ...
75 : !> \param force_env ...
76 : !> \param geo_section ...
77 : !> \par History
78 : !> none
79 : !> \author Teodoro Laino - created [tlaino] - 03.2008 - Zurich University
80 : ! **************************************************************************************************
81 5460 : SUBROUTINE cell_opt_env_create(cell_env, force_env, geo_section)
82 : TYPE(cell_opt_env_type), INTENT(OUT) :: cell_env
83 : TYPE(force_env_type), POINTER :: force_env
84 : TYPE(section_vals_type), POINTER :: geo_section
85 :
86 : CHARACTER(LEN=4) :: label
87 : INTEGER :: ip, output_unit
88 : REAL(KIND=dp), DIMENSION(3) :: r
89 : TYPE(cell_type), POINTER :: cell
90 : TYPE(cp_logger_type), POINTER :: logger
91 : TYPE(cp_subsys_type), POINTER :: subsys
92 : TYPE(particle_list_type), POINTER :: particles
93 :
94 210 : NULLIFY (cell_env%ref_cell, cell, subsys, particles)
95 210 : CALL force_env_get(force_env, cell=cell, subsys=subsys)
96 210 : CALL cell_create(cell_env%ref_cell)
97 210 : CALL cell_clone(cell, cell_env%ref_cell, tag="REF_CELL_OPT")
98 210 : CALL section_vals_val_get(geo_section, "KEEP_ANGLES", l_val=cell_env%keep_angles)
99 210 : CALL section_vals_val_get(geo_section, "KEEP_SYMMETRY", l_val=cell_env%keep_symmetry)
100 210 : CALL section_vals_val_get(geo_section, "PRESSURE_TOLERANCE", r_val=cell_env%pres_tol)
101 210 : CALL section_vals_val_get(geo_section, "CONSTRAINT", i_val=cell_env%constraint_id)
102 :
103 : ! Compute the rotation matrix that give the cell vectors in the "canonical" orientation
104 11130 : cell_env%rot_matrix = MATMUL(cell_env%ref_cell%hmat, cell%h_inv)
105 :
106 : ! Get the external pressure
107 : CALL read_external_press_tensor(geo_section, cell, cell_env%pres_ext, cell_env%mtrx, &
108 210 : cell_env%rot_matrix)
109 :
110 : ! Rotate particles accordingly
111 210 : CALL cp_subsys_get(subsys, particles=particles)
112 18266 : DO ip = 1, particles%n_els
113 18056 : r = MATMUL(TRANSPOSE(cell_env%rot_matrix), particles%els(ip)%r)
114 72434 : particles%els(ip)%r = r
115 : END DO
116 :
117 : ! Print cell optimisation setup
118 210 : NULLIFY (logger)
119 210 : logger => cp_get_default_logger()
120 210 : output_unit = cp_print_key_unit_nr(logger, geo_section, "PRINT%CELL", extension=".Log")
121 210 : IF (output_unit > 0) THEN
122 : WRITE (UNIT=output_unit, FMT="(/,T2,A,T61,F20.1)") &
123 105 : "CELL_OPT| Pressure tolerance [bar]: ", cp_unit_from_cp2k(cell_env%pres_tol, "bar")
124 105 : IF (cell_env%keep_angles) THEN
125 : WRITE (UNIT=output_unit, FMT="(T2,A,T78,A3)") &
126 11 : "CELL_OPT| Keep angles between the cell vectors: ", "YES"
127 : ELSE
128 : WRITE (UNIT=output_unit, FMT="(T2,A,T78,A3)") &
129 94 : "CELL_OPT| Keep angles between the cell vectors: ", " NO"
130 : END IF
131 105 : IF (cell_env%keep_symmetry) THEN
132 : WRITE (UNIT=output_unit, FMT="(T2,A,T78,A3)") &
133 19 : "CELL_OPT| Keep cell symmetry: ", "YES"
134 : ELSE
135 : WRITE (UNIT=output_unit, FMT="(T2,A,T78,A3)") &
136 86 : "CELL_OPT| Keep cell symmetry: ", " NO"
137 : END IF
138 105 : SELECT CASE (cell_env%constraint_id)
139 : CASE (fix_x)
140 0 : label = " X"
141 : CASE (fix_y)
142 0 : label = " Y"
143 : CASE (fix_z)
144 1 : label = " Z"
145 : CASE (fix_xy)
146 1 : label = " XY"
147 : CASE (fix_xz)
148 0 : label = " XZ"
149 : CASE (fix_yz)
150 0 : label = " YZ"
151 : CASE (fix_none)
152 105 : label = "NONE"
153 : END SELECT
154 : WRITE (UNIT=output_unit, FMT="(T2,A,T77,A4)") &
155 105 : "CELL_OPT| Constraint: ", label
156 : END IF
157 210 : CALL cp_print_key_finished_output(output_unit, logger, geo_section, "PRINT%CELL")
158 :
159 210 : END SUBROUTINE cell_opt_env_create
160 :
161 : ! **************************************************************************************************
162 : !> \brief ...
163 : !> \param cell_env ...
164 : !> \par History
165 : !> none
166 : !> \author Teodoro Laino - created [tlaino] - 03.2008 - Zurich University
167 : ! **************************************************************************************************
168 210 : SUBROUTINE cell_opt_env_release(cell_env)
169 : TYPE(cell_opt_env_type), INTENT(INOUT) :: cell_env
170 :
171 210 : CALL cell_release(cell_env%ref_cell)
172 :
173 210 : END SUBROUTINE cell_opt_env_release
174 :
175 0 : END MODULE cell_opt_types
|