• Home
  • Features
  • Pricing
  • Docs
  • Announcements
  • Sign In

trixi-framework / libtrixi / 18356394504

08 Oct 2025 07:54PM UTC coverage: 97.485% (+0.5%) from 97.027%
18356394504

Pull #172

github

web-flow
Merge 33b49036e into 3e1d8e6bf
Pull Request #172: RFC: Source terms via callback

16 of 16 new or added lines in 1 file covered. (100.0%)

16 existing lines in 3 files now uncovered.

1163 of 1193 relevant lines covered (97.49%)

469865.67 hits per line

Source File
Press 'n' to go to next uncovered line, 'b' for previous

97.37
/src/api.f90
1
!>
2
!! @addtogroup api_f Fortran API
3
!!
4
!! **NOTE**: It is a known limitation of doxygen that Fortran interfaces will be listed as
5
!! "Data Types". Please refer to the "Functions/Subroutines" section instead.
6
!!
7
!! @{
8

9
module LibTrixi
10
  implicit none
11

12
  interface
13
    !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
14
    !! Setup                                                                              !!
15
    !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
16

17
    !>
18
    !! @fn LibTrixi::trixi_initialize_c::trixi_initialize_c(project_directory, depot_path)
19
    !!
20
    !! @brief Initialize Julia runtime environment (C char pointer version)
21
    !!
22
    !! Initialize Julia and activate the project at `project_directory`. If `depot_path` is
23
    !! given, forcefully set the environment variable `JULIA_DEPOT_PATH` to the value of
24
    !! depot_path`. If `depot_path` is not given, then proceed as follows: If
25
    !! `JULIA_DEPOT_PATH` is already set, do not touch it. Otherwise, set
26
    !! `JULIA_DEPOT_PATH` to `project_directory` + `default_depot_path`.
27
    !!
28
    !! This routine must be called before most other libtrixi routines can be used.
29
    !! Libtrixi maybe only be initialized once; subsequent calls to `trixi_initialize` are
30
    !! erroneous.
31
    !!
32
    !! @param[in]  project_directory  Path to project directory (C char pointer)
33
    !! @param[in]  depot_path         Path to Julia depot path (optional, C char pointer)
34
    !!
35
    !! @see @ref trixi_initialize        "trixi_initialize (Fortran convenience version)"
36
    !! @see @ref trixi_initialize_api_c  "trixi_initialize (C API)"
37
    subroutine trixi_initialize_c(project_directory, depot_path) bind(c, name='trixi_initialize')
38
      use, intrinsic :: iso_c_binding, only: c_char
39
      character(kind=c_char), dimension(*), intent(in) :: project_directory
40
      character(kind=c_char), dimension(*), intent(in), optional :: depot_path
41
    end subroutine
42

43
    !>
44
    !! @fn LibTrixi::trixi_finalize::trixi_finalize()
45
    !!
46
    !! @brief Finalize Julia runtime environment.
47
    !!
48
    !! Clean up internal states. This routine should be executed near the end of the
49
    !! process' lifetime. After the call to `trixi_finalize`, no other libtrixi routines may
50
    !! be called anymore, including `trixi_finalize` itself.
51
    !!
52
    !! @see @ref trixi_finalize_api_c "trixi_finalize (C API)"
53
    subroutine trixi_finalize() bind(c)
54
    end subroutine
55

56

57

58
    !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
59
    !! Version information                                                                !!
60
    !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
61

62
    !>
63
    !! @fn LibTrixi::trixi_version_library_major::trixi_version_library_major()
64
    !!
65
    !! @brief Return major version number of libtrixi.
66
    !!
67
    !! @return Major version number as integer.
68
    !!
69
    !! @see @ref trixi_version_library_major_api_c "trixi_version_library_major (C API)"
70
    integer(c_int) function trixi_version_library_major() bind(c)
71
      use, intrinsic :: iso_c_binding, only: c_int
72
    end function
73

74
    !>
75
    !! @fn LibTrixi::trixi_version_library_minor::trixi_version_library_minor()
76
    !!
77
    !! @brief Return minor version number of libtrixi.
78
    !!
79
    !! @return Minor version number as integer.
80
    !!
81
    !! @see @ref trixi_version_library_minor_api_c "trixi_version_library_minor (C API)"
82
    integer(c_int) function trixi_version_library_minor() bind(c)
83
      use, intrinsic :: iso_c_binding, only: c_int
84
    end function
85

86
    !>
87
    !! @fn LibTrixi::trixi_version_library_patch::trixi_version_library_patch()
88
    !!
89
    !! @brief Return patch version number of libtrixi.
90
    !!
91
    !! @return Patch version number as integer.
92
    !!
93
    !! @see @ref trixi_version_library_patch_api_c "trixi_version_library_patch (C API)"
94
    integer(c_int) function trixi_version_library_patch() bind(c)
95
      use, intrinsic :: iso_c_binding, only: c_int
96
    end function
97

98
    !>
99
    !! @fn LibTrixi::trixi_version_library_c::trixi_version_library_c()
100
    !!
101
    !! @brief Return full version string of libtrixi (C char pointer version).
102
    !!
103
    !! @return Full version string as C char pointer.
104
    !!
105
    !! @see @ref trixi_version_library
106
    !!           "trixi_version_library (Fortran convenience version)"
107
    !! @see @ref trixi_version_library_api_c
108
    !!           "trixi_version_library (C API)"
109
    type(c_ptr) function trixi_version_library_c() bind(c, name='trixi_version_library')
110
      use, intrinsic :: iso_c_binding, only: c_ptr
111
    end function
112

113
    !>
114
    !! @fn LibTrixi::trixi_version_julia_c::trixi_version_julia_c()
115
    !!
116
    !! @brief Return name and version of loaded julia packages LibTrixi directly depends on
117
    !!        (C char pointer version).
118
    !!
119
    !! @return Name and version of loaded julia packages as C char pointer.
120
    !!
121
    !! @see @ref trixi_version_julia
122
    !!           "trixi_version_julia (Fortran convenience version)"
123
    !! @see @ref trixi_version_julia_api_c
124
    !!           "trixi_version_julia (C API)"
125
    type(c_ptr) function trixi_version_julia_c() bind(c, name='trixi_version_julia')
126
      use, intrinsic :: iso_c_binding, only: c_ptr
127
    end function
128

129
    !>
130
    !! @fn LibTrixi::trixi_version_julia_extended_c::trixi_version_julia_extended_c()
131
    !!
132
    !! @brief Return name and version of all loaded julia packages (C char pointer version).
133
    !!
134
    !! @return Name and version of loaded julia packages as C char pointer.
135
    !!
136
    !! @see @ref trixi_version_julia_extended
137
    !!           "trixi_version_julia_extended (Fortran convenience version)"
138
    !! @see @ref trixi_version_julia_extended_api_c
139
    !!           "trixi_version_julia_extended (C API)"
140
    type(c_ptr) function trixi_version_julia_extended_c() &
141
      bind(c, name='trixi_version_julia_extended')
142
      use, intrinsic :: iso_c_binding, only: c_ptr
143
    end function
144
  
145

146

147
    !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
148
    !! Simulation control                                                                 !!
149
    !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
150

151
    !>
152
    !! @fn LibTrixi::trixi_initialize_simulation_c::trixi_initialize_simulation_c(libelexir)
153
    !!
154
    !! @brief Set up Trixi simulation (C char pointer version)
155
    !!
156
    !! @param[in]  libelixir  Path to libelexir file.
157
    !!
158
    !! @return handle (integer) to Trixi simulation instance
159
    !!
160
    !! @see @ref trixi_initialize_simulation
161
    !!           "trixi_initialize_simulation (Fortran convenience version)"
162
    !! @see @ref trixi_initialize_simulation_api_c
163
    !!           "trixi_initialize_simulation (C API)"
164
    integer(c_int) function trixi_initialize_simulation_c(libelixir) &
165
      bind(c, name='trixi_initialize_simulation')
166
      use, intrinsic :: iso_c_binding, only: c_char, c_int
167
      character(kind=c_char), dimension(*), intent(in) :: libelixir
168
    end function
169

170
    !>
171
    !! @fn LibTrixi::trixi_is_finished_c::trixi_is_finished_c(handle)
172
    !!
173
    !! @brief Check if simulation is finished (C integer version)
174
    !!
175
    !! @param[in]  handle  simulation handle
176
    !!
177
    !! @return 1 if finished, 0 if not
178
    !!
179
    !! @see @ref trixi_is_finished
180
    !!           "trixi_is_finished (Fortran convenience version)"
181
    !! @see @ref trixi_is_finished_api_c
182
    !!           "trixi_is_finished (C API)"
183
    integer(c_int) function trixi_is_finished_c(handle) bind(c, name='trixi_is_finished')
184
      use, intrinsic :: iso_c_binding, only: c_int
185
      integer(c_int), value, intent(in) :: handle
186
    end function
187

188
    !>
189
    !! @fn LibTrixi::trixi_step::trixi_step(handle)
190
    !!
191
    !! @brief Perform next simulation step
192
    !!
193
    !! @param[in]  handle  simulation handle
194
    !!
195
    !! @see @ref trixi_step_api_c "trixi_step (C API)"
196
    subroutine trixi_step(handle) bind(c)
197
      use, intrinsic :: iso_c_binding, only: c_int
198
      integer(c_int), value, intent(in) :: handle
199
    end subroutine
200

201
    !>
202
    !! @fn LibTrixi::trixi_finalize_simulation::trixi_finalize_simulation(handle)
203
    !!
204
    !! @brief Finalize simulation
205
    !!
206
    !! @param[in]  handle  simulation handle
207
    !!
208
    !! @see trixi_finalize_simulation_api_c "trixi_finalize_simulation (C API)"
209
    subroutine trixi_finalize_simulation(handle) bind(c)
210
      use, intrinsic :: iso_c_binding, only: c_int
211
      integer(c_int), value, intent(in) :: handle
212
    end subroutine
213

214

215

216
    !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
217
    !! Simulation data                                                                    !!
218
    !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
219

220
    !>
221
    !! @fn LibTrixi::trixi_calculate_dt::trixi_calculate_dt(handle)
222
    !!
223
    !! @brief Get time step length
224
    !!
225
    !! @param[in]  handle  simulation handle
226
    !!
227
    !! @return Time step length
228
    !!
229
    !! @see @ref trixi_calculate_dt_api_c "trixi_calculate_dt (C API)"
230
    real(c_double) function trixi_calculate_dt(handle) bind(c)
231
      use, intrinsic :: iso_c_binding, only: c_int, c_double
232
      integer(c_int), value, intent(in) :: handle
233
    end function
234

235
    !>
236
    !! @fn LibTrixi::trixi_ndims::trixi_ndims(handle)
237
    !!
238
    !! @brief Return number of spatial dimensions
239
    !!
240
    !! @param[in]  handle  simulation handle
241
    !!
242
    !! @see @ref trixi_ndims_api_c "trixi_ndims (C API)"
243
    integer(c_int) function trixi_ndims(handle) bind(c)
244
      use, intrinsic :: iso_c_binding, only: c_int
245
      integer(c_int), value, intent(in) :: handle
246
    end function
247

248
    !>
249
    !! @fn LibTrixi::trixi_nelements::trixi_nelements(handle)
250
    !!
251
    !! @brief Return number of local elements
252
    !!
253
    !! @param[in]  handle  simulation handle
254
    !!
255
    !! @see @ref trixi_nelements_api_c "trixi_nelements (C API)"
256
    integer(c_int) function trixi_nelements(handle) bind(c)
257
      use, intrinsic :: iso_c_binding, only: c_int
258
      integer(c_int), value, intent(in) :: handle
259
    end function
260

261
    !>
262
    !! @fn LibTrixi::trixi_nelementsglobal::trixi_nelementsglobal(handle)
263
    !!
264
    !! @brief Return global number of elements
265
    !!
266
    !! @param[in]  handle  simulation handle
267
    !!
268
    !! @see @ref trixi_nelementsglobal_api_c "trixi_nelementsglobal (C API)"
269
    integer(c_int) function trixi_nelementsglobal(handle) bind(c)
270
      use, intrinsic :: iso_c_binding, only: c_int
271
      integer(c_int), value, intent(in) :: handle
272
    end function
273

274
    !>
275
    !! @fn LibTrixi::trixi_ndofs::trixi_ndofs(handle)
276
    !!
277
    !! @brief Return number of local degrees of freedom
278
    !!
279
    !! @param[in]  handle  simulation handle
280
    !!
281
    !! @see @ref trixi_ndofs_api_c "trixi_ndofs (C API)"
282
    integer(c_int) function trixi_ndofs(handle) bind(c)
283
      use, intrinsic :: iso_c_binding, only: c_int
284
      integer(c_int), value, intent(in) :: handle
285
    end function
286

287
    !>
288
    !! @fn LibTrixi::trixi_ndofsglobal::trixi_ndofsglobal(handle)
289
    !!
290
    !! @brief Return global number of degrees of freedom
291
    !!
292
    !! @param[in]  handle  simulation handle
293
    !!
294
    !! @see @ref trixi_ndofsglobal_api_c "trixi_ndofsglobal (C API)"
295
    integer(c_int) function trixi_ndofsglobal(handle) bind(c)
296
      use, intrinsic :: iso_c_binding, only: c_int
297
      integer(c_int), value, intent(in) :: handle
298
    end function
299

300
    !>
301
    !! @fn LibTrixi::trixi_ndofselement::trixi_ndofselement(handle)
302
    !!
303
    !! @brief Return number of degrees of freedom per element.
304
    !!
305
    !! @param[in]  handle  simulation handle
306
    !!
307
    !! @see @ref trixi_ndofselement_api_c "trixi_ndofselement (C API)"
308
    integer(c_int) function trixi_ndofselement(handle) bind(c)
309
      use, intrinsic :: iso_c_binding, only: c_int
310
      integer(c_int), value, intent(in) :: handle
311
    end function
312

313
    !>
314
    !! @fn LibTrixi::trixi_nvariables::trixi_nvariables(handle)
315
    !!
316
    !! @brief Return number of (conservative) variables
317
    !!
318
    !! @param[in]  handle  simulation handle
319
    !!
320
    !! @see @ref trixi_nvariables_api_c "trixi_nvariables (C API"
321
    integer(c_int) function trixi_nvariables(handle) bind(c)
322
      use, intrinsic :: iso_c_binding, only: c_int
323
      integer(c_int), value, intent(in) :: handle
324
    end function
325

326
    !>
327
    !! @fn LibTrixi::trixi_nnodes::trixi_nnodes(handle)
328
    !!
329
    !! @brief Return number of quadrature nodes per dimension.
330
    !!
331
    !! @param[in]  handle  simulation handle
332
    !!
333
    !! @see @ref trixi_nnodes_api_c "trixi_nnodes (C API)"
334
    integer(c_int) function trixi_nnodes(handle) bind(c)
335
      use, intrinsic :: iso_c_binding, only: c_int
336
      integer(c_int), value, intent(in) :: handle
337
    end function
338

339
    !>
340
    !! @fn LibTrixi::trixi_load_node_reference_coordinates::trixi_load_node_reference_coordinates(handle, node_coords)
341
    !!
342
    !! @brief Get reference coordinates of 1D quadrature nodes.
343
    !!
344
    !! The reference coordinates in [-1,1] of the quadrature nodes in the current DG scheme are
345
    !! stored in the provided array `node_coords`. The given array has to be of correct size,
346
    !! i.e. `nnodes`, and memory has to be allocated beforehand.
347
    !!
348
    !! @param[in]   handle       simulation handle
349
    !! @param[out]  node_coords  node reference coordinates
350
    !!
351
    !! @see @ref trixi_load_node_reference_coordinates_api_c "trixi_load_node_reference_coordinates (C API)"
352
    subroutine trixi_load_node_reference_coordinates(handle, node_coords) bind(c)
353
      use, intrinsic :: iso_c_binding, only: c_int, c_double
354
      integer(c_int), value, intent(in) :: handle
355
      real(c_double), dimension(*), intent(out) :: node_coords
356
    end subroutine
357

358
    !>
359
    !! @fn LibTrixi::trixi_load_node_weights::trixi_load_node_weights(handle, node_weights)
360
    !!
361
    !! @brief Get weights of 1D quadrature nodes.
362
    !!
363
    !! The weights of the quadrature nodes in the current DG scheme are stored in the provided
364
    !! array `node_weights`. The given array has to be of correct size, i.e. `nnodes`, and
365
    !! memory has to be allocated beforehand.
366
    !!
367
    !! @param[in]   handle        simulation handle
368
    !! @param[out]  node_weights  node weights
369
    !!
370
    !! @see @ref trixi_load_node_weights_api_c "trixi_load_node_weights (C API)"
371
    subroutine trixi_load_node_weights(handle, node_weights) bind(c)
372
      use, intrinsic :: iso_c_binding, only: c_int, c_double
373
      integer(c_int), value, intent(in) :: handle
374
      real(c_double), dimension(*), intent(out) :: node_weights
375
    end subroutine
376

377
    !>
378
    !! @anchor trixi_load_conservative_var_api_c
379
    !!
380
    !! @brief Load conservative variable.
381
    !!
382
    !! The values for the conservative variable at position `variable_id` at every degree of
383
    !! freedom are stored in the given array `data`.
384
    !! 
385
    !! The given array has to be of correct size (ndofs) and memory has to be allocated
386
    !! beforehand.
387
    !!
388
    !! @param[in]   handle       simulation handle
389
    !! @param[in]   variable_id  index of variable
390
    !! @param[out]  data         values for all degrees of freedom
391
    subroutine trixi_load_conservative_var(handle, variable_id, data) bind(c)
392
      use, intrinsic :: iso_c_binding, only: c_int, c_double
393
      integer(c_int), value, intent(in) :: handle
394
      integer(c_int), value, intent(in) :: variable_id
395
      real(c_double), dimension(*), intent(out) :: data
396
    end subroutine
397

398
    !>
399
    !! @fn LibTrixi::trixi_load_primitive_var::trixi_load_primitive_var(handle, variable_id, data)
400
    !!
401
    !! @brief Load primitive variable
402
    !!
403
    !! @param[in]  handle       simulation handle
404
    !! @param[in]  variable_id  index of variable
405
    !! @param[out] data         primitive variable values for all degrees of freedom
406
    !!
407
    !! @see @ref trixi_load_primitive_var_api_c "trixi_load_primitive_var (C API)"
408
    subroutine trixi_load_primitive_var(handle, variable_id, data) bind(c)
409
      use, intrinsic :: iso_c_binding, only: c_int, c_double
410
      integer(c_int), value, intent(in) :: handle
411
      integer(c_int), value, intent(in) :: variable_id
412
      real(c_double), dimension(*), intent(out) :: data
413
    end subroutine
414

415
    !>
416
    !! @fn LibTrixi::trixi_get_simulation_time::trixi_get_simulation_time(handle)
417
    !!
418
    !! @brief Return current physical time.
419
    !!
420
    !! @param[in]  handle  simulation handle
421
    !!
422
    !! @return  physical time
423
    !!
424
    !! @see @ref trixi_get_simulation_time_api_c "trixi_get_simulation_time (C API)"
425
    real(c_double) function trixi_get_simulation_time(handle) bind(c)
426
      use, intrinsic :: iso_c_binding, only: c_int, c_double
427
      integer(c_int), value, intent(in) :: handle
428
    end function
429

430
    !>
431
    !! @fn LibTrixi::trixi_load_element_averaged_primitive_var::trixi_load_element_averaged_primitive_var(handle, variable_id, data)
432
    !!
433
    !! @brief Load element averages for primitive variable
434
    !!
435
    !! @param[in]  handle       simulation handle
436
    !! @param[in]  variable_id  index of variable
437
    !! @param[out] data         averaged values for all elements
438
    !!
439
    !! @see @ref trixi_load_element_averaged_primitive_var_api_c "trixi_load_element_averaged_primitive_var (C API)"
440
    subroutine trixi_load_element_averaged_primitive_var(handle, variable_id, data) bind(c)
441
      use, intrinsic :: iso_c_binding, only: c_int, c_double
442
      integer(c_int), value, intent(in) :: handle
443
      integer(c_int), value, intent(in) :: variable_id
444
      real(c_double), dimension(*), intent(out) :: data
445
    end subroutine
446

447
    !>
448
    !! @anchor trixi_store_conservative_var_api_c
449
    !!
450
    !! @brief Store conservative variable.
451
    !!
452
    !! The values for the conservative variable at position `variable_id` at every degree of
453
    !! freedom are read from the given array `data` and written to Trixi.jl's internal
454
    !! storage.
455
    !! 
456
    !! The given array has to be of correct size (ndofs).
457
    !!
458
    !! @param[in]  handle       simulation handle
459
    !! @param[in]  variable_id  index of variable
460
    !! @param[in]  data         values for all degrees of freedom
461
    subroutine trixi_store_conservative_var(handle, variable_id, data) bind(c)
462
      use, intrinsic :: iso_c_binding, only: c_int, c_double
463
      integer(c_int), value, intent(in) :: handle
464
      integer(c_int), value, intent(in) :: variable_id
465
      real(c_double), dimension(*), intent(in) :: data
466
    end subroutine
467

468
    !>
469
    !! @fn LibTrixi::trixi_register_data::trixi_register_data(handle, variable_id, data)
470
    !!
471
    !! @brief Store data vector in current simulation's registry
472
    !!
473
    !! @param[in]  handle  simulation handle
474
    !! @param[in]  index   index in registry where data vector will be stored
475
    !! @param[in]  size    size of given data vector
476
    !! @param[in]  data    data vector to store
477
    !!
478
    !! @see @ref trixi_register_data_api_c "trixi_register_data (C API)"
479
    subroutine trixi_register_data(handle, index, size, data) bind(c)
480
      use, intrinsic :: iso_c_binding, only: c_int, c_double
481
      integer(c_int), value, intent(in) :: handle
482
      integer(c_int), value, intent(in) :: index
483
      integer(c_int), value, intent(in) :: size
484
      real(c_double), dimension(*), intent(in) :: data
485
    end subroutine
486

487
    !>
488
    !! @anchor trixi_get_conservative_vars_pointer_api_c
489
    !!
490
    !! @brief Return pointer to internal data vector.
491
    !!
492
    !! The returned pointer points to the beginning of the internal data array used in
493
    !! Trixi.jl. This array contains the conservative variables, i.e. density, momentum
494
    !! density in the three Cartesian coordinates, and energy density, in this sequence.
495
    !! The pointer can be used to read, but also to write these variables. The latter
496
    !! should be done with care. Writing while a time step in being performed will lead to
497
    !! undefined behavior.
498
    !!
499
    !! @param[in]  handle  simulation handle
500
    type (c_ptr) function trixi_get_conservative_vars_pointer(handle) bind(c)
501
      use, intrinsic :: iso_c_binding, only: c_int, c_ptr
502
      integer(c_int), value, intent(in) :: handle
503
    end function
504

505

506

507
    !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
508
    !! t8code                                                                             !!
509
    !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
510
    !>
511
    !! @fn LibTrixi::trixi_get_t8code_forest::trixi_get_t8code_forest(handle)
512
    !!
513
    !! @brief Get t8code forest
514
    !!
515
    !! @param[in]  handle       simulation handle
516
    !!
517
    !! @return t8code forest
518
    !!
519
    !! @see @ref trixi_get_t8code_forest_api_c "trixi_get_t8code_forest (C API)"
520
    type (c_ptr) function trixi_get_t8code_forest(handle) bind(c)
521
      use, intrinsic :: iso_c_binding, only: c_int, c_ptr
522
      integer(c_int), value, intent(in) :: handle
523
    end function
524

525

526

527
    !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
528
    !! Misc                                                                               !!
529
    !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
530

531
    !>
532
    !! @fn LibTrixi::trixi_eval_julia_c::trixi_eval_julia_c(code)
533
    !!
534
    !! @brief Execute Julia code (C char pointer version)
535
    !!
536
    !! @warning Only for development. Code is not checked prior to execution.
537
    !!
538
    !! @see @ref trixi_eval_julia       "trixi_eval_julia_c (Fortran convenience version)"
539
    !! @see @ref trixi_eval_julia_api_c "trixi_eval_julia_c (C API)"
540
    subroutine trixi_eval_julia_c(code) bind(c, name='trixi_eval_julia')
541
      use, intrinsic :: iso_c_binding, only: c_char
542
      character(kind=c_char), dimension(*), intent(in) :: code
543
    end subroutine
544
  end interface
545

546
  contains
547

548
  !>
549
  !! @brief Initialize Julia runtime environment (Fortran convenience version)
550
  !!
551
  !! @param[in]  project_directory  Path to project directory (Fortran string).
552
  !! @param[in]  depot_path         Path to Julia depot path (Fortran string).
553
  !!
554
  !! @see @ref trixi_initialize_c::trixi_initialize_c
555
  !!           "trixi_initialize_c (C char pointer version)"
556
  !! @see @ref trixi_initialize_api_c
557
  !!           "trixi_initialize (C API)"
558
  subroutine trixi_initialize(project_directory, depot_path)
11✔
559
    use, intrinsic :: iso_c_binding, only: c_null_char
560
    character(len=*), intent(in) :: project_directory
561
    character(len=*), intent(in), optional :: depot_path
562

563
    if (present(depot_path)) then
11✔
564
      call trixi_initialize_c(trim(adjustl(project_directory)) // c_null_char, &
UNCOV
565
                              trim(adjustl(depot_path)) // c_null_char)
×
566
    else
567
      call trixi_initialize_c(trim(adjustl(project_directory)) // c_null_char)
11✔
568
    end if
569
  end subroutine
11✔
570

571
  !>
572
  !! @brief Return full version string of libtrixi (Fortran convenience version).
573
  !!
574
  !! @return Full version string as Fortran allocatable string.
575
  !!
576
  !! @see @ref trixi_version_library_c::trixi_version_library_c
577
  !!           "trixi_version_library_c (C char pointer version)"
578
  !! @see @ref trixi_version_library_api_c
579
  !!           "trixi_version_library (C API)"
580
  function trixi_version_library()
3✔
581
    use, intrinsic :: iso_c_binding, only: c_char, c_null_char, c_f_pointer
582
    character(len=:), allocatable :: trixi_version_library
583
    character(len=128, kind=c_char), pointer :: buffer
584
    integer :: length, i
585

586
    ! Associate buffer with C pointer
587
    call c_f_pointer(trixi_version_library_c(), buffer)
3✔
588

589
    ! Determine the actual length of the version string
590
    length = 0
3✔
591
    do i = 1,128
30✔
592
      if ( buffer(i:i) == c_null_char ) exit
30✔
593
      length = length + 1
27✔
594
    end do
595

596
    ! Store relevant part in return value
597
    trixi_version_library = buffer(1:(length + 1))
3✔
598
  end function
3✔
599

600
  !>
601
  !! @brief Return name and version of loaded julia packages LibTrixi directly depends on
602
  !!        (Fortran convenience version).
603
  !!
604
  !! @return Name and version of loaded julia packages as Fortran allocatable string.
605
  !!
606
  !! @see @ref trixi_version_julia_c::trixi_version_julia_c
607
  !!           "trixi_version_julia_c (C char pointer version)"
608
  !! @see @ref trixi_version_julia_api_c
609
  !!           "trixi_version_julia (C API)"
610
  function trixi_version_julia()
2✔
611
    use, intrinsic :: iso_c_binding, only: c_char, c_null_char, c_f_pointer
612
    character(len=:), allocatable :: trixi_version_julia
613
    character(len=1024, kind=c_char), pointer :: buffer
614
    integer :: length, i
615

616
    ! Associate buffer with C pointer
617
    call c_f_pointer(trixi_version_julia_c(), buffer)
2✔
618

619
    ! Determine the actual length of the version string
620
    length = 0
2✔
621
    do i = 1,1024
342✔
622
      if ( buffer(i:i) == c_null_char ) exit
342✔
623
      length = length + 1
340✔
624
    end do
625

626
    ! Store relevant part in return value
627
    trixi_version_julia = buffer(1:(length + 1))
2✔
628
  end function
2✔
629

630
  !>
631
  !! @brief Return name and version of all loaded julia packages
632
  !!        (Fortran convenience version).
633
  !!
634
  !! @return Name and version of loaded julia packages as Fortran allocatable string.
635
  !!
636
  !! @see @ref trixi_version_julia_extended_c::trixi_version_julia_extended_c
637
  !!           "trixi_version_julia_extended_c (C char pointer version)"
638
  !! @see @ref trixi_version_julia_extended_api_c
639
  !!           "trixi_version_julia_extended (C API)"
640
  function trixi_version_julia_extended()
3✔
641
    use, intrinsic :: iso_c_binding, only: c_char, c_null_char, c_f_pointer
642
    character(len=:), allocatable :: trixi_version_julia_extended
643
    character(len=8192, kind=c_char), pointer :: buffer
644
    integer :: length, i
645

646
    ! Associate buffer with C pointer
647
    call c_f_pointer(trixi_version_julia_extended_c(), buffer)
3✔
648

649
    ! Determine the actual length of the version string
650
    length = 0
3✔
651
    do i = 1,8192
16,251✔
652
      if ( buffer(i:i) == c_null_char ) exit
16,251✔
653
      length = length + 1
16,248✔
654
    end do
655

656
    ! Store relevant part in return value
657
    trixi_version_julia_extended = buffer(1:(length + 1))
3✔
658
  end function
3✔
659

660
  !>
661
  !! @brief Set up Trixi simulation (Fortran convenience version)
662
  !!
663
  !! @param[in]  libelixir  Path to libelexir file.
664
  !!
665
  !! @return handle (integer) to Trixi simulation instance
666
  !!
667
  !! @see @ref trixi_initialize_simulation_c::trixi_initialize_simulation_c
668
  !!           "trixi_initialize_simulation_c (C char pointer version)"
669
  !! @see @ref trixi_initialize_simulation_api_c
670
  !!           "trixi_initialize_simulation (C API)"
671
  integer(c_int) function trixi_initialize_simulation(libelixir)
9✔
672
    use, intrinsic :: iso_c_binding, only: c_int, c_null_char
673
    character(len=*), intent(in) :: libelixir
674

675
    trixi_initialize_simulation = trixi_initialize_simulation_c(trim(adjustl(libelixir)) // c_null_char)
9✔
676
  end function
18✔
677

678
  !>
679
  !! @brief Check if simulation is finished (Fortran convenience version)
680
  !!
681
  !! @param[in]  handle  simulation handle
682
  !!
683
  !! @return true if finished, false if not
684
  !!
685
  !! @see @ref trixi_is_finished_c::trixi_is_finished_c
686
  !!           "trixi_is_finished (C integer version)"
687
  !! @see @ref trixi_is_finished_api_c
688
  !!           "trixi_is_finished (C API)"
689
  logical function trixi_is_finished(handle)
6,220✔
690
    use, intrinsic :: iso_c_binding, only: c_int
691
    integer(c_int), intent(in) :: handle
692

693
    trixi_is_finished = trixi_is_finished_c(handle) == 1
6,220✔
694
  end function
6,220✔
695

696
  !>
697
  !! @brief Execute Julia code (Fortran convenience version)
698
  !!
699
  !! @warning Only for development. Code is not checked prior to execution.
700
  !!
701
  !! @see @ref trixi_eval_julia_c::trixi_eval_julia_c
702
  !!           "trixi_eval_julia_c (C char pointer version)"
703
  !! @see @ref trixi_eval_julia_api_c
704
  !!           "trixi_eval_julia_c (C API)"
705
  subroutine trixi_eval_julia(code)
3✔
706
    use, intrinsic :: iso_c_binding, only: c_null_char
707
    character(len=*), intent(in) :: code
708

709
    call trixi_eval_julia_c(trim(adjustl(code)) // c_null_char)
3✔
710
  end subroutine
3✔
711
  
712
end module
713

714
!>
715
!! @}
STATUS · Troubleshooting · Open an Issue · Sales · Support · CAREERS · ENTERPRISE · START FREE · SCHEDULE DEMO
ANNOUNCEMENTS · TWITTER · TOS & SLA · Supported CI Services · What's a CI service? · Automated Testing

© 2026 Coveralls, Inc