(git:3add494)
cp_dlaf_utils_api.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  USE iso_c_binding, ONLY: c_char,&
10  c_int,&
11  c_loc,&
12  c_null_char,&
13  c_ptr
14 #include "../base/base_uses.f90"
15 
16  IMPLICIT NONE
17 
18  PRIVATE
19 
20  CHARACTER(len=*), PARAMETER, PRIVATE :: moduleN = 'cp_dlaf_utils_api'
21 
24 
25 CONTAINS
26 
27 ! **************************************************************************************************
28 !> \brief Initialize DLA-Future and pika runtime
29 !> \author Rocco Meli
30 !> \author Mikael Simberg
31 !> \author Mathieu Taillefumier
32 ! **************************************************************************************************
33  SUBROUTINE cp_dlaf_initialize()
34  CHARACTER(len=*), PARAMETER :: routinen = 'cp_dlaf_initialize'
35  INTEGER, PARAMETER :: dlaf_argc = 1, pika_argc = 1
36 
37  CHARACTER(len=5, kind=C_CHAR), ALLOCATABLE, TARGET :: dlaf_argv(:), pika_argv(:)
38  INTEGER :: handle
39  TYPE(c_ptr), ALLOCATABLE, DIMENSION(:) :: dlaf_argv_ptr, pika_argv_ptr
40  INTERFACE
41  SUBROUTINE dlaf_init(pika_argc, pika_argv, dlaf_argc, dlaf_argv) bind(C, name='dlaf_initialize')
42  IMPORT :: c_ptr, c_int
43  TYPE(c_ptr), DIMENSION(*) :: pika_argv
44  TYPE(c_ptr), DIMENSION(*) :: dlaf_argv
45  INTEGER(kind=c_int), value :: pika_argc
46  INTEGER(kind=c_int), value :: dlaf_argc
47  END SUBROUTINE dlaf_init
48  END INTERFACE
49 
50  CALL timeset(routinen, handle)
51 
52 #if defined(__DLAF)
53  ALLOCATE (pika_argv(pika_argc))
54  pika_argv(1) = "dlaf"//c_null_char
55  ALLOCATE (dlaf_argv(dlaf_argc))
56  dlaf_argv(1) = "dlaf"//c_null_char
57 
58  ALLOCATE (pika_argv_ptr(pika_argc))
59  pika_argv_ptr(1) = c_loc(pika_argv(1))
60  ALLOCATE (dlaf_argv_ptr(dlaf_argc))
61  dlaf_argv_ptr(1) = c_loc(dlaf_argv(1))
62 
63  CALL dlaf_init(pika_argc, pika_argv_ptr, dlaf_argc, dlaf_argv_ptr)
64 #else
65  mark_used(pika_argv)
66  mark_used(pika_argv_ptr)
67  mark_used(pika_argc)
68  mark_used(dlaf_argv)
69  mark_used(dlaf_argv_ptr)
70  mark_used(dlaf_argc)
71 #endif
72 
73  CALL timestop(handle)
74  END SUBROUTINE cp_dlaf_initialize
75 
76 ! **************************************************************************************************
77 !> \brief Finalize DLA-Future and pika runtime
78 !> \author Rocco Meli
79 !> \author Mikael Simberg
80 !> \author Mathieu Taillefumier
81 ! **************************************************************************************************
82  SUBROUTINE cp_dlaf_finalize()
83  CHARACTER(len=*), PARAMETER :: routinen = 'cp_dlaf_finalize'
84 
85  INTEGER :: handle
86  INTERFACE
87  SUBROUTINE dlaf_finalize_aux() &
88  bind(c, name='dlaf_finalize')
89  END SUBROUTINE dlaf_finalize_aux
90  END INTERFACE
91 
92  CALL timeset(routinen, handle)
93 
94 #if defined(__DLAF)
95  CALL dlaf_finalize_aux()
96 #endif
97 
98  CALL timestop(handle)
99  END SUBROUTINE cp_dlaf_finalize
100 
101 ! **************************************************************************************************
102 !> \brief Create DLA-Future grid from BLACS context
103 !> \param blacs_context ...
104 !> \author Rocco Meli
105 !> \author Mikael Simberg
106 !> \author Mathieu Taillefumier
107 ! **************************************************************************************************
108  SUBROUTINE cp_dlaf_create_grid(blacs_context)
109  INTEGER, INTENT(IN) :: blacs_context
110 
111  CHARACTER(len=*), PARAMETER :: routinen = 'cp_dlaf_create_grid'
112 
113  INTEGER :: handle
114  INTERFACE
115  SUBROUTINE dlaf_create_grid(blacs_contxt) &
116  bind(c, name='dlaf_create_grid_from_blacs')
117  IMPORT :: c_int
118  INTEGER(KIND=C_INT), VALUE :: blacs_contxt
119  END SUBROUTINE
120  END INTERFACE
121 
122  CALL timeset(routinen, handle)
123 
124 #if defined(__DLAF)
125  CALL dlaf_create_grid(blacs_context)
126 #else
127  mark_used(blacs_context)
128  cpabort("CP2K compiled without the DLA-Future library.")
129 #endif
130 
131  CALL timestop(handle)
132  END SUBROUTINE cp_dlaf_create_grid
133 
134 ! **************************************************************************************************
135 !> \brief Free DLA-Future grid corresponding to BLACS context
136 !> \param blacs_context ...
137 !> \author Rocco Meli
138 !> \author Mikael Simberg
139 !> \author Mathieu Taillefumier
140 ! **************************************************************************************************
141  SUBROUTINE cp_dlaf_free_grid(blacs_context)
142  INTEGER, INTENT(IN) :: blacs_context
143 
144  CHARACTER(len=*), PARAMETER :: routinen = 'cp_dlaf_free_grid'
145 
146  INTEGER :: handle
147  INTERFACE
148  SUBROUTINE dlaf_free_grid(blacs_contxt) &
149  bind(c, name='dlaf_free_grid')
150  IMPORT :: c_int
151  INTEGER(KIND=C_INT), VALUE :: blacs_contxt
152  END SUBROUTINE
153  END INTERFACE
154 
155  CALL timeset(routinen, handle)
156 
157 #if defined(__DLAF)
158  CALL dlaf_free_grid(blacs_context)
159 #else
160  mark_used(blacs_context)
161  cpabort("CP2K compiled without the DLA-Future library.")
162 #endif
163 
164  CALL timestop(handle)
165  END SUBROUTINE cp_dlaf_free_grid
166 
167 END MODULE cp_dlaf_utils_api
subroutine, public cp_dlaf_create_grid(blacs_context)
Create DLA-Future grid from BLACS context.
subroutine, public cp_dlaf_finalize()
Finalize DLA-Future and pika runtime.
subroutine, public cp_dlaf_free_grid(blacs_context)
Free DLA-Future grid corresponding to BLACS context.
subroutine, public cp_dlaf_initialize()
Initialize DLA-Future and pika runtime.