source: XIOS/dev/XIOS_DEV_CMIP6/src/interface/fortran/reorder_domain_interface.f90 @ 1492

Last change on this file since 1492 was 1492, checked in by oabramkina, 6 years ago

Updating fortran interface for attributes that have been recently introduced and the following filters:

duplicate_scalar_to_axis
reduce_axis_to_axis
reduce_scalar_to_scalar
reorder_domain
temporal_splitting.

File size: 878 bytes
Line 
1MODULE REORDER_DOMAIN_INTERFACE
2   USE, INTRINSIC :: ISO_C_BINDING
3
4   INTERFACE ! Ne pas appeler directement/Interface FORTRAN 2003 <-> C99
5
6      SUBROUTINE cxios_reorder_domain_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_reorder_domain_handle_create
12
13      SUBROUTINE cxios_reorder_domain_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_reorder_domain_valid_id
19
20   END INTERFACE
21
22END MODULE REORDER_DOMAIN_INTERFACE
Note: See TracBrowser for help on using the repository browser.