(git:374b731)
Loading...
Searching...
No Matches
pint_transformations.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
10 USE kinds, ONLY: dp
14 USE pint_staging, ONLY: staging_f2uf,&
17 USE pint_types, ONLY: pint_env_type
18#include "../base/base_uses.f90"
19
20 IMPLICIT NONE
21
22 PRIVATE
23 LOGICAL, PRIVATE, PARAMETER :: debug_this_module = .true.
24 CHARACTER(len=*), PARAMETER, PRIVATE :: moduleN = 'pint_transformations'
25
26 PUBLIC :: pint_x2u, &
27 pint_u2x, &
29
30CONTAINS
31
32! ***************************************************************************
33!> \brief Transforms from the x into the u variables
34!> (at the moment a staging transformation for the positions)
35!> \param pint_env the path integral environment
36!> \param ux will contain the u variable (defaults to pint_env%ux)
37!> \param x the positions to transform (defaults to pint_env%x)
38!> \par History
39!> Added normal mode transformation [hforbert]
40!> \author fawzi
41! **************************************************************************************************
42 SUBROUTINE pint_x2u(pint_env, ux, x)
43 TYPE(pint_env_type), INTENT(IN) :: pint_env
44 REAL(kind=dp), DIMENSION(:, :), INTENT(out), &
45 OPTIONAL, TARGET :: ux
46 REAL(kind=dp), DIMENSION(:, :), INTENT(in), &
47 OPTIONAL, TARGET :: x
48
49 REAL(kind=dp), DIMENSION(:, :), POINTER :: my_ux, my_x
50
51 my_x => pint_env%x
52 my_ux => pint_env%ux
53 IF (PRESENT(x)) my_x => x
54 IF (PRESENT(ux)) my_ux => ux
55 cpassert(ASSOCIATED(my_ux))
56 cpassert(ASSOCIATED(my_x))
57
58 IF (pint_env%transform == transformation_stage) THEN
59 CALL staging_x2u(pint_env%staging_env, ux=my_ux, x=my_x)
60 ELSE
61 CALL normalmode_x2u(pint_env%normalmode_env, ux=my_ux, x=my_x)
62 END IF
63 END SUBROUTINE pint_x2u
64
65! ***************************************************************************
66!> \brief transform from the u variable to the x (inverse of x2u)
67!> \param pint_env path integral environment
68!> \param ux the u variable (positions to be backtransformed)
69!> \param x will contain the positions
70!> \par History
71!> Added normal mode transformation by hforbert
72!> \author fawzi
73! **************************************************************************************************
74 SUBROUTINE pint_u2x(pint_env, ux, x)
75 TYPE(pint_env_type), INTENT(IN) :: pint_env
76 REAL(kind=dp), DIMENSION(:, :), INTENT(in), &
77 OPTIONAL, TARGET :: ux
78 REAL(kind=dp), DIMENSION(:, :), INTENT(out), &
79 OPTIONAL, TARGET :: x
80
81 REAL(kind=dp), DIMENSION(:, :), POINTER :: my_ux, my_x
82
83 my_x => pint_env%x
84 my_ux => pint_env%ux
85 IF (PRESENT(x)) my_x => x
86 IF (PRESENT(ux)) my_ux => ux
87 cpassert(ASSOCIATED(my_ux))
88 cpassert(ASSOCIATED(my_x))
89
90 IF (pint_env%transform == transformation_stage) THEN
91 CALL staging_u2x(pint_env%staging_env, ux=my_ux, x=my_x)
92 ELSE
93 CALL normalmode_u2x(pint_env%normalmode_env, ux=my_ux, x=my_x)
94 END IF
95 END SUBROUTINE pint_u2x
96
97! ***************************************************************************
98!> \brief transformation x to u for the forces
99!> \param pint_env the path integral environment
100!> \param uf will contain the accelerations for the transformed variables
101!> afterwards
102!> \param f the forces to transform
103!> \par History
104!> Added normal mode transformation [hforbert]
105!> Divide forces by the number of beads, since the replication
106!> environment (should) give raw forces [hforbert]
107!> \author fawzi
108! **************************************************************************************************
109 SUBROUTINE pint_f2uf(pint_env, uf, f)
110 TYPE(pint_env_type), INTENT(IN) :: pint_env
111 REAL(kind=dp), DIMENSION(:, :), INTENT(out), &
112 OPTIONAL, TARGET :: uf
113 REAL(kind=dp), DIMENSION(:, :), INTENT(in), &
114 OPTIONAL, TARGET :: f
115
116 REAL(kind=dp), DIMENSION(:, :), POINTER :: my_f, my_uf
117
118 my_f => pint_env%f
119 my_uf => pint_env%uf
120 IF (PRESENT(f)) my_f => f
121 IF (PRESENT(uf)) my_uf => uf
122 cpassert(ASSOCIATED(my_uf))
123 cpassert(ASSOCIATED(my_f))
124
125 IF (pint_env%transform == transformation_stage) THEN
126 CALL staging_f2uf(pint_env%staging_env, uf=my_uf, f=my_f)
127 ELSE
128 CALL normalmode_f2uf(pint_env%normalmode_env, uf=my_uf, f=my_f)
129 END IF
130
131 my_uf = my_uf/pint_env%mass_fict*pint_env%propagator%physpotscale
132 END SUBROUTINE pint_f2uf
133
134END MODULE pint_transformations
collects all constants needed in input so that they can be used without circular dependencies
integer, parameter, public transformation_stage
Defines the basic variable types.
Definition kinds.F:23
integer, parameter, public dp
Definition kinds.F:34
Data type and methods dealing with PI calcs in normal mode coords.
subroutine, public normalmode_x2u(normalmode_env, ux, x)
Transforms from the x into the u variables using a normal mode transformation for the positions.
subroutine, public normalmode_u2x(normalmode_env, ux, x)
transform from the u variable to the x (back normal mode transformation for the positions)
subroutine, public normalmode_f2uf(normalmode_env, uf, f)
normalmode transformation for the forces
Data type and methods dealing with PI calcs in staging coordinates.
pure subroutine, public staging_x2u(staging_env, ux, x)
Transforms from the x into the u variables using a staging transformation for the positions.
pure subroutine, public staging_f2uf(staging_env, uf, f)
staging transformation for the forces
pure subroutine, public staging_u2x(staging_env, ux, x)
transform from the u variable to the x (back staging transformation for the positions)
subroutine, public pint_x2u(pint_env, ux, x)
Transforms from the x into the u variables (at the moment a staging transformation for the positions)
subroutine, public pint_u2x(pint_env, ux, x)
transform from the u variable to the x (inverse of x2u)
subroutine, public pint_f2uf(pint_env, uf, f)
transformation x to u for the forces
environment for a path integral run
Definition pint_types.F:112