source: vendor/nemo/current/NEMOGCM/EXTERNAL/XIOS/src/interface/fortran/gridgroup_interface.f90 @ 44

Last change on this file since 44 was 44, checked in by cholod, 12 years ago

Load NEMO_TMP into vendor/nemo/current.

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