source: XMLIO_V2/dev/dev_rv/src4/xmlio/fortran/context_interface.f90 @ 242

Last change on this file since 242 was 242, checked in by hozdoba, 13 years ago

Ajout d'une partie d'Interface fortran pour la version 4

File size: 1.3 KB
Line 
1MODULE CONTEXT_INTERFACE
2   USE, INTRINSIC :: ISO_C_BINDING
3     
4   INTERFACE ! Ne pas appeler directement/Interface FORTRAN 2003 <-> C99
5     
6      SUBROUTINE xios_set_context_calendar_type(context_hdl, calendar_type ,calendar_type_size) BIND(C)
7         USE ISO_C_BINDING
8         INTEGER  (kind = C_INTPTR_T), VALUE        :: context_hdl
9         CHARACTER(kind = C_CHAR)    , DIMENSION(*) :: calendar_type
10         INTEGER  (kind = C_INT)                    :: calendar_type_size
11      END SUBROUTINE xios_set_context_calendar_type
12
13      SUBROUTINE xios_set_context_start_date(context_hdl, start_date ,start_date_size) BIND(C)
14         USE ISO_C_BINDING
15         INTEGER  (kind = C_INTPTR_T), VALUE        :: context_hdl
16         CHARACTER(kind = C_CHAR)    , DIMENSION(*) :: start_date
17         INTEGER  (kind = C_INT)                    :: start_date_size
18      END SUBROUTINE xios_set_context_start_date
19
20      SUBROUTINE xios_set_context_output_dir(context_hdl, output_dir ,output_dir_size) BIND(C)
21         USE ISO_C_BINDING
22         INTEGER  (kind = C_INTPTR_T), VALUE        :: context_hdl
23         CHARACTER(kind = C_CHAR)    , DIMENSION(*) :: output_dir
24         INTEGER  (kind = C_INT)                    :: output_dir_size
25      END SUBROUTINE xios_set_context_output_dir
26     
27   END INTERFACE
28     
29END MODULE CONTEXT_INTERFACE
Note: See TracBrowser for help on using the repository browser.