source: trunk/LMDZ.GENERIC/libf/phystd/xios_output_mod.F90 @ 1834

Last change on this file since 1834 was 1760, checked in by emillour, 7 years ago

Venus and Generic GCMS:
Corrections for the XIOS calendar; it must first be defined and operations
(e.g. definition of start_date) must come afterwards.
Note that for the Generic model where number of month/year and
number of days per month may vary from one simulation to the next, it
might be better to define the calendar via the XML file than in the code.
EM

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