(git:374b731)
Loading...
Searching...
No Matches
qs_oce_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! **************************************************************************************************
9
11 USE kinds, ONLY: dp
14#include "./base/base_uses.f90"
15
16 IMPLICIT NONE
17
18 PRIVATE
19
20! *** Global parameters (only in this module)
21
22 CHARACTER(len=*), PARAMETER, PRIVATE :: moduleN = 'qs_oce_types'
23
24! *** Define a oce matrix type ***
25
26! **************************************************************************************************
27 TYPE qlist_type
28 TYPE(block_p_type), DIMENSION(:), POINTER :: sac => null()
29 REAL(KIND=dp), DIMENSION(:), POINTER :: r2 => null()
30 REAL(KIND=dp), DIMENSION(:, :), POINTER :: r => null()
31 INTEGER :: n = -1
32 INTEGER, DIMENSION(:), POINTER :: index_list => null()
33 INTEGER, DIMENSION(:), POINTER :: list => null()
34 END TYPE qlist_type
35
36! **************************************************************************************************
38 TYPE(sap_int_type), DIMENSION(:), POINTER :: intac => null()
39 END TYPE
40
41! *** Public data types ***
42
43 PUBLIC :: oce_matrix_type
44
45! *** Public subroutines ***
46
47 PUBLIC :: allocate_oce_set, &
50
51CONTAINS
52
53! **************************************************************************************************
54!> \brief Allocate and initialize the matrix set of oce coefficients.
55!> \param oce_set ...
56!> \param nkind ...
57!> \version 1.0
58! **************************************************************************************************
59 SUBROUTINE allocate_oce_set(oce_set, nkind)
60 TYPE(oce_matrix_type), POINTER :: oce_set
61 INTEGER, INTENT(IN) :: nkind
62
63 INTEGER :: i
64
65 ALLOCATE (oce_set%intac(nkind*nkind))
66 DO i = 1, nkind*nkind
67 NULLIFY (oce_set%intac(i)%alist)
68 NULLIFY (oce_set%intac(i)%asort)
69 NULLIFY (oce_set%intac(i)%aindex)
70 END DO
71
72 END SUBROUTINE allocate_oce_set
73
74! **************************************************************************************************
75!> \brief ...
76!> \param oce_set ...
77! **************************************************************************************************
78 SUBROUTINE create_oce_set(oce_set)
79
80 TYPE(oce_matrix_type), POINTER :: oce_set
81
82 IF (ASSOCIATED(oce_set)) CALL deallocate_oce_set(oce_set)
83
84 ALLOCATE (oce_set)
85
86 NULLIFY (oce_set%intac)
87
88 END SUBROUTINE create_oce_set
89
90! **************************************************************************************************
91!> \brief Deallocate the matrix set of oce coefficients
92!> \param oce_set ...
93!> \date
94!> \author
95!> \version 1.0
96! **************************************************************************************************
97 SUBROUTINE deallocate_oce_set(oce_set)
98 TYPE(oce_matrix_type), POINTER :: oce_set
99
100 IF (.NOT. ASSOCIATED(oce_set)) RETURN
101
102 IF (ASSOCIATED(oce_set%intac)) CALL release_sap_int(oce_set%intac)
103
104 DEALLOCATE (oce_set)
105
106 END SUBROUTINE deallocate_oce_set
107
108! **************************************************************************************************
109
110END MODULE qs_oce_types
collect pointers to a block of reals
Defines the basic variable types.
Definition kinds.F:23
integer, parameter, public dp
Definition kinds.F:34
subroutine, public allocate_oce_set(oce_set, nkind)
Allocate and initialize the matrix set of oce coefficients.
subroutine, public create_oce_set(oce_set)
...
subroutine, public deallocate_oce_set(oce_set)
Deallocate the matrix set of oce coefficients.
General overlap type integrals containers.
subroutine, public release_sap_int(sap_int)
...