(git:374b731)
Loading...
Searching...
No Matches
tmc_move_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 tree nodes creation, searching, deallocation, references etc.
10!> \par History
11!> 11.2012 created [Mandes Schoenherr]
12!> \author Mandes 11/2012
13! **************************************************************************************************
14
16 USE kinds, ONLY: default_string_length,&
17 dp
18#include "../base/base_uses.f90"
19
20 IMPLICIT NONE
21
22 PRIVATE
23
24 CHARACTER(len=*), PARAMETER, PRIVATE :: moduleN = 'tmc_move_types'
25
26 !-- list of available move types
27 INTEGER, PARAMETER, PUBLIC :: mv_type_none = 0
28 INTEGER, PARAMETER, PUBLIC :: mv_type_swap_conf = 1 ! swapping of 2 configurations of different temperature
29 INTEGER, PARAMETER, PUBLIC :: mv_type_atom_trans = 2 ! atom translation (done in every posible direction)
30 INTEGER, PARAMETER, PUBLIC :: mv_type_mol_trans = 3 ! molecule translation (done in every posible direction)
31 INTEGER, PARAMETER, PUBLIC :: mv_type_mol_rot = 4 ! molecule rotation
32 INTEGER, PARAMETER, PUBLIC :: mv_type_proton_reorder = 5 ! reordering the protons within a chain of molecules
33 INTEGER, PARAMETER, PUBLIC :: mv_type_atom_swap = 6 ! swaps two atoms of different type
34 INTEGER, PARAMETER, PUBLIC :: mv_type_md = 7 ! certain amount of MD steps
35 INTEGER, PARAMETER, PUBLIC :: mv_type_volume_move = 8 ! volume move for NPT simulations
36 INTEGER, PARAMETER, PUBLIC :: mv_type_gausian_adapt = 9 ! gaussian adaptation
37 INTEGER, PARAMETER, PUBLIC :: mv_type_nmc_moves = 10 ! indentifies the Nested Monte Carlo move for master
38 INTEGER, PARAMETER, PUBLIC :: nr_mv_types = 10 !-- allways update the number of possible types!!
39
41
43 !-- mv_type, handling indeces to move type (are equal for all several configurations/temperatures)
44 REAL(kind=dp), DIMENSION(:), ALLOCATABLE :: mv_weight
45 !-- mv_size, moves are normaly done in interval ]-mv_size, mv_size[
46 ! 1st dimension are the different types, 2nd dim for configuration/temperature
47 REAL(kind=dp), DIMENSION(:, :), ALLOCATABLE :: mv_size
48 !-- acc_prob, probability of acceptance of a certain move type for a certain temperature
49 ! 1st dimension are the different move types, 2nd dim for configuration/temperature
50 REAL(kind=dp), DIMENSION(:, :), ALLOCATABLE :: acc_prob
51 !-- count, remembers the certain amount of moves of certain a move type and temperature
52 ! 1st dimension are the different types, 2nd dim for config./Temp
53 INTEGER, DIMENSION(:, :), ALLOCATABLE :: mv_count
54 !-- count, remembers the certain amount of accepted moves of a certain move type and temperature
55 ! 1st dimension are the different types, 2nd dim for config./Temp
56 INTEGER, DIMENSION(:, :), ALLOCATABLE :: acc_count
57 !-- subbox_prob, probability of acceptance of a certain move type within subbox,
58 ! done in Nested Monte Carlo routine
59 ! the moves are rejected if atom or center of mass leaves the subbox
60 ! 1st dimension are the different move types
61 INTEGER, DIMENSION(:, :), ALLOCATABLE :: subbox_acc_count
62 INTEGER, DIMENSION(:, :), ALLOCATABLE :: subbox_count
63 TYPE(list_atoms), DIMENSION(:), POINTER :: atom_lists => null()
64
65 !-- nmc_acc_prob, probability of acceptance of a certain move type,
66 ! done in Nested Monte Carlo routine, for different potential
67 ! 1st dimension are the different move types
68! REAL(KIND=dp), DIMENSION(:), ALLOCATABLE :: nmc_nr_acc
69! INTEGER, DIMENSION(:), ALLOCATABLE :: nmc_count
70 END TYPE tmc_move_type
71
72 TYPE list_atoms
73 CHARACTER(LEN=default_string_length), &
74 DIMENSION(:), POINTER :: atoms => null()
75 END TYPE list_atoms
76CONTAINS
77
78! **************************************************************************************************
79!> \brief allocating the module variables
80!> \param move_types pointer to the structure which should be deallocated
81!> \param nr_temp ...
82!> \author Mandes 11.2012
83!> \note deallocating the module variables
84! **************************************************************************************************
85 SUBROUTINE move_types_create(move_types, nr_temp)
86 TYPE(tmc_move_type), POINTER :: move_types
87 INTEGER :: nr_temp
88
89 cpassert(.NOT. ASSOCIATED(move_types))
90
91 ALLOCATE (move_types)
92 ALLOCATE (move_types%mv_weight(nr_mv_types))
93 move_types%mv_weight(:) = 0.0_dp
94 ALLOCATE (move_types%mv_size(nr_mv_types, nr_temp))
95 move_types%mv_size(:, :) = 0.0_dp
96 ALLOCATE (move_types%acc_prob(0:nr_mv_types, nr_temp))
97 move_types%acc_prob(:, :) = 0.0_dp
98 ALLOCATE (move_types%mv_count(0:nr_mv_types, nr_temp))
99 move_types%mv_count(:, :) = 0
100 ALLOCATE (move_types%acc_count(0:nr_mv_types, nr_temp))
101 move_types%acc_count(:, :) = 0
102 ALLOCATE (move_types%subbox_acc_count(nr_mv_types, nr_temp))
103 move_types%subbox_acc_count(:, :) = 0
104 ALLOCATE (move_types%subbox_count(nr_mv_types, nr_temp))
105 move_types%subbox_count(:, :) = 0
106 NULLIFY (move_types%atom_lists)
107 END SUBROUTINE move_types_create
108
109! **************************************************************************************************
110!> \brief deallocating the module variables
111!> \param move_types pointer to the structure which should be deallocated
112!> \author Mandes 11.2012
113!> \note deallocating the module variables
114! **************************************************************************************************
115 SUBROUTINE move_types_release(move_types)
116 TYPE(tmc_move_type), POINTER :: move_types
117
118 cpassert(ASSOCIATED(move_types))
119
120 IF (ASSOCIATED(move_types%atom_lists)) DEALLOCATE (move_types%atom_lists)
121 DEALLOCATE (move_types%mv_weight)
122 DEALLOCATE (move_types%mv_size)
123 DEALLOCATE (move_types%acc_prob)
124 DEALLOCATE (move_types%mv_count)
125 DEALLOCATE (move_types%acc_count)
126 DEALLOCATE (move_types%subbox_acc_count)
127 DEALLOCATE (move_types%subbox_count)
128 DEALLOCATE (move_types)
129 END SUBROUTINE move_types_release
130
131END MODULE tmc_move_types
Defines the basic variable types.
Definition kinds.F:23
integer, parameter, public dp
Definition kinds.F:34
integer, parameter, public default_string_length
Definition kinds.F:57
tree nodes creation, searching, deallocation, references etc.
integer, parameter, public mv_type_mol_rot
integer, parameter, public mv_type_volume_move
integer, parameter, public mv_type_proton_reorder
integer, parameter, public mv_type_swap_conf
integer, parameter, public mv_type_md
integer, parameter, public mv_type_mol_trans
subroutine, public move_types_create(move_types, nr_temp)
allocating the module variables
integer, parameter, public mv_type_atom_swap
integer, parameter, public mv_type_gausian_adapt
integer, parameter, public mv_type_atom_trans
integer, parameter, public nr_mv_types
integer, parameter, public mv_type_nmc_moves
subroutine, public move_types_release(move_types)
deallocating the module variables
integer, parameter, public mv_type_none