source: XMLIO_V2/dev/dev_rv/src/xmlio/fortran/igrid.f90 @ 270

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

Début nouvelle interface fortran

File size: 4.8 KB
Line 
1MODULE IGRID
2   USE, INTRINSIC :: ISO_C_BINDING
3   USE GRID_INTERFACE
4   USE GRIDGROUP_INTERFACE
5   
6   TYPE XGridHandle
7      INTEGER(kind = C_INTPTR_T) :: daddr
8   END TYPE XGridHandle
9   
10   TYPE XGridGroupHandle
11      INTEGER(kind = C_INTPTR_T) :: daddr
12   END TYPE XGridGroupHandle
13   
14   !----------------------------------------------------------------------------
15   INTERFACE set_grid_attributes
16      MODULE PROCEDURE set_grid_attributes_id,set_grid_attributes_hdl
17   END INTERFACE 
18   
19   INTERFACE set_grid_group_attributes
20      MODULE PROCEDURE set_gridgroup_attributes_id,set_gridgroup_attributes_hdl
21   END INTERFACE 
22   !----------------------------------------------------------------------------
23   
24   CONTAINS ! Fonctions disponibles pour les utilisateurs.
25   
26   SUBROUTINE set_grid_attributes_id(grid_id, name_, description_, domain_ref_, axis_ref_)
27      IMPLICIT NONE
28      TYPE(XGridHandle)                             :: grid_hdl
29      CHARACTER(len = *)               , INTENT(IN) :: grid_id
30      CHARACTER(len = *)     , OPTIONAL, INTENT(IN) :: name_
31      CHARACTER(len = *)     , OPTIONAL, INTENT(IN) :: description_
32      CHARACTER(len = *)     , OPTIONAL, INTENT(IN) :: domain_ref_
33      CHARACTER(len = *)     , OPTIONAL, INTENT(IN) :: axis_ref_
34     
35      CALL grid_handle_create(grid_hdl, grid_id)
36      CALL set_grid_attributes_hdl(grid_hdl, name_, description_, domain_ref_, axis_ref_)
37
38   END SUBROUTINE set_grid_attributes_id
39
40   SUBROUTINE set_grid_attributes_hdl(grid_hdl, name_, description_, domain_ref_, axis_ref_)
41      IMPLICIT NONE
42      TYPE      (XGridHandle)                       :: grid_hdl
43      CHARACTER(len = *)     , OPTIONAL, INTENT(IN) :: name_
44      CHARACTER(len = *)     , OPTIONAL, INTENT(IN) :: description_
45      CHARACTER(len = *)     , OPTIONAL, INTENT(IN) :: domain_ref_
46      CHARACTER(len = *)     , OPTIONAL, INTENT(IN) :: axis_ref_
47     
48      IF (PRESENT(name_))        THEN
49       CALL xios_set_grid_name(grid_hdl%daddr, name_, len(name_))
50      END IF
51      IF (PRESENT(description_)) THEN
52       CALL xios_set_grid_description(grid_hdl%daddr, description_, len(description_))
53      END IF
54      IF (PRESENT(domain_ref_))  THEN
55       CALL xios_set_grid_domain_ref(grid_hdl%daddr, domain_ref_, len(domain_ref_))
56      END IF
57      IF (PRESENT(axis_ref_))    THEN
58       CALL xios_set_grid_axis_ref(grid_hdl%daddr, axis_ref_, len(axis_ref_))
59      END IF
60   END SUBROUTINE set_grid_attributes_hdl
61   
62   SUBROUTINE set_gridgroup_attributes_id(gridgroup_id, name_, description_, domain_ref_, axis_ref_)
63      IMPLICIT NONE
64      TYPE(XGridGroupHandle)                        :: gridgroup_hdl
65      CHARACTER(len = *)               , INTENT(IN) :: gridgroup_id
66      CHARACTER(len = *)     , OPTIONAL, INTENT(IN) :: name_
67      CHARACTER(len = *)     , OPTIONAL, INTENT(IN) :: description_
68      CHARACTER(len = *)     , OPTIONAL, INTENT(IN) :: domain_ref_
69      CHARACTER(len = *)     , OPTIONAL, INTENT(IN) :: axis_ref_
70     
71      CALL gridgroup_handle_create(gridgroup_hdl, gridgroup_id)
72      CALL set_gridgroup_attributes_hdl(gridgroup_hdl, name_, description_, domain_ref_, axis_ref_)
73
74   END SUBROUTINE set_gridgroup_attributes_id
75
76   SUBROUTINE set_gridgroup_attributes_hdl(gridgroup_hdl, name_, description_, domain_ref_, axis_ref_)
77      IMPLICIT NONE
78      TYPE      (XGridGroupHandle)                  :: gridgroup_hdl
79      CHARACTER(len = *)     , OPTIONAL, INTENT(IN) :: name_
80      CHARACTER(len = *)     , OPTIONAL, INTENT(IN) :: description_
81      CHARACTER(len = *)     , OPTIONAL, INTENT(IN) :: domain_ref_
82      CHARACTER(len = *)     , OPTIONAL, INTENT(IN) :: axis_ref_
83     
84      IF (PRESENT(name_))        THEN
85       CALL xios_set_gridgroup_name(gridgroup_hdl%daddr, name_, len(name_))
86      END IF
87      IF (PRESENT(description_)) THEN
88       CALL xios_set_gridgroup_description(gridgroup_hdl%daddr, description_, len(description_))
89      END IF
90      IF (PRESENT(domain_ref_))  THEN
91       CALL xios_set_gridgroup_domain_ref(gridgroup_hdl%daddr, domain_ref_, len(domain_ref_))
92      END IF
93      IF (PRESENT(axis_ref_))    THEN
94       CALL xios_set_gridgroup_axis_ref(gridgroup_hdl%daddr, axis_ref_, len(axis_ref_))
95      END IF
96   END SUBROUTINE set_gridgroup_attributes_hdl
97
98   SUBROUTINE grid_handle_create(ret, idt)
99      IMPLICIT NONE
100      TYPE(XGridHandle), INTENT(OUT):: ret
101      CHARACTER(len = *), INTENT(IN) :: idt     
102      CALL xios_grid_handle_create(ret%daddr, idt, len(idt))           
103   END SUBROUTINE grid_handle_create
104   
105   SUBROUTINE gridgroup_handle_create(ret, idt)
106      IMPLICIT NONE
107      TYPE(XGridGroupHandle), INTENT(OUT):: ret
108      CHARACTER(len = *)     , INTENT(IN) :: idt     
109      CALL xios_gridgroup_handle_create(ret%daddr, idt, len(idt))           
110   END SUBROUTINE gridgroup_handle_create
111   
112END MODULE IGRID
Note: See TracBrowser for help on using the repository browser.