(git:374b731)
Loading...
Searching...
No Matches
al_system_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 the canonical sampling through velocity rescaling
10!> \author Teodoro Laino - 09.2007 University of Zurich [tlaino]
11! **************************************************************************************************
13 USE bibliography, ONLY: jones2011,&
14 cite_reference
20 USE kinds, ONLY: dp
21 USE simpar_types, ONLY: simpar_type
22#include "./base/base_uses.f90"
23
24 IMPLICIT NONE
25
26 PRIVATE
27 PUBLIC :: al_system_type, &
28 al_init, &
29 al_dealloc, &
31
32! **************************************************************************************************
33 TYPE al_thermo_type
34 INTEGER :: degrees_of_freedom = 0
35 REAL(KIND=dp) :: nkt = 0.0_dp
36 REAL(KIND=dp) :: chi = 0.0_dp
37 REAL(KIND=dp) :: mass = 0.0_dp
38 REAL(KIND=dp) :: region_kin_energy = 0.0_dp
39 END TYPE al_thermo_type
40
41! **************************************************************************************************
43 INTEGER :: region = 0, glob_num_al = 0, loc_num_al = 0
44 REAL(kind=dp) :: tau_nh = 0.0_dp, tau_langevin = 0.0_dp, dt_fact = 0.0_dp
45 REAL(kind=dp) :: dt = 0.0_dp
46 TYPE(al_thermo_type), POINTER :: nvt(:) => null()
47 TYPE(map_info_type), POINTER :: map_info => null()
48 END TYPE al_system_type
49
50! *** Global parameters ***
51 CHARACTER(len=*), PARAMETER, PRIVATE :: modulen = 'al_system_types'
52
53CONTAINS
54
55! **************************************************************************************************
56!> \brief Initialize type for Adaptive Langevin (AD_LANGEVIN)
57!> \param al ...
58!> \param simpar ...
59!> \param section ...
60!> \author Noam Bernstein [noamb] 02.2012
61! **************************************************************************************************
62 SUBROUTINE al_init(al, simpar, section)
63 TYPE(al_system_type), POINTER :: al
64 TYPE(simpar_type), POINTER :: simpar
65 TYPE(section_vals_type), POINTER :: section
66
67 NULLIFY (al%nvt)
68 NULLIFY (al%map_info)
69 al%loc_num_al = 0
70 al%glob_num_al = 0
71 al%dt_fact = 1.0_dp
72 al%dt = simpar%dt
73 CALL cite_reference(jones2011)
74 CALL section_vals_val_get(section, "TIMECON_NH", r_val=al%tau_nh)
75 CALL section_vals_val_get(section, "TIMECON_LANGEVIN", r_val=al%tau_langevin)
76 CALL create_map_info_type(al%map_info)
77
78 END SUBROUTINE al_init
79
80! **************************************************************************************************
81!> \brief Initialize NVT type for AD_LANGEVIN thermostat
82!> \param al ...
83!> \author Noam Bernstein [noamb] 02.2012
84! **************************************************************************************************
85 SUBROUTINE al_thermo_create(al)
86 TYPE(al_system_type), POINTER :: al
87
88 INTEGER :: i
89 REAL(kind=dp), ALLOCATABLE, DIMENSION(:, :, :) :: seed
90
91 cpassert(ASSOCIATED(al))
92 cpassert(.NOT. ASSOCIATED(al%nvt))
93
94 ALLOCATE (al%nvt(al%loc_num_al))
95 DO i = 1, al%loc_num_al
96 al%nvt(i)%chi = 0.0_dp
97 END DO
98 ! Initialize the gaussian stream random number
99 ALLOCATE (seed(3, 2, al%glob_num_al))
100
101 END SUBROUTINE al_thermo_create
102
103! **************************************************************************************************
104!> \brief Deallocate type for AD_LANGEVIN thermostat
105!> \param al ...
106!> \author Noam Bernstein [noamb] 02.2012
107! **************************************************************************************************
108 SUBROUTINE al_dealloc(al)
109 TYPE(al_system_type), POINTER :: al
110
111 IF (ASSOCIATED(al)) THEN
112 CALL al_thermo_dealloc(al%nvt)
113 CALL release_map_info_type(al%map_info)
114 DEALLOCATE (al)
115 END IF
116
117 END SUBROUTINE al_dealloc
118
119! **************************************************************************************************
120!> \brief Deallocate NVT type for AD_LANGEVIN thermostat
121!> \param nvt ...
122!> \author Noam Bernstein [noamb] 02.2012
123! **************************************************************************************************
124 SUBROUTINE al_thermo_dealloc(nvt)
125 TYPE(al_thermo_type), DIMENSION(:), POINTER :: nvt
126
127 IF (ASSOCIATED(nvt)) THEN
128 DEALLOCATE (nvt)
129 END IF
130 END SUBROUTINE al_thermo_dealloc
131
132END MODULE al_system_types
133
Type for the canonical sampling through velocity rescaling.
subroutine, public al_dealloc(al)
Deallocate type for AD_LANGEVIN thermostat.
subroutine, public al_thermo_create(al)
Initialize NVT type for AD_LANGEVIN thermostat.
subroutine, public al_init(al, simpar, section)
Initialize type for Adaptive Langevin (AD_LANGEVIN)
collects all references to literature in CP2K as new algorithms / method are included from literature...
integer, save, public jones2011
Lumps all possible extended system variables into one type for easy access and passing.
subroutine, public release_map_info_type(map_info)
release the map_info type
subroutine, public create_map_info_type(map_info)
create the map_info type
objects that represent the structure of input sections and the data contained in an input section
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
Type for storing MD parameters.
Simulation parameter type for molecular dynamics.