Ignore:
Timestamp:
07/06/11 13:55:03 (13 years ago)
Author:
hozdoba
Message:

Ajout d'une partie d'Interface fortran pour la version 4
Ajout des sorties netcdf4 pour la version 4

File:
1 edited

Legend:

Unmodified
Added
Removed
  • XMLIO_V2/dev/dev_rv/src4/xmlio/fortran/context_interface.f90

    r242 r249  
    2424         INTEGER  (kind = C_INT)                    :: output_dir_size 
    2525      END SUBROUTINE xios_set_context_output_dir 
     26       
     27      SUBROUTINE xios_context_handle_create(ret, idt, idt_size) BIND(C) 
     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 
     32      END SUBROUTINE xios_context_handle_create 
     33       
     34      SUBROUTINE xios_context_set_current(context, withswap) BIND(C) 
     35         import C_BOOL, C_INT, C_INTPTR_T 
     36         INTEGER (kind = C_INTPTR_T), VALUE :: context 
     37         LOGICAL (kind = C_BOOL)    , VALUE :: withswap 
     38      END SUBROUTINE xios_context_set_current 
     39 
     40      SUBROUTINE xios_context_create(context, context_id, context_id_size, calendar_type, & 
     41                                     year, month, day, hour, minute, second) BIND(C) 
     42         import C_CHAR, C_INT, C_INTPTR_T 
     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 
     47      END SUBROUTINE xios_context_create 
    2648      
    2749   END INTERFACE 
Note: See TracChangeset for help on using the changeset viewer.