(git:db3ef62)
deepmd_wrapper.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 Interface to the DeePMD-kit or a c++ wrapper.
10 !> \par History
11 !> 07.2019 created [Yongbin Zhuang]
12 !> 06.2021 refactored [Yunpei Liu]
13 !> 10.2023 adapt to DeePMD-kit C Interface [Yunpei Liu]
14 !> \author Yongbin Zhuang
15 ! **************************************************************************************************
16 
18  USE iso_c_binding, ONLY: c_char,&
19  c_double,&
20  c_int,&
21  c_null_char,&
22  c_null_ptr,&
23  c_ptr
24  USE kinds, ONLY: dp
25 #include "./base/base_uses.f90"
26 
27  IMPLICIT NONE
28  PRIVATE
29  PUBLIC :: deepmd_model_type, deepmd_model_load, deepmd_model_compute, deepmd_model_release
30 
31  TYPE deepmd_model_type
32  PRIVATE
33  TYPE(C_PTR) :: c_ptr = c_null_ptr
34  END TYPE deepmd_model_type
35 
36 CONTAINS
37 
38 ! **************************************************************************************************
39 !> \brief Load DP from a model file.
40 !> \param filename Path to the model file.
41 !> \return Pointer to the DP model.
42 ! **************************************************************************************************
43  FUNCTION deepmd_model_load(filename) RESULT(model)
44  CHARACTER(len=*), INTENT(INOUT) :: filename
45  TYPE(deepmd_model_type) :: model
46 
47  CHARACTER(LEN=*), PARAMETER :: routinen = 'deepmd_model_load'
48 
49  INTEGER :: handle
50  INTERFACE
51  FUNCTION newdeeppot(filename) BIND(C, name="DP_NewDeepPot")
52  IMPORT :: c_ptr, c_char
53  CHARACTER(kind=C_CHAR), DIMENSION(*) :: filename
54  TYPE(c_ptr) :: newdeeppot
55  END FUNCTION
56  END INTERFACE
57 
58  CALL timeset(routinen, handle)
59 
60 #if defined(__DEEPMD)
61  model%c_ptr = newdeeppot(filename=trim(filename)//c_null_char)
62 #else
63  cpabort("CP2K was compiled without libdeepmd_c library.")
64  mark_used(filename)
65  mark_used(model)
66 #endif
67 
68  CALL timestop(handle)
69  END FUNCTION deepmd_model_load
70 
71 ! **************************************************************************************************
72 !> \brief Compute energy, force and virial from DP.
73 !> \param model Pointer to the DP model.
74 !> \param natom Number of atoms.
75 !> \param coord Coordinates of the atoms.
76 !> \param atype Atom types.
77 !> \param cell Cell vectors.
78 !> \param energy Potential energy.
79 !> \param force Forces.
80 !> \param virial Virial tensor.
81 !> \param atomic_energy Atomic energies.
82 !> \param atomic_virial Atomic virial tensors.
83 ! **************************************************************************************************
84  SUBROUTINE deepmd_model_compute(model, natom, coord, atype, cell, energy, force, virial, &
85  atomic_energy, atomic_virial)
86  TYPE(deepmd_model_type) :: model
87  INTEGER :: natom
88  REAL(kind=dp), DIMENSION(natom, 3), INTENT(IN) :: coord
89  INTEGER, DIMENSION(natom), INTENT(IN) :: atype
90  REAL(kind=dp), DIMENSION(9), INTENT(IN) :: cell
91  REAL(kind=dp), INTENT(OUT) :: energy
92  REAL(kind=dp), DIMENSION(natom, 3), INTENT(OUT) :: force
93  REAL(kind=dp), DIMENSION(9), INTENT(OUT) :: virial
94  REAL(kind=dp), DIMENSION(natom), INTENT(OUT) :: atomic_energy
95  REAL(kind=dp), DIMENSION(natom, 9), INTENT(OUT) :: atomic_virial
96 
97  CHARACTER(LEN=*), PARAMETER :: routinen = 'deepmd_model_compute'
98 
99  INTEGER :: handle
100  INTERFACE
101  SUBROUTINE deeppotcompute(model, natom, coord, atype, cell, energy, force, virial, &
102  atomic_energy, atomic_virial) BIND(C, name="DP_DeepPotCompute")
103  IMPORT :: c_ptr, c_int, c_double
104  TYPE(c_ptr), VALUE :: model
105  INTEGER(C_INT), VALUE :: natom
106  REAL(c_double), DIMENSION(natom, 3) :: coord
107  INTEGER(C_INT), DIMENSION(natom) :: atype
108  REAL(c_double), DIMENSION(9) :: cell
109  REAL(c_double) :: energy
110  REAL(c_double), DIMENSION(natom, 3) :: force
111  REAL(c_double), DIMENSION(9) :: virial
112  REAL(c_double), DIMENSION(natom) :: atomic_energy
113  REAL(c_double), DIMENSION(natom, 9) :: atomic_virial
114  END SUBROUTINE
115  END INTERFACE
116 
117  CALL timeset(routinen, handle)
118 
119 #if defined(__DEEPMD)
120  CALL deeppotcompute(model=model%c_ptr, &
121  natom=natom, &
122  coord=coord, &
123  atype=atype, &
124  cell=cell, &
125  energy=energy, &
126  force=force, &
127  virial=virial, &
128  atomic_energy=atomic_energy, &
129  atomic_virial=atomic_virial)
130 #else
131  cpabort("CP2K was compiled without libdeepmd_c library.")
132  mark_used(model)
133  mark_used(natom)
134  mark_used(coord)
135  mark_used(atype)
136  mark_used(cell)
137  mark_used(energy)
138  mark_used(force)
139  mark_used(virial)
140  mark_used(atomic_energy)
141  mark_used(atomic_virial)
142 #endif
143 
144  CALL timestop(handle)
145  END SUBROUTINE
146 
147 ! **************************************************************************************************
148 !> \brief Releases a deepmd model and all its ressources.
149 !> \param model Pointer to the DP model.
150 ! **************************************************************************************************
151  SUBROUTINE deepmd_model_release(model)
152  TYPE(deepmd_model_type) :: model
153 
154  model%c_ptr = c_null_ptr
155  END SUBROUTINE deepmd_model_release
156 
157 END MODULE deepmd_wrapper
Interface to the DeePMD-kit or a c++ wrapper.
type(deepmd_model_type) function, public deepmd_model_load(filename)
Load DP from a model file.
subroutine, public deepmd_model_release(model)
Releases a deepmd model and all its ressources.
subroutine, public deepmd_model_compute(model, natom, coord, atype, cell, energy, force, virial, atomic_energy, atomic_virial)
Compute energy, force and virial from DP.
Defines the basic variable types.
Definition: kinds.F:23
integer, parameter, public dp
Definition: kinds.F:34