Loading [MathJax]/extensions/TeX/AMSsymbols.js
SIRIUS 7.5.0
Electronic structure library and applications
All Classes Namespaces Files Functions Variables Typedefs Enumerations Enumerator Friends Pages
sirius.f90
Go to the documentation of this file.
1! Warning! This file is automatically generated from sirius_api.cpp using the generate_api.py script!
2
3!> @file sirius.f90
4!! @brief Autogenerated Fortran module for the SIRIUS API.
5module sirius
6
7use, intrinsic :: iso_c_binding
8
9INTEGER, PARAMETER, PUBLIC :: SIRIUS_INTEGER_TYPE = 1
10INTEGER, PARAMETER, PUBLIC :: SIRIUS_LOGICAL_TYPE = 2
11INTEGER, PARAMETER, PUBLIC :: SIRIUS_STRING_TYPE = 3
12INTEGER, PARAMETER, PUBLIC :: SIRIUS_NUMBER_TYPE = 4
13INTEGER, PARAMETER, PUBLIC :: SIRIUS_OBJECT_TYPE = 5
14INTEGER, PARAMETER, PUBLIC :: SIRIUS_ARRAY_TYPE = 6
15
16INTEGER, PARAMETER, PUBLIC :: SIRIUS_INTEGER_ARRAY_TYPE = 7
17INTEGER, PARAMETER, PUBLIC :: SIRIUS_LOGICAL_ARRAY_TYPE = 8
18INTEGER, PARAMETER, PUBLIC :: SIRIUS_NUMBER_ARRAY_TYPE = 9
19INTEGER, PARAMETER, PUBLIC :: SIRIUS_STRING_ARRAY_TYPE = 10
20INTEGER, PARAMETER, PUBLIC :: SIRIUS_OBJECT_ARRAY_TYPE = 11
21INTEGER, PARAMETER, PUBLIC :: SIRIUS_ARRAY_ARRAY_TYPE = 12
22
23!> @brief Opaque wrapper for simulation context handler.
25 type(C_PTR) :: handler_ptr_
26end type
27
28!> @brief Opaque wrapper for DFT ground statee handler.
30 type(C_PTR) :: handler_ptr_
31end type
32
33!> @brief Opaque wrapper for K-point set handler.
35 type(C_PTR) :: handler_ptr_
36end type
37
38!> @brief Free any of the SIRIUS handlers (context, ground state or k-points).
40 module procedure sirius_free_handler_ctx, sirius_free_handler_ks, sirius_free_handler_dft
41end interface
42
43contains
44
45!> Internal function that adds trailing null character to the string to make it C-style.
46function string_f2c(f_string) result(res)
47 implicit none
48 character(kind=C_CHAR,len=*), intent(in) :: f_string
49 character(kind=C_CHAR,len=1) :: res(len_trim(f_string) + 1)
50 integer i
51 do i = 1, len_trim(f_string)
52 res(i) = f_string(i:i)
53 end do
54 res(len_trim(f_string) + 1) = c_null_char
55end function string_f2c
56
57!> Internal function that converts C-string (with trailing null character) to the Fortran string.
58function string_c2f(c_string) result(res)
59 implicit none
60 character(kind=C_CHAR,len=1), intent(in) :: c_string(:)
61 character(kind=C_CHAR,len=size(c_string) - 1) :: res
62 character(C_CHAR) c
63 integer i
64 do i = 1, size(c_string)
65 c = c_string(i)
66 if (c == c_null_char) then
67 res(i:) = ' '
68 exit
69 endif
70 res(i:i) = c
71 end do
72end function string_c2f
73!
74!> @brief Initialize the SIRIUS library.
75!> @param [in] call_mpi_init If .true. then MPI_Init must be called prior to initialization.
76!> @param [out] error_code Error code.
77subroutine sirius_initialize(call_mpi_init,error_code)
78implicit none
79!
80logical, target, intent(in) :: call_mpi_init
81integer, optional, target, intent(out) :: error_code
82!
83type(c_ptr) :: call_mpi_init_ptr
84logical(C_BOOL), target :: call_mpi_init_c_type
85type(c_ptr) :: error_code_ptr
86!
87interface
88subroutine sirius_initialize_aux(call_mpi_init,error_code)&
89&bind(C, name="sirius_initialize")
90use, intrinsic :: iso_c_binding
91type(c_ptr), value :: call_mpi_init
92type(c_ptr), value :: error_code
93end subroutine
94end interface
95!
96call_mpi_init_ptr = c_null_ptr
97call_mpi_init_c_type = call_mpi_init
98call_mpi_init_ptr = c_loc(call_mpi_init_c_type)
99error_code_ptr = c_null_ptr
100if (present(error_code)) then
101error_code_ptr = c_loc(error_code)
102endif
103call sirius_initialize_aux(call_mpi_init_ptr,error_code_ptr)
104end subroutine sirius_initialize
105
106!
107!> @brief Shut down the SIRIUS library
108!> @param [in] call_mpi_fin If .true. then MPI_Finalize must be called after the shutdown.
109!> @param [in] call_device_reset If .true. then cuda device is reset after shutdown.
110!> @param [in] call_fftw_fin If .true. then fft_cleanup must be called after the shutdown.
111!> @param [out] error_code Error code.
112subroutine sirius_finalize(call_mpi_fin,call_device_reset,call_fftw_fin,error_code)
113implicit none
114!
115logical, optional, target, intent(in) :: call_mpi_fin
116logical, optional, target, intent(in) :: call_device_reset
117logical, optional, target, intent(in) :: call_fftw_fin
118integer, optional, target, intent(out) :: error_code
119!
120type(c_ptr) :: call_mpi_fin_ptr
121logical(C_BOOL), target :: call_mpi_fin_c_type
122type(c_ptr) :: call_device_reset_ptr
123logical(C_BOOL), target :: call_device_reset_c_type
124type(c_ptr) :: call_fftw_fin_ptr
125logical(C_BOOL), target :: call_fftw_fin_c_type
126type(c_ptr) :: error_code_ptr
127!
128interface
129subroutine sirius_finalize_aux(call_mpi_fin,call_device_reset,call_fftw_fin,error_code)&
130&bind(C, name="sirius_finalize")
131use, intrinsic :: iso_c_binding
132type(c_ptr), value :: call_mpi_fin
133type(c_ptr), value :: call_device_reset
134type(c_ptr), value :: call_fftw_fin
135type(c_ptr), value :: error_code
136end subroutine
137end interface
138!
139call_mpi_fin_ptr = c_null_ptr
140if (present(call_mpi_fin)) then
141call_mpi_fin_c_type = call_mpi_fin
142call_mpi_fin_ptr = c_loc(call_mpi_fin_c_type)
143endif
144call_device_reset_ptr = c_null_ptr
145if (present(call_device_reset)) then
146call_device_reset_c_type = call_device_reset
147call_device_reset_ptr = c_loc(call_device_reset_c_type)
148endif
149call_fftw_fin_ptr = c_null_ptr
150if (present(call_fftw_fin)) then
151call_fftw_fin_c_type = call_fftw_fin
152call_fftw_fin_ptr = c_loc(call_fftw_fin_c_type)
153endif
154error_code_ptr = c_null_ptr
155if (present(error_code)) then
156error_code_ptr = c_loc(error_code)
157endif
158call sirius_finalize_aux(call_mpi_fin_ptr,call_device_reset_ptr,call_fftw_fin_ptr,&
159&error_code_ptr)
160if (present(call_mpi_fin)) then
161endif
162if (present(call_device_reset)) then
163endif
164if (present(call_fftw_fin)) then
165endif
166end subroutine sirius_finalize
167
168!
169!> @brief Start the timer.
170!> @param [in] name Timer label.
171!> @param [out] error_code Error code.
172subroutine sirius_start_timer(name,error_code)
173implicit none
174!
175character(*), target, intent(in) :: name
176integer, optional, target, intent(out) :: error_code
177!
178type(c_ptr) :: name_ptr
179character(C_CHAR), target, allocatable :: name_c_type(:)
180type(c_ptr) :: error_code_ptr
181!
182interface
183subroutine sirius_start_timer_aux(name,error_code)&
184&bind(C, name="sirius_start_timer")
185use, intrinsic :: iso_c_binding
186type(c_ptr), value :: name
187type(c_ptr), value :: error_code
188end subroutine
189end interface
190!
191name_ptr = c_null_ptr
192allocate(name_c_type(len(name)+1))
193name_c_type = string_f2c(name)
194name_ptr = c_loc(name_c_type)
195error_code_ptr = c_null_ptr
196if (present(error_code)) then
197error_code_ptr = c_loc(error_code)
198endif
199call sirius_start_timer_aux(name_ptr,error_code_ptr)
200deallocate(name_c_type)
201end subroutine sirius_start_timer
202
203!
204!> @brief Stop the running timer.
205!> @param [in] name Timer label.
206!> @param [out] error_code Error code.
207subroutine sirius_stop_timer(name,error_code)
208implicit none
209!
210character(*), target, intent(in) :: name
211integer, optional, target, intent(out) :: error_code
212!
213type(c_ptr) :: name_ptr
214character(C_CHAR), target, allocatable :: name_c_type(:)
215type(c_ptr) :: error_code_ptr
216!
217interface
218subroutine sirius_stop_timer_aux(name,error_code)&
219&bind(C, name="sirius_stop_timer")
220use, intrinsic :: iso_c_binding
221type(c_ptr), value :: name
222type(c_ptr), value :: error_code
223end subroutine
224end interface
225!
226name_ptr = c_null_ptr
227allocate(name_c_type(len(name)+1))
228name_c_type = string_f2c(name)
229name_ptr = c_loc(name_c_type)
230error_code_ptr = c_null_ptr
231if (present(error_code)) then
232error_code_ptr = c_loc(error_code)
233endif
234call sirius_stop_timer_aux(name_ptr,error_code_ptr)
235deallocate(name_c_type)
236end subroutine sirius_stop_timer
237
238!
239!> @brief Print all timers.
240!> @param [in] flatten If true, flat list of timers is printed.
241!> @param [out] error_code Error code.
242subroutine sirius_print_timers(flatten,error_code)
243implicit none
244!
245logical, target, intent(in) :: flatten
246integer, optional, target, intent(out) :: error_code
247!
248type(c_ptr) :: flatten_ptr
249logical(C_BOOL), target :: flatten_c_type
250type(c_ptr) :: error_code_ptr
251!
252interface
253subroutine sirius_print_timers_aux(flatten,error_code)&
254&bind(C, name="sirius_print_timers")
255use, intrinsic :: iso_c_binding
256type(c_ptr), value :: flatten
257type(c_ptr), value :: error_code
258end subroutine
259end interface
260!
261flatten_ptr = c_null_ptr
262flatten_c_type = flatten
263flatten_ptr = c_loc(flatten_c_type)
264error_code_ptr = c_null_ptr
265if (present(error_code)) then
266error_code_ptr = c_loc(error_code)
267endif
268call sirius_print_timers_aux(flatten_ptr,error_code_ptr)
269end subroutine sirius_print_timers
270
271!
272!> @brief Save all timers to JSON file.
273!> @param [in] fname Name of the output JSON file.
274!> @param [out] error_code Error code.
275subroutine sirius_serialize_timers(fname,error_code)
276implicit none
277!
278character(*), target, intent(in) :: fname
279integer, optional, target, intent(out) :: error_code
280!
281type(c_ptr) :: fname_ptr
282character(C_CHAR), target, allocatable :: fname_c_type(:)
283type(c_ptr) :: error_code_ptr
284!
285interface
286subroutine sirius_serialize_timers_aux(fname,error_code)&
287&bind(C, name="sirius_serialize_timers")
288use, intrinsic :: iso_c_binding
289type(c_ptr), value :: fname
290type(c_ptr), value :: error_code
291end subroutine
292end interface
293!
294fname_ptr = c_null_ptr
295allocate(fname_c_type(len(fname)+1))
296fname_c_type = string_f2c(fname)
297fname_ptr = c_loc(fname_c_type)
298error_code_ptr = c_null_ptr
299if (present(error_code)) then
300error_code_ptr = c_loc(error_code)
301endif
302call sirius_serialize_timers_aux(fname_ptr,error_code_ptr)
303deallocate(fname_c_type)
304end subroutine sirius_serialize_timers
305
306!
307!> @brief Check if the simulation context is initialized.
308!> @param [in] handler Simulation context handler.
309!> @param [out] status Status of the library (true if initialized)
310!> @param [out] error_code Error code.
311subroutine sirius_context_initialized(handler,status,error_code)
312implicit none
313!
314type(sirius_context_handler), target, intent(in) :: handler
315logical, target, intent(out) :: status
316integer, optional, target, intent(out) :: error_code
317!
318type(c_ptr) :: handler_ptr
319type(c_ptr) :: status_ptr
320logical(C_BOOL), target :: status_c_type
321type(c_ptr) :: error_code_ptr
322!
323interface
324subroutine sirius_context_initialized_aux(handler,status,error_code)&
325&bind(C, name="sirius_context_initialized")
326use, intrinsic :: iso_c_binding
327type(c_ptr), value :: handler
328type(c_ptr), value :: status
329type(c_ptr), value :: error_code
330end subroutine
331end interface
332!
333handler_ptr = c_null_ptr
334handler_ptr = c_loc(handler%handler_ptr_)
335status_ptr = c_null_ptr
336status_ptr = c_loc(status_c_type)
337error_code_ptr = c_null_ptr
338if (present(error_code)) then
339error_code_ptr = c_loc(error_code)
340endif
341call sirius_context_initialized_aux(handler_ptr,status_ptr,error_code_ptr)
342status = status_c_type
343end subroutine sirius_context_initialized
344
345!
346!> @brief Create context of the simulation.
347!> @details
348!> Simulation context is the complex data structure that holds all the parameters of the individual simulation.
349!> The context must be created, populated with the correct parameters and initialized before using all subsequent SIRIUS functions.
350!> @param [in] fcomm Entire communicator of the simulation.
351!> @param [out] handler New empty simulation context.
352!> @param [in] fcomm_k Communicator for k-point parallelization.
353!> @param [in] fcomm_band Communicator for band parallelization.
354!> @param [out] error_code Error code.
355subroutine sirius_create_context(fcomm,handler,fcomm_k,fcomm_band,error_code)
356implicit none
357!
358integer, value, intent(in) :: fcomm
359type(sirius_context_handler), target, intent(out) :: handler
360integer, optional, target, intent(in) :: fcomm_k
361integer, optional, target, intent(in) :: fcomm_band
362integer, optional, target, intent(out) :: error_code
363!
364type(c_ptr) :: handler_ptr
365type(c_ptr) :: fcomm_k_ptr
366type(c_ptr) :: fcomm_band_ptr
367type(c_ptr) :: error_code_ptr
368!
369interface
370subroutine sirius_create_context_aux(fcomm,handler,fcomm_k,fcomm_band,error_code)&
371&bind(C, name="sirius_create_context")
372use, intrinsic :: iso_c_binding
373integer(C_INT), value :: fcomm
374type(c_ptr), value :: handler
375type(c_ptr), value :: fcomm_k
376type(c_ptr), value :: fcomm_band
377type(c_ptr), value :: error_code
378end subroutine
379end interface
380!
381handler_ptr = c_null_ptr
382handler_ptr = c_loc(handler%handler_ptr_)
383fcomm_k_ptr = c_null_ptr
384if (present(fcomm_k)) then
385fcomm_k_ptr = c_loc(fcomm_k)
386endif
387fcomm_band_ptr = c_null_ptr
388if (present(fcomm_band)) then
389fcomm_band_ptr = c_loc(fcomm_band)
390endif
391error_code_ptr = c_null_ptr
392if (present(error_code)) then
393error_code_ptr = c_loc(error_code)
394endif
395call sirius_create_context_aux(fcomm,handler_ptr,fcomm_k_ptr,fcomm_band_ptr,error_code_ptr)
396end subroutine sirius_create_context
397
398!
399!> @brief Import parameters of simulation from a JSON string
400!> @param [in] handler Simulation context handler.
401!> @param [in] str JSON string with parameters or a JSON file.
402!> @param [out] error_code Error code
403subroutine sirius_import_parameters(handler,str,error_code)
404implicit none
405!
406type(sirius_context_handler), target, intent(in) :: handler
407character(*), target, intent(in) :: str
408integer, optional, target, intent(out) :: error_code
409!
410type(c_ptr) :: handler_ptr
411type(c_ptr) :: str_ptr
412character(C_CHAR), target, allocatable :: str_c_type(:)
413type(c_ptr) :: error_code_ptr
414!
415interface
416subroutine sirius_import_parameters_aux(handler,str,error_code)&
417&bind(C, name="sirius_import_parameters")
418use, intrinsic :: iso_c_binding
419type(c_ptr), value :: handler
420type(c_ptr), value :: str
421type(c_ptr), value :: error_code
422end subroutine
423end interface
424!
425handler_ptr = c_null_ptr
426handler_ptr = c_loc(handler%handler_ptr_)
427str_ptr = c_null_ptr
428allocate(str_c_type(len(str)+1))
429str_c_type = string_f2c(str)
430str_ptr = c_loc(str_c_type)
431error_code_ptr = c_null_ptr
432if (present(error_code)) then
433error_code_ptr = c_loc(error_code)
434endif
435call sirius_import_parameters_aux(handler_ptr,str_ptr,error_code_ptr)
436deallocate(str_c_type)
437end subroutine sirius_import_parameters
438
439!
440!> @brief Set parameters of the simulation.
441!> @param [in] handler Simulation context handler
442!> @param [in] lmax_apw Maximum orbital quantum number for APW functions.
443!> @param [in] lmax_rho Maximum orbital quantum number for density.
444!> @param [in] lmax_pot Maximum orbital quantum number for potential.
445!> @param [in] num_fv_states Number of first-variational states.
446!> @param [in] num_bands Number of bands.
447!> @param [in] num_mag_dims Number of magnetic dimensions.
448!> @param [in] pw_cutoff Cutoff for G-vectors.
449!> @param [in] gk_cutoff Cutoff for G+k-vectors.
450!> @param [in] fft_grid_size Size of the fine-grain FFT grid.
451!> @param [in] auto_rmt Set the automatic search of muffin-tin radii.
452!> @param [in] gamma_point True if this is a Gamma-point calculation.
453!> @param [in] use_symmetry True if crystal symmetry is taken into account.
454!> @param [in] so_correction True if spin-orbit correnctio is enabled.
455!> @param [in] valence_rel Valence relativity treatment.
456!> @param [in] core_rel Core relativity treatment.
457!> @param [in] iter_solver_tol_empty Tolerance for the empty states.
458!> @param [in] iter_solver_type Type of iterative solver.
459!> @param [in] verbosity Verbosity level.
460!> @param [in] hubbard_correction True if LDA+U correction is enabled.
461!> @param [in] hubbard_correction_kind Type of LDA+U implementation (simplified or full).
462!> @param [in] hubbard_full_orthogonalization Use all atomic orbitals found in all ps potentials to compute the orthogonalization operator.
463!> @param [in] hubbard_orbitals Type of localized orbitals.
464!> @param [in] sht_coverage Type of spherical coverage (0 for Lebedev-Laikov, 1 for uniform).
465!> @param [in] min_occupancy Minimum band occupancy to trat is as "occupied".
466!> @param [in] smearing Type of occupancy smearing.
467!> @param [in] smearing_width Smearing width
468!> @param [in] spglib_tol Tolerance for the spglib symmetry search.
469!> @param [in] electronic_structure_method Type of electronic structure method.
470!> @param [out] error_code Error code.
471subroutine sirius_set_parameters(handler,lmax_apw,lmax_rho,lmax_pot,num_fv_states,&
472&num_bands,num_mag_dims,pw_cutoff,gk_cutoff,fft_grid_size,auto_rmt,gamma_point,use_symmetry,&
473&so_correction,valence_rel,core_rel,iter_solver_tol_empty,iter_solver_type,verbosity,&
474&hubbard_correction,hubbard_correction_kind,hubbard_full_orthogonalization,hubbard_orbitals,&
475&sht_coverage,min_occupancy,smearing,smearing_width,spglib_tol,electronic_structure_method,&
476&error_code)
477implicit none
478!
479type(sirius_context_handler), target, intent(in) :: handler
480integer, optional, target, intent(in) :: lmax_apw
481integer, optional, target, intent(in) :: lmax_rho
482integer, optional, target, intent(in) :: lmax_pot
483integer, optional, target, intent(in) :: num_fv_states
484integer, optional, target, intent(in) :: num_bands
485integer, optional, target, intent(in) :: num_mag_dims
486real(8), optional, target, intent(in) :: pw_cutoff
487real(8), optional, target, intent(in) :: gk_cutoff
488integer, optional, target, intent(in) :: fft_grid_size(3)
489integer, optional, target, intent(in) :: auto_rmt
490logical, optional, target, intent(in) :: gamma_point
491logical, optional, target, intent(in) :: use_symmetry
492logical, optional, target, intent(in) :: so_correction
493character(*), optional, target, intent(in) :: valence_rel
494character(*), optional, target, intent(in) :: core_rel
495real(8), optional, target, intent(in) :: iter_solver_tol_empty
496character(*), optional, target, intent(in) :: iter_solver_type
497integer, optional, target, intent(in) :: verbosity
498logical, optional, target, intent(in) :: hubbard_correction
499integer, optional, target, intent(in) :: hubbard_correction_kind
500logical, optional, target, intent(in) :: hubbard_full_orthogonalization
501character(*), optional, target, intent(in) :: hubbard_orbitals
502integer, optional, target, intent(in) :: sht_coverage
503real(8), optional, target, intent(in) :: min_occupancy
504character(*), optional, target, intent(in) :: smearing
505real(8), optional, target, intent(in) :: smearing_width
506real(8), optional, target, intent(in) :: spglib_tol
507character(*), optional, target, intent(in) :: electronic_structure_method
508integer, optional, target, intent(out) :: error_code
509!
510type(c_ptr) :: handler_ptr
511type(c_ptr) :: lmax_apw_ptr
512type(c_ptr) :: lmax_rho_ptr
513type(c_ptr) :: lmax_pot_ptr
514type(c_ptr) :: num_fv_states_ptr
515type(c_ptr) :: num_bands_ptr
516type(c_ptr) :: num_mag_dims_ptr
517type(c_ptr) :: pw_cutoff_ptr
518type(c_ptr) :: gk_cutoff_ptr
519type(c_ptr) :: fft_grid_size_ptr
520type(c_ptr) :: auto_rmt_ptr
521type(c_ptr) :: gamma_point_ptr
522logical(C_BOOL), target :: gamma_point_c_type
523type(c_ptr) :: use_symmetry_ptr
524logical(C_BOOL), target :: use_symmetry_c_type
525type(c_ptr) :: so_correction_ptr
526logical(C_BOOL), target :: so_correction_c_type
527type(c_ptr) :: valence_rel_ptr
528character(C_CHAR), target, allocatable :: valence_rel_c_type(:)
529type(c_ptr) :: core_rel_ptr
530character(C_CHAR), target, allocatable :: core_rel_c_type(:)
531type(c_ptr) :: iter_solver_tol_empty_ptr
532type(c_ptr) :: iter_solver_type_ptr
533character(C_CHAR), target, allocatable :: iter_solver_type_c_type(:)
534type(c_ptr) :: verbosity_ptr
535type(c_ptr) :: hubbard_correction_ptr
536logical(C_BOOL), target :: hubbard_correction_c_type
537type(c_ptr) :: hubbard_correction_kind_ptr
538type(c_ptr) :: hubbard_full_orthogonalization_ptr
539logical(C_BOOL), target :: hubbard_full_orthogonalization_c_type
540type(c_ptr) :: hubbard_orbitals_ptr
541character(C_CHAR), target, allocatable :: hubbard_orbitals_c_type(:)
542type(c_ptr) :: sht_coverage_ptr
543type(c_ptr) :: min_occupancy_ptr
544type(c_ptr) :: smearing_ptr
545character(C_CHAR), target, allocatable :: smearing_c_type(:)
546type(c_ptr) :: smearing_width_ptr
547type(c_ptr) :: spglib_tol_ptr
548type(c_ptr) :: electronic_structure_method_ptr
549character(C_CHAR), target, allocatable :: electronic_structure_method_c_type(:)
550type(c_ptr) :: error_code_ptr
551!
552interface
553subroutine sirius_set_parameters_aux(handler,lmax_apw,lmax_rho,lmax_pot,num_fv_states,&
554&num_bands,num_mag_dims,pw_cutoff,gk_cutoff,fft_grid_size,auto_rmt,gamma_point,use_symmetry,&
555&so_correction,valence_rel,core_rel,iter_solver_tol_empty,iter_solver_type,verbosity,&
556&hubbard_correction,hubbard_correction_kind,hubbard_full_orthogonalization,hubbard_orbitals,&
557&sht_coverage,min_occupancy,smearing,smearing_width,spglib_tol,electronic_structure_method,&
558&error_code)&
559&bind(C, name="sirius_set_parameters")
560use, intrinsic :: iso_c_binding
561type(c_ptr), value :: handler
562type(c_ptr), value :: lmax_apw
563type(c_ptr), value :: lmax_rho
564type(c_ptr), value :: lmax_pot
565type(c_ptr), value :: num_fv_states
566type(c_ptr), value :: num_bands
567type(c_ptr), value :: num_mag_dims
568type(c_ptr), value :: pw_cutoff
569type(c_ptr), value :: gk_cutoff
570type(c_ptr), value :: fft_grid_size
571type(c_ptr), value :: auto_rmt
572type(c_ptr), value :: gamma_point
573type(c_ptr), value :: use_symmetry
574type(c_ptr), value :: so_correction
575type(c_ptr), value :: valence_rel
576type(c_ptr), value :: core_rel
577type(c_ptr), value :: iter_solver_tol_empty
578type(c_ptr), value :: iter_solver_type
579type(c_ptr), value :: verbosity
580type(c_ptr), value :: hubbard_correction
581type(c_ptr), value :: hubbard_correction_kind
582type(c_ptr), value :: hubbard_full_orthogonalization
583type(c_ptr), value :: hubbard_orbitals
584type(c_ptr), value :: sht_coverage
585type(c_ptr), value :: min_occupancy
586type(c_ptr), value :: smearing
587type(c_ptr), value :: smearing_width
588type(c_ptr), value :: spglib_tol
589type(c_ptr), value :: electronic_structure_method
590type(c_ptr), value :: error_code
591end subroutine
592end interface
593!
594handler_ptr = c_null_ptr
595handler_ptr = c_loc(handler%handler_ptr_)
596lmax_apw_ptr = c_null_ptr
597if (present(lmax_apw)) then
598lmax_apw_ptr = c_loc(lmax_apw)
599endif
600lmax_rho_ptr = c_null_ptr
601if (present(lmax_rho)) then
602lmax_rho_ptr = c_loc(lmax_rho)
603endif
604lmax_pot_ptr = c_null_ptr
605if (present(lmax_pot)) then
606lmax_pot_ptr = c_loc(lmax_pot)
607endif
608num_fv_states_ptr = c_null_ptr
609if (present(num_fv_states)) then
610num_fv_states_ptr = c_loc(num_fv_states)
611endif
612num_bands_ptr = c_null_ptr
613if (present(num_bands)) then
614num_bands_ptr = c_loc(num_bands)
615endif
616num_mag_dims_ptr = c_null_ptr
617if (present(num_mag_dims)) then
618num_mag_dims_ptr = c_loc(num_mag_dims)
619endif
620pw_cutoff_ptr = c_null_ptr
621if (present(pw_cutoff)) then
622pw_cutoff_ptr = c_loc(pw_cutoff)
623endif
624gk_cutoff_ptr = c_null_ptr
625if (present(gk_cutoff)) then
626gk_cutoff_ptr = c_loc(gk_cutoff)
627endif
628fft_grid_size_ptr = c_null_ptr
629if (present(fft_grid_size)) then
630fft_grid_size_ptr = c_loc(fft_grid_size)
631endif
632auto_rmt_ptr = c_null_ptr
633if (present(auto_rmt)) then
634auto_rmt_ptr = c_loc(auto_rmt)
635endif
636gamma_point_ptr = c_null_ptr
637if (present(gamma_point)) then
638gamma_point_c_type = gamma_point
639gamma_point_ptr = c_loc(gamma_point_c_type)
640endif
641use_symmetry_ptr = c_null_ptr
642if (present(use_symmetry)) then
643use_symmetry_c_type = use_symmetry
644use_symmetry_ptr = c_loc(use_symmetry_c_type)
645endif
646so_correction_ptr = c_null_ptr
647if (present(so_correction)) then
648so_correction_c_type = so_correction
649so_correction_ptr = c_loc(so_correction_c_type)
650endif
651valence_rel_ptr = c_null_ptr
652if (present(valence_rel)) then
653allocate(valence_rel_c_type(len(valence_rel)+1))
654valence_rel_c_type = string_f2c(valence_rel)
655valence_rel_ptr = c_loc(valence_rel_c_type)
656endif
657core_rel_ptr = c_null_ptr
658if (present(core_rel)) then
659allocate(core_rel_c_type(len(core_rel)+1))
660core_rel_c_type = string_f2c(core_rel)
661core_rel_ptr = c_loc(core_rel_c_type)
662endif
663iter_solver_tol_empty_ptr = c_null_ptr
664if (present(iter_solver_tol_empty)) then
665iter_solver_tol_empty_ptr = c_loc(iter_solver_tol_empty)
666endif
667iter_solver_type_ptr = c_null_ptr
668if (present(iter_solver_type)) then
669allocate(iter_solver_type_c_type(len(iter_solver_type)+1))
670iter_solver_type_c_type = string_f2c(iter_solver_type)
671iter_solver_type_ptr = c_loc(iter_solver_type_c_type)
672endif
673verbosity_ptr = c_null_ptr
674if (present(verbosity)) then
675verbosity_ptr = c_loc(verbosity)
676endif
677hubbard_correction_ptr = c_null_ptr
678if (present(hubbard_correction)) then
679hubbard_correction_c_type = hubbard_correction
680hubbard_correction_ptr = c_loc(hubbard_correction_c_type)
681endif
682hubbard_correction_kind_ptr = c_null_ptr
683if (present(hubbard_correction_kind)) then
684hubbard_correction_kind_ptr = c_loc(hubbard_correction_kind)
685endif
686hubbard_full_orthogonalization_ptr = c_null_ptr
687if (present(hubbard_full_orthogonalization)) then
688hubbard_full_orthogonalization_c_type = hubbard_full_orthogonalization
689hubbard_full_orthogonalization_ptr = c_loc(hubbard_full_orthogonalization_c_type)
690endif
691hubbard_orbitals_ptr = c_null_ptr
692if (present(hubbard_orbitals)) then
693allocate(hubbard_orbitals_c_type(len(hubbard_orbitals)+1))
694hubbard_orbitals_c_type = string_f2c(hubbard_orbitals)
695hubbard_orbitals_ptr = c_loc(hubbard_orbitals_c_type)
696endif
697sht_coverage_ptr = c_null_ptr
698if (present(sht_coverage)) then
699sht_coverage_ptr = c_loc(sht_coverage)
700endif
701min_occupancy_ptr = c_null_ptr
702if (present(min_occupancy)) then
703min_occupancy_ptr = c_loc(min_occupancy)
704endif
705smearing_ptr = c_null_ptr
706if (present(smearing)) then
707allocate(smearing_c_type(len(smearing)+1))
708smearing_c_type = string_f2c(smearing)
709smearing_ptr = c_loc(smearing_c_type)
710endif
711smearing_width_ptr = c_null_ptr
712if (present(smearing_width)) then
713smearing_width_ptr = c_loc(smearing_width)
714endif
715spglib_tol_ptr = c_null_ptr
716if (present(spglib_tol)) then
717spglib_tol_ptr = c_loc(spglib_tol)
718endif
719electronic_structure_method_ptr = c_null_ptr
720if (present(electronic_structure_method)) then
721allocate(electronic_structure_method_c_type(len(electronic_structure_method)+1))
722electronic_structure_method_c_type = string_f2c(electronic_structure_method)
723electronic_structure_method_ptr = c_loc(electronic_structure_method_c_type)
724endif
725error_code_ptr = c_null_ptr
726if (present(error_code)) then
727error_code_ptr = c_loc(error_code)
728endif
729call sirius_set_parameters_aux(handler_ptr,lmax_apw_ptr,lmax_rho_ptr,lmax_pot_ptr,&
730&num_fv_states_ptr,num_bands_ptr,num_mag_dims_ptr,pw_cutoff_ptr,gk_cutoff_ptr,fft_grid_size_ptr,&
731&auto_rmt_ptr,gamma_point_ptr,use_symmetry_ptr,so_correction_ptr,valence_rel_ptr,&
732&core_rel_ptr,iter_solver_tol_empty_ptr,iter_solver_type_ptr,verbosity_ptr,hubbard_correction_ptr,&
733&hubbard_correction_kind_ptr,hubbard_full_orthogonalization_ptr,hubbard_orbitals_ptr,&
734&sht_coverage_ptr,min_occupancy_ptr,smearing_ptr,smearing_width_ptr,spglib_tol_ptr,&
735&electronic_structure_method_ptr,error_code_ptr)
736if (present(gamma_point)) then
737endif
738if (present(use_symmetry)) then
739endif
740if (present(so_correction)) then
741endif
742if (present(valence_rel)) then
743deallocate(valence_rel_c_type)
744endif
745if (present(core_rel)) then
746deallocate(core_rel_c_type)
747endif
748if (present(iter_solver_type)) then
749deallocate(iter_solver_type_c_type)
750endif
751if (present(hubbard_correction)) then
752endif
753if (present(hubbard_full_orthogonalization)) then
754endif
755if (present(hubbard_orbitals)) then
756deallocate(hubbard_orbitals_c_type)
757endif
758if (present(smearing)) then
759deallocate(smearing_c_type)
760endif
761if (present(electronic_structure_method)) then
762deallocate(electronic_structure_method_c_type)
763endif
764end subroutine sirius_set_parameters
765
766!
767!> @brief Get parameters of the simulation.
768!> @param [in] handler Simulation context handler
769!> @param [out] lmax_apw Maximum orbital quantum number for APW functions.
770!> @param [out] lmax_rho Maximum orbital quantum number for density.
771!> @param [out] lmax_pot Maximum orbital quantum number for potential.
772!> @param [out] num_fv_states Number of first-variational states.
773!> @param [out] num_bands Number of bands.
774!> @param [out] num_spins Number of spins.
775!> @param [out] num_mag_dims Number of magnetic dimensions.
776!> @param [out] pw_cutoff Cutoff for G-vectors.
777!> @param [out] gk_cutoff Cutoff for G+k-vectors.
778!> @param [out] fft_grid_size Size of the fine-grain FFT grid.
779!> @param [out] auto_rmt Set the automatic search of muffin-tin radii.
780!> @param [out] gamma_point True if this is a Gamma-point calculation.
781!> @param [out] use_symmetry True if crystal symmetry is taken into account.
782!> @param [out] so_correction True if spin-orbit correnctio is enabled.
783!> @param [out] iter_solver_tol Tolerance of the iterative solver (deprecated).
784!> @param [out] iter_solver_tol_empty Tolerance for the empty states.
785!> @param [out] verbosity Verbosity level.
786!> @param [out] hubbard_correction True if LDA+U correction is enabled.
787!> @param [out] evp_work_count Internal counter of total eigen-value problem work.
788!> @param [out] num_loc_op_applied Internal counter of the number of wave-functions to which Hamiltonian was applied.
789!> @param [out] num_sym_op Number of symmetry operations discovered by spglib
790!> @param [out] electronic_structure_method Type of electronic structure method.
791!> @param [out] error_code Error code.
792subroutine sirius_get_parameters(handler,lmax_apw,lmax_rho,lmax_pot,num_fv_states,&
793&num_bands,num_spins,num_mag_dims,pw_cutoff,gk_cutoff,fft_grid_size,auto_rmt,gamma_point,&
794&use_symmetry,so_correction,iter_solver_tol,iter_solver_tol_empty,verbosity,hubbard_correction,&
795&evp_work_count,num_loc_op_applied,num_sym_op,electronic_structure_method,error_code)
796implicit none
797!
798type(sirius_context_handler), target, intent(in) :: handler
799integer, optional, target, intent(out) :: lmax_apw
800integer, optional, target, intent(out) :: lmax_rho
801integer, optional, target, intent(out) :: lmax_pot
802integer, optional, target, intent(out) :: num_fv_states
803integer, optional, target, intent(out) :: num_bands
804integer, optional, target, intent(out) :: num_spins
805integer, optional, target, intent(out) :: num_mag_dims
806real(8), optional, target, intent(out) :: pw_cutoff
807real(8), optional, target, intent(out) :: gk_cutoff
808integer, optional, target, intent(out) :: fft_grid_size(3)
809integer, optional, target, intent(out) :: auto_rmt
810logical, optional, target, intent(out) :: gamma_point
811logical, optional, target, intent(out) :: use_symmetry
812logical, optional, target, intent(out) :: so_correction
813real(8), optional, target, intent(out) :: iter_solver_tol
814real(8), optional, target, intent(out) :: iter_solver_tol_empty
815integer, optional, target, intent(out) :: verbosity
816logical, optional, target, intent(out) :: hubbard_correction
817real(8), optional, target, intent(out) :: evp_work_count
818integer, optional, target, intent(out) :: num_loc_op_applied
819integer, optional, target, intent(out) :: num_sym_op
820character(*), optional, target, intent(out) :: electronic_structure_method
821integer, optional, target, intent(out) :: error_code
822!
823type(c_ptr) :: handler_ptr
824type(c_ptr) :: lmax_apw_ptr
825type(c_ptr) :: lmax_rho_ptr
826type(c_ptr) :: lmax_pot_ptr
827type(c_ptr) :: num_fv_states_ptr
828type(c_ptr) :: num_bands_ptr
829type(c_ptr) :: num_spins_ptr
830type(c_ptr) :: num_mag_dims_ptr
831type(c_ptr) :: pw_cutoff_ptr
832type(c_ptr) :: gk_cutoff_ptr
833type(c_ptr) :: fft_grid_size_ptr
834type(c_ptr) :: auto_rmt_ptr
835type(c_ptr) :: gamma_point_ptr
836logical(C_BOOL), target :: gamma_point_c_type
837type(c_ptr) :: use_symmetry_ptr
838logical(C_BOOL), target :: use_symmetry_c_type
839type(c_ptr) :: so_correction_ptr
840logical(C_BOOL), target :: so_correction_c_type
841type(c_ptr) :: iter_solver_tol_ptr
842type(c_ptr) :: iter_solver_tol_empty_ptr
843type(c_ptr) :: verbosity_ptr
844type(c_ptr) :: hubbard_correction_ptr
845logical(C_BOOL), target :: hubbard_correction_c_type
846type(c_ptr) :: evp_work_count_ptr
847type(c_ptr) :: num_loc_op_applied_ptr
848type(c_ptr) :: num_sym_op_ptr
849type(c_ptr) :: electronic_structure_method_ptr
850character(C_CHAR), target, allocatable :: electronic_structure_method_c_type(:)
851type(c_ptr) :: error_code_ptr
852!
853interface
854subroutine sirius_get_parameters_aux(handler,lmax_apw,lmax_rho,lmax_pot,num_fv_states,&
855&num_bands,num_spins,num_mag_dims,pw_cutoff,gk_cutoff,fft_grid_size,auto_rmt,gamma_point,&
856&use_symmetry,so_correction,iter_solver_tol,iter_solver_tol_empty,verbosity,hubbard_correction,&
857&evp_work_count,num_loc_op_applied,num_sym_op,electronic_structure_method,error_code)&
858&bind(C, name="sirius_get_parameters")
859use, intrinsic :: iso_c_binding
860type(c_ptr), value :: handler
861type(c_ptr), value :: lmax_apw
862type(c_ptr), value :: lmax_rho
863type(c_ptr), value :: lmax_pot
864type(c_ptr), value :: num_fv_states
865type(c_ptr), value :: num_bands
866type(c_ptr), value :: num_spins
867type(c_ptr), value :: num_mag_dims
868type(c_ptr), value :: pw_cutoff
869type(c_ptr), value :: gk_cutoff
870type(c_ptr), value :: fft_grid_size
871type(c_ptr), value :: auto_rmt
872type(c_ptr), value :: gamma_point
873type(c_ptr), value :: use_symmetry
874type(c_ptr), value :: so_correction
875type(c_ptr), value :: iter_solver_tol
876type(c_ptr), value :: iter_solver_tol_empty
877type(c_ptr), value :: verbosity
878type(c_ptr), value :: hubbard_correction
879type(c_ptr), value :: evp_work_count
880type(c_ptr), value :: num_loc_op_applied
881type(c_ptr), value :: num_sym_op
882type(c_ptr), value :: electronic_structure_method
883type(c_ptr), value :: error_code
884end subroutine
885end interface
886!
887handler_ptr = c_null_ptr
888handler_ptr = c_loc(handler%handler_ptr_)
889lmax_apw_ptr = c_null_ptr
890if (present(lmax_apw)) then
891lmax_apw_ptr = c_loc(lmax_apw)
892endif
893lmax_rho_ptr = c_null_ptr
894if (present(lmax_rho)) then
895lmax_rho_ptr = c_loc(lmax_rho)
896endif
897lmax_pot_ptr = c_null_ptr
898if (present(lmax_pot)) then
899lmax_pot_ptr = c_loc(lmax_pot)
900endif
901num_fv_states_ptr = c_null_ptr
902if (present(num_fv_states)) then
903num_fv_states_ptr = c_loc(num_fv_states)
904endif
905num_bands_ptr = c_null_ptr
906if (present(num_bands)) then
907num_bands_ptr = c_loc(num_bands)
908endif
909num_spins_ptr = c_null_ptr
910if (present(num_spins)) then
911num_spins_ptr = c_loc(num_spins)
912endif
913num_mag_dims_ptr = c_null_ptr
914if (present(num_mag_dims)) then
915num_mag_dims_ptr = c_loc(num_mag_dims)
916endif
917pw_cutoff_ptr = c_null_ptr
918if (present(pw_cutoff)) then
919pw_cutoff_ptr = c_loc(pw_cutoff)
920endif
921gk_cutoff_ptr = c_null_ptr
922if (present(gk_cutoff)) then
923gk_cutoff_ptr = c_loc(gk_cutoff)
924endif
925fft_grid_size_ptr = c_null_ptr
926if (present(fft_grid_size)) then
927fft_grid_size_ptr = c_loc(fft_grid_size)
928endif
929auto_rmt_ptr = c_null_ptr
930if (present(auto_rmt)) then
931auto_rmt_ptr = c_loc(auto_rmt)
932endif
933gamma_point_ptr = c_null_ptr
934if (present(gamma_point)) then
935gamma_point_ptr = c_loc(gamma_point_c_type)
936endif
937use_symmetry_ptr = c_null_ptr
938if (present(use_symmetry)) then
939use_symmetry_ptr = c_loc(use_symmetry_c_type)
940endif
941so_correction_ptr = c_null_ptr
942if (present(so_correction)) then
943so_correction_ptr = c_loc(so_correction_c_type)
944endif
945iter_solver_tol_ptr = c_null_ptr
946if (present(iter_solver_tol)) then
947iter_solver_tol_ptr = c_loc(iter_solver_tol)
948endif
949iter_solver_tol_empty_ptr = c_null_ptr
950if (present(iter_solver_tol_empty)) then
951iter_solver_tol_empty_ptr = c_loc(iter_solver_tol_empty)
952endif
953verbosity_ptr = c_null_ptr
954if (present(verbosity)) then
955verbosity_ptr = c_loc(verbosity)
956endif
957hubbard_correction_ptr = c_null_ptr
958if (present(hubbard_correction)) then
959hubbard_correction_ptr = c_loc(hubbard_correction_c_type)
960endif
961evp_work_count_ptr = c_null_ptr
962if (present(evp_work_count)) then
963evp_work_count_ptr = c_loc(evp_work_count)
964endif
965num_loc_op_applied_ptr = c_null_ptr
966if (present(num_loc_op_applied)) then
967num_loc_op_applied_ptr = c_loc(num_loc_op_applied)
968endif
969num_sym_op_ptr = c_null_ptr
970if (present(num_sym_op)) then
971num_sym_op_ptr = c_loc(num_sym_op)
972endif
973electronic_structure_method_ptr = c_null_ptr
974if (present(electronic_structure_method)) then
975allocate(electronic_structure_method_c_type(len(electronic_structure_method)+1))
976electronic_structure_method_ptr = c_loc(electronic_structure_method_c_type)
977endif
978error_code_ptr = c_null_ptr
979if (present(error_code)) then
980error_code_ptr = c_loc(error_code)
981endif
982call sirius_get_parameters_aux(handler_ptr,lmax_apw_ptr,lmax_rho_ptr,lmax_pot_ptr,&
983&num_fv_states_ptr,num_bands_ptr,num_spins_ptr,num_mag_dims_ptr,pw_cutoff_ptr,gk_cutoff_ptr,&
984&fft_grid_size_ptr,auto_rmt_ptr,gamma_point_ptr,use_symmetry_ptr,so_correction_ptr,&
985&iter_solver_tol_ptr,iter_solver_tol_empty_ptr,verbosity_ptr,hubbard_correction_ptr,&
986&evp_work_count_ptr,num_loc_op_applied_ptr,num_sym_op_ptr,electronic_structure_method_ptr,&
987&error_code_ptr)
988if (present(gamma_point)) then
989gamma_point = gamma_point_c_type
990endif
991if (present(use_symmetry)) then
992use_symmetry = use_symmetry_c_type
993endif
994if (present(so_correction)) then
995so_correction = so_correction_c_type
996endif
997if (present(hubbard_correction)) then
998hubbard_correction = hubbard_correction_c_type
999endif
1000if (present(electronic_structure_method)) then
1001electronic_structure_method = string_c2f(electronic_structure_method_c_type)
1002deallocate(electronic_structure_method_c_type)
1003endif
1004end subroutine sirius_get_parameters
1005
1006!
1007!> @brief Add one of the XC functionals.
1008!> @param [in] handler Simulation context handler
1009!> @param [in] name LibXC label of the functional.
1010!> @param [out] error_code Error code.
1011subroutine sirius_add_xc_functional(handler,name,error_code)
1012implicit none
1013!
1014type(sirius_context_handler), target, intent(in) :: handler
1015character(*), target, intent(in) :: name
1016integer, optional, target, intent(out) :: error_code
1017!
1018type(c_ptr) :: handler_ptr
1019type(c_ptr) :: name_ptr
1020character(C_CHAR), target, allocatable :: name_c_type(:)
1021type(c_ptr) :: error_code_ptr
1022!
1023interface
1024subroutine sirius_add_xc_functional_aux(handler,name,error_code)&
1025&bind(C, name="sirius_add_xc_functional")
1026use, intrinsic :: iso_c_binding
1027type(c_ptr), value :: handler
1028type(c_ptr), value :: name
1029type(c_ptr), value :: error_code
1030end subroutine
1031end interface
1032!
1033handler_ptr = c_null_ptr
1034handler_ptr = c_loc(handler%handler_ptr_)
1035name_ptr = c_null_ptr
1036allocate(name_c_type(len(name)+1))
1037name_c_type = string_f2c(name)
1038name_ptr = c_loc(name_c_type)
1039error_code_ptr = c_null_ptr
1040if (present(error_code)) then
1041error_code_ptr = c_loc(error_code)
1042endif
1043call sirius_add_xc_functional_aux(handler_ptr,name_ptr,error_code_ptr)
1044deallocate(name_c_type)
1045end subroutine sirius_add_xc_functional
1046
1047!
1048!> @brief Set dimensions of the MPI grid.
1049!> @param [in] handler Simulation context handler
1050!> @param [in] ndims Number of dimensions.
1051!> @param [in] dims Size of each dimension.
1052!> @param [out] error_code Error code.
1053subroutine sirius_set_mpi_grid_dims(handler,ndims,dims,error_code)
1054implicit none
1055!
1056type(sirius_context_handler), target, intent(in) :: handler
1057integer, target, intent(in) :: ndims
1058integer, target, intent(in) :: dims(ndims)
1059integer, optional, target, intent(out) :: error_code
1060!
1061type(c_ptr) :: handler_ptr
1062type(c_ptr) :: ndims_ptr
1063type(c_ptr) :: dims_ptr
1064type(c_ptr) :: error_code_ptr
1065!
1066interface
1067subroutine sirius_set_mpi_grid_dims_aux(handler,ndims,dims,error_code)&
1068&bind(C, name="sirius_set_mpi_grid_dims")
1069use, intrinsic :: iso_c_binding
1070type(c_ptr), value :: handler
1071type(c_ptr), value :: ndims
1072type(c_ptr), value :: dims
1073type(c_ptr), value :: error_code
1074end subroutine
1075end interface
1076!
1077handler_ptr = c_null_ptr
1078handler_ptr = c_loc(handler%handler_ptr_)
1079ndims_ptr = c_null_ptr
1080ndims_ptr = c_loc(ndims)
1081dims_ptr = c_null_ptr
1082dims_ptr = c_loc(dims)
1083error_code_ptr = c_null_ptr
1084if (present(error_code)) then
1085error_code_ptr = c_loc(error_code)
1086endif
1087call sirius_set_mpi_grid_dims_aux(handler_ptr,ndims_ptr,dims_ptr,error_code_ptr)
1088end subroutine sirius_set_mpi_grid_dims
1089
1090!
1091!> @brief Set vectors of the unit cell.
1092!> @param [in] handler Simulation context handler
1093!> @param [in] a1 1st vector
1094!> @param [in] a2 2nd vector
1095!> @param [in] a3 3rd vector
1096!> @param [out] error_code Error code.
1097subroutine sirius_set_lattice_vectors(handler,a1,a2,a3,error_code)
1098implicit none
1099!
1100type(sirius_context_handler), target, intent(in) :: handler
1101real(8), target, intent(in) :: a1(3)
1102real(8), target, intent(in) :: a2(3)
1103real(8), target, intent(in) :: a3(3)
1104integer, optional, target, intent(out) :: error_code
1105!
1106type(c_ptr) :: handler_ptr
1107type(c_ptr) :: a1_ptr
1108type(c_ptr) :: a2_ptr
1109type(c_ptr) :: a3_ptr
1110type(c_ptr) :: error_code_ptr
1111!
1112interface
1113subroutine sirius_set_lattice_vectors_aux(handler,a1,a2,a3,error_code)&
1114&bind(C, name="sirius_set_lattice_vectors")
1115use, intrinsic :: iso_c_binding
1116type(c_ptr), value :: handler
1117type(c_ptr), value :: a1
1118type(c_ptr), value :: a2
1119type(c_ptr), value :: a3
1120type(c_ptr), value :: error_code
1121end subroutine
1122end interface
1123!
1124handler_ptr = c_null_ptr
1125handler_ptr = c_loc(handler%handler_ptr_)
1126a1_ptr = c_null_ptr
1127a1_ptr = c_loc(a1)
1128a2_ptr = c_null_ptr
1129a2_ptr = c_loc(a2)
1130a3_ptr = c_null_ptr
1131a3_ptr = c_loc(a3)
1132error_code_ptr = c_null_ptr
1133if (present(error_code)) then
1134error_code_ptr = c_loc(error_code)
1135endif
1136call sirius_set_lattice_vectors_aux(handler_ptr,a1_ptr,a2_ptr,a3_ptr,error_code_ptr)
1137end subroutine sirius_set_lattice_vectors
1138
1139!
1140!> @brief Initialize simulation context.
1141!> @param [in] handler Simulation context handler.
1142!> @param [out] error_code Error code.
1143subroutine sirius_initialize_context(handler,error_code)
1144implicit none
1145!
1146type(sirius_context_handler), target, intent(in) :: handler
1147integer, optional, target, intent(out) :: error_code
1148!
1149type(c_ptr) :: handler_ptr
1150type(c_ptr) :: error_code_ptr
1151!
1152interface
1153subroutine sirius_initialize_context_aux(handler,error_code)&
1154&bind(C, name="sirius_initialize_context")
1155use, intrinsic :: iso_c_binding
1156type(c_ptr), value :: handler
1157type(c_ptr), value :: error_code
1158end subroutine
1159end interface
1160!
1161handler_ptr = c_null_ptr
1162handler_ptr = c_loc(handler%handler_ptr_)
1163error_code_ptr = c_null_ptr
1164if (present(error_code)) then
1165error_code_ptr = c_loc(error_code)
1166endif
1167call sirius_initialize_context_aux(handler_ptr,error_code_ptr)
1168end subroutine sirius_initialize_context
1169
1170!
1171!> @brief Update simulation context after changing lattice or atomic positions.
1172!> @param [in] handler Simulation context handler.
1173!> @param [out] error_code Error code.
1174subroutine sirius_update_context(handler,error_code)
1175implicit none
1176!
1177type(sirius_context_handler), target, intent(in) :: handler
1178integer, optional, target, intent(out) :: error_code
1179!
1180type(c_ptr) :: handler_ptr
1181type(c_ptr) :: error_code_ptr
1182!
1183interface
1184subroutine sirius_update_context_aux(handler,error_code)&
1185&bind(C, name="sirius_update_context")
1186use, intrinsic :: iso_c_binding
1187type(c_ptr), value :: handler
1188type(c_ptr), value :: error_code
1189end subroutine
1190end interface
1191!
1192handler_ptr = c_null_ptr
1193handler_ptr = c_loc(handler%handler_ptr_)
1194error_code_ptr = c_null_ptr
1195if (present(error_code)) then
1196error_code_ptr = c_loc(error_code)
1197endif
1198call sirius_update_context_aux(handler_ptr,error_code_ptr)
1199end subroutine sirius_update_context
1200
1201!
1202!> @brief Print basic info
1203!> @param [in] handler Simulation context handler.
1204!> @param [out] error_code Error code.
1205subroutine sirius_print_info(handler,error_code)
1206implicit none
1207!
1208type(sirius_context_handler), target, intent(in) :: handler
1209integer, optional, target, intent(out) :: error_code
1210!
1211type(c_ptr) :: handler_ptr
1212type(c_ptr) :: error_code_ptr
1213!
1214interface
1215subroutine sirius_print_info_aux(handler,error_code)&
1216&bind(C, name="sirius_print_info")
1217use, intrinsic :: iso_c_binding
1218type(c_ptr), value :: handler
1219type(c_ptr), value :: error_code
1220end subroutine
1221end interface
1222!
1223handler_ptr = c_null_ptr
1224handler_ptr = c_loc(handler%handler_ptr_)
1225error_code_ptr = c_null_ptr
1226if (present(error_code)) then
1227error_code_ptr = c_loc(error_code)
1228endif
1229call sirius_print_info_aux(handler_ptr,error_code_ptr)
1230end subroutine sirius_print_info
1231
1232!
1233!> @brief Free any object handler created by SIRIUS.
1234!> @details
1235!> This is an internal function. Use sirius_free_handler() in your code.
1236!> @param [inout] handler Handler of the object.
1237!> @param [out] error_code Error code
1238subroutine sirius_free_object_handler(handler,error_code)
1239implicit none
1240!
1241type(c_ptr), target, intent(inout) :: handler
1242integer, optional, target, intent(out) :: error_code
1243!
1244type(c_ptr) :: handler_ptr
1245type(c_ptr) :: error_code_ptr
1246!
1247interface
1248subroutine sirius_free_object_handler_aux(handler,error_code)&
1249&bind(C, name="sirius_free_object_handler")
1250use, intrinsic :: iso_c_binding
1251type(c_ptr), value :: handler
1252type(c_ptr), value :: error_code
1253end subroutine
1254end interface
1255!
1256handler_ptr = c_null_ptr
1257handler_ptr = c_loc(handler)
1258error_code_ptr = c_null_ptr
1259if (present(error_code)) then
1260error_code_ptr = c_loc(error_code)
1261endif
1262call sirius_free_object_handler_aux(handler_ptr,error_code_ptr)
1263end subroutine sirius_free_object_handler
1264
1265!
1266!> @brief Set pointer to density or magnetization.
1267!> @param [in] handler Simulation context handler.
1268!> @param [in] label Label of the function.
1269!> @param [in] f_mt Pointer to the muffin-tin part of the function.
1270!> @param [in] lmmax Number of lm components.
1271!> @param [in] nrmtmax Maximum number of muffin-tin points.
1272!> @param [in] num_atoms Total number of atoms.
1273!> @param [in] f_rg Pointer to the regular-grid part of the function.
1274!> @param [in] size_x Size of X-dimension of FFT grid.
1275!> @param [in] size_y Size of Y-dimension of FFT grid.
1276!> @param [in] size_z Local or global size of Z-dimension of FFT grid depending on offset_z
1277!> @param [in] offset_z Offset in the Z-dimension of FFT grid for this MPI rank.
1278!> @param [out] error_code Error code
1279subroutine sirius_set_periodic_function_ptr(handler,label,f_mt,lmmax,nrmtmax,num_atoms,&
1280&f_rg,size_x,size_y,size_z,offset_z,error_code)
1281implicit none
1282!
1283type(sirius_context_handler), target, intent(in) :: handler
1284character(*), target, intent(in) :: label
1285real(8), optional, target, intent(in) :: f_mt(:,:,:)
1286integer, optional, target, intent(in) :: lmmax
1287integer, optional, target, intent(in) :: nrmtmax
1288integer, optional, target, intent(in) :: num_atoms
1289real(8), optional, target, intent(in) :: f_rg(:)
1290integer, optional, target, intent(in) :: size_x
1291integer, optional, target, intent(in) :: size_y
1292integer, optional, target, intent(in) :: size_z
1293integer, optional, target, intent(in) :: offset_z
1294integer, optional, target, intent(out) :: error_code
1295!
1296type(c_ptr) :: handler_ptr
1297type(c_ptr) :: label_ptr
1298character(C_CHAR), target, allocatable :: label_c_type(:)
1299type(c_ptr) :: f_mt_ptr
1300type(c_ptr) :: lmmax_ptr
1301type(c_ptr) :: nrmtmax_ptr
1302type(c_ptr) :: num_atoms_ptr
1303type(c_ptr) :: f_rg_ptr
1304type(c_ptr) :: size_x_ptr
1305type(c_ptr) :: size_y_ptr
1306type(c_ptr) :: size_z_ptr
1307type(c_ptr) :: offset_z_ptr
1308type(c_ptr) :: error_code_ptr
1309!
1310interface
1311subroutine sirius_set_periodic_function_ptr_aux(handler,label,f_mt,lmmax,nrmtmax,&
1312&num_atoms,f_rg,size_x,size_y,size_z,offset_z,error_code)&
1313&bind(C, name="sirius_set_periodic_function_ptr")
1314use, intrinsic :: iso_c_binding
1315type(c_ptr), value :: handler
1316type(c_ptr), value :: label
1317type(c_ptr), value :: f_mt
1318type(c_ptr), value :: lmmax
1319type(c_ptr), value :: nrmtmax
1320type(c_ptr), value :: num_atoms
1321type(c_ptr), value :: f_rg
1322type(c_ptr), value :: size_x
1323type(c_ptr), value :: size_y
1324type(c_ptr), value :: size_z
1325type(c_ptr), value :: offset_z
1326type(c_ptr), value :: error_code
1327end subroutine
1328end interface
1329!
1330handler_ptr = c_null_ptr
1331handler_ptr = c_loc(handler%handler_ptr_)
1332label_ptr = c_null_ptr
1333allocate(label_c_type(len(label)+1))
1334label_c_type = string_f2c(label)
1335label_ptr = c_loc(label_c_type)
1336f_mt_ptr = c_null_ptr
1337if (present(f_mt)) then
1338f_mt_ptr = c_loc(f_mt)
1339endif
1340lmmax_ptr = c_null_ptr
1341if (present(lmmax)) then
1342lmmax_ptr = c_loc(lmmax)
1343endif
1344nrmtmax_ptr = c_null_ptr
1345if (present(nrmtmax)) then
1346nrmtmax_ptr = c_loc(nrmtmax)
1347endif
1348num_atoms_ptr = c_null_ptr
1349if (present(num_atoms)) then
1350num_atoms_ptr = c_loc(num_atoms)
1351endif
1352f_rg_ptr = c_null_ptr
1353if (present(f_rg)) then
1354f_rg_ptr = c_loc(f_rg)
1355endif
1356size_x_ptr = c_null_ptr
1357if (present(size_x)) then
1358size_x_ptr = c_loc(size_x)
1359endif
1360size_y_ptr = c_null_ptr
1361if (present(size_y)) then
1362size_y_ptr = c_loc(size_y)
1363endif
1364size_z_ptr = c_null_ptr
1365if (present(size_z)) then
1366size_z_ptr = c_loc(size_z)
1367endif
1368offset_z_ptr = c_null_ptr
1369if (present(offset_z)) then
1370offset_z_ptr = c_loc(offset_z)
1371endif
1372error_code_ptr = c_null_ptr
1373if (present(error_code)) then
1374error_code_ptr = c_loc(error_code)
1375endif
1376call sirius_set_periodic_function_ptr_aux(handler_ptr,label_ptr,f_mt_ptr,lmmax_ptr,&
1377&nrmtmax_ptr,num_atoms_ptr,f_rg_ptr,size_x_ptr,size_y_ptr,size_z_ptr,offset_z_ptr,&
1378&error_code_ptr)
1379deallocate(label_c_type)
1381
1382!
1383!> @brief Set values of the periodic function.
1384!> @param [in] handler Handler of the DFT ground state object.
1385!> @param [in] label Label of the function.
1386!> @param [in] f_mt Pointer to the muffin-tin part of the function.
1387!> @param [in] lmmax Number of lm components.
1388!> @param [in] nrmtmax Maximum number of muffin-tin points.
1389!> @param [in] num_atoms Total number of atoms.
1390!> @param [in] f_rg Pointer to the regular-grid part of the function.
1391!> @param [in] size_x Size of X-dimension of FFT grid.
1392!> @param [in] size_y Size of Y-dimension of FFT grid.
1393!> @param [in] size_z Local or global size of Z-dimension of FFT grid depending on offset_z
1394!> @param [in] offset_z Offset in the Z-dimension of FFT grid for this MPI rank.
1395!> @param [out] error_code Error code.
1396subroutine sirius_set_periodic_function(handler,label,f_mt,lmmax,nrmtmax,num_atoms,&
1397&f_rg,size_x,size_y,size_z,offset_z,error_code)
1398implicit none
1399!
1400type(sirius_ground_state_handler), target, intent(in) :: handler
1401character(*), target, intent(in) :: label
1402real(8), optional, target, intent(in) :: f_mt(:,:,:)
1403integer, optional, target, intent(in) :: lmmax
1404integer, optional, target, intent(in) :: nrmtmax
1405integer, optional, target, intent(in) :: num_atoms
1406real(8), optional, target, intent(in) :: f_rg(:)
1407integer, optional, target, intent(in) :: size_x
1408integer, optional, target, intent(in) :: size_y
1409integer, optional, target, intent(in) :: size_z
1410integer, optional, target, intent(in) :: offset_z
1411integer, optional, target, intent(out) :: error_code
1412!
1413type(c_ptr) :: handler_ptr
1414type(c_ptr) :: label_ptr
1415character(C_CHAR), target, allocatable :: label_c_type(:)
1416type(c_ptr) :: f_mt_ptr
1417type(c_ptr) :: lmmax_ptr
1418type(c_ptr) :: nrmtmax_ptr
1419type(c_ptr) :: num_atoms_ptr
1420type(c_ptr) :: f_rg_ptr
1421type(c_ptr) :: size_x_ptr
1422type(c_ptr) :: size_y_ptr
1423type(c_ptr) :: size_z_ptr
1424type(c_ptr) :: offset_z_ptr
1425type(c_ptr) :: error_code_ptr
1426!
1427interface
1428subroutine sirius_set_periodic_function_aux(handler,label,f_mt,lmmax,nrmtmax,num_atoms,&
1429&f_rg,size_x,size_y,size_z,offset_z,error_code)&
1430&bind(C, name="sirius_set_periodic_function")
1431use, intrinsic :: iso_c_binding
1432type(c_ptr), value :: handler
1433type(c_ptr), value :: label
1434type(c_ptr), value :: f_mt
1435type(c_ptr), value :: lmmax
1436type(c_ptr), value :: nrmtmax
1437type(c_ptr), value :: num_atoms
1438type(c_ptr), value :: f_rg
1439type(c_ptr), value :: size_x
1440type(c_ptr), value :: size_y
1441type(c_ptr), value :: size_z
1442type(c_ptr), value :: offset_z
1443type(c_ptr), value :: error_code
1444end subroutine
1445end interface
1446!
1447handler_ptr = c_null_ptr
1448handler_ptr = c_loc(handler%handler_ptr_)
1449label_ptr = c_null_ptr
1450allocate(label_c_type(len(label)+1))
1451label_c_type = string_f2c(label)
1452label_ptr = c_loc(label_c_type)
1453f_mt_ptr = c_null_ptr
1454if (present(f_mt)) then
1455f_mt_ptr = c_loc(f_mt)
1456endif
1457lmmax_ptr = c_null_ptr
1458if (present(lmmax)) then
1459lmmax_ptr = c_loc(lmmax)
1460endif
1461nrmtmax_ptr = c_null_ptr
1462if (present(nrmtmax)) then
1463nrmtmax_ptr = c_loc(nrmtmax)
1464endif
1465num_atoms_ptr = c_null_ptr
1466if (present(num_atoms)) then
1467num_atoms_ptr = c_loc(num_atoms)
1468endif
1469f_rg_ptr = c_null_ptr
1470if (present(f_rg)) then
1471f_rg_ptr = c_loc(f_rg)
1472endif
1473size_x_ptr = c_null_ptr
1474if (present(size_x)) then
1475size_x_ptr = c_loc(size_x)
1476endif
1477size_y_ptr = c_null_ptr
1478if (present(size_y)) then
1479size_y_ptr = c_loc(size_y)
1480endif
1481size_z_ptr = c_null_ptr
1482if (present(size_z)) then
1483size_z_ptr = c_loc(size_z)
1484endif
1485offset_z_ptr = c_null_ptr
1486if (present(offset_z)) then
1487offset_z_ptr = c_loc(offset_z)
1488endif
1489error_code_ptr = c_null_ptr
1490if (present(error_code)) then
1491error_code_ptr = c_loc(error_code)
1492endif
1493call sirius_set_periodic_function_aux(handler_ptr,label_ptr,f_mt_ptr,lmmax_ptr,nrmtmax_ptr,&
1494&num_atoms_ptr,f_rg_ptr,size_x_ptr,size_y_ptr,size_z_ptr,offset_z_ptr,error_code_ptr)
1495deallocate(label_c_type)
1496end subroutine sirius_set_periodic_function
1497
1498!
1499!> @brief Get values of the periodic function.
1500!> @param [in] handler Handler of the DFT ground state object.
1501!> @param [in] label Label of the function.
1502!> @param [in] f_mt Pointer to the muffin-tin part of the function.
1503!> @param [in] lmmax Number of lm components.
1504!> @param [in] nrmtmax Maximum number of muffin-tin points.
1505!> @param [in] num_atoms Total number of atoms.
1506!> @param [in] f_rg Pointer to the regular-grid part of the function.
1507!> @param [in] size_x Size of X-dimension of FFT grid.
1508!> @param [in] size_y Size of Y-dimension of FFT grid.
1509!> @param [in] size_z Local or global size of Z-dimension of FFT grid depending on offset_z
1510!> @param [in] offset_z Offset in the Z-dimension of FFT grid for this MPI rank.
1511!> @param [out] error_code Error code
1512subroutine sirius_get_periodic_function(handler,label,f_mt,lmmax,nrmtmax,num_atoms,&
1513&f_rg,size_x,size_y,size_z,offset_z,error_code)
1514implicit none
1515!
1516type(sirius_ground_state_handler), target, intent(in) :: handler
1517character(*), target, intent(in) :: label
1518real(8), optional, target, intent(in) :: f_mt(:,:,:)
1519integer, optional, target, intent(in) :: lmmax
1520integer, optional, target, intent(in) :: nrmtmax
1521integer, optional, target, intent(in) :: num_atoms
1522real(8), optional, target, intent(in) :: f_rg(:)
1523integer, optional, target, intent(in) :: size_x
1524integer, optional, target, intent(in) :: size_y
1525integer, optional, target, intent(in) :: size_z
1526integer, optional, target, intent(in) :: offset_z
1527integer, optional, target, intent(out) :: error_code
1528!
1529type(c_ptr) :: handler_ptr
1530type(c_ptr) :: label_ptr
1531character(C_CHAR), target, allocatable :: label_c_type(:)
1532type(c_ptr) :: f_mt_ptr
1533type(c_ptr) :: lmmax_ptr
1534type(c_ptr) :: nrmtmax_ptr
1535type(c_ptr) :: num_atoms_ptr
1536type(c_ptr) :: f_rg_ptr
1537type(c_ptr) :: size_x_ptr
1538type(c_ptr) :: size_y_ptr
1539type(c_ptr) :: size_z_ptr
1540type(c_ptr) :: offset_z_ptr
1541type(c_ptr) :: error_code_ptr
1542!
1543interface
1544subroutine sirius_get_periodic_function_aux(handler,label,f_mt,lmmax,nrmtmax,num_atoms,&
1545&f_rg,size_x,size_y,size_z,offset_z,error_code)&
1546&bind(C, name="sirius_get_periodic_function")
1547use, intrinsic :: iso_c_binding
1548type(c_ptr), value :: handler
1549type(c_ptr), value :: label
1550type(c_ptr), value :: f_mt
1551type(c_ptr), value :: lmmax
1552type(c_ptr), value :: nrmtmax
1553type(c_ptr), value :: num_atoms
1554type(c_ptr), value :: f_rg
1555type(c_ptr), value :: size_x
1556type(c_ptr), value :: size_y
1557type(c_ptr), value :: size_z
1558type(c_ptr), value :: offset_z
1559type(c_ptr), value :: error_code
1560end subroutine
1561end interface
1562!
1563handler_ptr = c_null_ptr
1564handler_ptr = c_loc(handler%handler_ptr_)
1565label_ptr = c_null_ptr
1566allocate(label_c_type(len(label)+1))
1567label_c_type = string_f2c(label)
1568label_ptr = c_loc(label_c_type)
1569f_mt_ptr = c_null_ptr
1570if (present(f_mt)) then
1571f_mt_ptr = c_loc(f_mt)
1572endif
1573lmmax_ptr = c_null_ptr
1574if (present(lmmax)) then
1575lmmax_ptr = c_loc(lmmax)
1576endif
1577nrmtmax_ptr = c_null_ptr
1578if (present(nrmtmax)) then
1579nrmtmax_ptr = c_loc(nrmtmax)
1580endif
1581num_atoms_ptr = c_null_ptr
1582if (present(num_atoms)) then
1583num_atoms_ptr = c_loc(num_atoms)
1584endif
1585f_rg_ptr = c_null_ptr
1586if (present(f_rg)) then
1587f_rg_ptr = c_loc(f_rg)
1588endif
1589size_x_ptr = c_null_ptr
1590if (present(size_x)) then
1591size_x_ptr = c_loc(size_x)
1592endif
1593size_y_ptr = c_null_ptr
1594if (present(size_y)) then
1595size_y_ptr = c_loc(size_y)
1596endif
1597size_z_ptr = c_null_ptr
1598if (present(size_z)) then
1599size_z_ptr = c_loc(size_z)
1600endif
1601offset_z_ptr = c_null_ptr
1602if (present(offset_z)) then
1603offset_z_ptr = c_loc(offset_z)
1604endif
1605error_code_ptr = c_null_ptr
1606if (present(error_code)) then
1607error_code_ptr = c_loc(error_code)
1608endif
1609call sirius_get_periodic_function_aux(handler_ptr,label_ptr,f_mt_ptr,lmmax_ptr,nrmtmax_ptr,&
1610&num_atoms_ptr,f_rg_ptr,size_x_ptr,size_y_ptr,size_z_ptr,offset_z_ptr,error_code_ptr)
1611deallocate(label_c_type)
1612end subroutine sirius_get_periodic_function
1613
1614!
1615!> @brief Create k-point set from the list of k-points.
1616!> @param [in] handler Simulation context handler.
1617!> @param [in] num_kpoints Total number of k-points in the set.
1618!> @param [in] kpoints List of k-points in lattice coordinates.
1619!> @param [in] kpoint_weights Weights of k-points.
1620!> @param [in] init_kset If .true. k-set will be initialized.
1621!> @param [out] kset_handler Handler of the newly created k-point set.
1622!> @param [out] error_code Error code.
1623subroutine sirius_create_kset(handler,num_kpoints,kpoints,kpoint_weights,init_kset,&
1624&kset_handler,error_code)
1625implicit none
1626!
1627type(sirius_context_handler), target, intent(in) :: handler
1628integer, target, intent(in) :: num_kpoints
1629real(8), target, intent(in) :: kpoints(3,num_kpoints)
1630real(8), target, intent(in) :: kpoint_weights(num_kpoints)
1631logical, target, intent(in) :: init_kset
1632type(sirius_kpoint_set_handler), target, intent(out) :: kset_handler
1633integer, optional, target, intent(out) :: error_code
1634!
1635type(c_ptr) :: handler_ptr
1636type(c_ptr) :: num_kpoints_ptr
1637type(c_ptr) :: kpoints_ptr
1638type(c_ptr) :: kpoint_weights_ptr
1639type(c_ptr) :: init_kset_ptr
1640logical(C_BOOL), target :: init_kset_c_type
1641type(c_ptr) :: kset_handler_ptr
1642type(c_ptr) :: error_code_ptr
1643!
1644interface
1645subroutine sirius_create_kset_aux(handler,num_kpoints,kpoints,kpoint_weights,init_kset,&
1646&kset_handler,error_code)&
1647&bind(C, name="sirius_create_kset")
1648use, intrinsic :: iso_c_binding
1649type(c_ptr), value :: handler
1650type(c_ptr), value :: num_kpoints
1651type(c_ptr), value :: kpoints
1652type(c_ptr), value :: kpoint_weights
1653type(c_ptr), value :: init_kset
1654type(c_ptr), value :: kset_handler
1655type(c_ptr), value :: error_code
1656end subroutine
1657end interface
1658!
1659handler_ptr = c_null_ptr
1660handler_ptr = c_loc(handler%handler_ptr_)
1661num_kpoints_ptr = c_null_ptr
1662num_kpoints_ptr = c_loc(num_kpoints)
1663kpoints_ptr = c_null_ptr
1664kpoints_ptr = c_loc(kpoints)
1665kpoint_weights_ptr = c_null_ptr
1666kpoint_weights_ptr = c_loc(kpoint_weights)
1667init_kset_ptr = c_null_ptr
1668init_kset_c_type = init_kset
1669init_kset_ptr = c_loc(init_kset_c_type)
1670kset_handler_ptr = c_null_ptr
1671kset_handler_ptr = c_loc(kset_handler%handler_ptr_)
1672error_code_ptr = c_null_ptr
1673if (present(error_code)) then
1674error_code_ptr = c_loc(error_code)
1675endif
1676call sirius_create_kset_aux(handler_ptr,num_kpoints_ptr,kpoints_ptr,kpoint_weights_ptr,&
1677&init_kset_ptr,kset_handler_ptr,error_code_ptr)
1678end subroutine sirius_create_kset
1679
1680!
1681!> @brief Create k-point set from a grid.
1682!> @param [in] handler Simulation context handler.
1683!> @param [in] k_grid dimensions of the k points grid.
1684!> @param [in] k_shift k point shifts.
1685!> @param [in] use_symmetry If .true. k-set will be generated using symmetries.
1686!> @param [out] kset_handler Handler of the newly created k-point set.
1687!> @param [out] error_code Error code.
1688subroutine sirius_create_kset_from_grid(handler,k_grid,k_shift,use_symmetry,kset_handler,&
1689&error_code)
1690implicit none
1691!
1692type(sirius_context_handler), target, intent(in) :: handler
1693integer, target, intent(in) :: k_grid(3)
1694integer, target, intent(in) :: k_shift(3)
1695logical, target, intent(in) :: use_symmetry
1696type(sirius_kpoint_set_handler), target, intent(out) :: kset_handler
1697integer, optional, target, intent(out) :: error_code
1698!
1699type(c_ptr) :: handler_ptr
1700type(c_ptr) :: k_grid_ptr
1701type(c_ptr) :: k_shift_ptr
1702type(c_ptr) :: use_symmetry_ptr
1703logical(C_BOOL), target :: use_symmetry_c_type
1704type(c_ptr) :: kset_handler_ptr
1705type(c_ptr) :: error_code_ptr
1706!
1707interface
1708subroutine sirius_create_kset_from_grid_aux(handler,k_grid,k_shift,use_symmetry,&
1709&kset_handler,error_code)&
1710&bind(C, name="sirius_create_kset_from_grid")
1711use, intrinsic :: iso_c_binding
1712type(c_ptr), value :: handler
1713type(c_ptr), value :: k_grid
1714type(c_ptr), value :: k_shift
1715type(c_ptr), value :: use_symmetry
1716type(c_ptr), value :: kset_handler
1717type(c_ptr), value :: error_code
1718end subroutine
1719end interface
1720!
1721handler_ptr = c_null_ptr
1722handler_ptr = c_loc(handler%handler_ptr_)
1723k_grid_ptr = c_null_ptr
1724k_grid_ptr = c_loc(k_grid)
1725k_shift_ptr = c_null_ptr
1726k_shift_ptr = c_loc(k_shift)
1727use_symmetry_ptr = c_null_ptr
1728use_symmetry_c_type = use_symmetry
1729use_symmetry_ptr = c_loc(use_symmetry_c_type)
1730kset_handler_ptr = c_null_ptr
1731kset_handler_ptr = c_loc(kset_handler%handler_ptr_)
1732error_code_ptr = c_null_ptr
1733if (present(error_code)) then
1734error_code_ptr = c_loc(error_code)
1735endif
1736call sirius_create_kset_from_grid_aux(handler_ptr,k_grid_ptr,k_shift_ptr,use_symmetry_ptr,&
1737&kset_handler_ptr,error_code_ptr)
1738end subroutine sirius_create_kset_from_grid
1739
1740!
1741!> @brief Create a ground state object.
1742!> @param [in] ks_handler Handler of the k-point set.
1743!> @param [out] gs_handler Handler of the newly created ground state object.
1744!> @param [out] error_code Error code.
1745subroutine sirius_create_ground_state(ks_handler,gs_handler,error_code)
1746implicit none
1747!
1748type(sirius_kpoint_set_handler), target, intent(in) :: ks_handler
1749type(sirius_ground_state_handler), target, intent(out) :: gs_handler
1750integer, optional, target, intent(out) :: error_code
1751!
1752type(c_ptr) :: ks_handler_ptr
1753type(c_ptr) :: gs_handler_ptr
1754type(c_ptr) :: error_code_ptr
1755!
1756interface
1757subroutine sirius_create_ground_state_aux(ks_handler,gs_handler,error_code)&
1758&bind(C, name="sirius_create_ground_state")
1759use, intrinsic :: iso_c_binding
1760type(c_ptr), value :: ks_handler
1761type(c_ptr), value :: gs_handler
1762type(c_ptr), value :: error_code
1763end subroutine
1764end interface
1765!
1766ks_handler_ptr = c_null_ptr
1767ks_handler_ptr = c_loc(ks_handler%handler_ptr_)
1768gs_handler_ptr = c_null_ptr
1769gs_handler_ptr = c_loc(gs_handler%handler_ptr_)
1770error_code_ptr = c_null_ptr
1771if (present(error_code)) then
1772error_code_ptr = c_loc(error_code)
1773endif
1774call sirius_create_ground_state_aux(ks_handler_ptr,gs_handler_ptr,error_code_ptr)
1775end subroutine sirius_create_ground_state
1776
1777!
1778!> @brief Initialize k-point set.
1779!> @param [in] ks_handler K-point set handler.
1780!> @param [in] count Local number of k-points for each MPI rank.
1781!> @param [out] error_code Error code.
1782subroutine sirius_initialize_kset(ks_handler,count,error_code)
1783implicit none
1784!
1785type(sirius_kpoint_set_handler), target, intent(in) :: ks_handler
1786integer, optional, target, intent(in) :: count(:)
1787integer, optional, target, intent(out) :: error_code
1788!
1789type(c_ptr) :: ks_handler_ptr
1790type(c_ptr) :: count_ptr
1791type(c_ptr) :: error_code_ptr
1792!
1793interface
1794subroutine sirius_initialize_kset_aux(ks_handler,count,error_code)&
1795&bind(C, name="sirius_initialize_kset")
1796use, intrinsic :: iso_c_binding
1797type(c_ptr), value :: ks_handler
1798type(c_ptr), value :: count
1799type(c_ptr), value :: error_code
1800end subroutine
1801end interface
1802!
1803ks_handler_ptr = c_null_ptr
1804ks_handler_ptr = c_loc(ks_handler%handler_ptr_)
1805count_ptr = c_null_ptr
1806if (present(count)) then
1807count_ptr = c_loc(count)
1808endif
1809error_code_ptr = c_null_ptr
1810if (present(error_code)) then
1811error_code_ptr = c_loc(error_code)
1812endif
1813call sirius_initialize_kset_aux(ks_handler_ptr,count_ptr,error_code_ptr)
1814end subroutine sirius_initialize_kset
1815
1816!
1817!> @brief Find the ground state.
1818!> @param [in] gs_handler Handler of the ground state.
1819!> @param [in] density_tol Tolerance on RMS in density.
1820!> @param [in] energy_tol Tolerance in total energy difference.
1821!> @param [in] iter_solver_tol Initial tolerance of the iterative solver.
1822!> @param [in] initial_guess Boolean variable indicating if we want to start from the initial guess or from previous state.
1823!> @param [in] max_niter Maximum number of SCF iterations.
1824!> @param [in] save_state Boolean variable indicating if we want to save the ground state.
1825!> @param [out] converged Boolean variable indicating if the calculation has converged
1826!> @param [out] niter Actual number of SCF iterations.
1827!> @param [out] rho_min Minimum value of density on the real-space grid. If negative, total energy can't be trusted. Valid only if SCF calculation is converged.
1828!> @param [out] error_code Error code.
1829subroutine sirius_find_ground_state(gs_handler,density_tol,energy_tol,iter_solver_tol,&
1830&initial_guess,max_niter,save_state,converged,niter,rho_min,error_code)
1831implicit none
1832!
1833type(sirius_ground_state_handler), target, intent(in) :: gs_handler
1834real(8), optional, target, intent(in) :: density_tol
1835real(8), optional, target, intent(in) :: energy_tol
1836real(8), optional, target, intent(in) :: iter_solver_tol
1837logical, optional, target, intent(in) :: initial_guess
1838integer, optional, target, intent(in) :: max_niter
1839logical, optional, target, intent(in) :: save_state
1840logical, optional, target, intent(out) :: converged
1841integer, optional, target, intent(out) :: niter
1842real(8), optional, target, intent(out) :: rho_min
1843integer, optional, target, intent(out) :: error_code
1844!
1845type(c_ptr) :: gs_handler_ptr
1846type(c_ptr) :: density_tol_ptr
1847type(c_ptr) :: energy_tol_ptr
1848type(c_ptr) :: iter_solver_tol_ptr
1849type(c_ptr) :: initial_guess_ptr
1850logical(C_BOOL), target :: initial_guess_c_type
1851type(c_ptr) :: max_niter_ptr
1852type(c_ptr) :: save_state_ptr
1853logical(C_BOOL), target :: save_state_c_type
1854type(c_ptr) :: converged_ptr
1855logical(C_BOOL), target :: converged_c_type
1856type(c_ptr) :: niter_ptr
1857type(c_ptr) :: rho_min_ptr
1858type(c_ptr) :: error_code_ptr
1859!
1860interface
1861subroutine sirius_find_ground_state_aux(gs_handler,density_tol,energy_tol,iter_solver_tol,&
1862&initial_guess,max_niter,save_state,converged,niter,rho_min,error_code)&
1863&bind(C, name="sirius_find_ground_state")
1864use, intrinsic :: iso_c_binding
1865type(c_ptr), value :: gs_handler
1866type(c_ptr), value :: density_tol
1867type(c_ptr), value :: energy_tol
1868type(c_ptr), value :: iter_solver_tol
1869type(c_ptr), value :: initial_guess
1870type(c_ptr), value :: max_niter
1871type(c_ptr), value :: save_state
1872type(c_ptr), value :: converged
1873type(c_ptr), value :: niter
1874type(c_ptr), value :: rho_min
1875type(c_ptr), value :: error_code
1876end subroutine
1877end interface
1878!
1879gs_handler_ptr = c_null_ptr
1880gs_handler_ptr = c_loc(gs_handler%handler_ptr_)
1881density_tol_ptr = c_null_ptr
1882if (present(density_tol)) then
1883density_tol_ptr = c_loc(density_tol)
1884endif
1885energy_tol_ptr = c_null_ptr
1886if (present(energy_tol)) then
1887energy_tol_ptr = c_loc(energy_tol)
1888endif
1889iter_solver_tol_ptr = c_null_ptr
1890if (present(iter_solver_tol)) then
1891iter_solver_tol_ptr = c_loc(iter_solver_tol)
1892endif
1893initial_guess_ptr = c_null_ptr
1894if (present(initial_guess)) then
1895initial_guess_c_type = initial_guess
1896initial_guess_ptr = c_loc(initial_guess_c_type)
1897endif
1898max_niter_ptr = c_null_ptr
1899if (present(max_niter)) then
1900max_niter_ptr = c_loc(max_niter)
1901endif
1902save_state_ptr = c_null_ptr
1903if (present(save_state)) then
1904save_state_c_type = save_state
1905save_state_ptr = c_loc(save_state_c_type)
1906endif
1907converged_ptr = c_null_ptr
1908if (present(converged)) then
1909converged_ptr = c_loc(converged_c_type)
1910endif
1911niter_ptr = c_null_ptr
1912if (present(niter)) then
1913niter_ptr = c_loc(niter)
1914endif
1915rho_min_ptr = c_null_ptr
1916if (present(rho_min)) then
1917rho_min_ptr = c_loc(rho_min)
1918endif
1919error_code_ptr = c_null_ptr
1920if (present(error_code)) then
1921error_code_ptr = c_loc(error_code)
1922endif
1923call sirius_find_ground_state_aux(gs_handler_ptr,density_tol_ptr,energy_tol_ptr,&
1924&iter_solver_tol_ptr,initial_guess_ptr,max_niter_ptr,save_state_ptr,converged_ptr,&
1925&niter_ptr,rho_min_ptr,error_code_ptr)
1926if (present(initial_guess)) then
1927endif
1928if (present(save_state)) then
1929endif
1930if (present(converged)) then
1931converged = converged_c_type
1932endif
1933end subroutine sirius_find_ground_state
1934
1935!
1936!> @brief Check the self-consistent density
1937!> @param [in] gs_handler Handler of the ground state.
1938!> @param [out] error_code Error code
1939subroutine sirius_check_scf_density(gs_handler,error_code)
1940implicit none
1941!
1942type(sirius_ground_state_handler), target, intent(in) :: gs_handler
1943integer, optional, target, intent(out) :: error_code
1944!
1945type(c_ptr) :: gs_handler_ptr
1946type(c_ptr) :: error_code_ptr
1947!
1948interface
1949subroutine sirius_check_scf_density_aux(gs_handler,error_code)&
1950&bind(C, name="sirius_check_scf_density")
1951use, intrinsic :: iso_c_binding
1952type(c_ptr), value :: gs_handler
1953type(c_ptr), value :: error_code
1954end subroutine
1955end interface
1956!
1957gs_handler_ptr = c_null_ptr
1958gs_handler_ptr = c_loc(gs_handler%handler_ptr_)
1959error_code_ptr = c_null_ptr
1960if (present(error_code)) then
1961error_code_ptr = c_loc(error_code)
1962endif
1963call sirius_check_scf_density_aux(gs_handler_ptr,error_code_ptr)
1964end subroutine sirius_check_scf_density
1965
1966!
1967!> @brief Update a ground state object after change of atomic coordinates or lattice vectors.
1968!> @param [in] gs_handler Ground-state handler.
1969!> @param [out] error_code Error code
1970subroutine sirius_update_ground_state(gs_handler,error_code)
1971implicit none
1972!
1973type(sirius_ground_state_handler), target, intent(in) :: gs_handler
1974integer, optional, target, intent(out) :: error_code
1975!
1976type(c_ptr) :: gs_handler_ptr
1977type(c_ptr) :: error_code_ptr
1978!
1979interface
1980subroutine sirius_update_ground_state_aux(gs_handler,error_code)&
1981&bind(C, name="sirius_update_ground_state")
1982use, intrinsic :: iso_c_binding
1983type(c_ptr), value :: gs_handler
1984type(c_ptr), value :: error_code
1985end subroutine
1986end interface
1987!
1988gs_handler_ptr = c_null_ptr
1989gs_handler_ptr = c_loc(gs_handler%handler_ptr_)
1990error_code_ptr = c_null_ptr
1991if (present(error_code)) then
1992error_code_ptr = c_loc(error_code)
1993endif
1994call sirius_update_ground_state_aux(gs_handler_ptr,error_code_ptr)
1995end subroutine sirius_update_ground_state
1996
1997!
1998!> @brief Add new atom type to the unit cell.
1999!> @param [in] handler Simulation context handler.
2000!> @param [in] label Atom type unique label.
2001!> @param [in] fname Species file name (in JSON format).
2002!> @param [in] zn Nucleus charge.
2003!> @param [in] symbol Atomic symbol.
2004!> @param [in] mass Atomic mass.
2005!> @param [in] spin_orbit True if spin-orbit correction is enabled for this atom type.
2006!> @param [out] error_code Error code.
2007subroutine sirius_add_atom_type(handler,label,fname,zn,symbol,mass,spin_orbit,error_code)
2008implicit none
2009!
2010type(sirius_context_handler), target, intent(in) :: handler
2011character(*), target, intent(in) :: label
2012character(*), optional, target, intent(in) :: fname
2013integer, optional, target, intent(in) :: zn
2014character(*), optional, target, intent(in) :: symbol
2015real(8), optional, target, intent(in) :: mass
2016logical, optional, target, intent(in) :: spin_orbit
2017integer, optional, target, intent(out) :: error_code
2018!
2019type(c_ptr) :: handler_ptr
2020type(c_ptr) :: label_ptr
2021character(C_CHAR), target, allocatable :: label_c_type(:)
2022type(c_ptr) :: fname_ptr
2023character(C_CHAR), target, allocatable :: fname_c_type(:)
2024type(c_ptr) :: zn_ptr
2025type(c_ptr) :: symbol_ptr
2026character(C_CHAR), target, allocatable :: symbol_c_type(:)
2027type(c_ptr) :: mass_ptr
2028type(c_ptr) :: spin_orbit_ptr
2029logical(C_BOOL), target :: spin_orbit_c_type
2030type(c_ptr) :: error_code_ptr
2031!
2032interface
2033subroutine sirius_add_atom_type_aux(handler,label,fname,zn,symbol,mass,spin_orbit,&
2034&error_code)&
2035&bind(C, name="sirius_add_atom_type")
2036use, intrinsic :: iso_c_binding
2037type(c_ptr), value :: handler
2038type(c_ptr), value :: label
2039type(c_ptr), value :: fname
2040type(c_ptr), value :: zn
2041type(c_ptr), value :: symbol
2042type(c_ptr), value :: mass
2043type(c_ptr), value :: spin_orbit
2044type(c_ptr), value :: error_code
2045end subroutine
2046end interface
2047!
2048handler_ptr = c_null_ptr
2049handler_ptr = c_loc(handler%handler_ptr_)
2050label_ptr = c_null_ptr
2051allocate(label_c_type(len(label)+1))
2052label_c_type = string_f2c(label)
2053label_ptr = c_loc(label_c_type)
2054fname_ptr = c_null_ptr
2055if (present(fname)) then
2056allocate(fname_c_type(len(fname)+1))
2057fname_c_type = string_f2c(fname)
2058fname_ptr = c_loc(fname_c_type)
2059endif
2060zn_ptr = c_null_ptr
2061if (present(zn)) then
2062zn_ptr = c_loc(zn)
2063endif
2064symbol_ptr = c_null_ptr
2065if (present(symbol)) then
2066allocate(symbol_c_type(len(symbol)+1))
2067symbol_c_type = string_f2c(symbol)
2068symbol_ptr = c_loc(symbol_c_type)
2069endif
2070mass_ptr = c_null_ptr
2071if (present(mass)) then
2072mass_ptr = c_loc(mass)
2073endif
2074spin_orbit_ptr = c_null_ptr
2075if (present(spin_orbit)) then
2076spin_orbit_c_type = spin_orbit
2077spin_orbit_ptr = c_loc(spin_orbit_c_type)
2078endif
2079error_code_ptr = c_null_ptr
2080if (present(error_code)) then
2081error_code_ptr = c_loc(error_code)
2082endif
2083call sirius_add_atom_type_aux(handler_ptr,label_ptr,fname_ptr,zn_ptr,symbol_ptr,&
2084&mass_ptr,spin_orbit_ptr,error_code_ptr)
2085deallocate(label_c_type)
2086if (present(fname)) then
2087deallocate(fname_c_type)
2088endif
2089if (present(symbol)) then
2090deallocate(symbol_c_type)
2091endif
2092if (present(spin_orbit)) then
2093endif
2094end subroutine sirius_add_atom_type
2095
2096!
2097!> @brief Set radial grid of the atom type.
2098!> @param [in] handler Simulation context handler.
2099!> @param [in] label Atom type label.
2100!> @param [in] num_radial_points Number of radial grid points.
2101!> @param [in] radial_points List of radial grid points.
2102!> @param [out] error_code Error code.
2103subroutine sirius_set_atom_type_radial_grid(handler,label,num_radial_points,radial_points,&
2104&error_code)
2105implicit none
2106!
2107type(sirius_context_handler), target, intent(in) :: handler
2108character(*), target, intent(in) :: label
2109integer, target, intent(in) :: num_radial_points
2110real(8), target, intent(in) :: radial_points(num_radial_points)
2111integer, optional, target, intent(out) :: error_code
2112!
2113type(c_ptr) :: handler_ptr
2114type(c_ptr) :: label_ptr
2115character(C_CHAR), target, allocatable :: label_c_type(:)
2116type(c_ptr) :: num_radial_points_ptr
2117type(c_ptr) :: radial_points_ptr
2118type(c_ptr) :: error_code_ptr
2119!
2120interface
2121subroutine sirius_set_atom_type_radial_grid_aux(handler,label,num_radial_points,&
2122&radial_points,error_code)&
2123&bind(C, name="sirius_set_atom_type_radial_grid")
2124use, intrinsic :: iso_c_binding
2125type(c_ptr), value :: handler
2126type(c_ptr), value :: label
2127type(c_ptr), value :: num_radial_points
2128type(c_ptr), value :: radial_points
2129type(c_ptr), value :: error_code
2130end subroutine
2131end interface
2132!
2133handler_ptr = c_null_ptr
2134handler_ptr = c_loc(handler%handler_ptr_)
2135label_ptr = c_null_ptr
2136allocate(label_c_type(len(label)+1))
2137label_c_type = string_f2c(label)
2138label_ptr = c_loc(label_c_type)
2139num_radial_points_ptr = c_null_ptr
2140num_radial_points_ptr = c_loc(num_radial_points)
2141radial_points_ptr = c_null_ptr
2142radial_points_ptr = c_loc(radial_points)
2143error_code_ptr = c_null_ptr
2144if (present(error_code)) then
2145error_code_ptr = c_loc(error_code)
2146endif
2147call sirius_set_atom_type_radial_grid_aux(handler_ptr,label_ptr,num_radial_points_ptr,&
2148&radial_points_ptr,error_code_ptr)
2149deallocate(label_c_type)
2151
2152!
2153!> @brief Set radial grid of the free atom (up to effectice infinity).
2154!> @param [in] handler Simulation context handler.
2155!> @param [in] label Atom type label.
2156!> @param [in] num_radial_points Number of radial grid points.
2157!> @param [in] radial_points List of radial grid points.
2158!> @param [out] error_code Error code.
2159subroutine sirius_set_atom_type_radial_grid_inf(handler,label,num_radial_points,&
2160&radial_points,error_code)
2161implicit none
2162!
2163type(sirius_context_handler), target, intent(in) :: handler
2164character(*), target, intent(in) :: label
2165integer, target, intent(in) :: num_radial_points
2166real(8), target, intent(in) :: radial_points(num_radial_points)
2167integer, optional, target, intent(out) :: error_code
2168!
2169type(c_ptr) :: handler_ptr
2170type(c_ptr) :: label_ptr
2171character(C_CHAR), target, allocatable :: label_c_type(:)
2172type(c_ptr) :: num_radial_points_ptr
2173type(c_ptr) :: radial_points_ptr
2174type(c_ptr) :: error_code_ptr
2175!
2176interface
2177subroutine sirius_set_atom_type_radial_grid_inf_aux(handler,label,num_radial_points,&
2178&radial_points,error_code)&
2179&bind(C, name="sirius_set_atom_type_radial_grid_inf")
2180use, intrinsic :: iso_c_binding
2181type(c_ptr), value :: handler
2182type(c_ptr), value :: label
2183type(c_ptr), value :: num_radial_points
2184type(c_ptr), value :: radial_points
2185type(c_ptr), value :: error_code
2186end subroutine
2187end interface
2188!
2189handler_ptr = c_null_ptr
2190handler_ptr = c_loc(handler%handler_ptr_)
2191label_ptr = c_null_ptr
2192allocate(label_c_type(len(label)+1))
2193label_c_type = string_f2c(label)
2194label_ptr = c_loc(label_c_type)
2195num_radial_points_ptr = c_null_ptr
2196num_radial_points_ptr = c_loc(num_radial_points)
2197radial_points_ptr = c_null_ptr
2198radial_points_ptr = c_loc(radial_points)
2199error_code_ptr = c_null_ptr
2200if (present(error_code)) then
2201error_code_ptr = c_loc(error_code)
2202endif
2203call sirius_set_atom_type_radial_grid_inf_aux(handler_ptr,label_ptr,num_radial_points_ptr,&
2204&radial_points_ptr,error_code_ptr)
2205deallocate(label_c_type)
2207
2208!
2209!> @brief Add one of the radial functions.
2210!> @param [in] handler Simulation context handler.
2211!> @param [in] atom_type Label of the atom type.
2212!> @param [in] label Label of the radial function.
2213!> @param [in] rf Array with radial function values.
2214!> @param [in] num_points Length of radial function array.
2215!> @param [in] n Orbital quantum number.
2216!> @param [in] l angular momentum.
2217!> @param [in] idxrf1 First index of radial function (for Q-operator). Indices start from 1.
2218!> @param [in] idxrf2 Second index of radial function (for Q-operator). Indices start form 1.
2219!> @param [in] occ Occupancy of the wave-function.
2220!> @param [out] error_code Error code.
2221subroutine sirius_add_atom_type_radial_function(handler,atom_type,label,rf,num_points,&
2222&n,l,idxrf1,idxrf2,occ,error_code)
2223implicit none
2224!
2225type(sirius_context_handler), target, intent(in) :: handler
2226character(*), target, intent(in) :: atom_type
2227character(*), target, intent(in) :: label
2228real(8), target, intent(in) :: rf(num_points)
2229integer, target, intent(in) :: num_points
2230integer, optional, target, intent(in) :: n
2231integer, optional, target, intent(in) :: l
2232integer, optional, target, intent(in) :: idxrf1
2233integer, optional, target, intent(in) :: idxrf2
2234real(8), optional, target, intent(in) :: occ
2235integer, optional, target, intent(out) :: error_code
2236!
2237type(c_ptr) :: handler_ptr
2238type(c_ptr) :: atom_type_ptr
2239character(C_CHAR), target, allocatable :: atom_type_c_type(:)
2240type(c_ptr) :: label_ptr
2241character(C_CHAR), target, allocatable :: label_c_type(:)
2242type(c_ptr) :: rf_ptr
2243type(c_ptr) :: num_points_ptr
2244type(c_ptr) :: n_ptr
2245type(c_ptr) :: l_ptr
2246type(c_ptr) :: idxrf1_ptr
2247type(c_ptr) :: idxrf2_ptr
2248type(c_ptr) :: occ_ptr
2249type(c_ptr) :: error_code_ptr
2250!
2251interface
2252subroutine sirius_add_atom_type_radial_function_aux(handler,atom_type,label,rf,num_points,&
2253&n,l,idxrf1,idxrf2,occ,error_code)&
2254&bind(C, name="sirius_add_atom_type_radial_function")
2255use, intrinsic :: iso_c_binding
2256type(c_ptr), value :: handler
2257type(c_ptr), value :: atom_type
2258type(c_ptr), value :: label
2259type(c_ptr), value :: rf
2260type(c_ptr), value :: num_points
2261type(c_ptr), value :: n
2262type(c_ptr), value :: l
2263type(c_ptr), value :: idxrf1
2264type(c_ptr), value :: idxrf2
2265type(c_ptr), value :: occ
2266type(c_ptr), value :: error_code
2267end subroutine
2268end interface
2269!
2270handler_ptr = c_null_ptr
2271handler_ptr = c_loc(handler%handler_ptr_)
2272atom_type_ptr = c_null_ptr
2273allocate(atom_type_c_type(len(atom_type)+1))
2274atom_type_c_type = string_f2c(atom_type)
2275atom_type_ptr = c_loc(atom_type_c_type)
2276label_ptr = c_null_ptr
2277allocate(label_c_type(len(label)+1))
2278label_c_type = string_f2c(label)
2279label_ptr = c_loc(label_c_type)
2280rf_ptr = c_null_ptr
2281rf_ptr = c_loc(rf)
2282num_points_ptr = c_null_ptr
2283num_points_ptr = c_loc(num_points)
2284n_ptr = c_null_ptr
2285if (present(n)) then
2286n_ptr = c_loc(n)
2287endif
2288l_ptr = c_null_ptr
2289if (present(l)) then
2290l_ptr = c_loc(l)
2291endif
2292idxrf1_ptr = c_null_ptr
2293if (present(idxrf1)) then
2294idxrf1_ptr = c_loc(idxrf1)
2295endif
2296idxrf2_ptr = c_null_ptr
2297if (present(idxrf2)) then
2298idxrf2_ptr = c_loc(idxrf2)
2299endif
2300occ_ptr = c_null_ptr
2301if (present(occ)) then
2302occ_ptr = c_loc(occ)
2303endif
2304error_code_ptr = c_null_ptr
2305if (present(error_code)) then
2306error_code_ptr = c_loc(error_code)
2307endif
2308call sirius_add_atom_type_radial_function_aux(handler_ptr,atom_type_ptr,label_ptr,&
2309&rf_ptr,num_points_ptr,n_ptr,l_ptr,idxrf1_ptr,idxrf2_ptr,occ_ptr,error_code_ptr)
2310deallocate(atom_type_c_type)
2311deallocate(label_c_type)
2313
2314!
2315!> @brief Set the hubbard correction for the atomic type.
2316!> @param [in] handler Simulation context handler.
2317!> @param [in] label Atom type label.
2318!> @param [in] l Orbital quantum number.
2319!> @param [in] n principal quantum number (s, p, d, f)
2320!> @param [in] occ Atomic shell occupancy.
2321!> @param [in] U Hubbard U parameter.
2322!> @param [in] J Exchange J parameter for the full interaction treatment.
2323!> @param [in] alpha J_alpha for the simple interaction treatment.
2324!> @param [in] beta J_beta for the simple interaction treatment.
2325!> @param [in] J0 J0 for the simple interaction treatment.
2326!> @param [out] error_code Error code.
2327subroutine sirius_set_atom_type_hubbard(handler,label,l,n,occ,U,J,alpha,beta,J0,&
2328&error_code)
2329implicit none
2330!
2331type(sirius_context_handler), target, intent(in) :: handler
2332character(*), target, intent(in) :: label
2333integer, target, intent(in) :: l
2334integer, target, intent(in) :: n
2335real(8), target, intent(in) :: occ
2336real(8), target, intent(in) :: U
2337real(8), target, intent(in) :: J
2338real(8), target, intent(in) :: alpha
2339real(8), target, intent(in) :: beta
2340real(8), target, intent(in) :: J0
2341integer, optional, target, intent(out) :: error_code
2342!
2343type(c_ptr) :: handler_ptr
2344type(c_ptr) :: label_ptr
2345character(C_CHAR), target, allocatable :: label_c_type(:)
2346type(c_ptr) :: l_ptr
2347type(c_ptr) :: n_ptr
2348type(c_ptr) :: occ_ptr
2349type(c_ptr) :: U_ptr
2350type(c_ptr) :: J_ptr
2351type(c_ptr) :: alpha_ptr
2352type(c_ptr) :: beta_ptr
2353type(c_ptr) :: J0_ptr
2354type(c_ptr) :: error_code_ptr
2355!
2356interface
2357subroutine sirius_set_atom_type_hubbard_aux(handler,label,l,n,occ,U,J,alpha,beta,&
2358&J0,error_code)&
2359&bind(C, name="sirius_set_atom_type_hubbard")
2360use, intrinsic :: iso_c_binding
2361type(c_ptr), value :: handler
2362type(c_ptr), value :: label
2363type(c_ptr), value :: l
2364type(c_ptr), value :: n
2365type(c_ptr), value :: occ
2366type(c_ptr), value :: U
2367type(c_ptr), value :: J
2368type(c_ptr), value :: alpha
2369type(c_ptr), value :: beta
2370type(c_ptr), value :: J0
2371type(c_ptr), value :: error_code
2372end subroutine
2373end interface
2374!
2375handler_ptr = c_null_ptr
2376handler_ptr = c_loc(handler%handler_ptr_)
2377label_ptr = c_null_ptr
2378allocate(label_c_type(len(label)+1))
2379label_c_type = string_f2c(label)
2380label_ptr = c_loc(label_c_type)
2381l_ptr = c_null_ptr
2382l_ptr = c_loc(l)
2383n_ptr = c_null_ptr
2384n_ptr = c_loc(n)
2385occ_ptr = c_null_ptr
2386occ_ptr = c_loc(occ)
2387u_ptr = c_null_ptr
2388u_ptr = c_loc(u)
2389j_ptr = c_null_ptr
2390j_ptr = c_loc(j)
2391alpha_ptr = c_null_ptr
2392alpha_ptr = c_loc(alpha)
2393beta_ptr = c_null_ptr
2394beta_ptr = c_loc(beta)
2395j0_ptr = c_null_ptr
2396j0_ptr = c_loc(j0)
2397error_code_ptr = c_null_ptr
2398if (present(error_code)) then
2399error_code_ptr = c_loc(error_code)
2400endif
2401call sirius_set_atom_type_hubbard_aux(handler_ptr,label_ptr,l_ptr,n_ptr,occ_ptr,&
2402&u_ptr,j_ptr,alpha_ptr,beta_ptr,j0_ptr,error_code_ptr)
2403deallocate(label_c_type)
2404end subroutine sirius_set_atom_type_hubbard
2405
2406!
2407!> @brief Set ionic part of D-operator matrix.
2408!> @param [in] handler Simulation context handler.
2409!> @param [in] label Atom type label.
2410!> @param [in] num_beta Number of beta-projectors.
2411!> @param [in] dion Ionic part of D-operator matrix.
2412!> @param [out] error_code Error code.
2413subroutine sirius_set_atom_type_dion(handler,label,num_beta,dion,error_code)
2414implicit none
2415!
2416type(sirius_context_handler), target, intent(in) :: handler
2417character(*), target, intent(in) :: label
2418integer, target, intent(in) :: num_beta
2419real(8), target, intent(in) :: dion(num_beta, num_beta)
2420integer, optional, target, intent(out) :: error_code
2421!
2422type(c_ptr) :: handler_ptr
2423type(c_ptr) :: label_ptr
2424character(C_CHAR), target, allocatable :: label_c_type(:)
2425type(c_ptr) :: num_beta_ptr
2426type(c_ptr) :: dion_ptr
2427type(c_ptr) :: error_code_ptr
2428!
2429interface
2430subroutine sirius_set_atom_type_dion_aux(handler,label,num_beta,dion,error_code)&
2431&bind(C, name="sirius_set_atom_type_dion")
2432use, intrinsic :: iso_c_binding
2433type(c_ptr), value :: handler
2434type(c_ptr), value :: label
2435type(c_ptr), value :: num_beta
2436type(c_ptr), value :: dion
2437type(c_ptr), value :: error_code
2438end subroutine
2439end interface
2440!
2441handler_ptr = c_null_ptr
2442handler_ptr = c_loc(handler%handler_ptr_)
2443label_ptr = c_null_ptr
2444allocate(label_c_type(len(label)+1))
2445label_c_type = string_f2c(label)
2446label_ptr = c_loc(label_c_type)
2447num_beta_ptr = c_null_ptr
2448num_beta_ptr = c_loc(num_beta)
2449dion_ptr = c_null_ptr
2450dion_ptr = c_loc(dion)
2451error_code_ptr = c_null_ptr
2452if (present(error_code)) then
2453error_code_ptr = c_loc(error_code)
2454endif
2455call sirius_set_atom_type_dion_aux(handler_ptr,label_ptr,num_beta_ptr,dion_ptr,error_code_ptr)
2456deallocate(label_c_type)
2457end subroutine sirius_set_atom_type_dion
2458
2459!
2460!> @brief Set PAW related data.
2461!> @param [in] handler Simulation context handler.
2462!> @param [in] label Atom type label.
2463!> @param [in] core_energy Core-electrons energy contribution.
2464!> @param [in] occupations array of orbital occupancies
2465!> @param [in] num_occ size of the occupations array
2466!> @param [out] error_code Error code.
2467subroutine sirius_set_atom_type_paw(handler,label,core_energy,occupations,num_occ,&
2468&error_code)
2469implicit none
2470!
2471type(sirius_context_handler), target, intent(in) :: handler
2472character(*), target, intent(in) :: label
2473real(8), target, intent(in) :: core_energy
2474real(8), target, intent(in) :: occupations(num_occ)
2475integer, target, intent(in) :: num_occ
2476integer, optional, target, intent(out) :: error_code
2477!
2478type(c_ptr) :: handler_ptr
2479type(c_ptr) :: label_ptr
2480character(C_CHAR), target, allocatable :: label_c_type(:)
2481type(c_ptr) :: core_energy_ptr
2482type(c_ptr) :: occupations_ptr
2483type(c_ptr) :: num_occ_ptr
2484type(c_ptr) :: error_code_ptr
2485!
2486interface
2487subroutine sirius_set_atom_type_paw_aux(handler,label,core_energy,occupations,num_occ,&
2488&error_code)&
2489&bind(C, name="sirius_set_atom_type_paw")
2490use, intrinsic :: iso_c_binding
2491type(c_ptr), value :: handler
2492type(c_ptr), value :: label
2493type(c_ptr), value :: core_energy
2494type(c_ptr), value :: occupations
2495type(c_ptr), value :: num_occ
2496type(c_ptr), value :: error_code
2497end subroutine
2498end interface
2499!
2500handler_ptr = c_null_ptr
2501handler_ptr = c_loc(handler%handler_ptr_)
2502label_ptr = c_null_ptr
2503allocate(label_c_type(len(label)+1))
2504label_c_type = string_f2c(label)
2505label_ptr = c_loc(label_c_type)
2506core_energy_ptr = c_null_ptr
2507core_energy_ptr = c_loc(core_energy)
2508occupations_ptr = c_null_ptr
2509occupations_ptr = c_loc(occupations)
2510num_occ_ptr = c_null_ptr
2511num_occ_ptr = c_loc(num_occ)
2512error_code_ptr = c_null_ptr
2513if (present(error_code)) then
2514error_code_ptr = c_loc(error_code)
2515endif
2516call sirius_set_atom_type_paw_aux(handler_ptr,label_ptr,core_energy_ptr,occupations_ptr,&
2517&num_occ_ptr,error_code_ptr)
2518deallocate(label_c_type)
2519end subroutine sirius_set_atom_type_paw
2520
2521!
2522!> @brief Add atom to the unit cell.
2523!> @param [in] handler Simulation context handler.
2524!> @param [in] label Atom type label.
2525!> @param [in] position Atom position in lattice coordinates.
2526!> @param [in] vector_field Starting magnetization.
2527!> @param [out] error_code Error code.
2528subroutine sirius_add_atom(handler,label,position,vector_field,error_code)
2529implicit none
2530!
2531type(sirius_context_handler), target, intent(in) :: handler
2532character(*), target, intent(in) :: label
2533real(8), target, intent(in) :: position(3)
2534real(8), optional, target, intent(in) :: vector_field(3)
2535integer, optional, target, intent(out) :: error_code
2536!
2537type(c_ptr) :: handler_ptr
2538type(c_ptr) :: label_ptr
2539character(C_CHAR), target, allocatable :: label_c_type(:)
2540type(c_ptr) :: position_ptr
2541type(c_ptr) :: vector_field_ptr
2542type(c_ptr) :: error_code_ptr
2543!
2544interface
2545subroutine sirius_add_atom_aux(handler,label,position,vector_field,error_code)&
2546&bind(C, name="sirius_add_atom")
2547use, intrinsic :: iso_c_binding
2548type(c_ptr), value :: handler
2549type(c_ptr), value :: label
2550type(c_ptr), value :: position
2551type(c_ptr), value :: vector_field
2552type(c_ptr), value :: error_code
2553end subroutine
2554end interface
2555!
2556handler_ptr = c_null_ptr
2557handler_ptr = c_loc(handler%handler_ptr_)
2558label_ptr = c_null_ptr
2559allocate(label_c_type(len(label)+1))
2560label_c_type = string_f2c(label)
2561label_ptr = c_loc(label_c_type)
2562position_ptr = c_null_ptr
2563position_ptr = c_loc(position)
2564vector_field_ptr = c_null_ptr
2565if (present(vector_field)) then
2566vector_field_ptr = c_loc(vector_field)
2567endif
2568error_code_ptr = c_null_ptr
2569if (present(error_code)) then
2570error_code_ptr = c_loc(error_code)
2571endif
2572call sirius_add_atom_aux(handler_ptr,label_ptr,position_ptr,vector_field_ptr,error_code_ptr)
2573deallocate(label_c_type)
2574end subroutine sirius_add_atom
2575
2576!
2577!> @brief Set new atomic position.
2578!> @param [in] handler Simulation context handler.
2579!> @param [in] ia Index of atom; index starts form 1
2580!> @param [in] position Atom position in lattice coordinates.
2581!> @param [out] error_code Error code.
2582subroutine sirius_set_atom_position(handler,ia,position,error_code)
2583implicit none
2584!
2585type(sirius_context_handler), target, intent(in) :: handler
2586integer, target, intent(in) :: ia
2587real(8), target, intent(in) :: position(3)
2588integer, optional, target, intent(out) :: error_code
2589!
2590type(c_ptr) :: handler_ptr
2591type(c_ptr) :: ia_ptr
2592type(c_ptr) :: position_ptr
2593type(c_ptr) :: error_code_ptr
2594!
2595interface
2596subroutine sirius_set_atom_position_aux(handler,ia,position,error_code)&
2597&bind(C, name="sirius_set_atom_position")
2598use, intrinsic :: iso_c_binding
2599type(c_ptr), value :: handler
2600type(c_ptr), value :: ia
2601type(c_ptr), value :: position
2602type(c_ptr), value :: error_code
2603end subroutine
2604end interface
2605!
2606handler_ptr = c_null_ptr
2607handler_ptr = c_loc(handler%handler_ptr_)
2608ia_ptr = c_null_ptr
2609ia_ptr = c_loc(ia)
2610position_ptr = c_null_ptr
2611position_ptr = c_loc(position)
2612error_code_ptr = c_null_ptr
2613if (present(error_code)) then
2614error_code_ptr = c_loc(error_code)
2615endif
2616call sirius_set_atom_position_aux(handler_ptr,ia_ptr,position_ptr,error_code_ptr)
2617end subroutine sirius_set_atom_position
2618
2619!
2620!> @brief Set plane-wave coefficients of a periodic function.
2621!> @param [in] handler Ground state handler.
2622!> @param [in] label Label of the function.
2623!> @param [in] pw_coeffs Local array of plane-wave coefficients.
2624!> @param [in] transform_to_rg True if function has to be transformed to real-space grid.
2625!> @param [in] ngv Local number of G-vectors.
2626!> @param [in] gvl List of G-vectors in lattice coordinates (Miller indices).
2627!> @param [in] comm MPI communicator used in distribution of G-vectors
2628!> @param [out] error_code Error code.
2629subroutine sirius_set_pw_coeffs(handler,label,pw_coeffs,transform_to_rg,ngv,gvl,&
2630&comm,error_code)
2631implicit none
2632!
2633type(sirius_ground_state_handler), target, intent(in) :: handler
2634character(*), target, intent(in) :: label
2635complex(8), target, intent(in) :: pw_coeffs(:)
2636logical, optional, target, intent(in) :: transform_to_rg
2637integer, optional, target, intent(in) :: ngv
2638integer, optional, target, intent(in) :: gvl(:,:)
2639integer, optional, target, intent(in) :: comm
2640integer, optional, target, intent(out) :: error_code
2641!
2642type(c_ptr) :: handler_ptr
2643type(c_ptr) :: label_ptr
2644character(C_CHAR), target, allocatable :: label_c_type(:)
2645type(c_ptr) :: pw_coeffs_ptr
2646type(c_ptr) :: transform_to_rg_ptr
2647logical(C_BOOL), target :: transform_to_rg_c_type
2648type(c_ptr) :: ngv_ptr
2649type(c_ptr) :: gvl_ptr
2650type(c_ptr) :: comm_ptr
2651type(c_ptr) :: error_code_ptr
2652!
2653interface
2654subroutine sirius_set_pw_coeffs_aux(handler,label,pw_coeffs,transform_to_rg,ngv,&
2655&gvl,comm,error_code)&
2656&bind(C, name="sirius_set_pw_coeffs")
2657use, intrinsic :: iso_c_binding
2658type(c_ptr), value :: handler
2659type(c_ptr), value :: label
2660type(c_ptr), value :: pw_coeffs
2661type(c_ptr), value :: transform_to_rg
2662type(c_ptr), value :: ngv
2663type(c_ptr), value :: gvl
2664type(c_ptr), value :: comm
2665type(c_ptr), value :: error_code
2666end subroutine
2667end interface
2668!
2669handler_ptr = c_null_ptr
2670handler_ptr = c_loc(handler%handler_ptr_)
2671label_ptr = c_null_ptr
2672allocate(label_c_type(len(label)+1))
2673label_c_type = string_f2c(label)
2674label_ptr = c_loc(label_c_type)
2675pw_coeffs_ptr = c_null_ptr
2676pw_coeffs_ptr = c_loc(pw_coeffs)
2677transform_to_rg_ptr = c_null_ptr
2678if (present(transform_to_rg)) then
2679transform_to_rg_c_type = transform_to_rg
2680transform_to_rg_ptr = c_loc(transform_to_rg_c_type)
2681endif
2682ngv_ptr = c_null_ptr
2683if (present(ngv)) then
2684ngv_ptr = c_loc(ngv)
2685endif
2686gvl_ptr = c_null_ptr
2687if (present(gvl)) then
2688gvl_ptr = c_loc(gvl)
2689endif
2690comm_ptr = c_null_ptr
2691if (present(comm)) then
2692comm_ptr = c_loc(comm)
2693endif
2694error_code_ptr = c_null_ptr
2695if (present(error_code)) then
2696error_code_ptr = c_loc(error_code)
2697endif
2698call sirius_set_pw_coeffs_aux(handler_ptr,label_ptr,pw_coeffs_ptr,transform_to_rg_ptr,&
2699&ngv_ptr,gvl_ptr,comm_ptr,error_code_ptr)
2700deallocate(label_c_type)
2701if (present(transform_to_rg)) then
2702endif
2703end subroutine sirius_set_pw_coeffs
2704
2705!
2706!> @brief Get plane-wave coefficients of a periodic function.
2707!> @param [in] handler Ground state handler.
2708!> @param [in] label Label of the function.
2709!> @param [in] pw_coeffs Local array of plane-wave coefficients.
2710!> @param [in] ngv Local number of G-vectors.
2711!> @param [in] gvl List of G-vectors in lattice coordinates (Miller indices).
2712!> @param [in] comm MPI communicator used in distribution of G-vectors
2713!> @param [out] error_code Error code.
2714subroutine sirius_get_pw_coeffs(handler,label,pw_coeffs,ngv,gvl,comm,error_code)
2715implicit none
2716!
2717type(sirius_ground_state_handler), target, intent(in) :: handler
2718character(*), target, intent(in) :: label
2719complex(8), target, intent(in) :: pw_coeffs(:)
2720integer, optional, target, intent(in) :: ngv
2721integer, optional, target, intent(in) :: gvl(:,:)
2722integer, optional, target, intent(in) :: comm
2723integer, optional, target, intent(out) :: error_code
2724!
2725type(c_ptr) :: handler_ptr
2726type(c_ptr) :: label_ptr
2727character(C_CHAR), target, allocatable :: label_c_type(:)
2728type(c_ptr) :: pw_coeffs_ptr
2729type(c_ptr) :: ngv_ptr
2730type(c_ptr) :: gvl_ptr
2731type(c_ptr) :: comm_ptr
2732type(c_ptr) :: error_code_ptr
2733!
2734interface
2735subroutine sirius_get_pw_coeffs_aux(handler,label,pw_coeffs,ngv,gvl,comm,error_code)&
2736&bind(C, name="sirius_get_pw_coeffs")
2737use, intrinsic :: iso_c_binding
2738type(c_ptr), value :: handler
2739type(c_ptr), value :: label
2740type(c_ptr), value :: pw_coeffs
2741type(c_ptr), value :: ngv
2742type(c_ptr), value :: gvl
2743type(c_ptr), value :: comm
2744type(c_ptr), value :: error_code
2745end subroutine
2746end interface
2747!
2748handler_ptr = c_null_ptr
2749handler_ptr = c_loc(handler%handler_ptr_)
2750label_ptr = c_null_ptr
2751allocate(label_c_type(len(label)+1))
2752label_c_type = string_f2c(label)
2753label_ptr = c_loc(label_c_type)
2754pw_coeffs_ptr = c_null_ptr
2755pw_coeffs_ptr = c_loc(pw_coeffs)
2756ngv_ptr = c_null_ptr
2757if (present(ngv)) then
2758ngv_ptr = c_loc(ngv)
2759endif
2760gvl_ptr = c_null_ptr
2761if (present(gvl)) then
2762gvl_ptr = c_loc(gvl)
2763endif
2764comm_ptr = c_null_ptr
2765if (present(comm)) then
2766comm_ptr = c_loc(comm)
2767endif
2768error_code_ptr = c_null_ptr
2769if (present(error_code)) then
2770error_code_ptr = c_loc(error_code)
2771endif
2772call sirius_get_pw_coeffs_aux(handler_ptr,label_ptr,pw_coeffs_ptr,ngv_ptr,gvl_ptr,&
2773&comm_ptr,error_code_ptr)
2774deallocate(label_c_type)
2775end subroutine sirius_get_pw_coeffs
2776
2777!
2778!> @brief Initialize the subspace of wave-functions.
2779!> @param [in] gs_handler Ground state handler.
2780!> @param [in] ks_handler K-point set handler.
2781!> @param [out] error_code Error code.
2782subroutine sirius_initialize_subspace(gs_handler,ks_handler,error_code)
2783implicit none
2784!
2785type(sirius_ground_state_handler), target, intent(in) :: gs_handler
2786type(sirius_kpoint_set_handler), target, intent(in) :: ks_handler
2787integer, optional, target, intent(out) :: error_code
2788!
2789type(c_ptr) :: gs_handler_ptr
2790type(c_ptr) :: ks_handler_ptr
2791type(c_ptr) :: error_code_ptr
2792!
2793interface
2794subroutine sirius_initialize_subspace_aux(gs_handler,ks_handler,error_code)&
2795&bind(C, name="sirius_initialize_subspace")
2796use, intrinsic :: iso_c_binding
2797type(c_ptr), value :: gs_handler
2798type(c_ptr), value :: ks_handler
2799type(c_ptr), value :: error_code
2800end subroutine
2801end interface
2802!
2803gs_handler_ptr = c_null_ptr
2804gs_handler_ptr = c_loc(gs_handler%handler_ptr_)
2805ks_handler_ptr = c_null_ptr
2806ks_handler_ptr = c_loc(ks_handler%handler_ptr_)
2807error_code_ptr = c_null_ptr
2808if (present(error_code)) then
2809error_code_ptr = c_loc(error_code)
2810endif
2811call sirius_initialize_subspace_aux(gs_handler_ptr,ks_handler_ptr,error_code_ptr)
2812end subroutine sirius_initialize_subspace
2813
2814!
2815!> @brief Find eigen-states of the Hamiltonian
2816!> @param [in] gs_handler Ground state handler.
2817!> @param [in] ks_handler K-point set handler.
2818!> @param [in] precompute_pw Generate plane-wave coefficients of the potential
2819!> @param [in] precompute_rf Generate radial functions
2820!> @param [in] precompute_ri Generate radial integrals
2821!> @param [in] iter_solver_tol Iterative solver tolerance.
2822!> @param [out] error_code Error code.
2823subroutine sirius_find_eigen_states(gs_handler,ks_handler,precompute_pw,precompute_rf,&
2824&precompute_ri,iter_solver_tol,error_code)
2825implicit none
2826!
2827type(sirius_ground_state_handler), target, intent(in) :: gs_handler
2828type(sirius_kpoint_set_handler), target, intent(in) :: ks_handler
2829logical, optional, target, intent(in) :: precompute_pw
2830logical, optional, target, intent(in) :: precompute_rf
2831logical, optional, target, intent(in) :: precompute_ri
2832real(8), optional, target, intent(in) :: iter_solver_tol
2833integer, optional, target, intent(out) :: error_code
2834!
2835type(c_ptr) :: gs_handler_ptr
2836type(c_ptr) :: ks_handler_ptr
2837type(c_ptr) :: precompute_pw_ptr
2838logical(C_BOOL), target :: precompute_pw_c_type
2839type(c_ptr) :: precompute_rf_ptr
2840logical(C_BOOL), target :: precompute_rf_c_type
2841type(c_ptr) :: precompute_ri_ptr
2842logical(C_BOOL), target :: precompute_ri_c_type
2843type(c_ptr) :: iter_solver_tol_ptr
2844type(c_ptr) :: error_code_ptr
2845!
2846interface
2847subroutine sirius_find_eigen_states_aux(gs_handler,ks_handler,precompute_pw,precompute_rf,&
2848&precompute_ri,iter_solver_tol,error_code)&
2849&bind(C, name="sirius_find_eigen_states")
2850use, intrinsic :: iso_c_binding
2851type(c_ptr), value :: gs_handler
2852type(c_ptr), value :: ks_handler
2853type(c_ptr), value :: precompute_pw
2854type(c_ptr), value :: precompute_rf
2855type(c_ptr), value :: precompute_ri
2856type(c_ptr), value :: iter_solver_tol
2857type(c_ptr), value :: error_code
2858end subroutine
2859end interface
2860!
2861gs_handler_ptr = c_null_ptr
2862gs_handler_ptr = c_loc(gs_handler%handler_ptr_)
2863ks_handler_ptr = c_null_ptr
2864ks_handler_ptr = c_loc(ks_handler%handler_ptr_)
2865precompute_pw_ptr = c_null_ptr
2866if (present(precompute_pw)) then
2867precompute_pw_c_type = precompute_pw
2868precompute_pw_ptr = c_loc(precompute_pw_c_type)
2869endif
2870precompute_rf_ptr = c_null_ptr
2871if (present(precompute_rf)) then
2872precompute_rf_c_type = precompute_rf
2873precompute_rf_ptr = c_loc(precompute_rf_c_type)
2874endif
2875precompute_ri_ptr = c_null_ptr
2876if (present(precompute_ri)) then
2877precompute_ri_c_type = precompute_ri
2878precompute_ri_ptr = c_loc(precompute_ri_c_type)
2879endif
2880iter_solver_tol_ptr = c_null_ptr
2881if (present(iter_solver_tol)) then
2882iter_solver_tol_ptr = c_loc(iter_solver_tol)
2883endif
2884error_code_ptr = c_null_ptr
2885if (present(error_code)) then
2886error_code_ptr = c_loc(error_code)
2887endif
2888call sirius_find_eigen_states_aux(gs_handler_ptr,ks_handler_ptr,precompute_pw_ptr,&
2889&precompute_rf_ptr,precompute_ri_ptr,iter_solver_tol_ptr,error_code_ptr)
2890if (present(precompute_pw)) then
2891endif
2892if (present(precompute_rf)) then
2893endif
2894if (present(precompute_ri)) then
2895endif
2896end subroutine sirius_find_eigen_states
2897
2898!
2899!> @brief Generate initial density.
2900!> @param [in] handler Ground state handler.
2901!> @param [out] error_code Error code.
2902subroutine sirius_generate_initial_density(handler,error_code)
2903implicit none
2904!
2905type(sirius_ground_state_handler), target, intent(in) :: handler
2906integer, optional, target, intent(out) :: error_code
2907!
2908type(c_ptr) :: handler_ptr
2909type(c_ptr) :: error_code_ptr
2910!
2911interface
2912subroutine sirius_generate_initial_density_aux(handler,error_code)&
2913&bind(C, name="sirius_generate_initial_density")
2914use, intrinsic :: iso_c_binding
2915type(c_ptr), value :: handler
2916type(c_ptr), value :: error_code
2917end subroutine
2918end interface
2919!
2920handler_ptr = c_null_ptr
2921handler_ptr = c_loc(handler%handler_ptr_)
2922error_code_ptr = c_null_ptr
2923if (present(error_code)) then
2924error_code_ptr = c_loc(error_code)
2925endif
2926call sirius_generate_initial_density_aux(handler_ptr,error_code_ptr)
2928
2929!
2930!> @brief Generate effective potential and magnetic field.
2931!> @param [in] handler Ground state handler.
2932!> @param [out] error_code Error code.
2933subroutine sirius_generate_effective_potential(handler,error_code)
2934implicit none
2935!
2936type(sirius_ground_state_handler), target, intent(in) :: handler
2937integer, optional, target, intent(out) :: error_code
2938!
2939type(c_ptr) :: handler_ptr
2940type(c_ptr) :: error_code_ptr
2941!
2942interface
2943subroutine sirius_generate_effective_potential_aux(handler,error_code)&
2944&bind(C, name="sirius_generate_effective_potential")
2945use, intrinsic :: iso_c_binding
2946type(c_ptr), value :: handler
2947type(c_ptr), value :: error_code
2948end subroutine
2949end interface
2950!
2951handler_ptr = c_null_ptr
2952handler_ptr = c_loc(handler%handler_ptr_)
2953error_code_ptr = c_null_ptr
2954if (present(error_code)) then
2955error_code_ptr = c_loc(error_code)
2956endif
2957call sirius_generate_effective_potential_aux(handler_ptr,error_code_ptr)
2959
2960!
2961!> @brief Generate charge density and magnetization.
2962!> @param [in] gs_handler Ground state handler.
2963!> @param [in] add_core Add core charge density in the muffin-tins.
2964!> @param [in] transform_to_rg If true, density and magnetization are transformed to real-space grid.
2965!> @param [in] paw_only it true, only local PAW density is generated
2966!> @param [out] error_code Error code.
2967subroutine sirius_generate_density(gs_handler,add_core,transform_to_rg,paw_only,&
2968&error_code)
2969implicit none
2970!
2971type(sirius_ground_state_handler), target, intent(in) :: gs_handler
2972logical, optional, target, intent(in) :: add_core
2973logical, optional, target, intent(in) :: transform_to_rg
2974logical, optional, target, intent(in) :: paw_only
2975integer, optional, target, intent(out) :: error_code
2976!
2977type(c_ptr) :: gs_handler_ptr
2978type(c_ptr) :: add_core_ptr
2979logical(C_BOOL), target :: add_core_c_type
2980type(c_ptr) :: transform_to_rg_ptr
2981logical(C_BOOL), target :: transform_to_rg_c_type
2982type(c_ptr) :: paw_only_ptr
2983logical(C_BOOL), target :: paw_only_c_type
2984type(c_ptr) :: error_code_ptr
2985!
2986interface
2987subroutine sirius_generate_density_aux(gs_handler,add_core,transform_to_rg,paw_only,&
2988&error_code)&
2989&bind(C, name="sirius_generate_density")
2990use, intrinsic :: iso_c_binding
2991type(c_ptr), value :: gs_handler
2992type(c_ptr), value :: add_core
2993type(c_ptr), value :: transform_to_rg
2994type(c_ptr), value :: paw_only
2995type(c_ptr), value :: error_code
2996end subroutine
2997end interface
2998!
2999gs_handler_ptr = c_null_ptr
3000gs_handler_ptr = c_loc(gs_handler%handler_ptr_)
3001add_core_ptr = c_null_ptr
3002if (present(add_core)) then
3003add_core_c_type = add_core
3004add_core_ptr = c_loc(add_core_c_type)
3005endif
3006transform_to_rg_ptr = c_null_ptr
3007if (present(transform_to_rg)) then
3008transform_to_rg_c_type = transform_to_rg
3009transform_to_rg_ptr = c_loc(transform_to_rg_c_type)
3010endif
3011paw_only_ptr = c_null_ptr
3012if (present(paw_only)) then
3013paw_only_c_type = paw_only
3014paw_only_ptr = c_loc(paw_only_c_type)
3015endif
3016error_code_ptr = c_null_ptr
3017if (present(error_code)) then
3018error_code_ptr = c_loc(error_code)
3019endif
3020call sirius_generate_density_aux(gs_handler_ptr,add_core_ptr,transform_to_rg_ptr,&
3021&paw_only_ptr,error_code_ptr)
3022if (present(add_core)) then
3023endif
3024if (present(transform_to_rg)) then
3025endif
3026if (present(paw_only)) then
3027endif
3028end subroutine sirius_generate_density
3029
3030!
3031!> @brief Set band occupancies.
3032!> @param [in] ks_handler K-point set handler.
3033!> @param [in] ik Global index of k-point.
3034!> @param [in] ispn Spin component index.
3035!> @param [in] band_occupancies Array of band occupancies.
3036!> @param [out] error_code Error code.
3037subroutine sirius_set_band_occupancies(ks_handler,ik,ispn,band_occupancies,error_code)
3038implicit none
3039!
3040type(sirius_kpoint_set_handler), target, intent(in) :: ks_handler
3041integer, target, intent(in) :: ik
3042integer, target, intent(in) :: ispn
3043real(8), target, intent(in) :: band_occupancies(:)
3044integer, optional, target, intent(out) :: error_code
3045!
3046type(c_ptr) :: ks_handler_ptr
3047type(c_ptr) :: ik_ptr
3048type(c_ptr) :: ispn_ptr
3049type(c_ptr) :: band_occupancies_ptr
3050type(c_ptr) :: error_code_ptr
3051!
3052interface
3053subroutine sirius_set_band_occupancies_aux(ks_handler,ik,ispn,band_occupancies,error_code)&
3054&bind(C, name="sirius_set_band_occupancies")
3055use, intrinsic :: iso_c_binding
3056type(c_ptr), value :: ks_handler
3057type(c_ptr), value :: ik
3058type(c_ptr), value :: ispn
3059type(c_ptr), value :: band_occupancies
3060type(c_ptr), value :: error_code
3061end subroutine
3062end interface
3063!
3064ks_handler_ptr = c_null_ptr
3065ks_handler_ptr = c_loc(ks_handler%handler_ptr_)
3066ik_ptr = c_null_ptr
3067ik_ptr = c_loc(ik)
3068ispn_ptr = c_null_ptr
3069ispn_ptr = c_loc(ispn)
3070band_occupancies_ptr = c_null_ptr
3071band_occupancies_ptr = c_loc(band_occupancies)
3072error_code_ptr = c_null_ptr
3073if (present(error_code)) then
3074error_code_ptr = c_loc(error_code)
3075endif
3076call sirius_set_band_occupancies_aux(ks_handler_ptr,ik_ptr,ispn_ptr,band_occupancies_ptr,&
3077&error_code_ptr)
3078end subroutine sirius_set_band_occupancies
3079
3080!
3081!> @brief Set band occupancies.
3082!> @param [in] ks_handler K-point set handler.
3083!> @param [in] ik Global index of k-point.
3084!> @param [in] ispn Spin component.
3085!> @param [out] band_occupancies Array of band occupancies.
3086!> @param [out] error_code Error code.
3087subroutine sirius_get_band_occupancies(ks_handler,ik,ispn,band_occupancies,error_code)
3088implicit none
3089!
3090type(sirius_kpoint_set_handler), target, intent(in) :: ks_handler
3091integer, target, intent(in) :: ik
3092integer, target, intent(in) :: ispn
3093real(8), target, intent(out) :: band_occupancies(:)
3094integer, optional, target, intent(out) :: error_code
3095!
3096type(c_ptr) :: ks_handler_ptr
3097type(c_ptr) :: ik_ptr
3098type(c_ptr) :: ispn_ptr
3099type(c_ptr) :: band_occupancies_ptr
3100type(c_ptr) :: error_code_ptr
3101!
3102interface
3103subroutine sirius_get_band_occupancies_aux(ks_handler,ik,ispn,band_occupancies,error_code)&
3104&bind(C, name="sirius_get_band_occupancies")
3105use, intrinsic :: iso_c_binding
3106type(c_ptr), value :: ks_handler
3107type(c_ptr), value :: ik
3108type(c_ptr), value :: ispn
3109type(c_ptr), value :: band_occupancies
3110type(c_ptr), value :: error_code
3111end subroutine
3112end interface
3113!
3114ks_handler_ptr = c_null_ptr
3115ks_handler_ptr = c_loc(ks_handler%handler_ptr_)
3116ik_ptr = c_null_ptr
3117ik_ptr = c_loc(ik)
3118ispn_ptr = c_null_ptr
3119ispn_ptr = c_loc(ispn)
3120band_occupancies_ptr = c_null_ptr
3121band_occupancies_ptr = c_loc(band_occupancies)
3122error_code_ptr = c_null_ptr
3123if (present(error_code)) then
3124error_code_ptr = c_loc(error_code)
3125endif
3126call sirius_get_band_occupancies_aux(ks_handler_ptr,ik_ptr,ispn_ptr,band_occupancies_ptr,&
3127&error_code_ptr)
3128end subroutine sirius_get_band_occupancies
3129
3130!
3131!> @brief Get band energies.
3132!> @param [in] ks_handler K-point set handler.
3133!> @param [in] ik Global index of k-point.
3134!> @param [in] ispn Spin component.
3135!> @param [out] band_energies Array of band energies.
3136!> @param [out] error_code Error code.
3137subroutine sirius_get_band_energies(ks_handler,ik,ispn,band_energies,error_code)
3138implicit none
3139!
3140type(sirius_kpoint_set_handler), target, intent(in) :: ks_handler
3141integer, target, intent(in) :: ik
3142integer, target, intent(in) :: ispn
3143real(8), target, intent(out) :: band_energies(:)
3144integer, optional, target, intent(out) :: error_code
3145!
3146type(c_ptr) :: ks_handler_ptr
3147type(c_ptr) :: ik_ptr
3148type(c_ptr) :: ispn_ptr
3149type(c_ptr) :: band_energies_ptr
3150type(c_ptr) :: error_code_ptr
3151!
3152interface
3153subroutine sirius_get_band_energies_aux(ks_handler,ik,ispn,band_energies,error_code)&
3154&bind(C, name="sirius_get_band_energies")
3155use, intrinsic :: iso_c_binding
3156type(c_ptr), value :: ks_handler
3157type(c_ptr), value :: ik
3158type(c_ptr), value :: ispn
3159type(c_ptr), value :: band_energies
3160type(c_ptr), value :: error_code
3161end subroutine
3162end interface
3163!
3164ks_handler_ptr = c_null_ptr
3165ks_handler_ptr = c_loc(ks_handler%handler_ptr_)
3166ik_ptr = c_null_ptr
3167ik_ptr = c_loc(ik)
3168ispn_ptr = c_null_ptr
3169ispn_ptr = c_loc(ispn)
3170band_energies_ptr = c_null_ptr
3171band_energies_ptr = c_loc(band_energies)
3172error_code_ptr = c_null_ptr
3173if (present(error_code)) then
3174error_code_ptr = c_loc(error_code)
3175endif
3176call sirius_get_band_energies_aux(ks_handler_ptr,ik_ptr,ispn_ptr,band_energies_ptr,&
3177&error_code_ptr)
3178end subroutine sirius_get_band_energies
3179
3180!
3181!> @brief Get one of the total energy components.
3182!> @param [in] handler DFT ground state handler.
3183!> @param [in] label Label of the energy component to get.
3184!> @param [out] energy Total energy component.
3185!> @param [out] error_code Error code.
3186subroutine sirius_get_energy(handler,label,energy,error_code)
3187implicit none
3188!
3189type(sirius_ground_state_handler), target, intent(in) :: handler
3190character(*), target, intent(in) :: label
3191real(8), target, intent(out) :: energy
3192integer, optional, target, intent(out) :: error_code
3193!
3194type(c_ptr) :: handler_ptr
3195type(c_ptr) :: label_ptr
3196character(C_CHAR), target, allocatable :: label_c_type(:)
3197type(c_ptr) :: energy_ptr
3198type(c_ptr) :: error_code_ptr
3199!
3200interface
3201subroutine sirius_get_energy_aux(handler,label,energy,error_code)&
3202&bind(C, name="sirius_get_energy")
3203use, intrinsic :: iso_c_binding
3204type(c_ptr), value :: handler
3205type(c_ptr), value :: label
3206type(c_ptr), value :: energy
3207type(c_ptr), value :: error_code
3208end subroutine
3209end interface
3210!
3211handler_ptr = c_null_ptr
3212handler_ptr = c_loc(handler%handler_ptr_)
3213label_ptr = c_null_ptr
3214allocate(label_c_type(len(label)+1))
3215label_c_type = string_f2c(label)
3216label_ptr = c_loc(label_c_type)
3217energy_ptr = c_null_ptr
3218energy_ptr = c_loc(energy)
3219error_code_ptr = c_null_ptr
3220if (present(error_code)) then
3221error_code_ptr = c_loc(error_code)
3222endif
3223call sirius_get_energy_aux(handler_ptr,label_ptr,energy_ptr,error_code_ptr)
3224deallocate(label_c_type)
3225end subroutine sirius_get_energy
3226
3227!
3228!> @brief Get one of the total force components.
3229!> @param [in] handler DFT ground state handler.
3230!> @param [in] label Label of the force component to get.
3231!> @param [out] forces Total force component for each atom.
3232!> @param [out] error_code Error code.
3233subroutine sirius_get_forces(handler,label,forces,error_code)
3234implicit none
3235!
3236type(sirius_ground_state_handler), target, intent(in) :: handler
3237character(*), target, intent(in) :: label
3238real(8), target, intent(out) :: forces(:,:)
3239integer, optional, target, intent(out) :: error_code
3240!
3241type(c_ptr) :: handler_ptr
3242type(c_ptr) :: label_ptr
3243character(C_CHAR), target, allocatable :: label_c_type(:)
3244type(c_ptr) :: forces_ptr
3245type(c_ptr) :: error_code_ptr
3246!
3247interface
3248subroutine sirius_get_forces_aux(handler,label,forces,error_code)&
3249&bind(C, name="sirius_get_forces")
3250use, intrinsic :: iso_c_binding
3251type(c_ptr), value :: handler
3252type(c_ptr), value :: label
3253type(c_ptr), value :: forces
3254type(c_ptr), value :: error_code
3255end subroutine
3256end interface
3257!
3258handler_ptr = c_null_ptr
3259handler_ptr = c_loc(handler%handler_ptr_)
3260label_ptr = c_null_ptr
3261allocate(label_c_type(len(label)+1))
3262label_c_type = string_f2c(label)
3263label_ptr = c_loc(label_c_type)
3264forces_ptr = c_null_ptr
3265forces_ptr = c_loc(forces)
3266error_code_ptr = c_null_ptr
3267if (present(error_code)) then
3268error_code_ptr = c_loc(error_code)
3269endif
3270call sirius_get_forces_aux(handler_ptr,label_ptr,forces_ptr,error_code_ptr)
3271deallocate(label_c_type)
3272end subroutine sirius_get_forces
3273
3274!
3275!> @brief Get one of the stress tensor components.
3276!> @param [in] handler DFT ground state handler.
3277!> @param [in] label Label of the stress tensor component to get.
3278!> @param [out] stress_tensor Component of the total stress tensor.
3279!> @param [out] error_code Error code.
3280subroutine sirius_get_stress_tensor(handler,label,stress_tensor,error_code)
3281implicit none
3282!
3283type(sirius_ground_state_handler), target, intent(in) :: handler
3284character(*), target, intent(in) :: label
3285real(8), target, intent(out) :: stress_tensor(3, 3)
3286integer, optional, target, intent(out) :: error_code
3287!
3288type(c_ptr) :: handler_ptr
3289type(c_ptr) :: label_ptr
3290character(C_CHAR), target, allocatable :: label_c_type(:)
3291type(c_ptr) :: stress_tensor_ptr
3292type(c_ptr) :: error_code_ptr
3293!
3294interface
3295subroutine sirius_get_stress_tensor_aux(handler,label,stress_tensor,error_code)&
3296&bind(C, name="sirius_get_stress_tensor")
3297use, intrinsic :: iso_c_binding
3298type(c_ptr), value :: handler
3299type(c_ptr), value :: label
3300type(c_ptr), value :: stress_tensor
3301type(c_ptr), value :: error_code
3302end subroutine
3303end interface
3304!
3305handler_ptr = c_null_ptr
3306handler_ptr = c_loc(handler%handler_ptr_)
3307label_ptr = c_null_ptr
3308allocate(label_c_type(len(label)+1))
3309label_c_type = string_f2c(label)
3310label_ptr = c_loc(label_c_type)
3311stress_tensor_ptr = c_null_ptr
3312stress_tensor_ptr = c_loc(stress_tensor)
3313error_code_ptr = c_null_ptr
3314if (present(error_code)) then
3315error_code_ptr = c_loc(error_code)
3316endif
3317call sirius_get_stress_tensor_aux(handler_ptr,label_ptr,stress_tensor_ptr,error_code_ptr)
3318deallocate(label_c_type)
3319end subroutine sirius_get_stress_tensor
3320
3321!
3322!> @brief Get the number of beta-projectors for an atom type.
3323!> @param [in] handler Simulation context handler.
3324!> @param [in] label Atom type label.
3325!> @param [out] num_bp Number of beta projectors for each atom type.
3326!> @param [out] error_code Error code.
3327subroutine sirius_get_num_beta_projectors(handler,label,num_bp,error_code)
3328implicit none
3329!
3330type(sirius_context_handler), target, intent(in) :: handler
3331character(*), target, intent(in) :: label
3332integer, target, intent(out) :: num_bp
3333integer, optional, target, intent(out) :: error_code
3334!
3335type(c_ptr) :: handler_ptr
3336type(c_ptr) :: label_ptr
3337character(C_CHAR), target, allocatable :: label_c_type(:)
3338type(c_ptr) :: num_bp_ptr
3339type(c_ptr) :: error_code_ptr
3340!
3341interface
3342subroutine sirius_get_num_beta_projectors_aux(handler,label,num_bp,error_code)&
3343&bind(C, name="sirius_get_num_beta_projectors")
3344use, intrinsic :: iso_c_binding
3345type(c_ptr), value :: handler
3346type(c_ptr), value :: label
3347type(c_ptr), value :: num_bp
3348type(c_ptr), value :: error_code
3349end subroutine
3350end interface
3351!
3352handler_ptr = c_null_ptr
3353handler_ptr = c_loc(handler%handler_ptr_)
3354label_ptr = c_null_ptr
3355allocate(label_c_type(len(label)+1))
3356label_c_type = string_f2c(label)
3357label_ptr = c_loc(label_c_type)
3358num_bp_ptr = c_null_ptr
3359num_bp_ptr = c_loc(num_bp)
3360error_code_ptr = c_null_ptr
3361if (present(error_code)) then
3362error_code_ptr = c_loc(error_code)
3363endif
3364call sirius_get_num_beta_projectors_aux(handler_ptr,label_ptr,num_bp_ptr,error_code_ptr)
3365deallocate(label_c_type)
3366end subroutine sirius_get_num_beta_projectors
3367
3368!
3369!> @brief Get wave-functions.
3370!> @param [in] ks_handler K-point set handler.
3371!> @param [in] vkl Latttice coordinates of the k-point.
3372!> @param [in] spin Spin index in case of collinear magnetism.
3373!> @param [in] num_gvec_loc Local number of G-vectors for a k-point.
3374!> @param [in] gvec_loc List of G-vectors.
3375!> @param [out] evec Wave-functions.
3376!> @param [in] ld Leading dimension of evec array.
3377!> @param [in] num_spin_comp Number of spin components.
3378!> @param [out] error_code Error code
3379subroutine sirius_get_wave_functions(ks_handler,vkl,spin,num_gvec_loc,gvec_loc,evec,&
3380&ld,num_spin_comp,error_code)
3381implicit none
3382!
3383type(sirius_kpoint_set_handler), target, intent(in) :: ks_handler
3384real(8), optional, target, intent(in) :: vkl(3)
3385integer, optional, target, intent(in) :: spin
3386integer, optional, target, intent(in) :: num_gvec_loc
3387integer, optional, target, intent(in) :: gvec_loc(:,:)
3388complex(8), optional, target, intent(out) :: evec(:,:)
3389integer, optional, target, intent(in) :: ld
3390integer, optional, target, intent(in) :: num_spin_comp
3391integer, optional, target, intent(out) :: error_code
3392!
3393type(c_ptr) :: ks_handler_ptr
3394type(c_ptr) :: vkl_ptr
3395type(c_ptr) :: spin_ptr
3396type(c_ptr) :: num_gvec_loc_ptr
3397type(c_ptr) :: gvec_loc_ptr
3398type(c_ptr) :: evec_ptr
3399type(c_ptr) :: ld_ptr
3400type(c_ptr) :: num_spin_comp_ptr
3401type(c_ptr) :: error_code_ptr
3402!
3403interface
3404subroutine sirius_get_wave_functions_aux(ks_handler,vkl,spin,num_gvec_loc,gvec_loc,&
3405&evec,ld,num_spin_comp,error_code)&
3406&bind(C, name="sirius_get_wave_functions")
3407use, intrinsic :: iso_c_binding
3408type(c_ptr), value :: ks_handler
3409type(c_ptr), value :: vkl
3410type(c_ptr), value :: spin
3411type(c_ptr), value :: num_gvec_loc
3412type(c_ptr), value :: gvec_loc
3413type(c_ptr), value :: evec
3414type(c_ptr), value :: ld
3415type(c_ptr), value :: num_spin_comp
3416type(c_ptr), value :: error_code
3417end subroutine
3418end interface
3419!
3420ks_handler_ptr = c_null_ptr
3421ks_handler_ptr = c_loc(ks_handler%handler_ptr_)
3422vkl_ptr = c_null_ptr
3423if (present(vkl)) then
3424vkl_ptr = c_loc(vkl)
3425endif
3426spin_ptr = c_null_ptr
3427if (present(spin)) then
3428spin_ptr = c_loc(spin)
3429endif
3430num_gvec_loc_ptr = c_null_ptr
3431if (present(num_gvec_loc)) then
3432num_gvec_loc_ptr = c_loc(num_gvec_loc)
3433endif
3434gvec_loc_ptr = c_null_ptr
3435if (present(gvec_loc)) then
3436gvec_loc_ptr = c_loc(gvec_loc)
3437endif
3438evec_ptr = c_null_ptr
3439if (present(evec)) then
3440evec_ptr = c_loc(evec)
3441endif
3442ld_ptr = c_null_ptr
3443if (present(ld)) then
3444ld_ptr = c_loc(ld)
3445endif
3446num_spin_comp_ptr = c_null_ptr
3447if (present(num_spin_comp)) then
3448num_spin_comp_ptr = c_loc(num_spin_comp)
3449endif
3450error_code_ptr = c_null_ptr
3451if (present(error_code)) then
3452error_code_ptr = c_loc(error_code)
3453endif
3454call sirius_get_wave_functions_aux(ks_handler_ptr,vkl_ptr,spin_ptr,num_gvec_loc_ptr,&
3455&gvec_loc_ptr,evec_ptr,ld_ptr,num_spin_comp_ptr,error_code_ptr)
3456end subroutine sirius_get_wave_functions
3457
3458!
3459!> @brief Add descriptor of the augmented wave radial function.
3460!> @param [in] handler Simulation context handler.
3461!> @param [in] label Atom type label.
3462!> @param [in] n Principal quantum number.
3463!> @param [in] l Orbital quantum number.
3464!> @param [in] enu Linearization energy.
3465!> @param [in] dme Order of energy derivative.
3466!> @param [in] auto_enu True if automatic search of linearization energy is allowed for this radial solution.
3467!> @param [out] error_code Error code
3468subroutine sirius_add_atom_type_aw_descriptor(handler,label,n,l,enu,dme,auto_enu,&
3469&error_code)
3470implicit none
3471!
3472type(sirius_context_handler), target, intent(in) :: handler
3473character(*), target, intent(in) :: label
3474integer, target, intent(in) :: n
3475integer, target, intent(in) :: l
3476real(8), target, intent(in) :: enu
3477integer, target, intent(in) :: dme
3478logical, target, intent(in) :: auto_enu
3479integer, optional, target, intent(out) :: error_code
3480!
3481type(c_ptr) :: handler_ptr
3482type(c_ptr) :: label_ptr
3483character(C_CHAR), target, allocatable :: label_c_type(:)
3484type(c_ptr) :: n_ptr
3485type(c_ptr) :: l_ptr
3486type(c_ptr) :: enu_ptr
3487type(c_ptr) :: dme_ptr
3488type(c_ptr) :: auto_enu_ptr
3489logical(C_BOOL), target :: auto_enu_c_type
3490type(c_ptr) :: error_code_ptr
3491!
3492interface
3493subroutine sirius_add_atom_type_aw_descriptor_aux(handler,label,n,l,enu,dme,auto_enu,&
3494&error_code)&
3495&bind(C, name="sirius_add_atom_type_aw_descriptor")
3496use, intrinsic :: iso_c_binding
3497type(c_ptr), value :: handler
3498type(c_ptr), value :: label
3499type(c_ptr), value :: n
3500type(c_ptr), value :: l
3501type(c_ptr), value :: enu
3502type(c_ptr), value :: dme
3503type(c_ptr), value :: auto_enu
3504type(c_ptr), value :: error_code
3505end subroutine
3506end interface
3507!
3508handler_ptr = c_null_ptr
3509handler_ptr = c_loc(handler%handler_ptr_)
3510label_ptr = c_null_ptr
3511allocate(label_c_type(len(label)+1))
3512label_c_type = string_f2c(label)
3513label_ptr = c_loc(label_c_type)
3514n_ptr = c_null_ptr
3515n_ptr = c_loc(n)
3516l_ptr = c_null_ptr
3517l_ptr = c_loc(l)
3518enu_ptr = c_null_ptr
3519enu_ptr = c_loc(enu)
3520dme_ptr = c_null_ptr
3521dme_ptr = c_loc(dme)
3522auto_enu_ptr = c_null_ptr
3523auto_enu_c_type = auto_enu
3524auto_enu_ptr = c_loc(auto_enu_c_type)
3525error_code_ptr = c_null_ptr
3526if (present(error_code)) then
3527error_code_ptr = c_loc(error_code)
3528endif
3529call sirius_add_atom_type_aw_descriptor_aux(handler_ptr,label_ptr,n_ptr,l_ptr,enu_ptr,&
3530&dme_ptr,auto_enu_ptr,error_code_ptr)
3531deallocate(label_c_type)
3533
3534!
3535!> @brief Add descriptor of the local orbital radial function.
3536!> @param [in] handler Simulation context handler.
3537!> @param [in] label Atom type label.
3538!> @param [in] ilo Index of the local orbital to which the descriptor is added.
3539!> @param [in] n Principal quantum number.
3540!> @param [in] l Orbital quantum number.
3541!> @param [in] enu Linearization energy.
3542!> @param [in] dme Order of energy derivative.
3543!> @param [in] auto_enu True if automatic search of linearization energy is allowed for this radial solution.
3544!> @param [out] error_code Error code
3545subroutine sirius_add_atom_type_lo_descriptor(handler,label,ilo,n,l,enu,dme,auto_enu,&
3546&error_code)
3547implicit none
3548!
3549type(sirius_context_handler), target, intent(in) :: handler
3550character(*), target, intent(in) :: label
3551integer, target, intent(in) :: ilo
3552integer, target, intent(in) :: n
3553integer, target, intent(in) :: l
3554real(8), target, intent(in) :: enu
3555integer, target, intent(in) :: dme
3556logical, target, intent(in) :: auto_enu
3557integer, optional, target, intent(out) :: error_code
3558!
3559type(c_ptr) :: handler_ptr
3560type(c_ptr) :: label_ptr
3561character(C_CHAR), target, allocatable :: label_c_type(:)
3562type(c_ptr) :: ilo_ptr
3563type(c_ptr) :: n_ptr
3564type(c_ptr) :: l_ptr
3565type(c_ptr) :: enu_ptr
3566type(c_ptr) :: dme_ptr
3567type(c_ptr) :: auto_enu_ptr
3568logical(C_BOOL), target :: auto_enu_c_type
3569type(c_ptr) :: error_code_ptr
3570!
3571interface
3572subroutine sirius_add_atom_type_lo_descriptor_aux(handler,label,ilo,n,l,enu,dme,&
3573&auto_enu,error_code)&
3574&bind(C, name="sirius_add_atom_type_lo_descriptor")
3575use, intrinsic :: iso_c_binding
3576type(c_ptr), value :: handler
3577type(c_ptr), value :: label
3578type(c_ptr), value :: ilo
3579type(c_ptr), value :: n
3580type(c_ptr), value :: l
3581type(c_ptr), value :: enu
3582type(c_ptr), value :: dme
3583type(c_ptr), value :: auto_enu
3584type(c_ptr), value :: error_code
3585end subroutine
3586end interface
3587!
3588handler_ptr = c_null_ptr
3589handler_ptr = c_loc(handler%handler_ptr_)
3590label_ptr = c_null_ptr
3591allocate(label_c_type(len(label)+1))
3592label_c_type = string_f2c(label)
3593label_ptr = c_loc(label_c_type)
3594ilo_ptr = c_null_ptr
3595ilo_ptr = c_loc(ilo)
3596n_ptr = c_null_ptr
3597n_ptr = c_loc(n)
3598l_ptr = c_null_ptr
3599l_ptr = c_loc(l)
3600enu_ptr = c_null_ptr
3601enu_ptr = c_loc(enu)
3602dme_ptr = c_null_ptr
3603dme_ptr = c_loc(dme)
3604auto_enu_ptr = c_null_ptr
3605auto_enu_c_type = auto_enu
3606auto_enu_ptr = c_loc(auto_enu_c_type)
3607error_code_ptr = c_null_ptr
3608if (present(error_code)) then
3609error_code_ptr = c_loc(error_code)
3610endif
3611call sirius_add_atom_type_lo_descriptor_aux(handler_ptr,label_ptr,ilo_ptr,n_ptr,&
3612&l_ptr,enu_ptr,dme_ptr,auto_enu_ptr,error_code_ptr)
3613deallocate(label_c_type)
3615
3616!
3617!> @brief Set configuration of atomic levels.
3618!> @param [in] handler Simulation context handler.
3619!> @param [in] label Atom type label.
3620!> @param [in] n Principal quantum number.
3621!> @param [in] l Orbital quantum number.
3622!> @param [in] k kappa (used in relativistic solver).
3623!> @param [in] occupancy Level occupancy.
3624!> @param [in] core Tru if this is a core state.
3625!> @param [out] error_code Error code
3626subroutine sirius_set_atom_type_configuration(handler,label,n,l,k,occupancy,core,&
3627&error_code)
3628implicit none
3629!
3630type(sirius_context_handler), target, intent(in) :: handler
3631character(*), target, intent(in) :: label
3632integer, target, intent(in) :: n
3633integer, target, intent(in) :: l
3634integer, target, intent(in) :: k
3635real(8), target, intent(in) :: occupancy
3636logical, target, intent(in) :: core
3637integer, optional, target, intent(out) :: error_code
3638!
3639type(c_ptr) :: handler_ptr
3640type(c_ptr) :: label_ptr
3641character(C_CHAR), target, allocatable :: label_c_type(:)
3642type(c_ptr) :: n_ptr
3643type(c_ptr) :: l_ptr
3644type(c_ptr) :: k_ptr
3645type(c_ptr) :: occupancy_ptr
3646type(c_ptr) :: core_ptr
3647logical(C_BOOL), target :: core_c_type
3648type(c_ptr) :: error_code_ptr
3649!
3650interface
3651subroutine sirius_set_atom_type_configuration_aux(handler,label,n,l,k,occupancy,&
3652&core,error_code)&
3653&bind(C, name="sirius_set_atom_type_configuration")
3654use, intrinsic :: iso_c_binding
3655type(c_ptr), value :: handler
3656type(c_ptr), value :: label
3657type(c_ptr), value :: n
3658type(c_ptr), value :: l
3659type(c_ptr), value :: k
3660type(c_ptr), value :: occupancy
3661type(c_ptr), value :: core
3662type(c_ptr), value :: error_code
3663end subroutine
3664end interface
3665!
3666handler_ptr = c_null_ptr
3667handler_ptr = c_loc(handler%handler_ptr_)
3668label_ptr = c_null_ptr
3669allocate(label_c_type(len(label)+1))
3670label_c_type = string_f2c(label)
3671label_ptr = c_loc(label_c_type)
3672n_ptr = c_null_ptr
3673n_ptr = c_loc(n)
3674l_ptr = c_null_ptr
3675l_ptr = c_loc(l)
3676k_ptr = c_null_ptr
3677k_ptr = c_loc(k)
3678occupancy_ptr = c_null_ptr
3679occupancy_ptr = c_loc(occupancy)
3680core_ptr = c_null_ptr
3681core_c_type = core
3682core_ptr = c_loc(core_c_type)
3683error_code_ptr = c_null_ptr
3684if (present(error_code)) then
3685error_code_ptr = c_loc(error_code)
3686endif
3687call sirius_set_atom_type_configuration_aux(handler_ptr,label_ptr,n_ptr,l_ptr,k_ptr,&
3688&occupancy_ptr,core_ptr,error_code_ptr)
3689deallocate(label_c_type)
3691
3692!
3693!> @brief Generate Coulomb potential by solving Poisson equation
3694!> @param [in] handler DFT ground state handler
3695!> @param [out] vh_el Electronic part of Hartree potential at each atom's origin.
3696!> @param [out] error_code Error code
3697subroutine sirius_generate_coulomb_potential(handler,vh_el,error_code)
3698implicit none
3699!
3700type(sirius_ground_state_handler), target, intent(in) :: handler
3701real(8), optional, target, intent(out) :: vh_el(:)
3702integer, optional, target, intent(out) :: error_code
3703!
3704type(c_ptr) :: handler_ptr
3705type(c_ptr) :: vh_el_ptr
3706type(c_ptr) :: error_code_ptr
3707!
3708interface
3709subroutine sirius_generate_coulomb_potential_aux(handler,vh_el,error_code)&
3710&bind(C, name="sirius_generate_coulomb_potential")
3711use, intrinsic :: iso_c_binding
3712type(c_ptr), value :: handler
3713type(c_ptr), value :: vh_el
3714type(c_ptr), value :: error_code
3715end subroutine
3716end interface
3717!
3718handler_ptr = c_null_ptr
3719handler_ptr = c_loc(handler%handler_ptr_)
3720vh_el_ptr = c_null_ptr
3721if (present(vh_el)) then
3722vh_el_ptr = c_loc(vh_el)
3723endif
3724error_code_ptr = c_null_ptr
3725if (present(error_code)) then
3726error_code_ptr = c_loc(error_code)
3727endif
3728call sirius_generate_coulomb_potential_aux(handler_ptr,vh_el_ptr,error_code_ptr)
3730
3731!
3732!> @brief Generate XC potential using LibXC
3733!> @param [in] handler Ground state handler
3734!> @param [out] error_code Error code
3735subroutine sirius_generate_xc_potential(handler,error_code)
3736implicit none
3737!
3738type(sirius_ground_state_handler), target, intent(in) :: handler
3739integer, optional, target, intent(out) :: error_code
3740!
3741type(c_ptr) :: handler_ptr
3742type(c_ptr) :: error_code_ptr
3743!
3744interface
3745subroutine sirius_generate_xc_potential_aux(handler,error_code)&
3746&bind(C, name="sirius_generate_xc_potential")
3747use, intrinsic :: iso_c_binding
3748type(c_ptr), value :: handler
3749type(c_ptr), value :: error_code
3750end subroutine
3751end interface
3752!
3753handler_ptr = c_null_ptr
3754handler_ptr = c_loc(handler%handler_ptr_)
3755error_code_ptr = c_null_ptr
3756if (present(error_code)) then
3757error_code_ptr = c_loc(error_code)
3758endif
3759call sirius_generate_xc_potential_aux(handler_ptr,error_code_ptr)
3760end subroutine sirius_generate_xc_potential
3761
3762!
3763!> @brief Get communicator which is used to split k-points
3764!> @param [in] handler Simulation context handler
3765!> @param [out] fcomm Fortran communicator
3766!> @param [out] error_code Error code
3767subroutine sirius_get_kpoint_inter_comm(handler,fcomm,error_code)
3768implicit none
3769!
3770type(sirius_context_handler), target, intent(in) :: handler
3771integer, target, intent(out) :: fcomm
3772integer, optional, target, intent(out) :: error_code
3773!
3774type(c_ptr) :: handler_ptr
3775type(c_ptr) :: fcomm_ptr
3776type(c_ptr) :: error_code_ptr
3777!
3778interface
3779subroutine sirius_get_kpoint_inter_comm_aux(handler,fcomm,error_code)&
3780&bind(C, name="sirius_get_kpoint_inter_comm")
3781use, intrinsic :: iso_c_binding
3782type(c_ptr), value :: handler
3783type(c_ptr), value :: fcomm
3784type(c_ptr), value :: error_code
3785end subroutine
3786end interface
3787!
3788handler_ptr = c_null_ptr
3789handler_ptr = c_loc(handler%handler_ptr_)
3790fcomm_ptr = c_null_ptr
3791fcomm_ptr = c_loc(fcomm)
3792error_code_ptr = c_null_ptr
3793if (present(error_code)) then
3794error_code_ptr = c_loc(error_code)
3795endif
3796call sirius_get_kpoint_inter_comm_aux(handler_ptr,fcomm_ptr,error_code_ptr)
3797end subroutine sirius_get_kpoint_inter_comm
3798
3799!
3800!> @brief Get communicator which is used to parallise band problem
3801!> @param [in] handler Simulation context handler
3802!> @param [out] fcomm Fortran communicator
3803!> @param [out] error_code Error code
3804subroutine sirius_get_kpoint_inner_comm(handler,fcomm,error_code)
3805implicit none
3806!
3807type(sirius_context_handler), target, intent(in) :: handler
3808integer, target, intent(out) :: fcomm
3809integer, optional, target, intent(out) :: error_code
3810!
3811type(c_ptr) :: handler_ptr
3812type(c_ptr) :: fcomm_ptr
3813type(c_ptr) :: error_code_ptr
3814!
3815interface
3816subroutine sirius_get_kpoint_inner_comm_aux(handler,fcomm,error_code)&
3817&bind(C, name="sirius_get_kpoint_inner_comm")
3818use, intrinsic :: iso_c_binding
3819type(c_ptr), value :: handler
3820type(c_ptr), value :: fcomm
3821type(c_ptr), value :: error_code
3822end subroutine
3823end interface
3824!
3825handler_ptr = c_null_ptr
3826handler_ptr = c_loc(handler%handler_ptr_)
3827fcomm_ptr = c_null_ptr
3828fcomm_ptr = c_loc(fcomm)
3829error_code_ptr = c_null_ptr
3830if (present(error_code)) then
3831error_code_ptr = c_loc(error_code)
3832endif
3833call sirius_get_kpoint_inner_comm_aux(handler_ptr,fcomm_ptr,error_code_ptr)
3834end subroutine sirius_get_kpoint_inner_comm
3835
3836!
3837!> @brief Get communicator which is used to parallise FFT
3838!> @param [in] handler Simulation context handler
3839!> @param [out] fcomm Fortran communicator
3840!> @param [out] error_code Error code
3841subroutine sirius_get_fft_comm(handler,fcomm,error_code)
3842implicit none
3843!
3844type(sirius_context_handler), target, intent(in) :: handler
3845integer, target, intent(out) :: fcomm
3846integer, optional, target, intent(out) :: error_code
3847!
3848type(c_ptr) :: handler_ptr
3849type(c_ptr) :: fcomm_ptr
3850type(c_ptr) :: error_code_ptr
3851!
3852interface
3853subroutine sirius_get_fft_comm_aux(handler,fcomm,error_code)&
3854&bind(C, name="sirius_get_fft_comm")
3855use, intrinsic :: iso_c_binding
3856type(c_ptr), value :: handler
3857type(c_ptr), value :: fcomm
3858type(c_ptr), value :: error_code
3859end subroutine
3860end interface
3861!
3862handler_ptr = c_null_ptr
3863handler_ptr = c_loc(handler%handler_ptr_)
3864fcomm_ptr = c_null_ptr
3865fcomm_ptr = c_loc(fcomm)
3866error_code_ptr = c_null_ptr
3867if (present(error_code)) then
3868error_code_ptr = c_loc(error_code)
3869endif
3870call sirius_get_fft_comm_aux(handler_ptr,fcomm_ptr,error_code_ptr)
3871end subroutine sirius_get_fft_comm
3872
3873!
3874!> @brief Get total number of G-vectors on the fine grid.
3875!> @param [in] handler Simulation context handler
3876!> @param [out] num_gvec Total number of G-vectors
3877!> @param [out] error_code Error code
3878subroutine sirius_get_num_gvec(handler,num_gvec,error_code)
3879implicit none
3880!
3881type(sirius_context_handler), target, intent(in) :: handler
3882integer, target, intent(out) :: num_gvec
3883integer, optional, target, intent(out) :: error_code
3884!
3885type(c_ptr) :: handler_ptr
3886type(c_ptr) :: num_gvec_ptr
3887type(c_ptr) :: error_code_ptr
3888!
3889interface
3890subroutine sirius_get_num_gvec_aux(handler,num_gvec,error_code)&
3891&bind(C, name="sirius_get_num_gvec")
3892use, intrinsic :: iso_c_binding
3893type(c_ptr), value :: handler
3894type(c_ptr), value :: num_gvec
3895type(c_ptr), value :: error_code
3896end subroutine
3897end interface
3898!
3899handler_ptr = c_null_ptr
3900handler_ptr = c_loc(handler%handler_ptr_)
3901num_gvec_ptr = c_null_ptr
3902num_gvec_ptr = c_loc(num_gvec)
3903error_code_ptr = c_null_ptr
3904if (present(error_code)) then
3905error_code_ptr = c_loc(error_code)
3906endif
3907call sirius_get_num_gvec_aux(handler_ptr,num_gvec_ptr,error_code_ptr)
3908end subroutine sirius_get_num_gvec
3909
3910!
3911!> @brief Get G-vector arrays.
3912!> @param [in] handler Simulation context handler
3913!> @param [in] gvec G-vectors in lattice coordinates.
3914!> @param [in] gvec_cart G-vectors in Cartesian coordinates.
3915!> @param [in] gvec_len Length of G-vectors.
3916!> @param [in] index_by_gvec G-vector index by lattice coordinates.
3917!> @param [out] error_code Error code
3918subroutine sirius_get_gvec_arrays(handler,gvec,gvec_cart,gvec_len,index_by_gvec,&
3919&error_code)
3920implicit none
3921!
3922type(sirius_context_handler), target, intent(in) :: handler
3923integer, optional, target, intent(in) :: gvec(:,:)
3924real(8), optional, target, intent(in) :: gvec_cart(:,:)
3925real(8), optional, target, intent(in) :: gvec_len(:)
3926integer, optional, target, intent(in) :: index_by_gvec(:,:,:)
3927integer, optional, target, intent(out) :: error_code
3928!
3929type(c_ptr) :: handler_ptr
3930type(c_ptr) :: gvec_ptr
3931type(c_ptr) :: gvec_cart_ptr
3932type(c_ptr) :: gvec_len_ptr
3933type(c_ptr) :: index_by_gvec_ptr
3934type(c_ptr) :: error_code_ptr
3935!
3936interface
3937subroutine sirius_get_gvec_arrays_aux(handler,gvec,gvec_cart,gvec_len,index_by_gvec,&
3938&error_code)&
3939&bind(C, name="sirius_get_gvec_arrays")
3940use, intrinsic :: iso_c_binding
3941type(c_ptr), value :: handler
3942type(c_ptr), value :: gvec
3943type(c_ptr), value :: gvec_cart
3944type(c_ptr), value :: gvec_len
3945type(c_ptr), value :: index_by_gvec
3946type(c_ptr), value :: error_code
3947end subroutine
3948end interface
3949!
3950handler_ptr = c_null_ptr
3951handler_ptr = c_loc(handler%handler_ptr_)
3952gvec_ptr = c_null_ptr
3953if (present(gvec)) then
3954gvec_ptr = c_loc(gvec)
3955endif
3956gvec_cart_ptr = c_null_ptr
3957if (present(gvec_cart)) then
3958gvec_cart_ptr = c_loc(gvec_cart)
3959endif
3960gvec_len_ptr = c_null_ptr
3961if (present(gvec_len)) then
3962gvec_len_ptr = c_loc(gvec_len)
3963endif
3964index_by_gvec_ptr = c_null_ptr
3965if (present(index_by_gvec)) then
3966index_by_gvec_ptr = c_loc(index_by_gvec)
3967endif
3968error_code_ptr = c_null_ptr
3969if (present(error_code)) then
3970error_code_ptr = c_loc(error_code)
3971endif
3972call sirius_get_gvec_arrays_aux(handler_ptr,gvec_ptr,gvec_cart_ptr,gvec_len_ptr,&
3973&index_by_gvec_ptr,error_code_ptr)
3974end subroutine sirius_get_gvec_arrays
3975
3976!
3977!> @brief Get local number of FFT grid points.
3978!> @param [in] handler Simulation context handler
3979!> @param [out] num_fft_grid_points Local number of FFT grid points in the real-space mesh.
3980!> @param [out] error_code Error code.
3981subroutine sirius_get_num_fft_grid_points(handler,num_fft_grid_points,error_code)
3982implicit none
3983!
3984type(sirius_context_handler), target, intent(in) :: handler
3985integer, target, intent(out) :: num_fft_grid_points
3986integer, optional, target, intent(out) :: error_code
3987!
3988type(c_ptr) :: handler_ptr
3989type(c_ptr) :: num_fft_grid_points_ptr
3990type(c_ptr) :: error_code_ptr
3991!
3992interface
3993subroutine sirius_get_num_fft_grid_points_aux(handler,num_fft_grid_points,error_code)&
3994&bind(C, name="sirius_get_num_fft_grid_points")
3995use, intrinsic :: iso_c_binding
3996type(c_ptr), value :: handler
3997type(c_ptr), value :: num_fft_grid_points
3998type(c_ptr), value :: error_code
3999end subroutine
4000end interface
4001!
4002handler_ptr = c_null_ptr
4003handler_ptr = c_loc(handler%handler_ptr_)
4004num_fft_grid_points_ptr = c_null_ptr
4005num_fft_grid_points_ptr = c_loc(num_fft_grid_points)
4006error_code_ptr = c_null_ptr
4007if (present(error_code)) then
4008error_code_ptr = c_loc(error_code)
4009endif
4010call sirius_get_num_fft_grid_points_aux(handler_ptr,num_fft_grid_points_ptr,error_code_ptr)
4011end subroutine sirius_get_num_fft_grid_points
4012
4013!
4014!> @brief Get mapping between G-vector index and FFT index
4015!> @param [in] handler Simulation context handler
4016!> @param [out] fft_index Index inside FFT buffer
4017!> @param [out] error_code Error code.
4018subroutine sirius_get_fft_index(handler,fft_index,error_code)
4019implicit none
4020!
4021type(sirius_context_handler), target, intent(in) :: handler
4022integer, target, intent(out) :: fft_index(:)
4023integer, optional, target, intent(out) :: error_code
4024!
4025type(c_ptr) :: handler_ptr
4026type(c_ptr) :: fft_index_ptr
4027type(c_ptr) :: error_code_ptr
4028!
4029interface
4030subroutine sirius_get_fft_index_aux(handler,fft_index,error_code)&
4031&bind(C, name="sirius_get_fft_index")
4032use, intrinsic :: iso_c_binding
4033type(c_ptr), value :: handler
4034type(c_ptr), value :: fft_index
4035type(c_ptr), value :: error_code
4036end subroutine
4037end interface
4038!
4039handler_ptr = c_null_ptr
4040handler_ptr = c_loc(handler%handler_ptr_)
4041fft_index_ptr = c_null_ptr
4042fft_index_ptr = c_loc(fft_index)
4043error_code_ptr = c_null_ptr
4044if (present(error_code)) then
4045error_code_ptr = c_loc(error_code)
4046endif
4047call sirius_get_fft_index_aux(handler_ptr,fft_index_ptr,error_code_ptr)
4048end subroutine sirius_get_fft_index
4049
4050!
4051!> @brief Get maximum number of G+k vectors across all k-points in the set
4052!> @param [in] ks_handler K-point set handler.
4053!> @param [out] max_num_gkvec Maximum number of G+k vectors
4054!> @param [out] error_code Error code.
4055subroutine sirius_get_max_num_gkvec(ks_handler,max_num_gkvec,error_code)
4056implicit none
4057!
4058type(sirius_kpoint_set_handler), target, intent(in) :: ks_handler
4059integer, target, intent(out) :: max_num_gkvec
4060integer, optional, target, intent(out) :: error_code
4061!
4062type(c_ptr) :: ks_handler_ptr
4063type(c_ptr) :: max_num_gkvec_ptr
4064type(c_ptr) :: error_code_ptr
4065!
4066interface
4067subroutine sirius_get_max_num_gkvec_aux(ks_handler,max_num_gkvec,error_code)&
4068&bind(C, name="sirius_get_max_num_gkvec")
4069use, intrinsic :: iso_c_binding
4070type(c_ptr), value :: ks_handler
4071type(c_ptr), value :: max_num_gkvec
4072type(c_ptr), value :: error_code
4073end subroutine
4074end interface
4075!
4076ks_handler_ptr = c_null_ptr
4077ks_handler_ptr = c_loc(ks_handler%handler_ptr_)
4078max_num_gkvec_ptr = c_null_ptr
4079max_num_gkvec_ptr = c_loc(max_num_gkvec)
4080error_code_ptr = c_null_ptr
4081if (present(error_code)) then
4082error_code_ptr = c_loc(error_code)
4083endif
4084call sirius_get_max_num_gkvec_aux(ks_handler_ptr,max_num_gkvec_ptr,error_code_ptr)
4085end subroutine sirius_get_max_num_gkvec
4086
4087!
4088!> @brief Get all G+k vector related arrays
4089!> @param [in] ks_handler K-point set handler.
4090!> @param [in] ik Global index of k-point
4091!> @param [out] num_gkvec Number of G+k vectors.
4092!> @param [out] gvec_index Index of the G-vector part of G+k vector.
4093!> @param [out] gkvec G+k vectors in fractional coordinates.
4094!> @param [out] gkvec_cart G+k vectors in Cartesian coordinates.
4095!> @param [out] gkvec_len Length of G+k vectors.
4096!> @param [out] gkvec_tp Theta and Phi angles of G+k vectors.
4097!> @param [out] error_code Error code.
4098subroutine sirius_get_gkvec_arrays(ks_handler,ik,num_gkvec,gvec_index,gkvec,gkvec_cart,&
4099&gkvec_len,gkvec_tp,error_code)
4100implicit none
4101!
4102type(sirius_kpoint_set_handler), target, intent(in) :: ks_handler
4103integer, target, intent(in) :: ik
4104integer, target, intent(out) :: num_gkvec
4105integer, target, intent(out) :: gvec_index(:)
4106real(8), target, intent(out) :: gkvec(:,:)
4107real(8), target, intent(out) :: gkvec_cart(:,:)
4108real(8), target, intent(out) :: gkvec_len(:)
4109real(8), target, intent(out) :: gkvec_tp(:,:)
4110integer, optional, target, intent(out) :: error_code
4111!
4112type(c_ptr) :: ks_handler_ptr
4113type(c_ptr) :: ik_ptr
4114type(c_ptr) :: num_gkvec_ptr
4115type(c_ptr) :: gvec_index_ptr
4116type(c_ptr) :: gkvec_ptr
4117type(c_ptr) :: gkvec_cart_ptr
4118type(c_ptr) :: gkvec_len_ptr
4119type(c_ptr) :: gkvec_tp_ptr
4120type(c_ptr) :: error_code_ptr
4121!
4122interface
4123subroutine sirius_get_gkvec_arrays_aux(ks_handler,ik,num_gkvec,gvec_index,gkvec,&
4124&gkvec_cart,gkvec_len,gkvec_tp,error_code)&
4125&bind(C, name="sirius_get_gkvec_arrays")
4126use, intrinsic :: iso_c_binding
4127type(c_ptr), value :: ks_handler
4128type(c_ptr), value :: ik
4129type(c_ptr), value :: num_gkvec
4130type(c_ptr), value :: gvec_index
4131type(c_ptr), value :: gkvec
4132type(c_ptr), value :: gkvec_cart
4133type(c_ptr), value :: gkvec_len
4134type(c_ptr), value :: gkvec_tp
4135type(c_ptr), value :: error_code
4136end subroutine
4137end interface
4138!
4139ks_handler_ptr = c_null_ptr
4140ks_handler_ptr = c_loc(ks_handler%handler_ptr_)
4141ik_ptr = c_null_ptr
4142ik_ptr = c_loc(ik)
4143num_gkvec_ptr = c_null_ptr
4144num_gkvec_ptr = c_loc(num_gkvec)
4145gvec_index_ptr = c_null_ptr
4146gvec_index_ptr = c_loc(gvec_index)
4147gkvec_ptr = c_null_ptr
4148gkvec_ptr = c_loc(gkvec)
4149gkvec_cart_ptr = c_null_ptr
4150gkvec_cart_ptr = c_loc(gkvec_cart)
4151gkvec_len_ptr = c_null_ptr
4152gkvec_len_ptr = c_loc(gkvec_len)
4153gkvec_tp_ptr = c_null_ptr
4154gkvec_tp_ptr = c_loc(gkvec_tp)
4155error_code_ptr = c_null_ptr
4156if (present(error_code)) then
4157error_code_ptr = c_loc(error_code)
4158endif
4159call sirius_get_gkvec_arrays_aux(ks_handler_ptr,ik_ptr,num_gkvec_ptr,gvec_index_ptr,&
4160&gkvec_ptr,gkvec_cart_ptr,gkvec_len_ptr,gkvec_tp_ptr,error_code_ptr)
4161end subroutine sirius_get_gkvec_arrays
4162
4163!
4164!> @brief Get the unit-step function.
4165!> @param [in] handler Simulation context handler
4166!> @param [out] cfunig Plane-wave coefficients of step function.
4167!> @param [out] cfunrg Values of the step function on the regular grid.
4168!> @param [in] num_rg_points Number of real-space points.
4169!> @param [out] error_code Error code.
4170subroutine sirius_get_step_function(handler,cfunig,cfunrg,num_rg_points,error_code)
4171implicit none
4172!
4173type(sirius_context_handler), target, intent(in) :: handler
4174complex(8), target, intent(out) :: cfunig(:)
4175real(8), target, intent(out) :: cfunrg(:)
4176integer, target, intent(in) :: num_rg_points
4177integer, optional, target, intent(out) :: error_code
4178!
4179type(c_ptr) :: handler_ptr
4180type(c_ptr) :: cfunig_ptr
4181type(c_ptr) :: cfunrg_ptr
4182type(c_ptr) :: num_rg_points_ptr
4183type(c_ptr) :: error_code_ptr
4184!
4185interface
4186subroutine sirius_get_step_function_aux(handler,cfunig,cfunrg,num_rg_points,error_code)&
4187&bind(C, name="sirius_get_step_function")
4188use, intrinsic :: iso_c_binding
4189type(c_ptr), value :: handler
4190type(c_ptr), value :: cfunig
4191type(c_ptr), value :: cfunrg
4192type(c_ptr), value :: num_rg_points
4193type(c_ptr), value :: error_code
4194end subroutine
4195end interface
4196!
4197handler_ptr = c_null_ptr
4198handler_ptr = c_loc(handler%handler_ptr_)
4199cfunig_ptr = c_null_ptr
4200cfunig_ptr = c_loc(cfunig)
4201cfunrg_ptr = c_null_ptr
4202cfunrg_ptr = c_loc(cfunrg)
4203num_rg_points_ptr = c_null_ptr
4204num_rg_points_ptr = c_loc(num_rg_points)
4205error_code_ptr = c_null_ptr
4206if (present(error_code)) then
4207error_code_ptr = c_loc(error_code)
4208endif
4209call sirius_get_step_function_aux(handler_ptr,cfunig_ptr,cfunrg_ptr,num_rg_points_ptr,&
4210&error_code_ptr)
4211end subroutine sirius_get_step_function
4212
4213!
4214!> @brief Set LAPW Hamiltonian radial integrals.
4215!> @param [in] handler Simulation context handler.
4216!> @param [in] ia Index of atom.
4217!> @param [in] lmmax Number of lm-component of the potential.
4218!> @param [in] val Values of the radial integrals.
4219!> @param [in] l1 1st index of orbital quantum number.
4220!> @param [in] o1 1st index of radial function order for l1.
4221!> @param [in] ilo1 1st index or local orbital.
4222!> @param [in] l2 2nd index of orbital quantum number.
4223!> @param [in] o2 2nd index of radial function order for l2.
4224!> @param [in] ilo2 2nd index or local orbital.
4225!> @param [out] error_code Error code.
4226subroutine sirius_set_h_radial_integrals(handler,ia,lmmax,val,l1,o1,ilo1,l2,o2,ilo2,&
4227&error_code)
4228implicit none
4229!
4230type(sirius_context_handler), target, intent(in) :: handler
4231integer, target, intent(in) :: ia
4232integer, target, intent(in) :: lmmax
4233real(8), target, intent(in) :: val
4234integer, optional, target, intent(in) :: l1
4235integer, optional, target, intent(in) :: o1
4236integer, optional, target, intent(in) :: ilo1
4237integer, optional, target, intent(in) :: l2
4238integer, optional, target, intent(in) :: o2
4239integer, optional, target, intent(in) :: ilo2
4240integer, optional, target, intent(out) :: error_code
4241!
4242type(c_ptr) :: handler_ptr
4243type(c_ptr) :: ia_ptr
4244type(c_ptr) :: lmmax_ptr
4245type(c_ptr) :: val_ptr
4246type(c_ptr) :: l1_ptr
4247type(c_ptr) :: o1_ptr
4248type(c_ptr) :: ilo1_ptr
4249type(c_ptr) :: l2_ptr
4250type(c_ptr) :: o2_ptr
4251type(c_ptr) :: ilo2_ptr
4252type(c_ptr) :: error_code_ptr
4253!
4254interface
4255subroutine sirius_set_h_radial_integrals_aux(handler,ia,lmmax,val,l1,o1,ilo1,l2,&
4256&o2,ilo2,error_code)&
4257&bind(C, name="sirius_set_h_radial_integrals")
4258use, intrinsic :: iso_c_binding
4259type(c_ptr), value :: handler
4260type(c_ptr), value :: ia
4261type(c_ptr), value :: lmmax
4262type(c_ptr), value :: val
4263type(c_ptr), value :: l1
4264type(c_ptr), value :: o1
4265type(c_ptr), value :: ilo1
4266type(c_ptr), value :: l2
4267type(c_ptr), value :: o2
4268type(c_ptr), value :: ilo2
4269type(c_ptr), value :: error_code
4270end subroutine
4271end interface
4272!
4273handler_ptr = c_null_ptr
4274handler_ptr = c_loc(handler%handler_ptr_)
4275ia_ptr = c_null_ptr
4276ia_ptr = c_loc(ia)
4277lmmax_ptr = c_null_ptr
4278lmmax_ptr = c_loc(lmmax)
4279val_ptr = c_null_ptr
4280val_ptr = c_loc(val)
4281l1_ptr = c_null_ptr
4282if (present(l1)) then
4283l1_ptr = c_loc(l1)
4284endif
4285o1_ptr = c_null_ptr
4286if (present(o1)) then
4287o1_ptr = c_loc(o1)
4288endif
4289ilo1_ptr = c_null_ptr
4290if (present(ilo1)) then
4291ilo1_ptr = c_loc(ilo1)
4292endif
4293l2_ptr = c_null_ptr
4294if (present(l2)) then
4295l2_ptr = c_loc(l2)
4296endif
4297o2_ptr = c_null_ptr
4298if (present(o2)) then
4299o2_ptr = c_loc(o2)
4300endif
4301ilo2_ptr = c_null_ptr
4302if (present(ilo2)) then
4303ilo2_ptr = c_loc(ilo2)
4304endif
4305error_code_ptr = c_null_ptr
4306if (present(error_code)) then
4307error_code_ptr = c_loc(error_code)
4308endif
4309call sirius_set_h_radial_integrals_aux(handler_ptr,ia_ptr,lmmax_ptr,val_ptr,l1_ptr,&
4310&o1_ptr,ilo1_ptr,l2_ptr,o2_ptr,ilo2_ptr,error_code_ptr)
4311end subroutine sirius_set_h_radial_integrals
4312
4313!
4314!> @brief Set LAPW overlap radial integral.
4315!> @param [in] handler Simulation context handler.
4316!> @param [in] ia Index of atom.
4317!> @param [in] val Value of the radial integral.
4318!> @param [in] l Orbital quantum number.
4319!> @param [in] o1 1st index of radial function order.
4320!> @param [in] ilo1 1st index or local orbital.
4321!> @param [in] o2 2nd index of radial function order.
4322!> @param [in] ilo2 2nd index or local orbital.
4323!> @param [out] error_code Error code.
4324subroutine sirius_set_o_radial_integral(handler,ia,val,l,o1,ilo1,o2,ilo2,error_code)
4325implicit none
4326!
4327type(sirius_context_handler), target, intent(in) :: handler
4328integer, target, intent(in) :: ia
4329real(8), target, intent(in) :: val
4330integer, target, intent(in) :: l
4331integer, optional, target, intent(in) :: o1
4332integer, optional, target, intent(in) :: ilo1
4333integer, optional, target, intent(in) :: o2
4334integer, optional, target, intent(in) :: ilo2
4335integer, optional, target, intent(out) :: error_code
4336!
4337type(c_ptr) :: handler_ptr
4338type(c_ptr) :: ia_ptr
4339type(c_ptr) :: val_ptr
4340type(c_ptr) :: l_ptr
4341type(c_ptr) :: o1_ptr
4342type(c_ptr) :: ilo1_ptr
4343type(c_ptr) :: o2_ptr
4344type(c_ptr) :: ilo2_ptr
4345type(c_ptr) :: error_code_ptr
4346!
4347interface
4348subroutine sirius_set_o_radial_integral_aux(handler,ia,val,l,o1,ilo1,o2,ilo2,error_code)&
4349&bind(C, name="sirius_set_o_radial_integral")
4350use, intrinsic :: iso_c_binding
4351type(c_ptr), value :: handler
4352type(c_ptr), value :: ia
4353type(c_ptr), value :: val
4354type(c_ptr), value :: l
4355type(c_ptr), value :: o1
4356type(c_ptr), value :: ilo1
4357type(c_ptr), value :: o2
4358type(c_ptr), value :: ilo2
4359type(c_ptr), value :: error_code
4360end subroutine
4361end interface
4362!
4363handler_ptr = c_null_ptr
4364handler_ptr = c_loc(handler%handler_ptr_)
4365ia_ptr = c_null_ptr
4366ia_ptr = c_loc(ia)
4367val_ptr = c_null_ptr
4368val_ptr = c_loc(val)
4369l_ptr = c_null_ptr
4370l_ptr = c_loc(l)
4371o1_ptr = c_null_ptr
4372if (present(o1)) then
4373o1_ptr = c_loc(o1)
4374endif
4375ilo1_ptr = c_null_ptr
4376if (present(ilo1)) then
4377ilo1_ptr = c_loc(ilo1)
4378endif
4379o2_ptr = c_null_ptr
4380if (present(o2)) then
4381o2_ptr = c_loc(o2)
4382endif
4383ilo2_ptr = c_null_ptr
4384if (present(ilo2)) then
4385ilo2_ptr = c_loc(ilo2)
4386endif
4387error_code_ptr = c_null_ptr
4388if (present(error_code)) then
4389error_code_ptr = c_loc(error_code)
4390endif
4391call sirius_set_o_radial_integral_aux(handler_ptr,ia_ptr,val_ptr,l_ptr,o1_ptr,ilo1_ptr,&
4392&o2_ptr,ilo2_ptr,error_code_ptr)
4393end subroutine sirius_set_o_radial_integral
4394
4395!
4396!> @brief Set a correction to LAPW overlap radial integral.
4397!> @param [in] handler Simulation context handler.
4398!> @param [in] ia Index of atom.
4399!> @param [in] val Value of the radial integral.
4400!> @param [in] l1 1st index of orbital quantum number.
4401!> @param [in] o1 1st index of radial function order for l1.
4402!> @param [in] ilo1 1st index or local orbital.
4403!> @param [in] l2 2nd index of orbital quantum number.
4404!> @param [in] o2 2nd index of radial function order for l2.
4405!> @param [in] ilo2 2nd index or local orbital.
4406!> @param [out] error_code Error code.
4407subroutine sirius_set_o1_radial_integral(handler,ia,val,l1,o1,ilo1,l2,o2,ilo2,error_code)
4408implicit none
4409!
4410type(sirius_context_handler), target, intent(in) :: handler
4411integer, target, intent(in) :: ia
4412real(8), target, intent(in) :: val
4413integer, optional, target, intent(in) :: l1
4414integer, optional, target, intent(in) :: o1
4415integer, optional, target, intent(in) :: ilo1
4416integer, optional, target, intent(in) :: l2
4417integer, optional, target, intent(in) :: o2
4418integer, optional, target, intent(in) :: ilo2
4419integer, optional, target, intent(out) :: error_code
4420!
4421type(c_ptr) :: handler_ptr
4422type(c_ptr) :: ia_ptr
4423type(c_ptr) :: val_ptr
4424type(c_ptr) :: l1_ptr
4425type(c_ptr) :: o1_ptr
4426type(c_ptr) :: ilo1_ptr
4427type(c_ptr) :: l2_ptr
4428type(c_ptr) :: o2_ptr
4429type(c_ptr) :: ilo2_ptr
4430type(c_ptr) :: error_code_ptr
4431!
4432interface
4433subroutine sirius_set_o1_radial_integral_aux(handler,ia,val,l1,o1,ilo1,l2,o2,ilo2,&
4434&error_code)&
4435&bind(C, name="sirius_set_o1_radial_integral")
4436use, intrinsic :: iso_c_binding
4437type(c_ptr), value :: handler
4438type(c_ptr), value :: ia
4439type(c_ptr), value :: val
4440type(c_ptr), value :: l1
4441type(c_ptr), value :: o1
4442type(c_ptr), value :: ilo1
4443type(c_ptr), value :: l2
4444type(c_ptr), value :: o2
4445type(c_ptr), value :: ilo2
4446type(c_ptr), value :: error_code
4447end subroutine
4448end interface
4449!
4450handler_ptr = c_null_ptr
4451handler_ptr = c_loc(handler%handler_ptr_)
4452ia_ptr = c_null_ptr
4453ia_ptr = c_loc(ia)
4454val_ptr = c_null_ptr
4455val_ptr = c_loc(val)
4456l1_ptr = c_null_ptr
4457if (present(l1)) then
4458l1_ptr = c_loc(l1)
4459endif
4460o1_ptr = c_null_ptr
4461if (present(o1)) then
4462o1_ptr = c_loc(o1)
4463endif
4464ilo1_ptr = c_null_ptr
4465if (present(ilo1)) then
4466ilo1_ptr = c_loc(ilo1)
4467endif
4468l2_ptr = c_null_ptr
4469if (present(l2)) then
4470l2_ptr = c_loc(l2)
4471endif
4472o2_ptr = c_null_ptr
4473if (present(o2)) then
4474o2_ptr = c_loc(o2)
4475endif
4476ilo2_ptr = c_null_ptr
4477if (present(ilo2)) then
4478ilo2_ptr = c_loc(ilo2)
4479endif
4480error_code_ptr = c_null_ptr
4481if (present(error_code)) then
4482error_code_ptr = c_loc(error_code)
4483endif
4484call sirius_set_o1_radial_integral_aux(handler_ptr,ia_ptr,val_ptr,l1_ptr,o1_ptr,&
4485&ilo1_ptr,l2_ptr,o2_ptr,ilo2_ptr,error_code_ptr)
4486end subroutine sirius_set_o1_radial_integral
4487
4488!
4489!> @brief Set LAPW radial functions
4490!> @param [in] handler Simulation context handler.
4491!> @param [in] ia Index of atom.
4492!> @param [in] deriv_order Radial derivative order.
4493!> @param [in] f Values of the radial function.
4494!> @param [in] l Orbital quantum number.
4495!> @param [in] o Order of radial function for l.
4496!> @param [in] ilo Local orbital index.
4497!> @param [out] error_code Error code.
4498subroutine sirius_set_radial_function(handler,ia,deriv_order,f,l,o,ilo,error_code)
4499implicit none
4500!
4501type(sirius_context_handler), target, intent(in) :: handler
4502integer, target, intent(in) :: ia
4503integer, target, intent(in) :: deriv_order
4504real(8), target, intent(in) :: f(:)
4505integer, optional, target, intent(in) :: l
4506integer, optional, target, intent(in) :: o
4507integer, optional, target, intent(in) :: ilo
4508integer, optional, target, intent(out) :: error_code
4509!
4510type(c_ptr) :: handler_ptr
4511type(c_ptr) :: ia_ptr
4512type(c_ptr) :: deriv_order_ptr
4513type(c_ptr) :: f_ptr
4514type(c_ptr) :: l_ptr
4515type(c_ptr) :: o_ptr
4516type(c_ptr) :: ilo_ptr
4517type(c_ptr) :: error_code_ptr
4518!
4519interface
4520subroutine sirius_set_radial_function_aux(handler,ia,deriv_order,f,l,o,ilo,error_code)&
4521&bind(C, name="sirius_set_radial_function")
4522use, intrinsic :: iso_c_binding
4523type(c_ptr), value :: handler
4524type(c_ptr), value :: ia
4525type(c_ptr), value :: deriv_order
4526type(c_ptr), value :: f
4527type(c_ptr), value :: l
4528type(c_ptr), value :: o
4529type(c_ptr), value :: ilo
4530type(c_ptr), value :: error_code
4531end subroutine
4532end interface
4533!
4534handler_ptr = c_null_ptr
4535handler_ptr = c_loc(handler%handler_ptr_)
4536ia_ptr = c_null_ptr
4537ia_ptr = c_loc(ia)
4538deriv_order_ptr = c_null_ptr
4539deriv_order_ptr = c_loc(deriv_order)
4540f_ptr = c_null_ptr
4541f_ptr = c_loc(f)
4542l_ptr = c_null_ptr
4543if (present(l)) then
4544l_ptr = c_loc(l)
4545endif
4546o_ptr = c_null_ptr
4547if (present(o)) then
4548o_ptr = c_loc(o)
4549endif
4550ilo_ptr = c_null_ptr
4551if (present(ilo)) then
4552ilo_ptr = c_loc(ilo)
4553endif
4554error_code_ptr = c_null_ptr
4555if (present(error_code)) then
4556error_code_ptr = c_loc(error_code)
4557endif
4558call sirius_set_radial_function_aux(handler_ptr,ia_ptr,deriv_order_ptr,f_ptr,l_ptr,&
4559&o_ptr,ilo_ptr,error_code_ptr)
4560end subroutine sirius_set_radial_function
4561
4562!
4563!> @brief Set equivalent atoms.
4564!> @param [in] handler Simulation context handler.
4565!> @param [in] equivalent_atoms Array with equivalent atom IDs.
4566!> @param [out] error_code Error code.
4567subroutine sirius_set_equivalent_atoms(handler,equivalent_atoms,error_code)
4568implicit none
4569!
4570type(sirius_context_handler), target, intent(in) :: handler
4571integer, target, intent(in) :: equivalent_atoms(:)
4572integer, optional, target, intent(out) :: error_code
4573!
4574type(c_ptr) :: handler_ptr
4575type(c_ptr) :: equivalent_atoms_ptr
4576type(c_ptr) :: error_code_ptr
4577!
4578interface
4579subroutine sirius_set_equivalent_atoms_aux(handler,equivalent_atoms,error_code)&
4580&bind(C, name="sirius_set_equivalent_atoms")
4581use, intrinsic :: iso_c_binding
4582type(c_ptr), value :: handler
4583type(c_ptr), value :: equivalent_atoms
4584type(c_ptr), value :: error_code
4585end subroutine
4586end interface
4587!
4588handler_ptr = c_null_ptr
4589handler_ptr = c_loc(handler%handler_ptr_)
4590equivalent_atoms_ptr = c_null_ptr
4591equivalent_atoms_ptr = c_loc(equivalent_atoms)
4592error_code_ptr = c_null_ptr
4593if (present(error_code)) then
4594error_code_ptr = c_loc(error_code)
4595endif
4596call sirius_set_equivalent_atoms_aux(handler_ptr,equivalent_atoms_ptr,error_code_ptr)
4597end subroutine sirius_set_equivalent_atoms
4598
4599!
4600!> @brief Set the new spherical potential.
4601!> @param [in] handler Ground state handler.
4602!> @param [out] error_code Error code.
4603subroutine sirius_update_atomic_potential(handler,error_code)
4604implicit none
4605!
4606type(sirius_ground_state_handler), target, intent(in) :: handler
4607integer, optional, target, intent(out) :: error_code
4608!
4609type(c_ptr) :: handler_ptr
4610type(c_ptr) :: error_code_ptr
4611!
4612interface
4613subroutine sirius_update_atomic_potential_aux(handler,error_code)&
4614&bind(C, name="sirius_update_atomic_potential")
4615use, intrinsic :: iso_c_binding
4616type(c_ptr), value :: handler
4617type(c_ptr), value :: error_code
4618end subroutine
4619end interface
4620!
4621handler_ptr = c_null_ptr
4622handler_ptr = c_loc(handler%handler_ptr_)
4623error_code_ptr = c_null_ptr
4624if (present(error_code)) then
4625error_code_ptr = c_loc(error_code)
4626endif
4627call sirius_update_atomic_potential_aux(handler_ptr,error_code_ptr)
4628end subroutine sirius_update_atomic_potential
4629
4630!
4631!> @brief Return the total number of sections defined in the input JSON schema.
4632!> @param [out] length Number of sections.
4633!> @param [out] error_code Error code.
4634subroutine sirius_option_get_number_of_sections(length,error_code)
4635implicit none
4636!
4637integer, target, intent(out) :: length
4638integer, optional, target, intent(out) :: error_code
4639!
4640type(c_ptr) :: length_ptr
4641type(c_ptr) :: error_code_ptr
4642!
4643interface
4644subroutine sirius_option_get_number_of_sections_aux(length,error_code)&
4645&bind(C, name="sirius_option_get_number_of_sections")
4646use, intrinsic :: iso_c_binding
4647type(c_ptr), value :: length
4648type(c_ptr), value :: error_code
4649end subroutine
4650end interface
4651!
4652length_ptr = c_null_ptr
4653length_ptr = c_loc(length)
4654error_code_ptr = c_null_ptr
4655if (present(error_code)) then
4656error_code_ptr = c_loc(error_code)
4657endif
4658call sirius_option_get_number_of_sections_aux(length_ptr,error_code_ptr)
4660
4661!
4662!> @brief Return the name of a given section.
4663!> @param [in] elem Index of the section (starting from 1).
4664!> @param [out] section_name Name of the section
4665!> @param [in] section_name_length Maximum length of the output string. Enough capacity should be provided.
4666!> @param [out] error_code Error code.
4667subroutine sirius_option_get_section_name(elem,section_name,section_name_length,&
4668&error_code)
4669implicit none
4670!
4671integer, value, intent(in) :: elem
4672character(*), target, intent(out) :: section_name
4673integer, value, intent(in) :: section_name_length
4674integer, optional, target, intent(out) :: error_code
4675!
4676type(c_ptr) :: section_name_ptr
4677character(C_CHAR), target, allocatable :: section_name_c_type(:)
4678type(c_ptr) :: error_code_ptr
4679!
4680interface
4681subroutine sirius_option_get_section_name_aux(elem,section_name,section_name_length,&
4682&error_code)&
4683&bind(C, name="sirius_option_get_section_name")
4684use, intrinsic :: iso_c_binding
4685integer(C_INT), value :: elem
4686type(c_ptr), value :: section_name
4687integer(C_INT), value :: section_name_length
4688type(c_ptr), value :: error_code
4689end subroutine
4690end interface
4691!
4692section_name_ptr = c_null_ptr
4693allocate(section_name_c_type(len(section_name)+1))
4694section_name_ptr = c_loc(section_name_c_type)
4695error_code_ptr = c_null_ptr
4696if (present(error_code)) then
4697error_code_ptr = c_loc(error_code)
4698endif
4699call sirius_option_get_section_name_aux(elem,section_name_ptr,section_name_length,&
4700&error_code_ptr)
4701section_name = string_c2f(section_name_c_type)
4702deallocate(section_name_c_type)
4703end subroutine sirius_option_get_section_name
4704
4705!
4706!> @brief Return the number of options in a given section.
4707!> @param [in] section Name of the seciton.
4708!> @param [out] length Number of options contained in the section.
4709!> @param [out] error_code Error code.
4710subroutine sirius_option_get_section_length(section,length,error_code)
4711implicit none
4712!
4713character(*), target, intent(in) :: section
4714integer, target, intent(out) :: length
4715integer, optional, target, intent(out) :: error_code
4716!
4717type(c_ptr) :: section_ptr
4718character(C_CHAR), target, allocatable :: section_c_type(:)
4719type(c_ptr) :: length_ptr
4720type(c_ptr) :: error_code_ptr
4721!
4722interface
4723subroutine sirius_option_get_section_length_aux(section,length,error_code)&
4724&bind(C, name="sirius_option_get_section_length")
4725use, intrinsic :: iso_c_binding
4726type(c_ptr), value :: section
4727type(c_ptr), value :: length
4728type(c_ptr), value :: error_code
4729end subroutine
4730end interface
4731!
4732section_ptr = c_null_ptr
4733allocate(section_c_type(len(section)+1))
4734section_c_type = string_f2c(section)
4735section_ptr = c_loc(section_c_type)
4736length_ptr = c_null_ptr
4737length_ptr = c_loc(length)
4738error_code_ptr = c_null_ptr
4739if (present(error_code)) then
4740error_code_ptr = c_loc(error_code)
4741endif
4742call sirius_option_get_section_length_aux(section_ptr,length_ptr,error_code_ptr)
4743deallocate(section_c_type)
4745
4746!
4747!> @brief Return information about the option.
4748!> @param [in] section Name of the section.
4749!> @param [in] elem Index of the option (starting from 1)
4750!> @param [out] key_name Name of the option.
4751!> @param [in] key_name_len Maximum length for the string (on the caller side). No allocation is done.
4752!> @param [out] type Type of the option (real, integer, boolean, string, or array of the same types).
4753!> @param [out] length Length of the default value (1 for the scalar types, otherwise the lenght of the array).
4754!> @param [out] enum_size Number of elements in the enum type, zero otherwise.
4755!> @param [out] title Short description of the option (can be empty).
4756!> @param [in] title_len Maximum length for the short description.
4757!> @param [out] description Detailed description of the option (can be empty).
4758!> @param [in] description_len Maximum length for the detailed description.
4759!> @param [out] error_code Error code.
4760subroutine sirius_option_get_info(section,elem,key_name,key_name_len,type,length,&
4761&enum_size,title,title_len,description,description_len,error_code)
4762implicit none
4763!
4764character(*), target, intent(in) :: section
4765integer, value, intent(in) :: elem
4766character(*), target, intent(out) :: key_name
4767integer, value, intent(in) :: key_name_len
4768integer, target, intent(out) :: type
4769integer, target, intent(out) :: length
4770integer, target, intent(out) :: enum_size
4771character(*), target, intent(out) :: title
4772integer, value, intent(in) :: title_len
4773character(*), target, intent(out) :: description
4774integer, value, intent(in) :: description_len
4775integer, optional, target, intent(out) :: error_code
4776!
4777type(c_ptr) :: section_ptr
4778character(C_CHAR), target, allocatable :: section_c_type(:)
4779type(c_ptr) :: key_name_ptr
4780character(C_CHAR), target, allocatable :: key_name_c_type(:)
4781type(c_ptr) :: type_ptr
4782type(c_ptr) :: length_ptr
4783type(c_ptr) :: enum_size_ptr
4784type(c_ptr) :: title_ptr
4785character(C_CHAR), target, allocatable :: title_c_type(:)
4786type(c_ptr) :: description_ptr
4787character(C_CHAR), target, allocatable :: description_c_type(:)
4788type(c_ptr) :: error_code_ptr
4789!
4790interface
4791subroutine sirius_option_get_info_aux(section,elem,key_name,key_name_len,type,length,&
4792&enum_size,title,title_len,description,description_len,error_code)&
4793&bind(C, name="sirius_option_get_info")
4794use, intrinsic :: iso_c_binding
4795type(c_ptr), value :: section
4796integer(C_INT), value :: elem
4797type(c_ptr), value :: key_name
4798integer(C_INT), value :: key_name_len
4799type(c_ptr), value :: type
4800type(c_ptr), value :: length
4801type(c_ptr), value :: enum_size
4802type(c_ptr), value :: title
4803integer(C_INT), value :: title_len
4804type(c_ptr), value :: description
4805integer(C_INT), value :: description_len
4806type(c_ptr), value :: error_code
4807end subroutine
4808end interface
4809!
4810section_ptr = c_null_ptr
4811allocate(section_c_type(len(section)+1))
4812section_c_type = string_f2c(section)
4813section_ptr = c_loc(section_c_type)
4814key_name_ptr = c_null_ptr
4815allocate(key_name_c_type(len(key_name)+1))
4816key_name_ptr = c_loc(key_name_c_type)
4817type_ptr = c_null_ptr
4818type_ptr = c_loc(type)
4819length_ptr = c_null_ptr
4820length_ptr = c_loc(length)
4821enum_size_ptr = c_null_ptr
4822enum_size_ptr = c_loc(enum_size)
4823title_ptr = c_null_ptr
4824allocate(title_c_type(len(title)+1))
4825title_ptr = c_loc(title_c_type)
4826description_ptr = c_null_ptr
4827allocate(description_c_type(len(description)+1))
4828description_ptr = c_loc(description_c_type)
4829error_code_ptr = c_null_ptr
4830if (present(error_code)) then
4831error_code_ptr = c_loc(error_code)
4832endif
4833call sirius_option_get_info_aux(section_ptr,elem,key_name_ptr,key_name_len,type_ptr,&
4834&length_ptr,enum_size_ptr,title_ptr,title_len,description_ptr,description_len,error_code_ptr)
4835deallocate(section_c_type)
4836key_name = string_c2f(key_name_c_type)
4837deallocate(key_name_c_type)
4838title = string_c2f(title_c_type)
4839deallocate(title_c_type)
4840description = string_c2f(description_c_type)
4841deallocate(description_c_type)
4842end subroutine sirius_option_get_info
4843
4844!
4845!> @brief Return the default value of the option as defined in the JSON schema.
4846!> @param [in] section Name of the section of interest.
4847!> @param [in] name Name of the element
4848!> @param [in] type Type of the option (real, integer, boolean)
4849!> @param [in] data_ptr Output buffer for the default value or list of values.
4850!> @param [in] max_length Maximum length of the buffer containing the default values.
4851!> @param [in] enum_idx Index of the element in case of the enum type.
4852!> @param [out] error_code Error code.
4853subroutine sirius_option_get(section,name,type,data_ptr,max_length,enum_idx,error_code)
4854implicit none
4855!
4856character(*), target, intent(in) :: section
4857character(*), target, intent(in) :: name
4858integer, target, intent(in) :: type
4859type(c_ptr), value, intent(in) :: data_ptr
4860integer, optional, target, intent(in) :: max_length
4861integer, optional, target, intent(in) :: enum_idx
4862integer, optional, target, intent(out) :: error_code
4863!
4864type(c_ptr) :: section_ptr
4865character(C_CHAR), target, allocatable :: section_c_type(:)
4866type(c_ptr) :: name_ptr
4867character(C_CHAR), target, allocatable :: name_c_type(:)
4868type(c_ptr) :: type_ptr
4869type(c_ptr) :: max_length_ptr
4870type(c_ptr) :: enum_idx_ptr
4871type(c_ptr) :: error_code_ptr
4872!
4873interface
4874subroutine sirius_option_get_aux(section,name,type,data_ptr,max_length,enum_idx,&
4875&error_code)&
4876&bind(C, name="sirius_option_get")
4877use, intrinsic :: iso_c_binding
4878type(c_ptr), value :: section
4879type(c_ptr), value :: name
4880type(c_ptr), value :: type
4881type(c_ptr), value :: data_ptr
4882type(c_ptr), value :: max_length
4883type(c_ptr), value :: enum_idx
4884type(c_ptr), value :: error_code
4885end subroutine
4886end interface
4887!
4888section_ptr = c_null_ptr
4889allocate(section_c_type(len(section)+1))
4890section_c_type = string_f2c(section)
4891section_ptr = c_loc(section_c_type)
4892name_ptr = c_null_ptr
4893allocate(name_c_type(len(name)+1))
4894name_c_type = string_f2c(name)
4895name_ptr = c_loc(name_c_type)
4896type_ptr = c_null_ptr
4897type_ptr = c_loc(type)
4898max_length_ptr = c_null_ptr
4899if (present(max_length)) then
4900max_length_ptr = c_loc(max_length)
4901endif
4902enum_idx_ptr = c_null_ptr
4903if (present(enum_idx)) then
4904enum_idx_ptr = c_loc(enum_idx)
4905endif
4906error_code_ptr = c_null_ptr
4907if (present(error_code)) then
4908error_code_ptr = c_loc(error_code)
4909endif
4910call sirius_option_get_aux(section_ptr,name_ptr,type_ptr,data_ptr,max_length_ptr,&
4911&enum_idx_ptr,error_code_ptr)
4912deallocate(section_c_type)
4913deallocate(name_c_type)
4914end subroutine sirius_option_get
4915
4916!
4917!> @brief Set the value of the option name in a (internal) json dictionary
4918!> @param [in] handler Simulation context handler.
4919!> @param [in] section string containing the options in json format
4920!> @param [in] name name of the element to pick
4921!> @param [in] type Type of the option (real, integer, boolean)
4922!> @param [in] data_ptr Buffer for the value or list of values.
4923!> @param [in] max_length Maximum length of the buffer containing the default values.
4924!> @param [in] append If true then value is appended to the list of values.
4925!> @param [out] error_code Error code.
4926subroutine sirius_option_set(handler,section,name,type,data_ptr,max_length,append,&
4927&error_code)
4928implicit none
4929!
4930type(sirius_context_handler), target, intent(in) :: handler
4931character(*), target, intent(in) :: section
4932character(*), target, intent(in) :: name
4933integer, target, intent(in) :: type
4934type(c_ptr), value, intent(in) :: data_ptr
4935integer, optional, target, intent(in) :: max_length
4936logical, optional, target, intent(in) :: append
4937integer, optional, target, intent(out) :: error_code
4938!
4939type(c_ptr) :: handler_ptr
4940type(c_ptr) :: section_ptr
4941character(C_CHAR), target, allocatable :: section_c_type(:)
4942type(c_ptr) :: name_ptr
4943character(C_CHAR), target, allocatable :: name_c_type(:)
4944type(c_ptr) :: type_ptr
4945type(c_ptr) :: max_length_ptr
4946type(c_ptr) :: append_ptr
4947logical(C_BOOL), target :: append_c_type
4948type(c_ptr) :: error_code_ptr
4949!
4950interface
4951subroutine sirius_option_set_aux(handler,section,name,type,data_ptr,max_length,append,&
4952&error_code)&
4953&bind(C, name="sirius_option_set")
4954use, intrinsic :: iso_c_binding
4955type(c_ptr), value :: handler
4956type(c_ptr), value :: section
4957type(c_ptr), value :: name
4958type(c_ptr), value :: type
4959type(c_ptr), value :: data_ptr
4960type(c_ptr), value :: max_length
4961type(c_ptr), value :: append
4962type(c_ptr), value :: error_code
4963end subroutine
4964end interface
4965!
4966handler_ptr = c_null_ptr
4967handler_ptr = c_loc(handler%handler_ptr_)
4968section_ptr = c_null_ptr
4969allocate(section_c_type(len(section)+1))
4970section_c_type = string_f2c(section)
4971section_ptr = c_loc(section_c_type)
4972name_ptr = c_null_ptr
4973allocate(name_c_type(len(name)+1))
4974name_c_type = string_f2c(name)
4975name_ptr = c_loc(name_c_type)
4976type_ptr = c_null_ptr
4977type_ptr = c_loc(type)
4978max_length_ptr = c_null_ptr
4979if (present(max_length)) then
4980max_length_ptr = c_loc(max_length)
4981endif
4982append_ptr = c_null_ptr
4983if (present(append)) then
4984append_c_type = append
4985append_ptr = c_loc(append_c_type)
4986endif
4987error_code_ptr = c_null_ptr
4988if (present(error_code)) then
4989error_code_ptr = c_loc(error_code)
4990endif
4991call sirius_option_set_aux(handler_ptr,section_ptr,name_ptr,type_ptr,data_ptr,max_length_ptr,&
4992&append_ptr,error_code_ptr)
4993deallocate(section_c_type)
4994deallocate(name_c_type)
4995if (present(append)) then
4996endif
4997end subroutine sirius_option_set
4998
4999!
5000!> @brief Dump the runtime setup in a file.
5001!> @param [in] handler Simulation context handler.
5002!> @param [in] filename String containing the name of the file.
5003!> @param [out] error_code Error code
5004subroutine sirius_dump_runtime_setup(handler,filename,error_code)
5005implicit none
5006!
5007type(sirius_context_handler), target, intent(in) :: handler
5008character(*), target, intent(in) :: filename
5009integer, optional, target, intent(out) :: error_code
5010!
5011type(c_ptr) :: handler_ptr
5012type(c_ptr) :: filename_ptr
5013character(C_CHAR), target, allocatable :: filename_c_type(:)
5014type(c_ptr) :: error_code_ptr
5015!
5016interface
5017subroutine sirius_dump_runtime_setup_aux(handler,filename,error_code)&
5018&bind(C, name="sirius_dump_runtime_setup")
5019use, intrinsic :: iso_c_binding
5020type(c_ptr), value :: handler
5021type(c_ptr), value :: filename
5022type(c_ptr), value :: error_code
5023end subroutine
5024end interface
5025!
5026handler_ptr = c_null_ptr
5027handler_ptr = c_loc(handler%handler_ptr_)
5028filename_ptr = c_null_ptr
5029allocate(filename_c_type(len(filename)+1))
5030filename_c_type = string_f2c(filename)
5031filename_ptr = c_loc(filename_c_type)
5032error_code_ptr = c_null_ptr
5033if (present(error_code)) then
5034error_code_ptr = c_loc(error_code)
5035endif
5036call sirius_dump_runtime_setup_aux(handler_ptr,filename_ptr,error_code_ptr)
5037deallocate(filename_c_type)
5038end subroutine sirius_dump_runtime_setup
5039
5040!
5041!> @brief Get the first-variational eigen vectors
5042!> @param [in] handler K-point set handler
5043!> @param [in] ik Global index of the k-point
5044!> @param [out] fv_evec Output first-variational eigenvector array
5045!> @param [in] ld Leading dimension of fv_evec
5046!> @param [in] num_fv_states Number of first-variational states
5047!> @param [out] error_code Error code
5048subroutine sirius_get_fv_eigen_vectors(handler,ik,fv_evec,ld,num_fv_states,error_code)
5049implicit none
5050!
5051type(sirius_kpoint_set_handler), target, intent(in) :: handler
5052integer, target, intent(in) :: ik
5053complex(8), target, intent(out) :: fv_evec(:,:)
5054integer, target, intent(in) :: ld
5055integer, target, intent(in) :: num_fv_states
5056integer, optional, target, intent(out) :: error_code
5057!
5058type(c_ptr) :: handler_ptr
5059type(c_ptr) :: ik_ptr
5060type(c_ptr) :: fv_evec_ptr
5061type(c_ptr) :: ld_ptr
5062type(c_ptr) :: num_fv_states_ptr
5063type(c_ptr) :: error_code_ptr
5064!
5065interface
5066subroutine sirius_get_fv_eigen_vectors_aux(handler,ik,fv_evec,ld,num_fv_states,error_code)&
5067&bind(C, name="sirius_get_fv_eigen_vectors")
5068use, intrinsic :: iso_c_binding
5069type(c_ptr), value :: handler
5070type(c_ptr), value :: ik
5071type(c_ptr), value :: fv_evec
5072type(c_ptr), value :: ld
5073type(c_ptr), value :: num_fv_states
5074type(c_ptr), value :: error_code
5075end subroutine
5076end interface
5077!
5078handler_ptr = c_null_ptr
5079handler_ptr = c_loc(handler%handler_ptr_)
5080ik_ptr = c_null_ptr
5081ik_ptr = c_loc(ik)
5082fv_evec_ptr = c_null_ptr
5083fv_evec_ptr = c_loc(fv_evec)
5084ld_ptr = c_null_ptr
5085ld_ptr = c_loc(ld)
5086num_fv_states_ptr = c_null_ptr
5087num_fv_states_ptr = c_loc(num_fv_states)
5088error_code_ptr = c_null_ptr
5089if (present(error_code)) then
5090error_code_ptr = c_loc(error_code)
5091endif
5092call sirius_get_fv_eigen_vectors_aux(handler_ptr,ik_ptr,fv_evec_ptr,ld_ptr,num_fv_states_ptr,&
5093&error_code_ptr)
5094end subroutine sirius_get_fv_eigen_vectors
5095
5096!
5097!> @brief Get the first-variational eigen values
5098!> @param [in] handler K-point set handler
5099!> @param [in] ik Global index of the k-point
5100!> @param [out] fv_eval Output first-variational eigenvector array
5101!> @param [in] num_fv_states Number of first-variational states
5102!> @param [out] error_code Error code
5103subroutine sirius_get_fv_eigen_values(handler,ik,fv_eval,num_fv_states,error_code)
5104implicit none
5105!
5106type(sirius_kpoint_set_handler), target, intent(in) :: handler
5107integer, target, intent(in) :: ik
5108real(8), target, intent(out) :: fv_eval(:)
5109integer, target, intent(in) :: num_fv_states
5110integer, optional, target, intent(out) :: error_code
5111!
5112type(c_ptr) :: handler_ptr
5113type(c_ptr) :: ik_ptr
5114type(c_ptr) :: fv_eval_ptr
5115type(c_ptr) :: num_fv_states_ptr
5116type(c_ptr) :: error_code_ptr
5117!
5118interface
5119subroutine sirius_get_fv_eigen_values_aux(handler,ik,fv_eval,num_fv_states,error_code)&
5120&bind(C, name="sirius_get_fv_eigen_values")
5121use, intrinsic :: iso_c_binding
5122type(c_ptr), value :: handler
5123type(c_ptr), value :: ik
5124type(c_ptr), value :: fv_eval
5125type(c_ptr), value :: num_fv_states
5126type(c_ptr), value :: error_code
5127end subroutine
5128end interface
5129!
5130handler_ptr = c_null_ptr
5131handler_ptr = c_loc(handler%handler_ptr_)
5132ik_ptr = c_null_ptr
5133ik_ptr = c_loc(ik)
5134fv_eval_ptr = c_null_ptr
5135fv_eval_ptr = c_loc(fv_eval)
5136num_fv_states_ptr = c_null_ptr
5137num_fv_states_ptr = c_loc(num_fv_states)
5138error_code_ptr = c_null_ptr
5139if (present(error_code)) then
5140error_code_ptr = c_loc(error_code)
5141endif
5142call sirius_get_fv_eigen_values_aux(handler_ptr,ik_ptr,fv_eval_ptr,num_fv_states_ptr,&
5143&error_code_ptr)
5144end subroutine sirius_get_fv_eigen_values
5145
5146!
5147!> @brief Get the second-variational eigen vectors
5148!> @param [in] handler K-point set handler
5149!> @param [in] ik Global index of the k-point
5150!> @param [out] sv_evec Output second-variational eigenvector array
5151!> @param [in] num_bands Number of second-variational bands.
5152!> @param [out] error_code Error code
5153subroutine sirius_get_sv_eigen_vectors(handler,ik,sv_evec,num_bands,error_code)
5154implicit none
5155!
5156type(sirius_kpoint_set_handler), target, intent(in) :: handler
5157integer, target, intent(in) :: ik
5158complex(8), target, intent(out) :: sv_evec(:,:)
5159integer, target, intent(in) :: num_bands
5160integer, optional, target, intent(out) :: error_code
5161!
5162type(c_ptr) :: handler_ptr
5163type(c_ptr) :: ik_ptr
5164type(c_ptr) :: sv_evec_ptr
5165type(c_ptr) :: num_bands_ptr
5166type(c_ptr) :: error_code_ptr
5167!
5168interface
5169subroutine sirius_get_sv_eigen_vectors_aux(handler,ik,sv_evec,num_bands,error_code)&
5170&bind(C, name="sirius_get_sv_eigen_vectors")
5171use, intrinsic :: iso_c_binding
5172type(c_ptr), value :: handler
5173type(c_ptr), value :: ik
5174type(c_ptr), value :: sv_evec
5175type(c_ptr), value :: num_bands
5176type(c_ptr), value :: error_code
5177end subroutine
5178end interface
5179!
5180handler_ptr = c_null_ptr
5181handler_ptr = c_loc(handler%handler_ptr_)
5182ik_ptr = c_null_ptr
5183ik_ptr = c_loc(ik)
5184sv_evec_ptr = c_null_ptr
5185sv_evec_ptr = c_loc(sv_evec)
5186num_bands_ptr = c_null_ptr
5187num_bands_ptr = c_loc(num_bands)
5188error_code_ptr = c_null_ptr
5189if (present(error_code)) then
5190error_code_ptr = c_loc(error_code)
5191endif
5192call sirius_get_sv_eigen_vectors_aux(handler_ptr,ik_ptr,sv_evec_ptr,num_bands_ptr,&
5193&error_code_ptr)
5194end subroutine sirius_get_sv_eigen_vectors
5195
5196!
5197!> @brief Set the values of the function on the regular grid.
5198!> @param [in] handler DFT ground state handler.
5199!> @param [in] label Label of the function.
5200!> @param [in] grid_dims Dimensions of the FFT grid.
5201!> @param [in] local_box_origin Coordinates of the local box origin for each MPI rank
5202!> @param [in] local_box_size Dimensions of the local box for each MPI rank.
5203!> @param [in] fcomm Fortran communicator used to partition FFT grid into local boxes.
5204!> @param [in] values Values of the function (local buffer for each MPI rank).
5205!> @param [in] transform_to_pw If true, transform function to PW domain.
5206!> @param [out] error_code Error code
5207subroutine sirius_set_rg_values(handler,label,grid_dims,local_box_origin,local_box_size,&
5208&fcomm,values,transform_to_pw,error_code)
5209implicit none
5210!
5211type(sirius_ground_state_handler), target, intent(in) :: handler
5212character(*), target, intent(in) :: label
5213integer, target, intent(in) :: grid_dims(3)
5214integer, target, intent(in) :: local_box_origin(:,:)
5215integer, target, intent(in) :: local_box_size(:,:)
5216integer, target, intent(in) :: fcomm
5217real(8), target, intent(in) :: values
5218logical, optional, target, intent(in) :: transform_to_pw
5219integer, optional, target, intent(out) :: error_code
5220!
5221type(c_ptr) :: handler_ptr
5222type(c_ptr) :: label_ptr
5223character(C_CHAR), target, allocatable :: label_c_type(:)
5224type(c_ptr) :: grid_dims_ptr
5225type(c_ptr) :: local_box_origin_ptr
5226type(c_ptr) :: local_box_size_ptr
5227type(c_ptr) :: fcomm_ptr
5228type(c_ptr) :: values_ptr
5229type(c_ptr) :: transform_to_pw_ptr
5230logical(C_BOOL), target :: transform_to_pw_c_type
5231type(c_ptr) :: error_code_ptr
5232!
5233interface
5234subroutine sirius_set_rg_values_aux(handler,label,grid_dims,local_box_origin,local_box_size,&
5235&fcomm,values,transform_to_pw,error_code)&
5236&bind(C, name="sirius_set_rg_values")
5237use, intrinsic :: iso_c_binding
5238type(c_ptr), value :: handler
5239type(c_ptr), value :: label
5240type(c_ptr), value :: grid_dims
5241type(c_ptr), value :: local_box_origin
5242type(c_ptr), value :: local_box_size
5243type(c_ptr), value :: fcomm
5244type(c_ptr), value :: values
5245type(c_ptr), value :: transform_to_pw
5246type(c_ptr), value :: error_code
5247end subroutine
5248end interface
5249!
5250handler_ptr = c_null_ptr
5251handler_ptr = c_loc(handler%handler_ptr_)
5252label_ptr = c_null_ptr
5253allocate(label_c_type(len(label)+1))
5254label_c_type = string_f2c(label)
5255label_ptr = c_loc(label_c_type)
5256grid_dims_ptr = c_null_ptr
5257grid_dims_ptr = c_loc(grid_dims)
5258local_box_origin_ptr = c_null_ptr
5259local_box_origin_ptr = c_loc(local_box_origin)
5260local_box_size_ptr = c_null_ptr
5261local_box_size_ptr = c_loc(local_box_size)
5262fcomm_ptr = c_null_ptr
5263fcomm_ptr = c_loc(fcomm)
5264values_ptr = c_null_ptr
5265values_ptr = c_loc(values)
5266transform_to_pw_ptr = c_null_ptr
5267if (present(transform_to_pw)) then
5268transform_to_pw_c_type = transform_to_pw
5269transform_to_pw_ptr = c_loc(transform_to_pw_c_type)
5270endif
5271error_code_ptr = c_null_ptr
5272if (present(error_code)) then
5273error_code_ptr = c_loc(error_code)
5274endif
5275call sirius_set_rg_values_aux(handler_ptr,label_ptr,grid_dims_ptr,local_box_origin_ptr,&
5276&local_box_size_ptr,fcomm_ptr,values_ptr,transform_to_pw_ptr,error_code_ptr)
5277deallocate(label_c_type)
5278if (present(transform_to_pw)) then
5279endif
5280end subroutine sirius_set_rg_values
5281
5282!
5283!> @brief Get the values of the function on the regular grid.
5284!> @param [in] handler DFT ground state handler.
5285!> @param [in] label Label of the function.
5286!> @param [in] grid_dims Dimensions of the FFT grid.
5287!> @param [in] local_box_origin Coordinates of the local box origin for each MPI rank
5288!> @param [in] local_box_size Dimensions of the local box for each MPI rank.
5289!> @param [in] fcomm Fortran communicator used to partition FFT grid into local boxes.
5290!> @param [out] values Values of the function (local buffer for each MPI rank).
5291!> @param [in] transform_to_rg If true, transform function to regular grid before fetching the values.
5292!> @param [out] error_code Error code
5293subroutine sirius_get_rg_values(handler,label,grid_dims,local_box_origin,local_box_size,&
5294&fcomm,values,transform_to_rg,error_code)
5295implicit none
5296!
5297type(sirius_ground_state_handler), target, intent(in) :: handler
5298character(*), target, intent(in) :: label
5299integer, target, intent(in) :: grid_dims(3)
5300integer, target, intent(in) :: local_box_origin(:,:)
5301integer, target, intent(in) :: local_box_size(:,:)
5302integer, target, intent(in) :: fcomm
5303real(8), target, intent(out) :: values
5304logical, optional, target, intent(in) :: transform_to_rg
5305integer, optional, target, intent(out) :: error_code
5306!
5307type(c_ptr) :: handler_ptr
5308type(c_ptr) :: label_ptr
5309character(C_CHAR), target, allocatable :: label_c_type(:)
5310type(c_ptr) :: grid_dims_ptr
5311type(c_ptr) :: local_box_origin_ptr
5312type(c_ptr) :: local_box_size_ptr
5313type(c_ptr) :: fcomm_ptr
5314type(c_ptr) :: values_ptr
5315type(c_ptr) :: transform_to_rg_ptr
5316logical(C_BOOL), target :: transform_to_rg_c_type
5317type(c_ptr) :: error_code_ptr
5318!
5319interface
5320subroutine sirius_get_rg_values_aux(handler,label,grid_dims,local_box_origin,local_box_size,&
5321&fcomm,values,transform_to_rg,error_code)&
5322&bind(C, name="sirius_get_rg_values")
5323use, intrinsic :: iso_c_binding
5324type(c_ptr), value :: handler
5325type(c_ptr), value :: label
5326type(c_ptr), value :: grid_dims
5327type(c_ptr), value :: local_box_origin
5328type(c_ptr), value :: local_box_size
5329type(c_ptr), value :: fcomm
5330type(c_ptr), value :: values
5331type(c_ptr), value :: transform_to_rg
5332type(c_ptr), value :: error_code
5333end subroutine
5334end interface
5335!
5336handler_ptr = c_null_ptr
5337handler_ptr = c_loc(handler%handler_ptr_)
5338label_ptr = c_null_ptr
5339allocate(label_c_type(len(label)+1))
5340label_c_type = string_f2c(label)
5341label_ptr = c_loc(label_c_type)
5342grid_dims_ptr = c_null_ptr
5343grid_dims_ptr = c_loc(grid_dims)
5344local_box_origin_ptr = c_null_ptr
5345local_box_origin_ptr = c_loc(local_box_origin)
5346local_box_size_ptr = c_null_ptr
5347local_box_size_ptr = c_loc(local_box_size)
5348fcomm_ptr = c_null_ptr
5349fcomm_ptr = c_loc(fcomm)
5350values_ptr = c_null_ptr
5351values_ptr = c_loc(values)
5352transform_to_rg_ptr = c_null_ptr
5353if (present(transform_to_rg)) then
5354transform_to_rg_c_type = transform_to_rg
5355transform_to_rg_ptr = c_loc(transform_to_rg_c_type)
5356endif
5357error_code_ptr = c_null_ptr
5358if (present(error_code)) then
5359error_code_ptr = c_loc(error_code)
5360endif
5361call sirius_get_rg_values_aux(handler_ptr,label_ptr,grid_dims_ptr,local_box_origin_ptr,&
5362&local_box_size_ptr,fcomm_ptr,values_ptr,transform_to_rg_ptr,error_code_ptr)
5363deallocate(label_c_type)
5364if (present(transform_to_rg)) then
5365endif
5366end subroutine sirius_get_rg_values
5367
5368!
5369!> @brief Get the total magnetization of the system.
5370!> @param [in] handler DFT ground state handler.
5371!> @param [out] mag 3D magnetization vector (x,y,z components).
5372!> @param [out] error_code Error code
5373subroutine sirius_get_total_magnetization(handler,mag,error_code)
5374implicit none
5375!
5376type(sirius_ground_state_handler), target, intent(in) :: handler
5377real(8), target, intent(out) :: mag
5378integer, optional, target, intent(out) :: error_code
5379!
5380type(c_ptr) :: handler_ptr
5381type(c_ptr) :: mag_ptr
5382type(c_ptr) :: error_code_ptr
5383!
5384interface
5385subroutine sirius_get_total_magnetization_aux(handler,mag,error_code)&
5386&bind(C, name="sirius_get_total_magnetization")
5387use, intrinsic :: iso_c_binding
5388type(c_ptr), value :: handler
5389type(c_ptr), value :: mag
5390type(c_ptr), value :: error_code
5391end subroutine
5392end interface
5393!
5394handler_ptr = c_null_ptr
5395handler_ptr = c_loc(handler%handler_ptr_)
5396mag_ptr = c_null_ptr
5397mag_ptr = c_loc(mag)
5398error_code_ptr = c_null_ptr
5399if (present(error_code)) then
5400error_code_ptr = c_loc(error_code)
5401endif
5402call sirius_get_total_magnetization_aux(handler_ptr,mag_ptr,error_code_ptr)
5403end subroutine sirius_get_total_magnetization
5404
5405!
5406!> @brief Get the total number of kpoints
5407!> @param [in] handler Kpoint set handler
5408!> @param [out] num_kpoints number of kpoints in the set
5409!> @param [out] error_code Error code.
5410subroutine sirius_get_num_kpoints(handler,num_kpoints,error_code)
5411implicit none
5412!
5413type(sirius_kpoint_set_handler), target, intent(in) :: handler
5414integer, target, intent(out) :: num_kpoints
5415integer, optional, target, intent(out) :: error_code
5416!
5417type(c_ptr) :: handler_ptr
5418type(c_ptr) :: num_kpoints_ptr
5419type(c_ptr) :: error_code_ptr
5420!
5421interface
5422subroutine sirius_get_num_kpoints_aux(handler,num_kpoints,error_code)&
5423&bind(C, name="sirius_get_num_kpoints")
5424use, intrinsic :: iso_c_binding
5425type(c_ptr), value :: handler
5426type(c_ptr), value :: num_kpoints
5427type(c_ptr), value :: error_code
5428end subroutine
5429end interface
5430!
5431handler_ptr = c_null_ptr
5432handler_ptr = c_loc(handler%handler_ptr_)
5433num_kpoints_ptr = c_null_ptr
5434num_kpoints_ptr = c_loc(num_kpoints)
5435error_code_ptr = c_null_ptr
5436if (present(error_code)) then
5437error_code_ptr = c_loc(error_code)
5438endif
5439call sirius_get_num_kpoints_aux(handler_ptr,num_kpoints_ptr,error_code_ptr)
5440end subroutine sirius_get_num_kpoints
5441
5442!
5443!> @brief Get the kpoint properties
5444!> @param [in] handler Kpoint set handler
5445!> @param [in] ik Index of the kpoint
5446!> @param [out] weight Weight of the kpoint
5447!> @param [out] coordinates Coordinates of the kpoint
5448!> @param [out] error_code Error code.
5449subroutine sirius_get_kpoint_properties(handler,ik,weight,coordinates,error_code)
5450implicit none
5451!
5452type(sirius_kpoint_set_handler), target, intent(in) :: handler
5453integer, target, intent(in) :: ik
5454real(8), target, intent(out) :: weight
5455real(8), optional, target, intent(out) :: coordinates
5456integer, optional, target, intent(out) :: error_code
5457!
5458type(c_ptr) :: handler_ptr
5459type(c_ptr) :: ik_ptr
5460type(c_ptr) :: weight_ptr
5461type(c_ptr) :: coordinates_ptr
5462type(c_ptr) :: error_code_ptr
5463!
5464interface
5465subroutine sirius_get_kpoint_properties_aux(handler,ik,weight,coordinates,error_code)&
5466&bind(C, name="sirius_get_kpoint_properties")
5467use, intrinsic :: iso_c_binding
5468type(c_ptr), value :: handler
5469type(c_ptr), value :: ik
5470type(c_ptr), value :: weight
5471type(c_ptr), value :: coordinates
5472type(c_ptr), value :: error_code
5473end subroutine
5474end interface
5475!
5476handler_ptr = c_null_ptr
5477handler_ptr = c_loc(handler%handler_ptr_)
5478ik_ptr = c_null_ptr
5479ik_ptr = c_loc(ik)
5480weight_ptr = c_null_ptr
5481weight_ptr = c_loc(weight)
5482coordinates_ptr = c_null_ptr
5483if (present(coordinates)) then
5484coordinates_ptr = c_loc(coordinates)
5485endif
5486error_code_ptr = c_null_ptr
5487if (present(error_code)) then
5488error_code_ptr = c_loc(error_code)
5489endif
5490call sirius_get_kpoint_properties_aux(handler_ptr,ik_ptr,weight_ptr,coordinates_ptr,&
5491&error_code_ptr)
5492end subroutine sirius_get_kpoint_properties
5493
5494!
5495!> @brief Set callback function to compute various radial integrals.
5496!> @param [in] handler Simulation context handler.
5497!> @param [in] label Lable of the callback function.
5498!> @param [in] fptr Pointer to callback function.
5499!> @param [out] error_code Error code.
5500subroutine sirius_set_callback_function(handler,label,fptr,error_code)
5501implicit none
5502!
5503type(sirius_context_handler), target, intent(in) :: handler
5504character(*), target, intent(in) :: label
5505type(c_funptr), value, intent(in) :: fptr
5506integer, optional, target, intent(out) :: error_code
5507!
5508type(c_ptr) :: handler_ptr
5509type(c_ptr) :: label_ptr
5510character(C_CHAR), target, allocatable :: label_c_type(:)
5511type(c_ptr) :: error_code_ptr
5512!
5513interface
5514subroutine sirius_set_callback_function_aux(handler,label,fptr,error_code)&
5515&bind(C, name="sirius_set_callback_function")
5516use, intrinsic :: iso_c_binding
5517type(c_ptr), value :: handler
5518type(c_ptr), value :: label
5519type(c_funptr), value :: fptr
5520type(c_ptr), value :: error_code
5521end subroutine
5522end interface
5523!
5524handler_ptr = c_null_ptr
5525handler_ptr = c_loc(handler%handler_ptr_)
5526label_ptr = c_null_ptr
5527allocate(label_c_type(len(label)+1))
5528label_c_type = string_f2c(label)
5529label_ptr = c_loc(label_c_type)
5530error_code_ptr = c_null_ptr
5531if (present(error_code)) then
5532error_code_ptr = c_loc(error_code)
5533endif
5534call sirius_set_callback_function_aux(handler_ptr,label_ptr,fptr,error_code_ptr)
5535deallocate(label_c_type)
5536end subroutine sirius_set_callback_function
5537
5538!
5539!> @brief Robust wave function optimizer.
5540!> @param [in] handler Ground state handler.
5541!> @param [in] ks_handler K-point set handler.
5542!> @param [out] error_code Error code.
5543subroutine sirius_nlcg(handler,ks_handler,error_code)
5544implicit none
5545!
5546type(sirius_ground_state_handler), target, intent(in) :: handler
5547type(sirius_kpoint_set_handler), target, intent(in) :: ks_handler
5548integer, optional, target, intent(out) :: error_code
5549!
5550type(c_ptr) :: handler_ptr
5551type(c_ptr) :: ks_handler_ptr
5552type(c_ptr) :: error_code_ptr
5553!
5554interface
5555subroutine sirius_nlcg_aux(handler,ks_handler,error_code)&
5556&bind(C, name="sirius_nlcg")
5557use, intrinsic :: iso_c_binding
5558type(c_ptr), value :: handler
5559type(c_ptr), value :: ks_handler
5560type(c_ptr), value :: error_code
5561end subroutine
5562end interface
5563!
5564handler_ptr = c_null_ptr
5565handler_ptr = c_loc(handler%handler_ptr_)
5566ks_handler_ptr = c_null_ptr
5567ks_handler_ptr = c_loc(ks_handler%handler_ptr_)
5568error_code_ptr = c_null_ptr
5569if (present(error_code)) then
5570error_code_ptr = c_loc(error_code)
5571endif
5572call sirius_nlcg_aux(handler_ptr,ks_handler_ptr,error_code_ptr)
5573end subroutine sirius_nlcg
5574
5575!
5576!> @brief Robust wave function optimizer
5577!> @param [in] handler Ground state handler.
5578!> @param [in] ks_handler K-point set handler.
5579!> @param [in] temp Temperature in Kelvin
5580!> @param [in] smearing smearing label
5581!> @param [in] kappa pseudo-Hamiltonian scalar preconditioner
5582!> @param [in] tau backtracking search reduction parameter
5583!> @param [in] tol CG tolerance
5584!> @param [in] maxiter CG maxiter
5585!> @param [in] restart CG restart
5586!> @param [in] processing_unit processing_unit = ["cpu"|"gpu"|"none"]
5587!> @param [out] converged None
5588!> @param [out] error_code Error code.
5589subroutine sirius_nlcg_params(handler,ks_handler,temp,smearing,kappa,tau,tol,maxiter,&
5590&restart,processing_unit,converged,error_code)
5591implicit none
5592!
5593type(sirius_ground_state_handler), target, intent(in) :: handler
5594type(sirius_kpoint_set_handler), target, intent(in) :: ks_handler
5595real(8), target, intent(in) :: temp
5596character(*), target, intent(in) :: smearing
5597real(8), target, intent(in) :: kappa
5598real(8), target, intent(in) :: tau
5599real(8), target, intent(in) :: tol
5600integer, target, intent(in) :: maxiter
5601integer, target, intent(in) :: restart
5602character(*), target, intent(in) :: processing_unit
5603logical, target, intent(out) :: converged
5604integer, optional, target, intent(out) :: error_code
5605!
5606type(c_ptr) :: handler_ptr
5607type(c_ptr) :: ks_handler_ptr
5608type(c_ptr) :: temp_ptr
5609type(c_ptr) :: smearing_ptr
5610character(C_CHAR), target, allocatable :: smearing_c_type(:)
5611type(c_ptr) :: kappa_ptr
5612type(c_ptr) :: tau_ptr
5613type(c_ptr) :: tol_ptr
5614type(c_ptr) :: maxiter_ptr
5615type(c_ptr) :: restart_ptr
5616type(c_ptr) :: processing_unit_ptr
5617character(C_CHAR), target, allocatable :: processing_unit_c_type(:)
5618type(c_ptr) :: converged_ptr
5619logical(C_BOOL), target :: converged_c_type
5620type(c_ptr) :: error_code_ptr
5621!
5622interface
5623subroutine sirius_nlcg_params_aux(handler,ks_handler,temp,smearing,kappa,tau,tol,&
5624&maxiter,restart,processing_unit,converged,error_code)&
5625&bind(C, name="sirius_nlcg_params")
5626use, intrinsic :: iso_c_binding
5627type(c_ptr), value :: handler
5628type(c_ptr), value :: ks_handler
5629type(c_ptr), value :: temp
5630type(c_ptr), value :: smearing
5631type(c_ptr), value :: kappa
5632type(c_ptr), value :: tau
5633type(c_ptr), value :: tol
5634type(c_ptr), value :: maxiter
5635type(c_ptr), value :: restart
5636type(c_ptr), value :: processing_unit
5637type(c_ptr), value :: converged
5638type(c_ptr), value :: error_code
5639end subroutine
5640end interface
5641!
5642handler_ptr = c_null_ptr
5643handler_ptr = c_loc(handler%handler_ptr_)
5644ks_handler_ptr = c_null_ptr
5645ks_handler_ptr = c_loc(ks_handler%handler_ptr_)
5646temp_ptr = c_null_ptr
5647temp_ptr = c_loc(temp)
5648smearing_ptr = c_null_ptr
5649allocate(smearing_c_type(len(smearing)+1))
5650smearing_c_type = string_f2c(smearing)
5651smearing_ptr = c_loc(smearing_c_type)
5652kappa_ptr = c_null_ptr
5653kappa_ptr = c_loc(kappa)
5654tau_ptr = c_null_ptr
5655tau_ptr = c_loc(tau)
5656tol_ptr = c_null_ptr
5657tol_ptr = c_loc(tol)
5658maxiter_ptr = c_null_ptr
5659maxiter_ptr = c_loc(maxiter)
5660restart_ptr = c_null_ptr
5661restart_ptr = c_loc(restart)
5662processing_unit_ptr = c_null_ptr
5663allocate(processing_unit_c_type(len(processing_unit)+1))
5664processing_unit_c_type = string_f2c(processing_unit)
5665processing_unit_ptr = c_loc(processing_unit_c_type)
5666converged_ptr = c_null_ptr
5667converged_ptr = c_loc(converged_c_type)
5668error_code_ptr = c_null_ptr
5669if (present(error_code)) then
5670error_code_ptr = c_loc(error_code)
5671endif
5672call sirius_nlcg_params_aux(handler_ptr,ks_handler_ptr,temp_ptr,smearing_ptr,kappa_ptr,&
5673&tau_ptr,tol_ptr,maxiter_ptr,restart_ptr,processing_unit_ptr,converged_ptr,error_code_ptr)
5674deallocate(smearing_c_type)
5675deallocate(processing_unit_c_type)
5676converged = converged_c_type
5677end subroutine sirius_nlcg_params
5678
5679!
5680!> @brief Add a non-local Hubbard interaction V for a pair of atoms.
5681!> @param [in] handler Simulation context handler.
5682!> @param [in] atom_pair atom pair for the V term
5683!> @param [in] translation translation vector between the two unit cells containing the atoms
5684!> @param [in] n principal quantum number of the atomic levels involved in the V correction
5685!> @param [in] l angular momentum of the atomic levels
5686!> @param [in] coupling value of the V constant
5687!> @param [out] error_code Error code.
5688subroutine sirius_add_hubbard_atom_pair(handler,atom_pair,translation,n,l,coupling,&
5689&error_code)
5690implicit none
5691!
5692type(sirius_context_handler), target, intent(in) :: handler
5693integer, target, intent(in) :: atom_pair(2)
5694integer, target, intent(in) :: translation(3)
5695integer, target, intent(in) :: n(2)
5696integer, target, intent(in) :: l(2)
5697real(8), target, intent(in) :: coupling
5698integer, optional, target, intent(out) :: error_code
5699!
5700type(c_ptr) :: handler_ptr
5701type(c_ptr) :: atom_pair_ptr
5702type(c_ptr) :: translation_ptr
5703type(c_ptr) :: n_ptr
5704type(c_ptr) :: l_ptr
5705type(c_ptr) :: coupling_ptr
5706type(c_ptr) :: error_code_ptr
5707!
5708interface
5709subroutine sirius_add_hubbard_atom_pair_aux(handler,atom_pair,translation,n,l,coupling,&
5710&error_code)&
5711&bind(C, name="sirius_add_hubbard_atom_pair")
5712use, intrinsic :: iso_c_binding
5713type(c_ptr), value :: handler
5714type(c_ptr), value :: atom_pair
5715type(c_ptr), value :: translation
5716type(c_ptr), value :: n
5717type(c_ptr), value :: l
5718type(c_ptr), value :: coupling
5719type(c_ptr), value :: error_code
5720end subroutine
5721end interface
5722!
5723handler_ptr = c_null_ptr
5724handler_ptr = c_loc(handler%handler_ptr_)
5725atom_pair_ptr = c_null_ptr
5726atom_pair_ptr = c_loc(atom_pair)
5727translation_ptr = c_null_ptr
5728translation_ptr = c_loc(translation)
5729n_ptr = c_null_ptr
5730n_ptr = c_loc(n)
5731l_ptr = c_null_ptr
5732l_ptr = c_loc(l)
5733coupling_ptr = c_null_ptr
5734coupling_ptr = c_loc(coupling)
5735error_code_ptr = c_null_ptr
5736if (present(error_code)) then
5737error_code_ptr = c_loc(error_code)
5738endif
5739call sirius_add_hubbard_atom_pair_aux(handler_ptr,atom_pair_ptr,translation_ptr,&
5740&n_ptr,l_ptr,coupling_ptr,error_code_ptr)
5741end subroutine sirius_add_hubbard_atom_pair
5742
5743!
5744!> @brief Generate H0.
5745!> @param [in] handler Ground state handler.
5746!> @param [out] error_code Error code
5747subroutine sirius_create_h0(handler,error_code)
5748implicit none
5749!
5750type(sirius_ground_state_handler), target, intent(in) :: handler
5751integer, optional, target, intent(out) :: error_code
5752!
5753type(c_ptr) :: handler_ptr
5754type(c_ptr) :: error_code_ptr
5755!
5756interface
5757subroutine sirius_create_h0_aux(handler,error_code)&
5758&bind(C, name="sirius_create_H0")
5759use, intrinsic :: iso_c_binding
5760type(c_ptr), value :: handler
5761type(c_ptr), value :: error_code
5762end subroutine
5763end interface
5764!
5765handler_ptr = c_null_ptr
5766handler_ptr = c_loc(handler%handler_ptr_)
5767error_code_ptr = c_null_ptr
5768if (present(error_code)) then
5769error_code_ptr = c_loc(error_code)
5770endif
5771call sirius_create_h0_aux(handler_ptr,error_code_ptr)
5772end subroutine sirius_create_h0
5773
5774!
5775!> @brief Interface to linear solver.
5776!> @param [in] handler DFT ground state handler.
5777!> @param [in] vkq K+q-point in lattice coordinates
5778!> @param [in] num_gvec_kq_loc Local number of G-vectors for k+q-point
5779!> @param [in] gvec_kq_loc Local list of G-vectors for k+q-point.
5780!> @param [inout] dpsi Left-hand side of the linear equation.
5781!> @param [in] psi Unperturbed eigenvectors.
5782!> @param [in] eigvals Unperturbed eigenvalues.
5783!> @param [inout] dvpsi Right-hand side of the linear equation (dV * psi)
5784!> @param [in] ld Leading dimension of dpsi, psi, dvpsi.
5785!> @param [in] num_spin_comp Number of spin components.
5786!> @param [in] alpha_pv Constant for the projector.
5787!> @param [in] spin Current spin channel.
5788!> @param [in] nbnd_occ Number of occupied bands.
5789!> @param [in] tol Tolerance for the unconverged residuals (residual L2-norm should be below this value).
5790!> @param [out] niter Average number of iterations.
5791!> @param [out] error_code Error code
5792subroutine sirius_linear_solver(handler,vkq,num_gvec_kq_loc,gvec_kq_loc,dpsi,psi,&
5793&eigvals,dvpsi,ld,num_spin_comp,alpha_pv,spin,nbnd_occ,tol,niter,error_code)
5794implicit none
5795!
5796type(sirius_ground_state_handler), target, intent(in) :: handler
5797real(8), target, intent(in) :: vkq(3)
5798integer, target, intent(in) :: num_gvec_kq_loc
5799integer, target, intent(in) :: gvec_kq_loc(3, num_gvec_kq_loc)
5800complex(8), target, intent(inout) :: dpsi(ld, num_spin_comp)
5801complex(8), target, intent(in) :: psi(ld, num_spin_comp)
5802real(8), target, intent(in) :: eigvals(*)
5803complex(8), target, intent(inout) :: dvpsi(ld, num_spin_comp)
5804integer, target, intent(in) :: ld
5805integer, target, intent(in) :: num_spin_comp
5806real(8), target, intent(in) :: alpha_pv
5807integer, target, intent(in) :: spin
5808integer, target, intent(in) :: nbnd_occ
5809real(8), target, intent(in) :: tol
5810integer, target, intent(out) :: niter
5811integer, optional, target, intent(out) :: error_code
5812!
5813type(c_ptr) :: handler_ptr
5814type(c_ptr) :: vkq_ptr
5815type(c_ptr) :: num_gvec_kq_loc_ptr
5816type(c_ptr) :: gvec_kq_loc_ptr
5817type(c_ptr) :: dpsi_ptr
5818type(c_ptr) :: psi_ptr
5819type(c_ptr) :: eigvals_ptr
5820type(c_ptr) :: dvpsi_ptr
5821type(c_ptr) :: ld_ptr
5822type(c_ptr) :: num_spin_comp_ptr
5823type(c_ptr) :: alpha_pv_ptr
5824type(c_ptr) :: spin_ptr
5825type(c_ptr) :: nbnd_occ_ptr
5826type(c_ptr) :: tol_ptr
5827type(c_ptr) :: niter_ptr
5828type(c_ptr) :: error_code_ptr
5829!
5830interface
5831subroutine sirius_linear_solver_aux(handler,vkq,num_gvec_kq_loc,gvec_kq_loc,dpsi,&
5832&psi,eigvals,dvpsi,ld,num_spin_comp,alpha_pv,spin,nbnd_occ,tol,niter,error_code)&
5833&bind(C, name="sirius_linear_solver")
5834use, intrinsic :: iso_c_binding
5835type(c_ptr), value :: handler
5836type(c_ptr), value :: vkq
5837type(c_ptr), value :: num_gvec_kq_loc
5838type(c_ptr), value :: gvec_kq_loc
5839type(c_ptr), value :: dpsi
5840type(c_ptr), value :: psi
5841type(c_ptr), value :: eigvals
5842type(c_ptr), value :: dvpsi
5843type(c_ptr), value :: ld
5844type(c_ptr), value :: num_spin_comp
5845type(c_ptr), value :: alpha_pv
5846type(c_ptr), value :: spin
5847type(c_ptr), value :: nbnd_occ
5848type(c_ptr), value :: tol
5849type(c_ptr), value :: niter
5850type(c_ptr), value :: error_code
5851end subroutine
5852end interface
5853!
5854handler_ptr = c_null_ptr
5855handler_ptr = c_loc(handler%handler_ptr_)
5856vkq_ptr = c_null_ptr
5857vkq_ptr = c_loc(vkq)
5858num_gvec_kq_loc_ptr = c_null_ptr
5859num_gvec_kq_loc_ptr = c_loc(num_gvec_kq_loc)
5860gvec_kq_loc_ptr = c_null_ptr
5861gvec_kq_loc_ptr = c_loc(gvec_kq_loc)
5862dpsi_ptr = c_null_ptr
5863dpsi_ptr = c_loc(dpsi)
5864psi_ptr = c_null_ptr
5865psi_ptr = c_loc(psi)
5866eigvals_ptr = c_null_ptr
5867eigvals_ptr = c_loc(eigvals)
5868dvpsi_ptr = c_null_ptr
5869dvpsi_ptr = c_loc(dvpsi)
5870ld_ptr = c_null_ptr
5871ld_ptr = c_loc(ld)
5872num_spin_comp_ptr = c_null_ptr
5873num_spin_comp_ptr = c_loc(num_spin_comp)
5874alpha_pv_ptr = c_null_ptr
5875alpha_pv_ptr = c_loc(alpha_pv)
5876spin_ptr = c_null_ptr
5877spin_ptr = c_loc(spin)
5878nbnd_occ_ptr = c_null_ptr
5879nbnd_occ_ptr = c_loc(nbnd_occ)
5880tol_ptr = c_null_ptr
5881tol_ptr = c_loc(tol)
5882niter_ptr = c_null_ptr
5883niter_ptr = c_loc(niter)
5884error_code_ptr = c_null_ptr
5885if (present(error_code)) then
5886error_code_ptr = c_loc(error_code)
5887endif
5888call sirius_linear_solver_aux(handler_ptr,vkq_ptr,num_gvec_kq_loc_ptr,gvec_kq_loc_ptr,&
5889&dpsi_ptr,psi_ptr,eigvals_ptr,dvpsi_ptr,ld_ptr,num_spin_comp_ptr,alpha_pv_ptr,spin_ptr,&
5890&nbnd_occ_ptr,tol_ptr,niter_ptr,error_code_ptr)
5891end subroutine sirius_linear_solver
5892
5893!
5894!> @brief Generate D-operator matrix.
5895!> @param [in] handler Ground state handler.
5896!> @param [out] error_code Error code
5897subroutine sirius_generate_d_operator_matrix(handler,error_code)
5898implicit none
5899!
5900type(sirius_ground_state_handler), target, intent(in) :: handler
5901integer, optional, target, intent(out) :: error_code
5902!
5903type(c_ptr) :: handler_ptr
5904type(c_ptr) :: error_code_ptr
5905!
5906interface
5907subroutine sirius_generate_d_operator_matrix_aux(handler,error_code)&
5908&bind(C, name="sirius_generate_d_operator_matrix")
5909use, intrinsic :: iso_c_binding
5910type(c_ptr), value :: handler
5911type(c_ptr), value :: error_code
5912end subroutine
5913end interface
5914!
5915handler_ptr = c_null_ptr
5916handler_ptr = c_loc(handler%handler_ptr_)
5917error_code_ptr = c_null_ptr
5918if (present(error_code)) then
5919error_code_ptr = c_loc(error_code)
5920endif
5921call sirius_generate_d_operator_matrix_aux(handler_ptr,error_code_ptr)
5923
5924!
5925!> @brief Save DFT ground state (density and potential)
5926!> @param [in] gs_handler Ground-state handler.
5927!> @param [in] file_name Name of the file that stores the saved data.
5928!> @param [out] error_code Error code
5929subroutine sirius_save_state(gs_handler,file_name,error_code)
5930implicit none
5931!
5932type(sirius_ground_state_handler), target, intent(in) :: gs_handler
5933character(*), target, intent(in) :: file_name
5934integer, optional, target, intent(out) :: error_code
5935!
5936type(c_ptr) :: gs_handler_ptr
5937type(c_ptr) :: file_name_ptr
5938character(C_CHAR), target, allocatable :: file_name_c_type(:)
5939type(c_ptr) :: error_code_ptr
5940!
5941interface
5942subroutine sirius_save_state_aux(gs_handler,file_name,error_code)&
5943&bind(C, name="sirius_save_state")
5944use, intrinsic :: iso_c_binding
5945type(c_ptr), value :: gs_handler
5946type(c_ptr), value :: file_name
5947type(c_ptr), value :: error_code
5948end subroutine
5949end interface
5950!
5951gs_handler_ptr = c_null_ptr
5952gs_handler_ptr = c_loc(gs_handler%handler_ptr_)
5953file_name_ptr = c_null_ptr
5954allocate(file_name_c_type(len(file_name)+1))
5955file_name_c_type = string_f2c(file_name)
5956file_name_ptr = c_loc(file_name_c_type)
5957error_code_ptr = c_null_ptr
5958if (present(error_code)) then
5959error_code_ptr = c_loc(error_code)
5960endif
5961call sirius_save_state_aux(gs_handler_ptr,file_name_ptr,error_code_ptr)
5962deallocate(file_name_c_type)
5963end subroutine sirius_save_state
5964
5965!
5966!> @brief Save DFT ground state (density and potential)
5967!> @param [in] handler Ground-state handler.
5968!> @param [in] file_name Name of the file that stores the saved data.
5969!> @param [out] error_code Error code
5970subroutine sirius_load_state(handler,file_name,error_code)
5971implicit none
5972!
5973type(sirius_ground_state_handler), target, intent(in) :: handler
5974character(*), target, intent(in) :: file_name
5975integer, optional, target, intent(out) :: error_code
5976!
5977type(c_ptr) :: handler_ptr
5978type(c_ptr) :: file_name_ptr
5979character(C_CHAR), target, allocatable :: file_name_c_type(:)
5980type(c_ptr) :: error_code_ptr
5981!
5982interface
5983subroutine sirius_load_state_aux(handler,file_name,error_code)&
5984&bind(C, name="sirius_load_state")
5985use, intrinsic :: iso_c_binding
5986type(c_ptr), value :: handler
5987type(c_ptr), value :: file_name
5988type(c_ptr), value :: error_code
5989end subroutine
5990end interface
5991!
5992handler_ptr = c_null_ptr
5993handler_ptr = c_loc(handler%handler_ptr_)
5994file_name_ptr = c_null_ptr
5995allocate(file_name_c_type(len(file_name)+1))
5996file_name_c_type = string_f2c(file_name)
5997file_name_ptr = c_loc(file_name_c_type)
5998error_code_ptr = c_null_ptr
5999if (present(error_code)) then
6000error_code_ptr = c_loc(error_code)
6001endif
6002call sirius_load_state_aux(handler_ptr,file_name_ptr,error_code_ptr)
6003deallocate(file_name_c_type)
6004end subroutine sirius_load_state
6005
6006!
6007!> @brief Set density matrix.
6008!> @param [in] handler Ground-state handler.
6009!> @param [in] ia Index of atom.
6010!> @param [in] dm Input density matrix.
6011!> @param [in] ld Leading dimension of the density matrix.
6012!> @param [out] error_code Error code.
6013subroutine sirius_set_density_matrix(handler,ia,dm,ld,error_code)
6014implicit none
6015!
6016type(sirius_ground_state_handler), target, intent(in) :: handler
6017integer, target, intent(in) :: ia
6018complex(8), target, intent(in) :: dm(ld, ld, 3)
6019integer, target, intent(in) :: ld
6020integer, optional, target, intent(out) :: error_code
6021!
6022type(c_ptr) :: handler_ptr
6023type(c_ptr) :: ia_ptr
6024type(c_ptr) :: dm_ptr
6025type(c_ptr) :: ld_ptr
6026type(c_ptr) :: error_code_ptr
6027!
6028interface
6029subroutine sirius_set_density_matrix_aux(handler,ia,dm,ld,error_code)&
6030&bind(C, name="sirius_set_density_matrix")
6031use, intrinsic :: iso_c_binding
6032type(c_ptr), value :: handler
6033type(c_ptr), value :: ia
6034type(c_ptr), value :: dm
6035type(c_ptr), value :: ld
6036type(c_ptr), value :: error_code
6037end subroutine
6038end interface
6039!
6040handler_ptr = c_null_ptr
6041handler_ptr = c_loc(handler%handler_ptr_)
6042ia_ptr = c_null_ptr
6043ia_ptr = c_loc(ia)
6044dm_ptr = c_null_ptr
6045dm_ptr = c_loc(dm)
6046ld_ptr = c_null_ptr
6047ld_ptr = c_loc(ld)
6048error_code_ptr = c_null_ptr
6049if (present(error_code)) then
6050error_code_ptr = c_loc(error_code)
6051endif
6052call sirius_set_density_matrix_aux(handler_ptr,ia_ptr,dm_ptr,ld_ptr,error_code_ptr)
6053end subroutine sirius_set_density_matrix
6054
6055
6056subroutine sirius_free_handler_ctx(handler, error_code)
6057 implicit none
6058 type(sirius_context_handler), intent(inout) :: handler
6059 integer, optional, target, intent(out) :: error_code
6060 call sirius_free_object_handler(handler%handler_ptr_, error_code)
6061end subroutine sirius_free_handler_ctx
6062
6063subroutine sirius_free_handler_ks(handler, error_code)
6064 implicit none
6065 type(sirius_kpoint_set_handler), intent(inout) :: handler
6066 integer, optional, target, intent(out) :: error_code
6067 call sirius_free_object_handler(handler%handler_ptr_, error_code)
6068end subroutine sirius_free_handler_ks
6069
6070subroutine sirius_free_handler_dft(handler, error_code)
6071 implicit none
6072 type(sirius_ground_state_handler), intent(inout) :: handler
6073 integer, optional, target, intent(out) :: error_code
6074 call sirius_free_object_handler(handler%handler_ptr_, error_code)
6075end subroutine sirius_free_handler_dft
6076
6077end module
Free any of the SIRIUS handlers (context, ground state or k-points).
Definition: sirius.f90:39
Namespace of the SIRIUS library.
Definition: sirius.f90:5
subroutine sirius_get_max_num_gkvec(ks_handler, max_num_gkvec, error_code)
Get maximum number of G+k vectors across all k-points in the set.
Definition: sirius.f90:4056
subroutine sirius_set_atom_position(handler, ia, position, error_code)
Set new atomic position.
Definition: sirius.f90:2583
subroutine sirius_set_callback_function(handler, label, fptr, error_code)
Set callback function to compute various radial integrals.
Definition: sirius.f90:5501
subroutine sirius_option_get(section, name, type, data_ptr, max_length, enum_idx, error_code)
Return the default value of the option as defined in the JSON schema.
Definition: sirius.f90:4854
subroutine sirius_get_wave_functions(ks_handler, vkl, spin, num_gvec_loc, gvec_loc, evec, ld, num_spin_comp, error_code)
Get wave-functions.
Definition: sirius.f90:3381
subroutine sirius_generate_xc_potential(handler, error_code)
Generate XC potential using LibXC.
Definition: sirius.f90:3736
subroutine sirius_set_density_matrix(handler, ia, dm, ld, error_code)
Set density matrix.
Definition: sirius.f90:6014
subroutine sirius_create_kset_from_grid(handler, k_grid, k_shift, use_symmetry, kset_handler, error_code)
Create k-point set from a grid.
Definition: sirius.f90:1690
subroutine sirius_get_kpoint_properties(handler, ik, weight, coordinates, error_code)
Get the kpoint properties.
Definition: sirius.f90:5450
subroutine sirius_set_o_radial_integral(handler, ia, val, l, o1, ilo1, o2, ilo2, error_code)
Set LAPW overlap radial integral.
Definition: sirius.f90:4325
subroutine sirius_serialize_timers(fname, error_code)
Save all timers to JSON file.
Definition: sirius.f90:276
subroutine sirius_linear_solver(handler, vkq, num_gvec_kq_loc, gvec_kq_loc, dpsi, psi, eigvals, dvpsi, ld, num_spin_comp, alpha_pv, spin, nbnd_occ, tol, niter, error_code)
Interface to linear solver.
Definition: sirius.f90:5794
subroutine sirius_get_num_fft_grid_points(handler, num_fft_grid_points, error_code)
Get local number of FFT grid points.
Definition: sirius.f90:3982
subroutine sirius_set_equivalent_atoms(handler, equivalent_atoms, error_code)
Set equivalent atoms.
Definition: sirius.f90:4568
subroutine sirius_option_get_number_of_sections(length, error_code)
Return the total number of sections defined in the input JSON schema.
Definition: sirius.f90:4635
subroutine sirius_get_fv_eigen_vectors(handler, ik, fv_evec, ld, num_fv_states, error_code)
Get the first-variational eigen vectors.
Definition: sirius.f90:5049
character(kind=c_char, len=size(c_string) - 1) function string_c2f(c_string)
Internal function that converts C-string (with trailing null character) to the Fortran string.
Definition: sirius.f90:59
subroutine sirius_get_fft_index(handler, fft_index, error_code)
Get mapping between G-vector index and FFT index.
Definition: sirius.f90:4019
subroutine sirius_set_radial_function(handler, ia, deriv_order, f, l, o, ilo, error_code)
Set LAPW radial functions.
Definition: sirius.f90:4499
subroutine sirius_stop_timer(name, error_code)
Stop the running timer.
Definition: sirius.f90:208
subroutine sirius_add_atom_type_radial_function(handler, atom_type, label, rf, num_points, n, l, idxrf1, idxrf2, occ, error_code)
Add one of the radial functions.
Definition: sirius.f90:2223
subroutine sirius_update_ground_state(gs_handler, error_code)
Update a ground state object after change of atomic coordinates or lattice vectors.
Definition: sirius.f90:1971
subroutine sirius_update_context(handler, error_code)
Update simulation context after changing lattice or atomic positions.
Definition: sirius.f90:1175
subroutine sirius_initialize_context(handler, error_code)
Initialize simulation context.
Definition: sirius.f90:1144
subroutine sirius_get_gkvec_arrays(ks_handler, ik, num_gkvec, gvec_index, gkvec, gkvec_cart, gkvec_len, gkvec_tp, error_code)
Get all G+k vector related arrays.
Definition: sirius.f90:4100
subroutine sirius_get_fft_comm(handler, fcomm, error_code)
Get communicator which is used to parallise FFT.
Definition: sirius.f90:3842
subroutine sirius_create_kset(handler, num_kpoints, kpoints, kpoint_weights, init_kset, kset_handler, error_code)
Create k-point set from the list of k-points.
Definition: sirius.f90:1625
subroutine sirius_create_context(fcomm, handler, fcomm_k, fcomm_band, error_code)
Create context of the simulation.
Definition: sirius.f90:356
subroutine sirius_set_atom_type_radial_grid(handler, label, num_radial_points, radial_points, error_code)
Set radial grid of the atom type.
Definition: sirius.f90:2105
subroutine sirius_generate_effective_potential(handler, error_code)
Generate effective potential and magnetic field.
Definition: sirius.f90:2934
subroutine sirius_nlcg(handler, ks_handler, error_code)
Robust wave function optimizer.
Definition: sirius.f90:5544
subroutine sirius_set_mpi_grid_dims(handler, ndims, dims, error_code)
Set dimensions of the MPI grid.
Definition: sirius.f90:1054
subroutine sirius_add_atom_type(handler, label, fname, zn, symbol, mass, spin_orbit, error_code)
Add new atom type to the unit cell.
Definition: sirius.f90:2008
subroutine sirius_create_ground_state(ks_handler, gs_handler, error_code)
Create a ground state object.
Definition: sirius.f90:1746
subroutine sirius_get_band_occupancies(ks_handler, ik, ispn, band_occupancies, error_code)
Set band occupancies.
Definition: sirius.f90:3088
subroutine sirius_generate_d_operator_matrix(handler, error_code)
Generate D-operator matrix.
Definition: sirius.f90:5898
subroutine sirius_get_num_gvec(handler, num_gvec, error_code)
Get total number of G-vectors on the fine grid.
Definition: sirius.f90:3879
subroutine sirius_get_fv_eigen_values(handler, ik, fv_eval, num_fv_states, error_code)
Get the first-variational eigen values.
Definition: sirius.f90:5104
subroutine sirius_print_info(handler, error_code)
Print basic info.
Definition: sirius.f90:1206
subroutine sirius_get_forces(handler, label, forces, error_code)
Get one of the total force components.
Definition: sirius.f90:3234
character(kind=c_char, len=1) function, dimension(len_trim(f_string)+1) string_f2c(f_string)
Internal function that adds trailing null character to the string to make it C-style.
Definition: sirius.f90:47
subroutine sirius_finalize(call_mpi_fin, call_device_reset, call_fftw_fin, error_code)
Shut down the SIRIUS library.
Definition: sirius.f90:113
subroutine sirius_check_scf_density(gs_handler, error_code)
Check the self-consistent density.
Definition: sirius.f90:1940
subroutine sirius_add_atom_type_aw_descriptor(handler, label, n, l, enu, dme, auto_enu, error_code)
Add descriptor of the augmented wave radial function.
Definition: sirius.f90:3470
subroutine sirius_option_get_section_length(section, length, error_code)
Return the number of options in a given section.
Definition: sirius.f90:4711
subroutine sirius_get_num_beta_projectors(handler, label, num_bp, error_code)
Get the number of beta-projectors for an atom type.
Definition: sirius.f90:3328
subroutine sirius_update_atomic_potential(handler, error_code)
Set the new spherical potential.
Definition: sirius.f90:4604
subroutine sirius_set_atom_type_radial_grid_inf(handler, label, num_radial_points, radial_points, error_code)
Set radial grid of the free atom (up to effectice infinity).
Definition: sirius.f90:2161
subroutine sirius_import_parameters(handler, str, error_code)
Import parameters of simulation from a JSON string.
Definition: sirius.f90:404
subroutine sirius_set_parameters(handler, lmax_apw, lmax_rho, lmax_pot, num_fv_states, num_bands, num_mag_dims, pw_cutoff, gk_cutoff, fft_grid_size, auto_rmt, gamma_point, use_symmetry, so_correction, valence_rel, core_rel, iter_solver_tol_empty, iter_solver_type, verbosity, hubbard_correction, hubbard_correction_kind, hubbard_full_orthogonalization, hubbard_orbitals, sht_coverage, min_occupancy, smearing, smearing_width, spglib_tol, electronic_structure_method, error_code)
Set parameters of the simulation.
Definition: sirius.f90:477
subroutine sirius_get_gvec_arrays(handler, gvec, gvec_cart, gvec_len, index_by_gvec, error_code)
Get G-vector arrays.
Definition: sirius.f90:3920
subroutine sirius_save_state(gs_handler, file_name, error_code)
Save DFT ground state (density and potential)
Definition: sirius.f90:5930
subroutine sirius_set_atom_type_paw(handler, label, core_energy, occupations, num_occ, error_code)
Set PAW related data.
Definition: sirius.f90:2469
subroutine sirius_set_o1_radial_integral(handler, ia, val, l1, o1, ilo1, l2, o2, ilo2, error_code)
Set a correction to LAPW overlap radial integral.
Definition: sirius.f90:4408
subroutine sirius_dump_runtime_setup(handler, filename, error_code)
Dump the runtime setup in a file.
Definition: sirius.f90:5005
subroutine sirius_option_get_info(section, elem, key_name, key_name_len, type, length, enum_size, title, title_len, description, description_len, error_code)
Return information about the option.
Definition: sirius.f90:4762
subroutine sirius_get_band_energies(ks_handler, ik, ispn, band_energies, error_code)
Get band energies.
Definition: sirius.f90:3138
subroutine sirius_get_num_kpoints(handler, num_kpoints, error_code)
Get the total number of kpoints.
Definition: sirius.f90:5411
subroutine sirius_set_atom_type_dion(handler, label, num_beta, dion, error_code)
Set ionic part of D-operator matrix.
Definition: sirius.f90:2414
subroutine sirius_get_periodic_function(handler, label, f_mt, lmmax, nrmtmax, num_atoms, f_rg, size_x, size_y, size_z, offset_z, error_code)
Get values of the periodic function.
Definition: sirius.f90:1514
subroutine sirius_option_set(handler, section, name, type, data_ptr, max_length, append, error_code)
Set the value of the option name in a (internal) json dictionary.
Definition: sirius.f90:4928
subroutine sirius_context_initialized(handler, status, error_code)
Check if the simulation context is initialized.
Definition: sirius.f90:312
subroutine sirius_load_state(handler, file_name, error_code)
Save DFT ground state (density and potential)
Definition: sirius.f90:5971
subroutine sirius_option_get_section_name(elem, section_name, section_name_length, error_code)
Return the name of a given section.
Definition: sirius.f90:4669
subroutine sirius_print_timers(flatten, error_code)
Print all timers.
Definition: sirius.f90:243
subroutine sirius_set_periodic_function(handler, label, f_mt, lmmax, nrmtmax, num_atoms, f_rg, size_x, size_y, size_z, offset_z, error_code)
Set values of the periodic function.
Definition: sirius.f90:1398
subroutine sirius_get_stress_tensor(handler, label, stress_tensor, error_code)
Get one of the stress tensor components.
Definition: sirius.f90:3281
subroutine sirius_set_band_occupancies(ks_handler, ik, ispn, band_occupancies, error_code)
Set band occupancies.
Definition: sirius.f90:3038
subroutine sirius_add_atom(handler, label, position, vector_field, error_code)
Add atom to the unit cell.
Definition: sirius.f90:2529
subroutine sirius_add_hubbard_atom_pair(handler, atom_pair, translation, n, l, coupling, error_code)
Add a non-local Hubbard interaction V for a pair of atoms.
Definition: sirius.f90:5690
subroutine sirius_set_lattice_vectors(handler, a1, a2, a3, error_code)
Set vectors of the unit cell.
Definition: sirius.f90:1098
subroutine sirius_get_parameters(handler, lmax_apw, lmax_rho, lmax_pot, num_fv_states, num_bands, num_spins, num_mag_dims, pw_cutoff, gk_cutoff, fft_grid_size, auto_rmt, gamma_point, use_symmetry, so_correction, iter_solver_tol, iter_solver_tol_empty, verbosity, hubbard_correction, evp_work_count, num_loc_op_applied, num_sym_op, electronic_structure_method, error_code)
Get parameters of the simulation.
Definition: sirius.f90:796
subroutine sirius_add_atom_type_lo_descriptor(handler, label, ilo, n, l, enu, dme, auto_enu, error_code)
Add descriptor of the local orbital radial function.
Definition: sirius.f90:3547
subroutine sirius_free_object_handler(handler, error_code)
Free any object handler created by SIRIUS.
Definition: sirius.f90:1239
subroutine sirius_add_xc_functional(handler, name, error_code)
Add one of the XC functionals.
Definition: sirius.f90:1012
subroutine sirius_set_rg_values(handler, label, grid_dims, local_box_origin, local_box_size, fcomm, values, transform_to_pw, error_code)
Set the values of the function on the regular grid.
Definition: sirius.f90:5209
subroutine sirius_initialize(call_mpi_init, error_code)
Initialize the SIRIUS library.
Definition: sirius.f90:78
subroutine sirius_get_step_function(handler, cfunig, cfunrg, num_rg_points, error_code)
Get the unit-step function.
Definition: sirius.f90:4171
subroutine sirius_set_periodic_function_ptr(handler, label, f_mt, lmmax, nrmtmax, num_atoms, f_rg, size_x, size_y, size_z, offset_z, error_code)
Set pointer to density or magnetization.
Definition: sirius.f90:1281
subroutine sirius_set_atom_type_hubbard(handler, label, l, n, occ, U, J, alpha, beta, J0, error_code)
Set the hubbard correction for the atomic type.
Definition: sirius.f90:2329
subroutine sirius_get_kpoint_inter_comm(handler, fcomm, error_code)
Get communicator which is used to split k-points.
Definition: sirius.f90:3768
subroutine sirius_start_timer(name, error_code)
Start the timer.
Definition: sirius.f90:173
subroutine sirius_get_total_magnetization(handler, mag, error_code)
Get the total magnetization of the system.
Definition: sirius.f90:5374
subroutine sirius_generate_coulomb_potential(handler, vh_el, error_code)
Generate Coulomb potential by solving Poisson equation.
Definition: sirius.f90:3698
subroutine sirius_get_sv_eigen_vectors(handler, ik, sv_evec, num_bands, error_code)
Get the second-variational eigen vectors.
Definition: sirius.f90:5154
subroutine sirius_get_rg_values(handler, label, grid_dims, local_box_origin, local_box_size, fcomm, values, transform_to_rg, error_code)
Get the values of the function on the regular grid.
Definition: sirius.f90:5295
subroutine sirius_find_ground_state(gs_handler, density_tol, energy_tol, iter_solver_tol, initial_guess, max_niter, save_state, converged, niter, rho_min, error_code)
Find the ground state.
Definition: sirius.f90:1831
subroutine sirius_get_energy(handler, label, energy, error_code)
Get one of the total energy components.
Definition: sirius.f90:3187
subroutine sirius_set_atom_type_configuration(handler, label, n, l, k, occupancy, core, error_code)
Set configuration of atomic levels.
Definition: sirius.f90:3628
subroutine sirius_generate_density(gs_handler, add_core, transform_to_rg, paw_only, error_code)
Generate charge density and magnetization.
Definition: sirius.f90:2969
subroutine sirius_nlcg_params(handler, ks_handler, temp, smearing, kappa, tau, tol, maxiter, restart, processing_unit, converged, error_code)
Robust wave function optimizer.
Definition: sirius.f90:5591
subroutine sirius_set_h_radial_integrals(handler, ia, lmmax, val, l1, o1, ilo1, l2, o2, ilo2, error_code)
Set LAPW Hamiltonian radial integrals.
Definition: sirius.f90:4228
subroutine sirius_generate_initial_density(handler, error_code)
Generate initial density.
Definition: sirius.f90:2903
subroutine sirius_create_h0(handler, error_code)
Generate H0.
Definition: sirius.f90:5748
subroutine sirius_get_kpoint_inner_comm(handler, fcomm, error_code)
Get communicator which is used to parallise band problem.
Definition: sirius.f90:3805
subroutine sirius_set_pw_coeffs(handler, label, pw_coeffs, transform_to_rg, ngv, gvl, comm, error_code)
Set plane-wave coefficients of a periodic function.
Definition: sirius.f90:2631
subroutine sirius_get_pw_coeffs(handler, label, pw_coeffs, ngv, gvl, comm, error_code)
Get plane-wave coefficients of a periodic function.
Definition: sirius.f90:2715
subroutine sirius_find_eigen_states(gs_handler, ks_handler, precompute_pw, precompute_rf, precompute_ri, iter_solver_tol, error_code)
Find eigen-states of the Hamiltonian.
Definition: sirius.f90:2825
subroutine sirius_initialize_subspace(gs_handler, ks_handler, error_code)
Initialize the subspace of wave-functions.
Definition: sirius.f90:2783
subroutine sirius_initialize_kset(ks_handler, count, error_code)
Initialize k-point set.
Definition: sirius.f90:1783
Opaque wrapper for simulation context handler.
Definition: sirius.f90:24
Opaque wrapper for DFT ground statee handler.
Definition: sirius.f90:29
Opaque wrapper for K-point set handler.
Definition: sirius.f90:34