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

trixi-framework / libtrixi / 16653889260

31 Jul 2025 03:55PM UTC coverage: 96.663% (-0.4%) from 97.027%
16653889260

Pull #219

github

web-flow
Merge a15a65e80 into 21bcea2ff
Pull Request #219: RFC: raw data access

35 of 40 new or added lines in 4 files covered. (87.5%)

17 existing lines in 4 files now uncovered.

1014 of 1049 relevant lines covered (96.66%)

462002.27 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
    !! @fn LibTrixi::trixi_load_primitive_vars::trixi_load_primitive_vars(handle, variable_id, data)
379
    !!
380
    !! @brief Load primitive variable
381
    !!
382
    !! @param[in]  handle       simulation handle
383
    !! @param[in]  variable_id  index of variable
384
    !! @param[out] data         primitive variable values for all degrees of freedom
385
    !!
386
    !! @see @ref trixi_load_primitive_vars_api_c "trixi_load_primitive_vars (C API)"
387
    subroutine trixi_load_primitive_vars(handle, variable_id, data) bind(c)
388
      use, intrinsic :: iso_c_binding, only: c_int, c_double
389
      integer(c_int), value, intent(in) :: handle
390
      integer(c_int), value, intent(in) :: variable_id
391
      real(c_double), dimension(*), intent(out) :: data
392
    end subroutine
393

394
    !>
395
    !! @fn LibTrixi::trixi_get_simulation_time::trixi_get_simulation_time(handle)
396
    !!
397
    !! @brief Return current physical time.
398
    !!
399
    !! @param[in]  handle  simulation handle
400
    !!
401
    !! @return  physical time
402
    !!
403
    !! @see @ref trixi_get_simulation_time_api_c "trixi_get_simulation_time (C API)"
404
    real(c_double) function trixi_get_simulation_time(handle) bind(c)
405
      use, intrinsic :: iso_c_binding, only: c_int, c_double
406
      integer(c_int), value, intent(in) :: handle
407
    end function
408

409
    !>
410
    !! @fn LibTrixi::trixi_load_element_averaged_primitive_vars::trixi_load_element_averaged_primitive_vars(handle, variable_id, data)
411
    !!
412
    !! @brief Load element averages for primitive variable
413
    !!
414
    !! @param[in]  handle       simulation handle
415
    !! @param[in]  variable_id  index of variable
416
    !! @param[out] data         averaged values for all elements
417
    !!
418
    !! @see @ref trixi_load_element_averaged_primitive_vars_api_c "trixi_load_element_averaged_primitive_vars (C API)"
419
    subroutine trixi_load_element_averaged_primitive_vars(handle, variable_id, data) bind(c)
420
      use, intrinsic :: iso_c_binding, only: c_int, c_double
421
      integer(c_int), value, intent(in) :: handle
422
      integer(c_int), value, intent(in) :: variable_id
423
      real(c_double), dimension(*), intent(out) :: data
424
    end subroutine
425

426
    !>
427
    !! @fn LibTrixi::trixi_register_data::trixi_register_data(handle, variable_id, data)
428
    !!
429
    !! @brief Store data vector in current simulation's registry
430
    !!
431
    !! @param[in]  handle  simulation handle
432
    !! @param[in]  index   index in registry where data vector will be stored
433
    !! @param[in]  size    size of given data vector
434
    !! @param[in]  data    data vector to store
435
    !!
436
    !! @see @ref trixi_register_data_api_c "trixi_register_data (C API)"
437
    subroutine trixi_register_data(handle, index, size, data) bind(c)
438
      use, intrinsic :: iso_c_binding, only: c_int, c_double
439
      integer(c_int), value, intent(in) :: handle
440
      integer(c_int), value, intent(in) :: index
441
      integer(c_int), value, intent(in) :: size
442
      real(c_double), dimension(*), intent(in) :: data
443
    end subroutine
444

445
    !>
446
    !! @anchor trixi_get_data_pointer_api_c
447
    !!
448
    !! @brief Return pointer to internal data vector.
449
    !!
450
    !! The returned pointer points to the beginning of the internal data array used in
451
    !! Trixi.jl. This array contains the conservative variables, i.e. density, momentum
452
    !! density in the three Cartesian coordinates, and energy density, in this sequence.
453
    !! The pointer can be used to read, but also to write these variables. The latter
454
    !! should be done with care. Writing while a time step in being performed will lead to
455
    !! undefined behavior.
456
    !!
457
    !! @param[in]  handle  simulation handle
458
    type (c_ptr) function trixi_get_data_pointer(handle) bind(c)
459
      use, intrinsic :: iso_c_binding, only: c_int, c_ptr
