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

Last change on this file since 1723 was 1682, checked in by emillour, 8 years ago

All GCMs: set things up to enable pluging physics with dynamico

  • dyn3d
  • gcm.F90 : move I/O initialization (dates) to be done before physics

initialization

  • dyn3dpar
  • gcm.F : move I/O initialization (dates) to be done before physics

initialization

  • dynphy_lonlat:
  • inigeomphy_mod.F90 : add ind_cell_glo computation and transfer

to init_geometry

  • phy_common:
  • geometry_mod.F90 : add ind_cell_glo module variable to store global

column index

  • print_control_mod.F90 : make initialization occur via init_print_control_mod

to avoid circular module dependencies

  • init_print_control_mod.F90 : added to initialize print_control_mod module

variables

  • mod_phys_lmdz_mpi_data.F90 : use print_control_mod (rather than iniprint.h)
  • mod_phys_lmdz_para.F90 : use print_control_mod (rather than iniprint.h)
  • mod_phys_lmdz_omp_data.F90 : add is_omp_master (alias of is_omp_root) module

variable and use print_control_mod (rather than
iniprint.h)

  • physics_distribution_mod.F90 : add call to init_dimphy in

init_physics_distribution

  • xios_writefield.F90 : generic routine to output field with XIOS (for debug)
  • misc:
  • handle_err_m.F90 : call abort_physic, rather than abort_gcm
  • wxios.F90 : updates to enable unstructured grids

set module variable g_ctx_name to "LMDZ"
wxios_init(): remove call to wxios_context_init
wxios_context_init(): call xios_context_initialize with COMM_LMDZ_PHY
add routine wxios_set_context() to get handle and set context to XIOS
wxios_domain_param(): change arguments and generate the domain in-place
add wxios_domain_param_unstructured(): generate domain for unstructured case

NB: access is via "domain group" (whereas it is via "domain" in

wxios_domain_param)

  • dynphy_lonlat/phy[std|mars|venus|titan]:
  • iniphysiq_mod.F90 : Remove call to init_dimphy (which is now done in

phy_common/physics_distribution_mod.F90)

EM

