World Builder  0.1.0-pre
A geodyanmic initial conditions generator
wrapper_fortran.f90
Go to the documentation of this file.
2 use, INTRINSIC :: iso_c_binding!, ONLY: C_PTR
3  IMPLICIT NONE
4 
5  ! Create an interface with the create world function
6  INTERFACE
7  SUBROUTINE create_world(cworld, file_name) bind(C, NAME='create_world')
8  use, INTRINSIC :: iso_c_binding, only: c_ptr
9  IMPLICIT NONE
10  ! This argument is a pointer passed by reference.
11  TYPE(c_ptr), INTENT(OUT) :: cworld
12  character(len=1), intent(in) :: file_name
13  END SUBROUTINE create_world
14 
15  ! Create an interface with the 2d tempearture function of the World builder
16  SUBROUTINE temperature_2d(cworld, x, z, depth, gravity, temperature) bind(C, NAME='temperature_2d')
17  use, INTRINSIC :: iso_c_binding
18  IMPLICIT NONE
19  ! This argument is a pointer passed by value.
20  TYPE(c_ptr), INTENT(IN), VALUE :: cworld
21  REAL(C_DOUBLE), intent(in), value :: x
22  REAL(C_DOUBLE), intent(in), value :: z
23  REAL(C_DOUBLE), intent(in), value :: depth
24  REAL(C_DOUBLE), intent(in), value :: gravity
25  REAL(C_DOUBLE), intent(out) :: temperature
26  END SUBROUTINE temperature_2d
27 
28  ! Create an interface with the 3d tempearture function of the World builder
29  SUBROUTINE temperature_3d(cworld, x, y, z, depth, gravity, temperature) bind(C, NAME='temperature_3d')
30  use, INTRINSIC :: iso_c_binding
31  IMPLICIT NONE
32  ! This argument is a pointer passed by value.
33  TYPE(c_ptr), INTENT(IN), VALUE :: cworld
34  REAL(C_DOUBLE), intent(in), value :: x
35  REAL(C_DOUBLE), intent(in), value :: y
36  REAL(C_DOUBLE), intent(in), value :: z
37  REAL(C_DOUBLE), intent(in), value :: depth
38  REAL(C_DOUBLE), intent(in), value :: gravity
39  REAL(C_DOUBLE), intent(out) :: temperature
40  END SUBROUTINE temperature_3d
41 
42  ! Create an interface with the 2d composition function of the World builder
43  SUBROUTINE composition_2d(cworld, x, z, depth, composition_number, composition) bind(C, NAME='composition_2d')
44  use, INTRINSIC :: iso_c_binding
45  IMPLICIT NONE
46  ! This argument is a pointer passed by value.
47  TYPE(c_ptr), INTENT(IN), VALUE :: cworld
48  REAL(C_DOUBLE), intent(in), value :: x
49  REAL(C_DOUBLE), intent(in), value :: z
50  REAL(C_DOUBLE), intent(in), value :: depth
51  INTEGER(C_INT), intent(in), value :: composition_number
52  LOGICAL(C_BOOL), intent(out) :: composition
53  END SUBROUTINE composition_2d
54 
55  ! Create an interface with the 3d composition function of the World builder
56  SUBROUTINE composition_3d(cworld, x, y, z, depth, composition_number, composition) bind(C, NAME='composition_3d')
57  use, INTRINSIC :: iso_c_binding
58  IMPLICIT NONE
59  ! This argument is a pointer passed by value.
60  TYPE(c_ptr), INTENT(IN), VALUE :: cworld
61  REAL(C_DOUBLE), intent(in), value :: x
62  REAL(C_DOUBLE), intent(in), value :: y
63  REAL(C_DOUBLE), intent(in), value :: z
64  REAL(C_DOUBLE), intent(in), value :: depth
65  INTEGER(C_INT), intent(in), value :: composition_number
66  LOGICAL(C_BOOL), intent(out) :: composition
67  END SUBROUTINE composition_3d
68 
69  ! Create an interface with the release world function.
70  SUBROUTINE release_world(cworld) bind(C, NAME='release_world')
71  use, INTRINSIC :: iso_c_binding, only: c_ptr
72  IMPLICIT NONE
73  ! This argument is a pointer passed by value.
74  TYPE(c_ptr), INTENT(IN), VALUE :: cworld
75  END SUBROUTINE release_world
76  END INTERFACE
77 
78  TYPE(c_ptr) :: cworld
79  END MODULE worldbuilder
type(c_ptr) cworld