(git:1f285aa)
simpar_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 Type for storing MD parameters
10 !> \author CJM
11 !> \author Teodoro Laino [tlaino] - University of Zurich - 10.2008
12 !> reorganization of the original routines/modules
13 ! **************************************************************************************************
15 
16  USE kinds, ONLY: dp
17 #include "./base/base_uses.f90"
18 
19  IMPLICIT NONE
20 
21  PRIVATE
22 
23 ! **************************************************************************************************
24 !> \brief Simulation parameter type for molecular dynamics
25 !> \par History
26 !> created [CJM]
27 !> \author Teodoro Laino [tlaino] - University of Zurich - 10.2008
28 !> reorganization of the original routines/modules
29 ! **************************************************************************************************
30  TYPE simpar_type
31  INTEGER :: nsteps
32  INTEGER :: max_steps
33  REAL(KIND=dp) :: dt
34  REAL(KIND=dp) :: dt_fact
35  REAL(KIND=dp) :: dr_tol
36  REAL(KIND=dp) :: dsc_tol
37  REAL(KIND=dp) :: temp_ext
38  REAL(KIND=dp) :: temp_baro_ext
39  REAL(KIND=dp) :: temp_baro
40  REAL(KIND=dp) :: temp_tol
41  REAL(KIND=dp) :: temp_baro_tol
42  REAL(KIND=dp) :: p_ext
43  REAL(KIND=dp) :: cmass
44  REAL(KIND=dp) :: cmass_nph
45  REAL(KIND=dp) :: v0
46  REAL(KIND=dp) :: e0
47  REAL(KIND=dp) :: v_shock
48  REAL(KIND=dp) :: p0
49  REAL(KIND=dp) :: f_annealing
50  REAL(KIND=dp) :: f_annealing_cell
51  REAL(KIND=dp) :: f_temperature_annealing
52  REAL(KIND=dp) :: gamma_nph
53  INTEGER :: ensemble
54  LOGICAL :: constraint
55  LOGICAL :: annealing
56  LOGICAL :: annealing_cell
57  LOGICAL :: temperature_annealing
58  LOGICAL :: dump_lm
59  LOGICAL :: angvel_zero
60  LOGICAL :: variable_dt
61  INTEGER :: nfree, nfree_rot_transl
62  INTEGER :: info_constraint
63  INTEGER :: lagrange_multipliers
64  REAL(KIND=dp) :: tau_cell
65  ! Constraints Parameters
66  REAL(KIND=dp) :: shake_tol, roll_tol
67  ! Langevin Parameters
68  REAL(KIND=dp) :: gamma
69  REAL(KIND=dp) :: noisy_gamma
70  REAL(KIND=dp) :: shadow_gamma
71  REAL(KIND=dp) :: var_w
72  ! RESPA Parameters
73  LOGICAL :: multi_time_switch, do_respa
74  INTEGER :: n_time_steps
75  ! SHELL parameters
76  REAL(KIND=dp) :: temp_sh_ext
77  REAL(KIND=dp) :: temp_sh_tol
78  LOGICAL :: temperature_per_kind
79  LOGICAL :: scale_temperature_per_kind
80  LOGICAL :: do_thermal_region
81  ! ADIABATIC parameters
82  REAL(KIND=dp) :: temp_slow
83  REAL(KIND=dp) :: temp_fast
84  REAL(KIND=dp) :: temp_tol_fast, temp_tol_slow
85  INTEGER :: n_resp_fast
86  ! Velocity softening Parameters
87  INTEGER :: soften_nsteps
88  REAL(KIND=dp) :: soften_alpha
89  REAL(KIND=dp) :: soften_delta
90  ! MD initialisation method
91  INTEGER :: initialization_method
92  END TYPE simpar_type
93 
94  PUBLIC :: simpar_type, &
97  CHARACTER(len=*), PARAMETER, PRIVATE :: moduleN = 'simpar_types'
98 
99 CONTAINS
100 ! **************************************************************************************************
101 !> \brief Creates the simulation parameters type
102 !> \param simpar ...
103 !> \author Teodoro Laino
104 ! **************************************************************************************************
105  SUBROUTINE create_simpar_type(simpar)
106  TYPE(simpar_type), POINTER :: simpar
107 
108  cpassert(.NOT. ASSOCIATED(simpar))
109  ALLOCATE (simpar)
110  END SUBROUTINE create_simpar_type
111 
112 ! **************************************************************************************************
113 !> \brief Releases the simulation parameters type
114 !> \param simpar ...
115 !> \author Teodoro Laino
116 ! **************************************************************************************************
117  SUBROUTINE release_simpar_type(simpar)
118  TYPE(simpar_type), POINTER :: simpar
119 
120  cpassert(ASSOCIATED(simpar))
121  DEALLOCATE (simpar)
122  END SUBROUTINE release_simpar_type
123 
124 END MODULE simpar_types
Calculation of the incomplete Gamma function F_n(t) for multi-center integrals over Cartesian Gaussia...
Definition: gamma.F:15
Defines the basic variable types.
Definition: kinds.F:23
integer, parameter, public dp
Definition: kinds.F:34
Type for storing MD parameters.
Definition: simpar_types.F:14
subroutine, public release_simpar_type(simpar)
Releases the simulation parameters type.
Definition: simpar_types.F:118
subroutine, public create_simpar_type(simpar)
Creates the simulation parameters type.
Definition: simpar_types.F:106