source: XMLIO_V2/dev/common/src/xmlio/fortran/context_interface.f90 @ 286

Last change on this file since 286 was 286, checked in by ymipsl, 13 years ago

reprise en main de la version de H. Ozdoba. Correction de différentes erreurs de conception et bug.
Version NEMO operationnel en client/server, interoperabilita avec OASIS, reconstition de fichiers via netcdf4/HDF5

YM

File size: 2.8 KB
RevLine 
[274]1MODULE CONTEXT_INTERFACE
2   USE, INTRINSIC :: ISO_C_BINDING
3     
4   INTERFACE ! Ne pas appeler directement/Interface FORTRAN 2003 <-> C99
5     
[286]6      SUBROUTINE cxios_set_context_calendar_type(context_hdl, calendar_type ,calendar_type_size) BIND(C)
[274]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)     , VALUE        :: calendar_type_size
[286]11      END SUBROUTINE cxios_set_context_calendar_type
[274]12
[286]13      SUBROUTINE cxios_set_context_start_date(context_hdl, start_date ,start_date_size) BIND(C)
[274]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)     , VALUE        :: start_date_size
[286]18      END SUBROUTINE cxios_set_context_start_date
[274]19
[286]20      SUBROUTINE cxios_set_context_output_dir(context_hdl, output_dir ,output_dir_size) BIND(C)
[274]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)     , VALUE        :: output_dir_size
[286]25      END SUBROUTINE cxios_set_context_output_dir
[274]26     
[286]27      SUBROUTINE cxios_context_handle_create(ret, idt, idt_size) BIND(C)
[274]28         import C_CHAR, C_INTPTR_T, C_INT
29         INTEGER  (kind = C_INTPTR_T)               :: ret
30         CHARACTER(kind = C_CHAR)    , DIMENSION(*) :: idt
31         INTEGER  (kind = C_INT)     , VALUE        :: idt_size
[286]32      END SUBROUTINE cxios_context_handle_create
[274]33     
[286]34      SUBROUTINE cxios_context_set_current(context, withswap) BIND(C)
[274]35         import C_BOOL, C_INT, C_INTPTR_T
36         INTEGER (kind = C_INTPTR_T), VALUE :: context
37         LOGICAL (kind = C_BOOL)    , VALUE :: withswap
[286]38      END SUBROUTINE cxios_context_set_current
[274]39
[286]40      SUBROUTINE cxios_context_create(context, context_id, context_id_size, calendar_type, &
[274]41                                     year, month, day, hour, minute, second) BIND(C)
[280]42         USE ISO_C_BINDING
[274]43         INTEGER  (kind = C_INTPTR_T)               :: context
44         CHARACTER(kind = C_CHAR)    , DIMENSION(*) :: context_id
45         INTEGER  (kind = C_INT)     , VALUE        :: context_id_size
46         INTEGER  (kind = C_INT)     , VALUE        :: calendar_type, year, month, day, hour, minute, second
[286]47      END SUBROUTINE cxios_context_create
[280]48
[286]49      SUBROUTINE cxios_context_valid_id(ret, idt, idt_size) BIND(C)
[280]50         USE ISO_C_BINDING
51         LOGICAL  (kind = C_BOOL)                   :: ret
52         CHARACTER(kind = C_CHAR)    , DIMENSION(*) :: idt
53         INTEGER  (kind = C_INT)     , VALUE        :: idt_size
[286]54      END SUBROUTINE cxios_context_valid_id
[280]55
[274]56   END INTERFACE
57     
58END MODULE CONTEXT_INTERFACE
Note: See TracBrowser for help on using the repository browser.