source: XIOS/trunk/src/interface/fortran/interpolate_axis_interface.f90 @ 786

Last change on this file since 786 was 786, checked in by mhnguyen, 8 years ago

Generating interface for transformations

+) Update Fortran interface for other transformations
+) Remove some redundant files
+) Update test to new interface

Test
+) On Curie
+) test_client and test_complete are correct

File size: 890 bytes
Line 
1MODULE INTERPOLATE_AXIS_INTERFACE
2   USE, INTRINSIC :: ISO_C_BINDING
3
4   INTERFACE ! Ne pas appeler directement/Interface FORTRAN 2003 <-> C99
5
6      SUBROUTINE cxios_interpolate_axis_handle_create(ret, idt, idt_size) BIND(C)
7         USE ISO_C_BINDING
8         INTEGER  (kind = C_INTPTR_T)               :: ret
9         CHARACTER(kind = C_CHAR)    , DIMENSION(*) :: idt
10         INTEGER  (kind = C_INT)     , VALUE        :: idt_size
11      END SUBROUTINE cxios_interpolate_axis_handle_create
12
13      SUBROUTINE cxios_interpolate_axis_valid_id(ret, idt, idt_size) BIND(C)
14         USE ISO_C_BINDING
15         LOGICAL  (kind = C_BOOL)                   :: ret
16         CHARACTER(kind = C_CHAR)    , DIMENSION(*) :: idt
17         INTEGER  (kind = C_INT)     , VALUE        :: idt_size
18      END SUBROUTINE cxios_interpolate_axis_valid_id
19
20   END INTERFACE
21
22END MODULE INTERPOLATE_AXIS_INTERFACE
Note: See TracBrowser for help on using the repository browser.