Graph Framework
Loading...
Searching...
No Matches
Embedding in Fortran code

Documentation for linking into a Fortran code base.

Introduction

This section assumes the reader is already familar with developing Fortran codes. The simplist method is to create a C callable function like the C binding exmaple. Then create a Fortran interface for it.

INTERFACE
SUBROUTINE fortran_callable bind(C, NAME='c_callable_function')
use, INTRINSIC :: iso_c_binding
IMPLICIT NONE
END SUBROUTINE
END INTERFACE

This subroutine can be called like any other Fortran subroutine.

CALL Fortran_Callable

Fortran Binding Interface

An alternative is to use the Fortran Language interface. The Fortran binding interface can be enabled as one of the cmake conifgure options. As an example, we will convert the making workflows turorial to use the Fortran language bindings.

SUBROUTINE fortran_binding
use, INTRINSIC :: iso_c_binding
IMPLICIT NONE
CLASS(graph_context), POINTER :: graph
TYPE(C_PTR) :: x
TYPE(C_PTR) :: m
TYPE(C_PTR) :: b
TYPE(C_PTR) :: y
TYPE(C_PTR) :: dydx
LOGICAL(C_BOOL), PARAMETER :: use_safe_math = .false.
graph => graph_double_context(use_safe_math);
x = graph%variable(1_c_long, 'x' // c_null_char)
m = graph%constant(0.4_c_double)
b = graph%constant(0.6_c_double)
y = graph%add(graph%mul(m, x), b)
dydx = graph%df(y, x);
CALL graph%set_variable(x, (/ 1.0_c_double, 2.0_c_double, 3.0_c_double /))
CALL graph%set_device_number(0)
CALL graph%add_item((/ graph_ptr(x) /), &
(/ graph_ptr(y), graph_ptr(dydx) /)) &
'my_first_kernel' // c_null_char, 3_c_long)
CALL graph%compile
CALL graph%run
CALL graph%print(0, (/ graph_ptr(x), graph_ptr(y), graph_ptr(dydx) /))
CALL graph%print(1, (/ graph_ptr(x), graph_ptr(y), graph_ptr(dydx) /))
CALL graph%print(2, (/ graph_ptr(x), graph_ptr(y), graph_ptr(dydx) /))
DEALLOCATE(graph)
END SUBROUTINE
Interface for the graph_context constructor with double type.
Definition graph_fortran_binding.f90:206
Module contains subroutines for calling this from fortran.
Definition graph_fortran_binding.f90:83
integer(c_intptr_t), dimension(0) graph_null_array
A null array for empty.
Definition graph_fortran_binding.f90:89
integer(c_intptr_t) function graph_ptr(node)
Convert a node to the pointer value.
Definition graph_fortran_binding.f90:916
Name space for graph nodes.
Definition arithmetic.hpp:13
Note
Graphs need to use the graph_fortran::graph_ptr function to get the pointer address of node.
The graph_fortran::graph_null_array allows setting array of nodes arguments to null.