source: XMLIO_SERVER/trunk/src/XMLIO/mod_context.f90 @ 26

Last change on this file since 26 was 26, checked in by ymipsl, 15 years ago

Mise à jour importante :

  • ajout de la grille type LMDZ
  • ajout des context
  • ajout de namelist pour parametrer l'utilisation du server : avec/sans MPI, en utlisant ou pas OASIS
File size: 7.5 KB
Line 
1MODULE mod_context
2  USE mod_xmlio_parameters
3  USE mod_sorted_list
4  USE mod_field
5  USE mod_field_group
6  USE mod_field_definition
7  USE mod_file
8  USE mod_file_group
9  USE mod_file_definition
10  USE mod_grid
11  USE mod_grid_group
12  USE mod_grid_definition
13  USE mod_axis
14  USE mod_axis_group
15  USE mod_axis_definition
16  USE mod_dependency
17
18
19  INTERFACE context__swap
20    MODULE PROCEDURE context__swap_id,context__swap_pt
21  END INTERFACE 
22 
23  TYPE, PUBLIC :: context
24    CHARACTER(len=str_len)         :: id
25    INTEGER                        :: number
26 
27    TYPE(vector_field),POINTER        :: field__field_Ids
28    TYPE(sorted_list),POINTER         :: field__Ids
29    TYPE(vector_field_group),POINTER  :: field_group__field_group_ids
30    TYPE(sorted_list),POINTER         :: field_group__Ids
31    TYPE(field_group),POINTER         :: field_definition__field_definition
32    TYPE(vector_file),POINTER         :: file__file_Ids
33    TYPE(sorted_list),POINTER         :: file__Ids
34    TYPE(vector_file_group),POINTER   :: file_group__file_group_Ids
35    TYPE(sorted_list),POINTER         :: file_group__Ids 
36    TYPE(file_group),POINTER          :: file_definition__file_definition 
37    TYPE(vector_grid),POINTER         :: grid__grid_Ids
38    TYPE(sorted_list),POINTER         :: grid__Ids 
39    TYPE(vector_grid_group),POINTER   :: grid_group__grid_group_Ids
40    TYPE(sorted_list),POINTER         :: grid_group__Ids 
41    TYPE(grid_group),POINTER          :: grid_definition__grid_definition
42    TYPE(vector_axis),POINTER         :: axis__axis_Ids
43    TYPE(sorted_list),POINTER         :: axis__Ids 
44    TYPE(vector_axis_group),POINTER   :: axis_group__axis_group_Ids
45    TYPE(sorted_list),POINTER         :: axis_group__Ids 
46    TYPE(axis_group),POINTER          :: axis_definition__axis_definition
47    TYPE(vector_file_dep),POINTER     :: dependency__file_enabled
48    TYPE(vector_field_out),POINTER    :: dependency__field_enabled 
49    TYPE(vector_field_dep),POINTER    :: dependency__field_id
50    TYPE(sorted_list),POINTER         :: dependency__sorted_id 
51 
52  END TYPE context
53 
54  INCLUDE 'vector_context_def.inc'
55  TYPE(vector_context),SAVE,POINTER  :: context_ids
56  TYPE(sorted_list),POINTER,SAVE,PRIVATE :: Ids
57
58 
59  CONTAINS
60    INCLUDE 'vector_context_contains.inc'
61   
62    SUBROUTINE context__init
63    IMPLICIT NONE
64
65      ALLOCATE(context_Ids)
66      ALLOCATE(Ids)
67
68      CALL vector_context__new(context_Ids)
69      CALL sorted_list__new(ids)
70
71    END SUBROUTINE context__init
72
73    SUBROUTINE context__get(Id,Pt_context)
74      USE string_function
75      IMPLICIT NONE
76      CHARACTER(LEN=*),INTENT(IN)     :: Id
77      TYPE(context),POINTER              :: Pt_context
78
79      INTEGER                         :: Pos
80      LOGICAL                         :: success
81   
82      CALL sorted_list__find(Ids,hash(Id),Pos,success)
83      IF (success) THEN
84        Pt_context=>context_ids%at(Pos)%Pt
85      ELSE
86        Pt_context=>NULL()
87      ENDIF
88   
89    END SUBROUTINE context__get
90
91    SUBROUTINE context__get_new(Id,pt_context)
92    USE string_function
93    IMPLICIT NONE
94      CHARACTER(LEN=*),INTENT(IN)     :: Id
95      TYPE(context),POINTER              :: Pt_context
96
97      INTEGER                         :: Pos
98      LOGICAL                         :: success
99     
100      CALL sorted_list__find(Ids,hash(Id),Pos,success)
101      IF (success) THEN
102        Pt_context=>context_ids%at(Pos)%Pt
103      ELSE
104        CALL vector_context__get_new(context_ids,pt_context,Pos)
105        pt_context%number=Pos
106        Pt_context%id=Id
107        CALL sorted_list__Add(Ids,hash(Id),Pos)
108       
109        ALLOCATE(pt_context%field__field_Ids )
110        ALLOCATE(pt_context%field__Ids )
111        ALLOCATE(pt_context%field_group__field_group_ids )
112        ALLOCATE(pt_context%field_group__field_group_ids )
113        ALLOCATE(pt_context%field_group__Ids )
114        ALLOCATE(pt_context%field_definition__field_definition )
115        ALLOCATE(pt_context%file__file_Ids)
116        ALLOCATE(pt_context%file__Ids)
117        ALLOCATE(pt_context%file_group__file_group_Ids)
118        ALLOCATE(pt_context%file_group__Ids) 
119        ALLOCATE(pt_context%file_definition__file_definition) 
120        ALLOCATE(pt_context%grid__grid_Ids)
121        ALLOCATE(pt_context%grid__Ids) 
122        ALLOCATE(pt_context%grid_group__grid_group_Ids)
123        ALLOCATE(pt_context%grid_group__Ids) 
124        ALLOCATE(pt_context%grid_definition__grid_definition)
125        ALLOCATE(pt_context%axis__axis_Ids)
126        ALLOCATE(pt_context%axis__Ids) 
127        ALLOCATE(pt_context%axis_group__axis_group_Ids)
128        ALLOCATE(pt_context%axis_group__Ids) 
129        ALLOCATE(pt_context%axis_definition__axis_definition)
130        ALLOCATE(pt_context%dependency__file_enabled)
131        ALLOCATE(pt_context%dependency__field_enabled) 
132        ALLOCATE(pt_context%dependency__field_id)
133        ALLOCATE(pt_context%dependency__sorted_id) 
134
135        CALL context__swap(pt_context)
136       
137        CALL field__init
138        CALL field_group__Init
139        CALL field_definition__Init
140
141        CALL axis__init
142        CALL axis_group__Init
143        CALL axis_definition__Init
144
145        CALL grid__init
146        CALL grid_group__Init
147        CALL grid_definition__Init
148
149        CALL file__init
150        CALL file_group__Init
151        CALL file_definition__Init
152
153      ENDIF
154
155    END SUBROUTINE context__get_new
156
157
158    SUBROUTINE context__create(Id)
159    IMPLICIT NONE
160      CHARACTER(LEN=*),INTENT(IN)     :: Id
161     
162      TYPE(context),POINTER              :: Pt_context
163
164      CALL context__get(Id,Pt_context)
165      IF (.NOT. ASSOCIATED(Pt_context)) CALL context__get_new(Id,Pt_context)
166     
167!      CALL field__init
168!      CALL field_group__init
169!      CALL field_definition__init
170     
171     END SUBROUTINE context__create
172
173     
174    SUBROUTINE context__swap_id(Id)
175    USE mod_field
176      IMPLICIT NONE
177      CHARACTER(LEN=*),INTENT(IN)     :: Id
178      TYPE(context),POINTER       :: Pt_context
179
180      INTEGER :: number
181     
182      CALL context__get(Id,Pt_context)
183      IF (.NOT. ASSOCIATED(Pt_context)) THEN
184!!      error message
185      ENDIF
186     
187      CALL context__swap(pt_context) 
188
189    END SUBROUTINE context__swap_id
190
191    SUBROUTINE context__swap_pt(Pt_context)
192    USE mod_field
193      IMPLICIT NONE
194      TYPE(context),POINTER       :: Pt_context
195
196      CALL field__swap_context(Pt_context%field__field_Ids ,Pt_context%field__Ids)
197      CALL field_group__swap_context(Pt_context%field_group__field_group_ids ,Pt_context%field_group__Ids)
198      CALL field_definition__swap_context(Pt_context%field_definition__field_definition)
199      CALL file__swap_context(Pt_context%file__file_Ids,Pt_context%file__Ids)
200      CALL file_group__swap_context(Pt_context%file_group__file_group_Ids,Pt_context%file_group__Ids)
201      CALL file_definition__swap_context(Pt_context%file_definition__file_definition) 
202      CALL grid__swap_context(pt_context%grid__grid_Ids,pt_context%grid__Ids) 
203      CALL grid_group__swap_context(pt_context%grid_group__grid_group_Ids,pt_context%grid_group__Ids) 
204      CALL grid_definition__swap_context(pt_context%grid_definition__grid_definition)
205      CALL axis__swap_context(pt_context%axis__axis_Ids,pt_context%axis__Ids) 
206      CALL axis_group__swap_context(pt_context%axis_group__axis_group_Ids,pt_context%axis_group__Ids) 
207      CALL axis_definition__swap_context(pt_context%axis_definition__axis_definition)
208      CALL dependency__swap_context(pt_context%dependency__file_enabled,pt_context%dependency__field_enabled,  &
209                                    pt_context%dependency__field_id,pt_context%dependency__sorted_id) 
210    END SUBROUTINE context__swap_pt
211
212
213END MODULE mod_context
Note: See TracBrowser for help on using the repository browser.