460
      integer(c_int), value, intent(in) :: handle
461
    end function
462

463

464

465
    !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
466
    !! t8code                                                                             !!
467
    !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
468
    !>
469
    !! @fn LibTrixi::trixi_get_t8code_forest::trixi_get_t8code_forest(handle)
470
    !!
471
    !! @brief Get t8code forest
472
    !!
473
    !! @param[in]  handle       simulation handle
474
    !!
475
    !! @return t8code forest
476
    !!
477
    !! @see @ref trixi_get_t8code_forest_api_c "trixi_get_t8code_forest (C API)"
478
    type (c_ptr) function trixi_get_t8code_forest(handle) bind(c)
479
      use, intrinsic :: iso_c_binding, only: c_int, c_ptr
480
      integer(c_int), value, intent(in) :: handle
481
    end function
482

483

484

485
    !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
486
    !! Misc                                                                               !!
487
    !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
488

489
    !>
490
    !! @fn LibTrixi::trixi_eval_julia_c::trixi_eval_julia_c(code)
491
    !!
492
    !! @brief Execute Julia code (C char pointer version)
493
    !!
494
    !! @warning Only for development. Code is not checked prior to execution.
495
    !!
496
    !! @see @ref trixi_eval_julia       "trixi_eval_julia_c (Fortran convenience version)"
497
    !! @see @ref trixi_eval_julia_api_c "trixi_eval_julia_c (C API)"
498
    subroutine trixi_eval_julia_c(code) bind(c, name='trixi_eval_julia')
499
      use, intrinsic :: iso_c_binding, only: c_char
500
      character(kind=c_char), dimension(*), intent(in) :: code
501
    end subroutine
502
  end interface
503

504
  contains
505

506
  !>
507
  !! @brief Initialize Julia runtime environment (Fortran convenience version)
508
  !!
509
  !! @param[in]  project_directory  Path to project directory (Fortran string).
510
  !! @param[in]  depot_path         Path to Julia depot path (Fortran string).
511
  !!
512
  !! @see @ref trixi_initialize_c::trixi_initialize_c
513
  !!           "trixi_initialize_c (C char pointer version)"
514
  !! @see @ref trixi_initialize_api_c
515
  !!           "trixi_initialize (C API)"
516
  subroutine trixi_initialize(project_directory, depot_path)
10✔
517
    use, intrinsic :: iso_c_binding, only: c_null_char
518
    character(len=*), intent(in) :: project_directory
519
    character(len=*), intent(in), optional :: depot_path
520

521
    if (present(depot_path)) then
