source: trunk/LMDZ.TITAN/libf/phytitan/xios_output_mod.F90 @ 3026

Last change on this file since 3026 was 1943, checked in by jvatant, 7 years ago

Add XIOS outputs for chemistry including "*_tot" fields (concat GCM+upper atm : 0->1300km )
Only in pseudo-pressure axis for now, pseudo-altitude TBD.
--JVO

File size: 10.8 KB
Line 
1MODULE xios_output_mod
2
3 IMPLICIT NONE
4 
5 INTEGER,PRIVATE,SAVE :: time_it=0 ! store number of iterations with calls to XIOS since start
6! does not need to be threadprivate; managed by omp master
7
8 CHARACTER(LEN=*), PARAMETER :: context_id= "LMDZ" ! same as in context_lmdz_physics.xml
9 
10#ifdef CPP_XIOS
11
12 INTERFACE send_xios_field
13    MODULE PROCEDURE histwrite0d_xios,histwrite2d_xios,histwrite3d_xios
14 END INTERFACE
15 
16
17CONTAINS
18
19  SUBROUTINE initialize_xios_output(day,timeofday,dtphys,daysec,&
20                                    presnivs,pseudoalt)
21!  USE mod_phys_lmdz_para, only: gather, bcast, &
22!                                jj_nb, jj_begin, jj_end, ii_begin, ii_end, &
23!                                mpi_size, mpi_rank, klon_mpi, &
24!                                is_sequential, is_south_pole_dyn
25  USE mod_phys_lmdz_para, ONLY: jj_nb, jj_begin, jj_end, ii_begin, ii_end, &
26                                mpi_size, mpi_rank, klon_mpi, &
27                                is_sequential, is_south_pole_dyn
28  USE mod_grid_phy_lmdz, ONLY: nbp_lon, nbp_lat, klon_glo, grid_type, unstructured
29  USE print_control_mod, ONLY: lunout, prt_level
30  USE mod_grid_phy_lmdz, ONLY: nbp_lon, nbp_lat
31  USE regular_lonlat_mod, ONLY: lon_reg, lat_reg
32  USE nrtype, ONLY: pi
33#ifdef CPP_XIOS
34  USE xios
35#endif
36  USE wxios, ONLY: wxios_domain_param, wxios_domain_param_unstructured, wxios_closedef
37 
38  USE comchem_h, ONLY: preskim, preskim_tot, zlaykim, zlaykim_tot
39 
40  IMPLICIT NONE
41 
42  REAL,INTENT(IN) :: day ! Number of elapsed sols since reference Ls=0.
43  REAL,INTENT(IN) :: timeofday ! "Universal time", given as fraction of sol (e.g.: 0.5 for noon).
44  REAL,INTENT(IN) :: dtphys ! physics time step (s)
45  REAL,INTENT(IN) :: daysec ! lengthof a standard day (s)
46  REAL,INTENT(IN) :: presnivs(:) ! vertical grid approximate pressure (Pa)
47  REAL,INTENT(IN) :: pseudoalt(:) ! vertical grid approximate altitude (km)
48 
49 
50  INTEGER :: i
51  INTEGER :: data_ibegin, data_iend
52  TYPE(xios_duration) :: timestep
53  TYPE(xios_date) :: time_origin
54  TYPE(xios_date) :: start_date
55 
56!$OMP BARRIER
57!$OMP MASTER
58
59    ! 1. Declare available vertical axes to be used in output files:
60    IF (prt_level>=10) WRITE(lunout,*) "initialize_xios_output: call xios_set_axis_attr for presnivs"
61    CALL xios_set_axis_attr("presnivs", n_glo=size(presnivs), value=presnivs,&
62                            unit="Pa",positive="down")
63    IF (prt_level>=10) WRITE(lunout,*) "initialize_xios_output: call xios_set_axis_attr for altitude"
64    CALL xios_set_axis_attr("altitude", n_glo=size(pseudoalt), value=pseudoalt,&
65                            unit="km",positive="up")
66   
67    IF (prt_level>=10) WRITE(lunout,*) "initialize_xios_output: call xios_set_axis_attr for preskim"
68    CALL xios_set_axis_attr("preskim", n_glo=size(preskim), value=preskim,&
69                            unit="Pa",positive="down")
70                         
71    IF (prt_level>=10) WRITE(lunout,*) "initialize_xios_output: call xios_set_axis_attr for preskim_tot"
72    CALL xios_set_axis_attr("preskim_tot", n_glo=size(preskim_tot), value=preskim_tot,&
73                            unit="Pa",positive="down")
74                           
75    ! Calculation of pseudo-altitudes is still to be done
76    !IF (prt_level>=10) WRITE(lunout,*) "initialize_xios_output: call xios_set_axis_attr for zlaykim"
77    !CALL xios_set_axis_attr("zlaykim", n_glo=size(preskim), value=preskim,&
78    !                        unit="km",positive="up")
79    !                     
80    !IF (prt_level>=10) WRITE(lunout,*) "initialize_xios_output: call xios_set_axis_attr for zlaykim_tot"
81    !CALL xios_set_axis_attr("zlaykim_tot", n_glo=size(zlaykim_tot), value=zlaykim_tot,&
82    !                        unit="km",positive="up")
83   
84   
85    ! 2. Declare horizontal domain
86    ! Set values for the mask:
87!    IF (mpi_rank == 0) THEN
88!        data_ibegin = 0
89!    ELSE
90!        data_ibegin = ii_begin - 1
91!    END IF
92
93!    IF (mpi_rank == mpi_size-1) THEN
94!        data_iend = nbp_lon
95!    ELSE
96!        data_iend = ii_end + 1
97!    END IF
98
99!    if (prt_level>=10) then
100!      write(lunout,*) "initialize_xios_output: mpirank=",mpi_rank," iibegin=",ii_begin , " ii_end=",ii_end," jjbegin=",jj_begin," jj_nb=",jj_nb," jj_end=",jj_end
101!      write(lunout,*) "initialize_xios_output: mpirank=",mpi_rank," nbp_lon=",nbp_lon," nbp_lat=",nbp_lat
102!      write(lunout,*) "initialize_xios_output: mpirank=",mpi_rank," data_ibegin=",data_ibegin," data_iend=",data_iend
103!      write(lunout,*) "initialize_xios_output: mpirank=",mpi_rank," data_ibegin=",data_ibegin," data_iend=",data_iend
104!      write(lunout,*) "initialize_xios_output: mpirank=",mpi_rank," is_south_pole=",is_south_pole_dyn
105!    endif
106
107!$OMP END MASTER
108!$OMP BARRIER
109    ! Initialize the XIOS domain coreesponding to this process:
110    if (prt_level>=10) write(lunout,*) "initialize_xios_output: call wxios_domain_param"
111!    CALL wxios_domain_param("dom_glo", is_sequential, nbp_lon, jj_nb, nbp_lon, nbp_lat, &
112!                            1, nbp_lon, ii_begin, ii_end, jj_begin, jj_end,             &
113!                            klon_mpi+2*(nbp_lon-1), data_ibegin, data_iend,             &
114!                            lat_reg*(180./pi), lon_reg*(180./pi),                       &
115!                            is_south_pole_dyn,mpi_rank)
116
117    IF (grid_type==unstructured) THEN
118      CALL wxios_domain_param_unstructured("dom_glo")
119    ELSE
120      CALL wxios_domain_param("dom_glo")
121    ENDIF
122
123!$OMP MASTER
124    ! 3. Declare calendar and time step
125    if (prt_level>=10) then
126     write(lunout,*) "initialize_xios_output: build calendar"
127    endif
128    timestep%second=dtphys
129    if (nint(dtphys).ne.dtphys) then
130      write(*,*) "initialize_xios_output: warning physics timestep is not an integer!"
131    endif
132    if (nint(daysec).ne.daysec) then
133      write(*,*) "initialize_xios_output: warning day length is not an integer!"
134    endif
135    ! Important: do no operations involving dates and calendars
136    ! before defining the calendar!
137    CALL xios_define_calendar(type="user_defined", &
138                              timestep=timestep, &
139                              day_length=nint(daysec), &
140                              month_lengths=[30,30,30,30,30,30,30,30,30,30,30,30])
141    !NB: it would make more sense to define months and their length in the
142    ! xml files and not to have them hard coded here.... to be improved...
143   
144    ! time origin of the simulation (default: 1st year/1st month/1st day, Ls=0)
145    time_origin=xios_date(1,1,1,0,0,0)
146    CALL xios_set_time_origin(time_origin=time_origin)
147!    if (prt_level>=10) then
148     write(lunout,*) "initialize_xios_output: time_origin=",time_origin
149!    endif
150
151    ! Now define the start time of this simulation
152    ! NB: we substract dtphys because we want to set the origin of the time axis
153    start_date=time_origin+xios_duration(0,0,day,0,0,timeofday*daysec-dtphys)
154    call xios_set_start_date(start_date=start_date)
155    if (prt_level>=10) then
156     write(lunout,*) "initialize_xios_output: start_date=",start_date
157    endif
158
159    ! 4. Finalize the context:
160    if (prt_level>=10) write(*,*) "initialize_xios_output: call wxios_closedef"
161    CALL wxios_closedef()
162
163!$OMP END MASTER
164!$OMP BARRIER
165 
166  END SUBROUTINE initialize_xios_output
167
168!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
169
170  SUBROUTINE finalize_xios_output
171  USE xios
172  IMPLICIT NONE
173!$OMP BARRIER   
174!$OMP MASTER
175    CALL xios_context_finalize
176!$OMP END MASTER   
177!$OMP BARRIER   
178 
179  END SUBROUTINE finalize_xios_output
180
181!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
182
183  SUBROUTINE update_xios_timestep
184  USE xios
185  IMPLICIT NONE
186    CALL set_xios_context
187!$OMP MASTER
188    time_it=time_it+1
189    CALL xios_update_calendar(time_it)
190!$OMP END MASTER   
191  END SUBROUTINE update_xios_timestep
192
193!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
194
195  SUBROUTINE set_xios_context
196  USE XIOS
197  IMPLICIT NONE
198    TYPE(xios_context) :: ctx_hdl
199
200!$OMP MASTER
201    CALL xios_get_handle(context_id,ctx_hdl)
202    CALL xios_set_current_context(ctx_hdl)
203!$OMP END MASTER   
204  END SUBROUTINE set_xios_context
205
206!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
207
208  SUBROUTINE histwrite0d_xios(field_name,field)
209  USE xios, ONLY: xios_send_field
210  USE print_control_mod, ONLY: prt_level, lunout
211  IMPLICIT NONE
212 
213    CHARACTER(LEN=*), INTENT(IN) :: field_name
214    REAL, INTENT(IN) :: field
215   
216    IF (prt_level >= 10) WRITE(lunout,*)'Begin histrwrite0d_xios ',trim(field_name)
217   
218!$OMP MASTER
219    CALL xios_send_field(field_name,field)
220!$OMP END MASTER
221   
222    IF (prt_level >= 10) WRITE(lunout,*)'End histrwrite0d_xios ',trim(field_name)
223   
224  END SUBROUTINE histwrite0d_xios
225
226!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
227
228  SUBROUTINE histwrite2d_xios(field_name,field)
229  USE dimphy, only: klon
230  USE mod_phys_lmdz_para, only: gather_omp, grid1Dto2D_mpi, &
231                                jj_nb, klon_mpi
232  USE xios, only: xios_send_field
233  USE print_control_mod, ONLY: prt_level, lunout
234  USE mod_grid_phy_lmdz, ONLY: nbp_lon
235  IMPLICIT NONE
236
237    CHARACTER(LEN=*), INTENT(IN) :: field_name
238    REAL, DIMENSION(:), INTENT(IN) :: field
239     
240    REAL,DIMENSION(klon_mpi) :: buffer_omp
241    REAL :: Field2d(nbp_lon,jj_nb)
242
243    IF (prt_level >= 10) WRITE(lunout,*)'Begin histrwrite2d_xios ',trim(field_name)
244
245    IF (SIZE(field)/=klon) CALL abort_physic('iophy::histwrite2d_xios','Field first DIMENSION not equal to klon',1)
246   
247    CALL Gather_omp(field,buffer_omp)   
248!$OMP MASTER
249    CALL grid1Dto2D_mpi(buffer_omp,Field2d)
250   
251    CALL xios_send_field(field_name, Field2d)
252!$OMP END MASTER   
253
254    IF (prt_level >= 10) WRITE(lunout,*)'End histrwrite2d_xios ',trim(field_name)
255  END SUBROUTINE histwrite2d_xios
256
257!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
258
259  SUBROUTINE histwrite3d_xios(field_name, field)
260  USE dimphy, only: klon, klev
261  USE mod_phys_lmdz_para, only: gather_omp, grid1Dto2D_mpi, &
262                                jj_nb, klon_mpi
263  USE xios, only: xios_send_field
264  USE print_control_mod, ONLY: prt_level,lunout
265  USE mod_grid_phy_lmdz, ONLY: nbp_lon
266
267  IMPLICIT NONE
268
269    CHARACTER(LEN=*), INTENT(IN) :: field_name
270    REAL, DIMENSION(:,:), INTENT(IN) :: field ! --> field(klon,:)
271
272    REAL,DIMENSION(klon_mpi,SIZE(field,2)) :: buffer_omp
273    REAL :: Field3d(nbp_lon,jj_nb,SIZE(field,2))
274    INTEGER :: ip, n, nlev
275
276  IF (prt_level >= 10) write(lunout,*)'Begin histrwrite3d_xios ',trim(field_name)
277
278    !Et on.... écrit
279    IF (SIZE(field,1)/=klon) CALL abort_physic('iophy::histwrite3d','Field first DIMENSION not equal to klon',1)
280    nlev=SIZE(field,2)
281
282
283    CALL Gather_omp(field,buffer_omp)
284!$OMP MASTER
285    CALL grid1Dto2D_mpi(buffer_omp,field3d)
286
287    CALL xios_send_field(field_name, Field3d(:,:,1:nlev))
288!$OMP END MASTER   
289
290    IF (prt_level >= 10) write(lunout,*)'End histrwrite3d_xios ',trim(field_name)
291  END SUBROUTINE histwrite3d_xios
292
293#endif
294
295END MODULE xios_output_mod
Note: See TracBrowser for help on using the repository browser.