(git:374b731)
Loading...
Searching...
No Matches
qs_gcp_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 gCP types for DFT calculations
10!> \author JGH (20.10.2018)
11! **************************************************************************************************
13
14 USE kinds, ONLY: default_string_length,&
15 dp
18#include "./base/base_uses.f90"
19
20 IMPLICIT NONE
21
22 PRIVATE
23
24 CHARACTER(len=*), PARAMETER, PRIVATE :: moduleN = 'qs_gcp_types'
25
26! **************************************************************************************************
27 TYPE qs_gcp_kind_type
28 INTEGER :: za
29 REAL(KIND=dp) :: asto
30 REAL(KIND=dp) :: rcsto
31 INTEGER :: nq
32 REAL(KIND=dp) :: nbvirt
33 REAL(KIND=dp) :: eamiss
34 REAL(KIND=dp), DIMENSION(6) :: al
35 REAL(KIND=dp), DIMENSION(6) :: cl
36 END TYPE qs_gcp_kind_type
37! **************************************************************************************************
39 LOGICAL :: do_gcp = .false.
40 LOGICAL :: verbose !extended output
41 CHARACTER(LEN=default_string_length) :: parameter_file_name
42 ! parameter input
43 CHARACTER(LEN=default_string_length), &
44 DIMENSION(:), POINTER :: kind_type => null()
45 REAL(kind=dp), DIMENSION(:), POINTER :: ea => null()
46 !global parameters
47 REAL(kind=dp) :: alpha, beta, sigma, eta
48 !neighborlist
50 DIMENSION(:), POINTER :: sab_gcp => null() ! neighborlists for pair interactions
51 !kind information
52 TYPE(qs_gcp_kind_type), DIMENSION(:), &
53 POINTER :: gcp_kind => null() ! atomic kind parameters
54 END TYPE qs_gcp_type
55! **************************************************************************************************
56
57 PUBLIC :: qs_gcp_type
58 PUBLIC :: qs_gcp_release
59
60! **************************************************************************************************
61CONTAINS
62! **************************************************************************************************
63!> \brief ...
64!> \param gcp_env ...
65! **************************************************************************************************
66 SUBROUTINE qs_gcp_release(gcp_env)
67
68 TYPE(qs_gcp_type), POINTER :: gcp_env
69
70 IF (ASSOCIATED(gcp_env)) THEN
71
72 CALL release_neighbor_list_sets(gcp_env%sab_gcp)
73 IF (ASSOCIATED(gcp_env%kind_type)) THEN
74 DEALLOCATE (gcp_env%kind_type)
75 END IF
76 IF (ASSOCIATED(gcp_env%ea)) THEN
77 DEALLOCATE (gcp_env%ea)
78 END IF
79
80 IF (ASSOCIATED(gcp_env%gcp_kind)) THEN
81 DEALLOCATE (gcp_env%gcp_kind)
82 END IF
83
84 DEALLOCATE (gcp_env)
85
86 END IF
87
88 END SUBROUTINE qs_gcp_release
89
90! **************************************************************************************************
91
92END MODULE qs_gcp_types
93
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
Definition of gCP types for DFT calculations.
subroutine, public qs_gcp_release(gcp_env)
...
Define the neighbor list data types and the corresponding functionality.
subroutine, public release_neighbor_list_sets(nlists)
releases an array of neighbor_list_sets