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.
mod_context.f90 in vendors/XMLIO_SERVER/current/src/XMLIO – NEMO

source: vendors/XMLIO_SERVER/current/src/XMLIO/mod_context.f90 @ 1897

Last change on this file since 1897 was 1897, checked in by flavoni, 14 years ago

importing XMLIO_SERVER vendor

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