File size: 8.9 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) write(lunout,*) "initialize_xios_output: build calendar"
105    timestep%second=dtphys
106    ! time origin of the simulation (default: 1st year/1st month/1st day, Ls=0)
107    time_origin=xios_date(1,1,1,0,0,0)
108    ! start date of the simulation (i.e time elapsed since last Ls=0)
109    start_date=xios_date(1,1,1,0,0,nint((day+timeofday)*daysec))
110    CALL xios_define_calendar(type="user_defined", &
111                              timestep=timestep, &
112                              day_length=nint(daysec), &
113                              start_date=start_date, &
114                              time_origin=time_origin, &
115                              month_lengths=[2])
116   
117    ! 4. Finalize the context:
118    if (prt_level>=10) write(*,*) "initialize_xios_output: call wxios_closedef"
119    CALL wxios_closedef()
120
121!$OMP END MASTER
122!$OMP BARRIER
123 
124  END SUBROUTINE initialize_xios_output
125
126!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
127
128  SUBROUTINE finalize_xios_output
129  USE xios
130  IMPLICIT NONE
131!$OMP BARRIER   
132!$OMP MASTER
133    CALL xios_context_finalize
134!$OMP END MASTER   
135!$OMP BARRIER   
136 
137  END SUBROUTINE finalize_xios_output
138
139!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
140
141  SUBROUTINE update_xios_timestep
142  USE xios
143  IMPLICIT NONE
144    CALL set_xios_context
145!$OMP MASTER
146    time_it=time_it+1
147    CALL xios_update_calendar(time_it)
148!$OMP END MASTER   
149  END SUBROUTINE update_xios_timestep
150
151!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
152
153  SUBROUTINE set_xios_context
154  USE XIOS
155  IMPLICIT NONE
156    TYPE(xios_context) :: ctx_hdl
157
158!$OMP MASTER
159    CALL xios_get_handle(context_id,ctx_hdl)
160    CALL xios_set_current_context(ctx_hdl)
161!$OMP END MASTER   
162  END SUBROUTINE set_xios_context
163
164!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
165
166  SUBROUTINE histwrite0d_xios(field_name,field)
167  USE xios, ONLY: xios_send_field
168  USE print_control_mod, ONLY: prt_level, lunout
169  IMPLICIT NONE
170 
171    CHARACTER(LEN=*), INTENT(IN) :: field_name
172    REAL, INTENT(IN) :: field
173   
174    IF (prt_level >= 10) WRITE(lunout,*)'Begin histrwrite0d_xios ',trim(field_name)
175   
176!$OMP MASTER
177    CALL xios_send_field(field_name,field)
178!$OMP END MASTER
179   
180    IF (prt_level >= 10) WRITE(lunout,*)'End histrwrite0d_xios ',trim(field_name)
181   
182  END SUBROUTINE histwrite0d_xios
183
184!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
185
186  SUBROUTINE histwrite2d_xios(field_name,field)
187  USE dimphy, only: klon
188  USE mod_phys_lmdz_para, only: gather_omp, grid1Dto2D_mpi, &
189                                jj_nb, klon_mpi
190  USE xios, only: xios_send_field
191  USE print_control_mod, ONLY: prt_level, lunout
192  USE mod_grid_phy_lmdz, ONLY: nbp_lon
193  IMPLICIT NONE
194
195    CHARACTER(LEN=*), INTENT(IN) :: field_name
196    REAL, DIMENSION(:), INTENT(IN) :: field
197     
198    REAL,DIMENSION(klon_mpi) :: buffer_omp
199    REAL :: Field2d(nbp_lon,jj_nb)
200
201    IF (prt_level >= 10) WRITE(lunout,*)'Begin histrwrite2d_xios ',trim(field_name)
202
203    IF (SIZE(field)/=klon) CALL abort_physic('iophy::histwrite2d_xios','Field first DIMENSION not equal to klon',1)
204   
205    CALL Gather_omp(field,buffer_omp)   
206!$OMP MASTER
207    CALL grid1Dto2D_mpi(buffer_omp,Field2d)
208   
209    CALL xios_send_field(field_name, Field2d)
210!$OMP END MASTER   
211
212    IF (prt_level >= 10) WRITE(lunout,*)'End histrwrite2d_xios ',trim(field_name)
213  END SUBROUTINE histwrite2d_xios
214
215!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
216
217  SUBROUTINE histwrite3d_xios(field_name, field)
218  USE dimphy, only: klon, klev
219  USE mod_phys_lmdz_para, only: gather_omp, grid1Dto2D_mpi, &
220                                jj_nb, klon_mpi
221  USE xios, only: xios_send_field
222  USE print_control_mod, ONLY: prt_level,lunout
223  USE mod_grid_phy_lmdz, ONLY: nbp_lon
224
225  IMPLICIT NONE
226
227    CHARACTER(LEN=*), INTENT(IN) :: field_name
228    REAL, DIMENSION(:,:), INTENT(IN) :: field ! --> field(klon,:)
229
230    REAL,DIMENSION(klon_mpi,SIZE(field,2)) :: buffer_omp
231    REAL :: Field3d(nbp_lon,jj_nb,SIZE(field,2))
232    INTEGER :: ip, n, nlev
233
234  IF (prt_level >= 10) write(lunout,*)'Begin histrwrite3d_xios ',trim(field_name)
235
236    !Et on.... écrit
237    IF (SIZE(field,1)/=klon) CALL abort_physic('iophy::histwrite3d','Field first DIMENSION not equal to klon',1)
238    nlev=SIZE(field,2)
239
240
241    CALL Gather_omp(field,buffer_omp)
242!$OMP MASTER
243    CALL grid1Dto2D_mpi(buffer_omp,field3d)
244
245    CALL xios_send_field(field_name, Field3d(:,:,1:nlev))
246!$OMP END MASTER   
247
248    IF (prt_level >= 10) write(lunout,*)'End histrwrite3d_xios ',trim(field_name)
249  END SUBROUTINE histwrite3d_xios
250
251#endif
252
253END MODULE xios_output_mod
Note: See TracBrowser for help on using the repository browser.