(git:ccc2433)
thermal_region_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 Thermal regions type: to initialize and control the temperature of
10 !> different regions
11 !> \par History
12 !> - Added support for langevin regions (2014/01/08, LT)
13 !> \author MI
14 ! **************************************************************************************************
16 
17  USE input_section_types, ONLY: section_vals_type
18  USE kinds, ONLY: dp
19 #include "../base/base_uses.f90"
20 
21  IMPLICIT NONE
22 
23  PRIVATE
24  PUBLIC :: thermal_regions_type, &
25  thermal_region_type, &
28 
29  TYPE thermal_regions_type
30  INTEGER :: nregions = 0
31  LOGICAL :: force_rescaling = .false.
32  REAL(KIND=dp) :: temp_reg0 = 0.0_dp
33  LOGICAL, DIMENSION(:), POINTER :: do_langevin => null()
34  TYPE(section_vals_type), POINTER :: section => null()
35  TYPE(thermal_region_type), DIMENSION(:), POINTER :: thermal_region => null()
36  END TYPE thermal_regions_type
37 
38  TYPE thermal_region_type
39  INTEGER :: region_index = 0, npart = 0
40  INTEGER, DIMENSION(:), POINTER :: part_index => null()
41  REAL(KIND=dp) :: ekin = 0.0_dp, noisy_gamma_region = 0.0_dp, temperature = 0.0_dp, temp_expected = 0.0_dp, temp_tol = 0.0_dp
42  END TYPE thermal_region_type
43 
44  CHARACTER(len=*), PARAMETER, PRIVATE :: moduleN = 'thermal_region_types'
45 CONTAINS
46 
47 ! **************************************************************************************************
48 !> \brief allocate thermal_regions
49 !> \param thermal_regions ...
50 !> \author
51 ! **************************************************************************************************
52  SUBROUTINE allocate_thermal_regions(thermal_regions)
53  TYPE(thermal_regions_type), INTENT(OUT) :: thermal_regions
54 
55  mark_used(thermal_regions)
56  END SUBROUTINE allocate_thermal_regions
57 
58 ! **************************************************************************************************
59 !> \brief release thermal_regions
60 !> \param thermal_regions ...
61 !> \author
62 ! **************************************************************************************************
63  SUBROUTINE release_thermal_regions(thermal_regions)
64 
65  TYPE(thermal_regions_type), INTENT(INOUT) :: thermal_regions
66 
67  INTEGER :: ireg
68 
69  IF (ASSOCIATED(thermal_regions%thermal_region)) THEN
70  DO ireg = 1, SIZE(thermal_regions%thermal_region)
71  DEALLOCATE (thermal_regions%thermal_region(ireg)%part_index)
72  END DO
73  DEALLOCATE (thermal_regions%thermal_region)
74  END IF
75  IF (ASSOCIATED(thermal_regions%do_langevin)) THEN
76  DEALLOCATE (thermal_regions%do_langevin)
77  END IF
78 
79  END SUBROUTINE release_thermal_regions
80 
81 END MODULE thermal_region_types
objects that represent the structure of input sections and the data contained in an input section
Defines the basic variable types.
Definition: kinds.F:23
integer, parameter, public dp
Definition: kinds.F:34
Thermal regions type: to initialize and control the temperature of different regions.
subroutine, public release_thermal_regions(thermal_regions)
release thermal_regions
subroutine, public allocate_thermal_regions(thermal_regions)
allocate thermal_regions