10✔
522
      call trixi_initialize_c(trim(adjustl(project_directory)) // c_null_char, &
UNCOV
523
                              trim(adjustl(depot_path)) // c_null_char)
×
524
    else
525
      call trixi_initialize_c(trim(adjustl(project_directory)) // c_null_char)
10✔
526
    end if
527
  end subroutine
10✔
528

529
  !>
530
  !! @brief Return full version string of libtrixi (Fortran convenience version).
531
  !!
532
  !! @return Full version string as Fortran allocatable string.
533
  !!
534
  !! @see @ref trixi_version_library_c::trixi_version_library_c
535
  !!           "trixi_version_library_c (C char pointer version)"
536
  !! @see @ref trixi_version_library_api_c
537
  !!           "trixi_version_library (C API)"
538
  function trixi_version_library()
3✔
539
    use, intrinsic :: iso_c_binding, only: c_char, c_null_char, c_f_pointer
540
    character(len=:), allocatable :: trixi_version_library
541
    character(len=128, kind=c_char), pointer :: buffer
542
    integer :: length, i
543

544
    ! Associate buffer with C pointer
545
    call c_f_pointer(trixi_version_library_c(), buffer)
3✔
546

547
    ! Determine the actual length of the version string
548
    length = 0
3✔
549
    do i = 1,128
30✔
550
      if ( buffer(i:i) == c_null_char ) exit
30✔
551
      length = length + 1
27✔
552
    end do
553

554
    ! Store relevant part in return value
555
    trixi_version_library = buffer(1:(length + 1))
3✔
556
  end function
3✔
557

558
  !>
559
  !! @brief Return name and version of loaded julia packages LibTrixi directly depends on
560
  !!        (Fortran convenience version).
561
  !!
562
  !! @return Name and version of loaded julia packages as Fortran allocatable string.
563
  !!
564
  !! @see @ref trixi_version_julia_c::trixi_version_julia_c
565
  !!           "trixi_version_julia_c (C char pointer version)"
566
  !! @see @ref trixi_version_julia_api_c
567
  !!           "trixi_version_julia (C API)"
568
  function trixi_version_julia()
2✔
569
    use, intrinsic :: iso_c_binding, only: c_char, c_null_char, c_f_pointer
570
    character(len=:), allocatable :: trixi_version_julia
571
    character(len=1024, kind=c_char), pointer :: buffer
572
    integer :: length, i
573

574
    ! Associate buffer with C pointer
575
    call c_f_pointer(trixi_version_julia_c(), buffer)
2✔
576

577
    ! Determine the actual length of the version string
578
    length = 0
2✔
579
    do i = 1,1024
342✔
580
      if ( buffer(i:i) == c_null_char ) exit
342✔
581
      length = length + 1
340✔
582
    end do
583

584
    ! Store relevant part in return value
585
    trixi_version_julia = buffer(1:(length + 1))
2✔
586
  end function
2✔
587

588
  !>
589
  !! @brief Return name and version of all loaded julia packages
590
  !!        (Fortran convenience version).
591
  !!
592
  !! @return Name and version of loaded julia packages as Fortran allocatable string.
593
  !!
594
  !! @see @ref trixi_version_julia_extended_c::trixi_version_julia_extended_c
595
  !!           "trixi_version_julia_extended_c (C char pointer version)"
596
  !! @see @ref trixi_version_julia_extended_api_c
597
  !!           "trixi_version_julia_extended (C API)"
598
  function trixi_version_julia_extended()
3✔
599
    use, intrinsic :: iso_c_binding, only: c_char, c_null_char, c_f_pointer
600
    character(len=:), allocatable :: trixi_version_julia_extended
601
    character(len=8192, kind=c_char), pointer :: buffer
602
    integer :: length, i
603

604
    ! Associate buffer with C pointer
605
    call c_f_pointer(trixi_version_julia_extended_c(), buffer)
3✔
606

607
    ! Determine the actual length of the version string
608
    length = 0
3✔
609
    do i = 1,8192
16,329✔
610
      if ( buffer(i:i) == c_null_char ) exit
16,329✔
611
      length = length + 1
16,326✔
612
    end do
613

614
    ! Store relevant part in return value
615
    trixi_version_julia_extended = buffer(1:(length + 1))
3✔
616
  end function
3✔
617

618
  !>
619
  !! @brief Set up Trixi simulation (Fortran convenience version)
620
  !!
621
  !! @param[in]  libelixir  Path to libelexir file.
622
  !!
623
  !! @return handle (integer) to Trixi simulation instance
624
  !!
625
  !! @see @ref trixi_initialize_simulation_c::trixi_initialize_simulation_c
626
  !!           "trixi_initialize_simulation_c (C char pointer version)"
627
  !! @see @ref trixi_initialize_simulation_api_c
628
  !!           "trixi_initialize_simulation (C API)"
629
  integer(c_int) function trixi_initialize_simulation(libelixir)
8✔
630
    use, intrinsic :: iso_c_binding, only: c_int, c_null_char
631
    character(len=*), intent(in) :: libelixir
632

633
    trixi_initialize_simulation = trixi_initialize_simulation_c(trim(adjustl(libelixir)) // c_null_char)
8✔
634
  end function
16✔
635

636
  !>
637
  !! @brief Check if simulation is finished (Fortran convenience version)
638
  !!
639
  !! @param[in]  handle  simulation handle
640
  !!
641
  !! @return true if finished, false if not
642
  !!
643
  !! @see @ref trixi_is_finished_c::trixi_is_finished_c
644
  !!           "trixi_is_finished (C integer version)"
645
  !! @see @ref trixi_is_finished_api_c
646
  !!           "trixi_is_finished (C API)"
647
  logical function trixi_is_finished(handle)
4,753✔
648
    use, intrinsic :: iso_c_binding, only: c_int
649
    integer(c_int), intent(in) :: handle
650

651
    trixi_is_finished = trixi_is_finished_c(handle) == 1
4,753✔
652
  end function
4,753✔
653

654
  !>
655
  !! @brief Execute Julia code (Fortran convenience version)
656
  !!
657
  !! @warning Only for development. Code is not checked prior to execution.
658
  !!
659
  !! @see @ref trixi_eval_julia_c::trixi_eval_julia_c
660
  !!           "trixi_eval_julia_c (C char pointer version)"
661
  !! @see @ref trixi_eval_julia_api_c
662
  !!           "trixi_eval_julia_c (C API)"
663
  subroutine trixi_eval_julia(code)
3✔
664
    use, intrinsic :: iso_c_binding, only: c_null_char
665
    character(len=*), intent(in) :: code
666

667
    call trixi_eval_julia_c(trim(adjustl(code)) // c_null_char)
3✔
668
  end subroutine
3✔
669
  
670
end module
671

672
!>
673
!! @}
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