(git:34ef472)
semi_empirical_expns3_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 Definition of the type to handle the 1/R^3 residual integral part
10 !> \author Teodoro Laino [tlaino] - 12.2008
11 ! **************************************************************************************************
13 
14  USE kinds, ONLY: dp
15 #include "./base/base_uses.f90"
16 
17  IMPLICIT NONE
18  PRIVATE
19 
20 ! **************************************************************************************************
21 !> \brief 1/R^3 expansion type
22 !> \author Teodoro Laino [tlaino] - 12.2008
23 ! **************************************************************************************************
24  TYPE semi_empirical_expns3_type
25  REAL(KIND=dp) :: core_core
26  REAL(KIND=dp), DIMENSION(9) :: e1b, e2a
27  REAL(KIND=dp), DIMENSION(81) :: w
28  END TYPE semi_empirical_expns3_type
29 
30 ! **************************************************************************************************
31 !> \brief 1/R^3 expansion type: array of pointers
32 !> \author Teodoro Laino [tlaino] - 12.2008
33 ! **************************************************************************************************
34  TYPE semi_empirical_expns3_p_type
35  TYPE(semi_empirical_expns3_type), POINTER :: expns3
36  END TYPE semi_empirical_expns3_p_type
37 
38  ! *** Global parameters ***
39  CHARACTER(len=*), PARAMETER, PRIVATE :: moduleN = 'semi_empirical_expns3_types'
40 
41  PUBLIC :: semi_empirical_expns3_p_type, &
44 
45 CONTAINS
46 
47 ! **************************************************************************************************
48 !> \brief Allocate semi-empirical 1/R^3 expansion type
49 !> \param expns3 ...
50 !> \author Teodoro Laino [tlaino] - 12.2008
51 ! **************************************************************************************************
52  SUBROUTINE semi_empirical_expns3_create(expns3)
53  TYPE(semi_empirical_expns3_type), POINTER :: expns3
54 
55  cpassert(.NOT. ASSOCIATED(expns3))
56  ALLOCATE (expns3)
57  expns3%core_core = 0.0_dp
58  expns3%e1b = 0.0_dp
59  expns3%e2a = 0.0_dp
60  expns3%w = 0.0_dp
61  END SUBROUTINE semi_empirical_expns3_create
62 
63 ! **************************************************************************************************
64 !> \brief Deallocate the semi-empirical type
65 !> \param expns3 ...
66 !> \author Teodoro Laino [tlaino] - 12.2008
67 ! **************************************************************************************************
68  SUBROUTINE semi_empirical_expns3_release(expns3)
69  TYPE(semi_empirical_expns3_type), POINTER :: expns3
70 
71  IF (ASSOCIATED(expns3)) THEN
72  DEALLOCATE (expns3)
73  END IF
74  END SUBROUTINE semi_empirical_expns3_release
75 
Defines the basic variable types.
Definition: kinds.F:23
integer, parameter, public dp
Definition: kinds.F:34
Definition of the type to handle the 1/R^3 residual integral part.
subroutine, public semi_empirical_expns3_release(expns3)
Deallocate the semi-empirical type.
subroutine, public semi_empirical_expns3_create(expns3)
Allocate semi-empirical 1/R^3 expansion type.