source: trunk/LMDZ.VENUS/libf/phyvenus/xios_output_mod.F90 @ 3461

Last change on this file since 3461 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 corresponding 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! VENUS IS SEEN UPSIDE DOWN, SO CENTRAL SYMMETRY TO PUT NORTH UP AGAIN
93!                           -1.*lat_reg*(180./pi), -1.*lon_reg*(180./pi),                &
94!                            is_south_pole_dyn,mpi_rank)
95
96    IF (grid_type==unstructured) THEN
97      CALL wxios_domain_param_unstructured("dom_glo",.true.)
98    ELSE
99      CALL wxios_domain_param("dom_glo",.true.)
100    ENDIF
101
102!$OMP MASTER
103    ! 3. Declare calendar and time step
104    if (prt_level>=10) then
105     write(lunout,*) "initialize_xios_output: build calendar"
106    endif
107    timestep%second=nint(dtphys)
108    if (nint(dtphys).ne.dtphys) then
109      write(*,*) "initialize_xios_output: warning physics timestep is not an integer!"
110    endif
111    if (nint(daysec).ne.daysec) then
112      write(*,*) "initialize_xios_output: warning day length is not an integer!"
113    endif
114    ! Important: do no operations involving dates and calendars
115    ! before defining the calendar!
116    CALL xios_define_calendar(type="user_defined", &
117                              timestep=timestep, &
118                              day_length=nint(daysec), &
119                              month_lengths=[2]) ! one month, 2 days long
120
121    ! time origin of the simulation (default: 1st year/1st month/1st day, Ls=0)
122    time_origin=xios_date(1,1,1,0,0,0)
123    CALL xios_set_time_origin(time_origin=time_origin)
124    if (prt_level>=10) then
125     write(lunout,*) "initialize_xios_output: time_origin=",time_origin
126    endif
127
128    ! Now define the start time of this simulation
129    ! NB: we substract dtphys because we want to set the origin of the time axis
130    start_date=time_origin+xios_duration(0,0,day,0,0,timeofday*daysec-dtphys)
131    call xios_set_start_date(start_date=start_date)
132    if (prt_level>=10) then
133     write(lunout,*) "initialize_xios_output: start_date=",start_date
134    endif
135   
136    ! 4. Finalize the context:
137    if (prt_level>=10) write(*,*) "initialize_xios_output: call wxios_closedef"
138    CALL wxios_closedef()
139
140!$OMP END MASTER
141!$OMP BARRIER
142 
143  END SUBROUTINE initialize_xios_output
144
145!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
146
147  SUBROUTINE finalize_xios_output
148  USE xios
149  IMPLICIT NONE
150!$OMP BARRIER   
151!$OMP MASTER
152    CALL xios_context_finalize
153!$OMP END MASTER   
154!$OMP BARRIER   
155 
156  END SUBROUTINE finalize_xios_output
157
158!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
159
160  SUBROUTINE update_xios_timestep
161  USE xios
162  IMPLICIT NONE
163    CALL set_xios_context
164!$OMP MASTER
165    time_it=time_it+1
166    CALL xios_update_calendar(time_it)
167!$OMP END MASTER   
168  END SUBROUTINE update_xios_timestep
169
170!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
171
172  SUBROUTINE set_xios_context
173  USE XIOS
174  IMPLICIT NONE
175    TYPE(xios_context) :: ctx_hdl
176
177!$OMP MASTER
178    CALL xios_get_handle(context_id,ctx_hdl)
179    CALL xios_set_current_context(ctx_hdl)
180!$OMP END MASTER   
181  END SUBROUTINE set_xios_context
182
183!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
184
185  SUBROUTINE histwrite0d_xios(field_name,field)
186  USE xios, ONLY: xios_send_field
187  USE print_control_mod, ONLY: prt_level, lunout
188  IMPLICIT NONE
189 
190    CHARACTER(LEN=*), INTENT(IN) :: field_name
191    REAL, INTENT(IN) :: field
192   
193    IF (prt_level >= 10) WRITE(lunout,*)'Begin histrwrite0d_xios ',trim(field_name)
194   
195!$OMP MASTER
196    CALL xios_send_field(field_name,field)
197!$OMP END MASTER
198   
199    IF (prt_level >= 10) WRITE(lunout,*)'End histrwrite0d_xios ',trim(field_name)
200   
201  END SUBROUTINE histwrite0d_xios
202
203!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
204
205  SUBROUTINE histwrite2d_xios(field_name,field)
206  USE dimphy, only: klon
207  USE mod_phys_lmdz_para, only: gather_omp, grid1Dto2D_mpi, &
208                                jj_nb, klon_mpi
209  USE xios, only: xios_send_field
210  USE print_control_mod, ONLY: prt_level, lunout
211  USE mod_grid_phy_lmdz, ONLY: nbp_lon
212  IMPLICIT NONE
213
214    CHARACTER(LEN=*), INTENT(IN) :: field_name
215    REAL, DIMENSION(:), INTENT(IN) :: field
216     
217    REAL,DIMENSION(klon_mpi) :: buffer_omp
218    REAL :: Field2d(nbp_lon,jj_nb)
219
220    IF (prt_level >= 10) WRITE(lunout,*)'Begin histrwrite2d_xios ',trim(field_name)
221
222    IF (SIZE(field)/=klon) CALL abort_physic('iophy::histwrite2d_xios','Field first DIMENSION not equal to klon',1)
223   
224    CALL Gather_omp(field,buffer_omp)   
225!$OMP MASTER
226    CALL grid1Dto2D_mpi(buffer_omp,Field2d)
227   
228    CALL xios_send_field(field_name, Field2d)
229!$OMP END MASTER   
230
231    IF (prt_level >= 10) WRITE(lunout,*)'End histrwrite2d_xios ',trim(field_name)
232  END SUBROUTINE histwrite2d_xios
233
234!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
235
236  SUBROUTINE histwrite3d_xios(field_name, field)
237  USE dimphy, only: klon, klev
238  USE mod_phys_lmdz_para, only: gather_omp, grid1Dto2D_mpi, &
239                                jj_nb, klon_mpi
240  USE xios, only: xios_send_field
241  USE print_control_mod, ONLY: prt_level,lunout
242  USE mod_grid_phy_lmdz, ONLY: nbp_lon
243
244  IMPLICIT NONE
245
246    CHARACTER(LEN=*), INTENT(IN) :: field_name
247    REAL, DIMENSION(:,:), INTENT(IN) :: field ! --> field(klon,:)
248
249    REAL,DIMENSION(klon_mpi,SIZE(field,2)) :: buffer_omp
250    REAL :: Field3d(nbp_lon,jj_nb,SIZE(field,2))
251    INTEGER :: ip, n, nlev
252
253  IF (prt_level >= 10) write(lunout,*)'Begin histrwrite3d_xios ',trim(field_name)
254
255    !Et on.... écrit
256    IF (SIZE(field,1)/=klon) CALL abort_physic('iophy::histwrite3d','Field first DIMENSION not equal to klon',1)
257    nlev=SIZE(field,2)
258
259
260    CALL Gather_omp(field,buffer_omp)
261!$OMP MASTER
262    CALL grid1Dto2D_mpi(buffer_omp,field3d)
263
264    CALL xios_send_field(field_name, Field3d(:,:,1:nlev))
265!$OMP END MASTER   
266
267    IF (prt_level >= 10) write(lunout,*)'End histrwrite3d_xios ',trim(field_name)
268  END SUBROUTINE histwrite3d_xios
269
270#endif
271
272END MODULE xios_output_mod
Note: See TracBrowser for help on using the repository browser.