(git:374b731)
Loading...
Searching...
No Matches
et_coupling_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 and initialisation of the et_coupling data type.
10!> \author Florian Schiffmann (01.2007,fschiff)
11! **************************************************************************************************
13
14 USE cp_fm_types, ONLY: cp_fm_release,&
16 USE dbcsr_api, ONLY: dbcsr_p_type
17 USE kinds, ONLY: dp
18#include "./base/base_uses.f90"
19
20 IMPLICIT NONE
21
22 PRIVATE
23
24 CHARACTER(len=*), PARAMETER, PRIVATE :: moduleN = 'et_coupling_types'
25
26! *** Public data types ***
27
28 PUBLIC :: et_coupling_type
29
30! *** Public subroutines ***
31
32 PUBLIC :: et_coupling_create, &
35
36! **************************************************************************************************
37!> \par History
38!> 01.2007 created [Florian Schiffmann]
39!> \author fschiff
40! **************************************************************************************************
42 TYPE(cp_fm_type), DIMENSION(:), POINTER :: et_mo_coeff => null()
43 TYPE(dbcsr_p_type), DIMENSION(:), POINTER :: rest_mat => null()
44 LOGICAL :: first_run = .false.
45 LOGICAL :: keep_matrix = .false.
46 REAL(kind=dp) :: energy = 0.0_dp, e1 = 0.0_dp, order_p = 0.0_dp
47 END TYPE
48
49CONTAINS
50
51! **************************************************************************************************
52!> \brief ...
53!> \param et_coupling ...
54! **************************************************************************************************
55 SUBROUTINE et_coupling_create(et_coupling)
56 TYPE(et_coupling_type), POINTER :: et_coupling
57
58 ALLOCATE (et_coupling)
59
60 NULLIFY (et_coupling%et_mo_coeff)
61 NULLIFY (et_coupling%rest_mat)
62 et_coupling%first_run = .true.
63 et_coupling%keep_matrix = .false.
64 ALLOCATE (et_coupling%rest_mat(2))
65
66 END SUBROUTINE et_coupling_create
67
68! **************************************************************************************************
69!> \brief ...
70!> \param et_coupling ...
71!> \param et_mo_coeff ...
72!> \param rest_mat ...
73! **************************************************************************************************
74 SUBROUTINE get_et_coupling_type(et_coupling, et_mo_coeff, rest_mat)
75 TYPE(et_coupling_type), POINTER :: et_coupling
76 TYPE(cp_fm_type), DIMENSION(:), OPTIONAL, POINTER :: et_mo_coeff
77 TYPE(dbcsr_p_type), DIMENSION(:), OPTIONAL, &
78 POINTER :: rest_mat
79
80 IF (PRESENT(et_mo_coeff)) et_mo_coeff => et_coupling%et_mo_coeff
81 IF (PRESENT(rest_mat)) rest_mat => et_coupling%rest_mat
82
83 END SUBROUTINE get_et_coupling_type
84
85! **************************************************************************************************
86!> \brief ...
87!> \param et_coupling ...
88!> \param et_mo_coeff ...
89!> \param rest_mat ...
90! **************************************************************************************************
91 SUBROUTINE set_et_coupling_type(et_coupling, et_mo_coeff, rest_mat)
92 TYPE(et_coupling_type), POINTER :: et_coupling
93 TYPE(cp_fm_type), DIMENSION(:), OPTIONAL, POINTER :: et_mo_coeff
94 TYPE(dbcsr_p_type), DIMENSION(:), OPTIONAL, &
95 POINTER :: rest_mat
96
97 IF (PRESENT(et_mo_coeff)) et_coupling%et_mo_coeff = et_mo_coeff
98 IF (PRESENT(rest_mat)) et_coupling%rest_mat => rest_mat
99
100 END SUBROUTINE set_et_coupling_type
101
102! **************************************************************************************************
103!> \brief ...
104!> \param et_coupling ...
105! **************************************************************************************************
106 SUBROUTINE et_coupling_release(et_coupling)
107 TYPE(et_coupling_type), POINTER :: et_coupling
108
109 CALL cp_fm_release(et_coupling%et_mo_coeff)
110 IF (ASSOCIATED(et_coupling%rest_mat)) THEN
111! CALL deallocate_matrix_set(et_coupling%rest_mat)
112 DEALLOCATE (et_coupling%rest_mat)
113 END IF
114
115 DEALLOCATE (et_coupling)
116 END SUBROUTINE et_coupling_release
117
118END MODULE et_coupling_types
119
represent a full matrix distributed on many processors
Definition cp_fm_types.F:15
Definition and initialisation of the et_coupling data type.
subroutine, public et_coupling_release(et_coupling)
...
subroutine, public set_et_coupling_type(et_coupling, et_mo_coeff, rest_mat)
...
subroutine, public et_coupling_create(et_coupling)
...
calculates the electron transfer coupling elements Wu, Van Voorhis, JCP 125, 164105 (2006)
Definition et_coupling.F:13
Defines the basic variable types.
Definition kinds.F:23
integer, parameter, public dp
Definition kinds.F:34
represent a full matrix