(git:374b731)
Loading...
Searching...
No Matches
md_ener_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 Split md_ener module from md_environment_type
10!> \author Teodoro Laino [tlaino] - 03.2008 - University of Zurich
11! **************************************************************************************************
13
14 USE kinds, ONLY: dp
15#include "../base/base_uses.f90"
16
17 IMPLICIT NONE
18
19 PRIVATE
20
21! **************************************************************************************************
23 INTEGER :: nfree = 0, nfree_shell = 0
24 REAL(kind=dp) :: constant = 0.0_dp
25 REAL(kind=dp) :: delta_cons = 0.0_dp, delta_epot = 0.0_dp
26 REAL(kind=dp) :: epot = 0.0_dp
27 REAL(kind=dp) :: ekin = 0.0_dp, ekin_qm = 0.0_dp
28 REAL(kind=dp) :: temp_part = 0.0_dp, temp_qm = 0.0_dp
29 REAL(kind=dp) :: temp_baro = 0.0_dp
30 REAL(kind=dp) :: ekin_coefs = 0.0_dp
31 REAL(kind=dp) :: temp_coefs = 0.0_dp
32 REAL(kind=dp) :: ekin_shell = 0.0_dp, temp_shell = 0.0_dp
33 REAL(kind=dp) :: thermostat_part_kin = 0.0_dp, thermostat_part_pot = 0.0_dp
34 REAL(kind=dp) :: thermostat_fast_kin = 0.0_dp, thermostat_fast_pot = 0.0_dp
35 REAL(kind=dp) :: thermostat_slow_kin = 0.0_dp, thermostat_slow_pot = 0.0_dp
36 REAL(kind=dp) :: thermostat_baro_kin = 0.0_dp, thermostat_baro_pot = 0.0_dp
37 REAL(kind=dp) :: thermostat_coef_kin = 0.0_dp, thermostat_coef_pot = 0.0_dp
38 REAL(kind=dp) :: thermostat_shell_kin = 0.0_dp, thermostat_shell_pot = 0.0_dp
39 REAL(kind=dp) :: baro_kin = 0.0_dp, baro_pot = 0.0_dp
40 REAL(kind=dp) :: vcom(3) = 0.0_dp, total_mass = 0.0_dp
41 REAL(kind=dp), DIMENSION(:), POINTER :: ekin_kind => null()
42 REAL(kind=dp), DIMENSION(:), POINTER :: temp_kind => null()
43 INTEGER, DIMENSION(:), POINTER :: nfree_kind => null()
44 REAL(kind=dp), DIMENSION(:), POINTER :: ekin_shell_kind => null()
45 REAL(kind=dp), DIMENSION(:), POINTER :: temp_shell_kind => null()
46 INTEGER, DIMENSION(:), POINTER :: nfree_shell_kind => null()
47 END TYPE md_ener_type
48
49! *** Public subroutines and data types ***
51
52! *** Global parameters ***
53
54 CHARACTER(len=*), PARAMETER, PRIVATE :: modulen = 'md_ener_types'
55
56CONTAINS
57
58! **************************************************************************************************
59!> \brief retains the given md_ener structure
60!> \param md_ener ...
61!> \par History
62!> 10.2007 created [MI]
63!> \author MI
64! **************************************************************************************************
65 SUBROUTINE create_md_ener(md_ener)
66 TYPE(md_ener_type), INTENT(OUT) :: md_ener
67
68 mark_used(md_ener)
69
70 END SUBROUTINE create_md_ener
71
72! **************************************************************************************************
73!> \brief releases the given md_ener structure
74!> \param md_ener ...
75!> \par History
76!> 10.2007 created [MI]
77!> \author MI
78! **************************************************************************************************
79 SUBROUTINE release_md_ener(md_ener)
80 TYPE(md_ener_type), INTENT(INOUT) :: md_ener
81
82 IF (ASSOCIATED(md_ener%temp_kind)) THEN
83 DEALLOCATE (md_ener%temp_kind)
84 END IF
85 IF (ASSOCIATED(md_ener%ekin_kind)) THEN
86 DEALLOCATE (md_ener%ekin_kind)
87 END IF
88 IF (ASSOCIATED(md_ener%nfree_kind)) THEN
89 DEALLOCATE (md_ener%nfree_kind)
90 END IF
91 IF (ASSOCIATED(md_ener%temp_shell_kind)) THEN
92 DEALLOCATE (md_ener%temp_shell_kind)
93 END IF
94 IF (ASSOCIATED(md_ener%ekin_shell_kind)) THEN
95 DEALLOCATE (md_ener%ekin_shell_kind)
96 END IF
97 IF (ASSOCIATED(md_ener%nfree_shell_kind)) THEN
98 DEALLOCATE (md_ener%nfree_shell_kind)
99 END IF
100
101 END SUBROUTINE release_md_ener
102
103! **************************************************************************************************
104!> \brief initialize to zero energies and temperatures
105!> \param md_ener ...
106!> \param tkind ...
107!> \param tshell ...
108!> \par History
109!> 10.2007 created [MI]
110!> \author MI
111! **************************************************************************************************
112 SUBROUTINE zero_md_ener(md_ener, tkind, tshell)
113 TYPE(md_ener_type), INTENT(INOUT) :: md_ener
114 LOGICAL, INTENT(IN) :: tkind, tshell
115
116 md_ener%ekin = 0.0_dp
117 md_ener%temp_part = 0.0_dp
118 md_ener%temp_baro = 0.0_dp
119 md_ener%ekin_coefs = 0.0_dp
120 md_ener%temp_coefs = 0.0_dp
121 md_ener%ekin_qm = 0.0_dp
122 md_ener%temp_qm = 0.0_dp
123 md_ener%ekin_shell = 0.0_dp
124 md_ener%temp_shell = 0.0_dp
125 md_ener%constant = 0.0_dp
126 md_ener%delta_cons = 0.0_dp
127 md_ener%delta_epot = 0.0_dp
128 md_ener%thermostat_part_kin = 0.0_dp
129 md_ener%thermostat_part_pot = 0.0_dp
130 md_ener%thermostat_fast_kin = 0.0_dp
131 md_ener%thermostat_fast_pot = 0.0_dp
132 md_ener%thermostat_slow_kin = 0.0_dp
133 md_ener%thermostat_slow_pot = 0.0_dp
134 md_ener%thermostat_coef_kin = 0.0_dp
135 md_ener%thermostat_coef_pot = 0.0_dp
136 md_ener%thermostat_baro_kin = 0.0_dp
137 md_ener%thermostat_baro_pot = 0.0_dp
138 md_ener%thermostat_shell_kin = 0.0_dp
139 md_ener%thermostat_shell_pot = 0.0_dp
140 md_ener%baro_kin = 0.0_dp
141 md_ener%baro_pot = 0.0_dp
142 IF (tkind) THEN
143 md_ener%temp_kind = 0.0_dp
144 md_ener%ekin_kind = 0.0_dp
145
146 IF (tshell) THEN
147 md_ener%temp_shell_kind = 0.0_dp
148 md_ener%ekin_shell_kind = 0.0_dp
149 END IF
150 END IF
151 md_ener%vcom(:) = 0.0_dp
152 md_ener%total_mass = 0.0_dp
153 END SUBROUTINE zero_md_ener
154
155END MODULE md_ener_types
Defines the basic variable types.
Definition kinds.F:23
integer, parameter, public dp
Definition kinds.F:34
Split md_ener module from md_environment_type.
subroutine, public zero_md_ener(md_ener, tkind, tshell)
initialize to zero energies and temperatures
subroutine, public release_md_ener(md_ener)
releases the given md_ener structure
subroutine, public create_md_ener(md_ener)
retains the given md_ener structure