Ignore:
Timestamp:
01/20/13 23:14:35 (11 years ago)
Author:
ymipsl
Message:

Add grid mask attribute

YM

File:
1 edited

Legend:

Unmodified
Added
Removed
  • XIOS/trunk/src/interface/fortran_attr/axis_interface_attr.f90

    r369 r415  
    3737      INTEGER  (kind = C_INT)     , VALUE        :: name_size 
    3838    END SUBROUTINE cxios_get_axis_name 
     39     
     40     
     41    SUBROUTINE cxios_set_axis_positive(axis_hdl, positive, positive_size) BIND(C) 
     42      USE ISO_C_BINDING 
     43      INTEGER (kind = C_INTPTR_T), VALUE :: axis_hdl 
     44      CHARACTER(kind = C_CHAR)    , DIMENSION(*) :: positive 
     45      INTEGER  (kind = C_INT)     , VALUE        :: positive_size 
     46    END SUBROUTINE cxios_set_axis_positive 
     47     
     48    SUBROUTINE cxios_get_axis_positive(axis_hdl, positive, positive_size) BIND(C) 
     49      USE ISO_C_BINDING 
     50      INTEGER (kind = C_INTPTR_T), VALUE :: axis_hdl 
     51      CHARACTER(kind = C_CHAR)    , DIMENSION(*) :: positive 
     52      INTEGER  (kind = C_INT)     , VALUE        :: positive_size 
     53    END SUBROUTINE cxios_get_axis_positive 
    3954     
    4055     
Note: See TracChangeset for help on using the changeset viewer.