New URL for NEMO forge!   http://forge.nemo-ocean.eu

Since March 2022 along with NEMO 4.2 release, the code development moved to a self-hosted GitLab.
This present forge is now archived and remained online for history.
axisgroup_interface_attr.f90 in vendors/XIOS/current/src/interface/fortran_attr – NEMO

source: vendors/XIOS/current/src/interface/fortran_attr/axisgroup_interface_attr.f90 @ 3428

Last change on this file since 3428 was 3428, checked in by rblod, 12 years ago

importing initial XIOS vendor drop

File size: 5.0 KB
Line 
1! * ************************************************************************** *
2! *               Interface auto generated - do not modify                     *
3! * ************************************************************************** *
4
5MODULE axisgroup_interface_attr
6  USE, INTRINSIC :: ISO_C_BINDING
7 
8  INTERFACE ! Do not call directly / interface FORTRAN 2003 <-> C99
9   
10   
11    SUBROUTINE cxios_set_axisgroup_group_ref(axisgroup_hdl, group_ref, group_ref_size) BIND(C)
12      USE ISO_C_BINDING
13      INTEGER (kind = C_INTPTR_T), VALUE :: axisgroup_hdl
14      CHARACTER(kind = C_CHAR)    , DIMENSION(*) :: group_ref
15      INTEGER  (kind = C_INT)     , VALUE        :: group_ref_size
16    END SUBROUTINE cxios_set_axisgroup_group_ref
17   
18    SUBROUTINE cxios_get_axisgroup_group_ref(axisgroup_hdl, group_ref, group_ref_size) BIND(C)
19      USE ISO_C_BINDING
20      INTEGER (kind = C_INTPTR_T), VALUE :: axisgroup_hdl
21      CHARACTER(kind = C_CHAR)    , DIMENSION(*) :: group_ref
22      INTEGER  (kind = C_INT)     , VALUE        :: group_ref_size
23    END SUBROUTINE cxios_get_axisgroup_group_ref
24   
25   
26    SUBROUTINE cxios_set_axisgroup_long_name(axisgroup_hdl, long_name, long_name_size) BIND(C)
27      USE ISO_C_BINDING
28      INTEGER (kind = C_INTPTR_T), VALUE :: axisgroup_hdl
29      CHARACTER(kind = C_CHAR)    , DIMENSION(*) :: long_name
30      INTEGER  (kind = C_INT)     , VALUE        :: long_name_size
31    END SUBROUTINE cxios_set_axisgroup_long_name
32   
33    SUBROUTINE cxios_get_axisgroup_long_name(axisgroup_hdl, long_name, long_name_size) BIND(C)
34      USE ISO_C_BINDING
35      INTEGER (kind = C_INTPTR_T), VALUE :: axisgroup_hdl
36      CHARACTER(kind = C_CHAR)    , DIMENSION(*) :: long_name
37      INTEGER  (kind = C_INT)     , VALUE        :: long_name_size
38    END SUBROUTINE cxios_get_axisgroup_long_name
39   
40   
41    SUBROUTINE cxios_set_axisgroup_name(axisgroup_hdl, name, name_size) BIND(C)
42      USE ISO_C_BINDING
43      INTEGER (kind = C_INTPTR_T), VALUE :: axisgroup_hdl
44      CHARACTER(kind = C_CHAR)    , DIMENSION(*) :: name
45      INTEGER  (kind = C_INT)     , VALUE        :: name_size
46    END SUBROUTINE cxios_set_axisgroup_name
47   
48    SUBROUTINE cxios_get_axisgroup_name(axisgroup_hdl, name, name_size) BIND(C)
49      USE ISO_C_BINDING
50      INTEGER (kind = C_INTPTR_T), VALUE :: axisgroup_hdl
51      CHARACTER(kind = C_CHAR)    , DIMENSION(*) :: name
52      INTEGER  (kind = C_INT)     , VALUE        :: name_size
53    END SUBROUTINE cxios_get_axisgroup_name
54   
55   
56    SUBROUTINE cxios_set_axisgroup_size(axisgroup_hdl, size) BIND(C)
57      USE ISO_C_BINDING
58      INTEGER (kind = C_INTPTR_T), VALUE :: axisgroup_hdl
59      INTEGER (KIND=C_INT)      , VALUE :: size
60    END SUBROUTINE cxios_set_axisgroup_size
61   
62    SUBROUTINE cxios_get_axisgroup_size(axisgroup_hdl, size) BIND(C)
63      USE ISO_C_BINDING
64      INTEGER (kind = C_INTPTR_T), VALUE :: axisgroup_hdl
65      INTEGER (KIND=C_INT)             :: size
66    END SUBROUTINE cxios_get_axisgroup_size
67   
68   
69    SUBROUTINE cxios_set_axisgroup_standard_name(axisgroup_hdl, standard_name, standard_name_size) BIND(C)
70      USE ISO_C_BINDING
71      INTEGER (kind = C_INTPTR_T), VALUE :: axisgroup_hdl
72      CHARACTER(kind = C_CHAR)    , DIMENSION(*) :: standard_name
73      INTEGER  (kind = C_INT)     , VALUE        :: standard_name_size
74    END SUBROUTINE cxios_set_axisgroup_standard_name
75   
76    SUBROUTINE cxios_get_axisgroup_standard_name(axisgroup_hdl, standard_name, standard_name_size) BIND(C)
77      USE ISO_C_BINDING
78      INTEGER (kind = C_INTPTR_T), VALUE :: axisgroup_hdl
79      CHARACTER(kind = C_CHAR)    , DIMENSION(*) :: standard_name
80      INTEGER  (kind = C_INT)     , VALUE        :: standard_name_size
81    END SUBROUTINE cxios_get_axisgroup_standard_name
82   
83   
84    SUBROUTINE cxios_set_axisgroup_unit(axisgroup_hdl, unit, unit_size) BIND(C)
85      USE ISO_C_BINDING
86      INTEGER (kind = C_INTPTR_T), VALUE :: axisgroup_hdl
87      CHARACTER(kind = C_CHAR)    , DIMENSION(*) :: unit
88      INTEGER  (kind = C_INT)     , VALUE        :: unit_size
89    END SUBROUTINE cxios_set_axisgroup_unit
90   
91    SUBROUTINE cxios_get_axisgroup_unit(axisgroup_hdl, unit, unit_size) BIND(C)
92      USE ISO_C_BINDING
93      INTEGER (kind = C_INTPTR_T), VALUE :: axisgroup_hdl
94      CHARACTER(kind = C_CHAR)    , DIMENSION(*) :: unit
95      INTEGER  (kind = C_INT)     , VALUE        :: unit_size
96    END SUBROUTINE cxios_get_axisgroup_unit
97   
98   
99    SUBROUTINE cxios_set_axisgroup_value(axisgroup_hdl, value, extent1) BIND(C)
100      USE ISO_C_BINDING
101      INTEGER (kind = C_INTPTR_T), VALUE       :: axisgroup_hdl
102      REAL (KIND=C_DOUBLE)     , DIMENSION(*) :: value
103      INTEGER (kind = C_INT), VALUE  :: extent1
104    END SUBROUTINE cxios_set_axisgroup_value
105   
106    SUBROUTINE cxios_get_axisgroup_value(axisgroup_hdl, value, extent1) BIND(C)
107      USE ISO_C_BINDING
108      INTEGER (kind = C_INTPTR_T), VALUE       :: axisgroup_hdl
109      REAL (KIND=C_DOUBLE)     , DIMENSION(*) :: value
110      INTEGER (kind = C_INT), VALUE  :: extent1
111    END SUBROUTINE cxios_get_axisgroup_value
112   
113   
114    END INTERFACE
115 
116END MODULE axisgroup_interface_attr
Note: See TracBrowser for help on using the repository browser.