MODULE xios_inca USE xios USE PRINT_INCA USE MOD_GRID_INCA USE MOD_INCA_MPI_DATA USE MOD_INCA_PARA USE MOD_CONST_MPI_INCA USE CONST_LMDZ USE IOIPSL USE PARAM_CHEM USE SURF_CHEM_MOD USE RATE_INDEX_MOD USE CHEM_TRACNM, ONLY: solsym USE SPECIES_NAMES USE AEROSOL_DIAG, ONLY : naero_grp, mrfname,mrfname_xml, mrfname_long, las, cla USE AEROSOL_MOD IMPLICIT NONE PRIVATE PUBLIC :: xios_inca_init , xios_inca_change_context, & xios_inca_update_calendar, xios_inca_context_finalize, & xios_inca_send_field, xios_inca_recv_field, xios_inca_recv_field_glo, xios_inca_recv_field_mpi ! !! Declaration of internal variables ! TYPE(xios_context) :: ctx_hdl_inca !! Handel for INCA !$OMP THREADPRIVATE(ctx_hdl_inca) TYPE(xios_fieldgroup) :: reacflux_hdl,reacrate_hdl, invoxy_hdl, phtrate_hdl, extfrc_hdl, extfrc_col_hdl, conc_spcs_hdl, emi_hdl, dryvd_hdl TYPE(xios_fieldgroup) :: tauinca1_hdl, pizinca1_hdl, cginca1_hdl, tauinca2_hdl, pizinca2_hdl, cginca2_hdl TYPE(xios_fieldgroup) :: drydep_hdl, hrate_hdl, od_hdl, od3d_hdl, source_hdl, emiNoBio_hdl,emiOrch_hdl TYPE(xios_fieldgroup) :: source0_hdl, source0_read_hdl, invoxy0_hdl, invoxy0_read_hdl TYPE(xios_fieldgroup) :: sed_hdl,wet_hdl,load_hdl,emialt_hdl,mdw_hdl,aerh2o_hdl TYPE(xios_fieldgroup) :: tau1_hdl, tau2_hdl,piz1_hdl,piz2_hdl,cg1_hdl,cg2_hdl TYPE(xios_fieldgroup) :: swtoaas_hdl,swtoacs_hdl,swsrfas_hdl,swsrfcs_hdl,fswtoaas_hdl,fswtoacs_hdl,fswsrfas_hdl,fswsrfcs_hdl, wetloss_hdl TYPE(xios_field) :: child !$OMP THREADPRIVATE(reacflux_hdl, reacrate_hdl,invoxy_hdl, phtrate_hdl, extfrc_hdl, extfrc_col_hdl, conc_spcs_hdl, emi_hdl,dryvd_hdl, child) !$OMP THREADPRIVATE(tauinca1_hdl, pizinca1_hdl, cginca1_hdl, tauinca2_hdl, pizinca2_hdl, cginca2_hdl) !$OMP THREADPRIVATE(drydep_hdl, hrate_hdl, od_hdl, od3d_hdl, source_hdl, emiNoBio_hdl,emiOrch_hdl) !$OMP THREADPRIVATE(sed_hdl,wet_hdl,load_hdl,emialt_hdl,mdw_hdl,aerh2o_hdl) !$OMP THREADPRIVATE(tau1_hdl, tau2_hdl,piz1_hdl,piz2_hdl,cg1_hdl,cg2_hdl) !$OMP THREADPRIVATE(swtoaas_hdl,swtoacs_hdl,swsrfas_hdl,swsrfcs_hdl,fswtoaas_hdl,fswtoacs_hdl,fswsrfas_hdl,fswsrfcs_hdl, wetloss_hdl) !$OMP THREADPRIVATE(source0_hdl, source0_read_hdl, invoxy0_hdl, invoxy0_read_hdl) CHARACTER(len=*),PARAMETER :: id="client" !! Id for initialization of INCA in 1 ! ==================================================================== ! INTERFACE : xios_inca_send_field ! ! Send a field to 1. ! ! DESCRIPTION : Send a field to 1. The field can have 1, 2 or 3 dimensions. ! This interface should be called at each time-step for each output varaiables. ! ! ==================================================================== INTERFACE xios_inca_send_field MODULE PROCEDURE xios_inca_send_field_r2d, xios_inca_send_field_r1d,xios_inca_send_field_r0d END INTERFACE INTERFACE xios_inca_recv_field MODULE PROCEDURE xios_inca_recv_field_r0d, xios_inca_recv_field_r1d, xios_inca_recv_field_r2d,xios_inca_recv_field_r3d END INTERFACE INTERFACE xios_inca_recv_field_mpi MODULE PROCEDURE xios_inca_recv_field_mpi_r1d END INTERFACE INTERFACE xios_inca_recv_field_glo MODULE PROCEDURE xios_inca_recv_field_glo_r1d,xios_inca_recv_field_glo_r2d,xios_inca_recv_field_glo_r3d END INTERFACE CONTAINS ! ==================================================================== ! SUBROUTINE : xios_inca_init ! ! Initialize variables needed for use of 1. ! ! DESCRIPTION : Initialization of specific varaiables needed to use 1 such as model domain and time step. ! ! ! ==================================================================== SUBROUTINE xios_inca_init(& COMM_LMDZ, timestep, year, month, day, & hour, ini_an, ini_mois, ini_jour, ini_heure, & io_lon, io_lat, presnivs) USE PARAM_CHEM, ONLY : use_group, LMDZ_10m_winds USE MOD_GEOMETRY_INCA, ONLY : longitude, latitude, boundslon, boundslat,ind_cell_glo USE MOD_GRID_INCA, ONLY : nvertex, plon_glo, grid_type, regular_lonlat, unstructured USE MOD_INCA_MPI_DATA, ONLY : ij_nb USE CONST_MOD, ONLY: PI USE INCA_DIM USE PRINT_INCA IMPLICIT NONE ! !! 0. Variable and parameter declaration ! !! 0.1 Input variables ! INTEGER, INTENT(in) :: COMM_LMDZ !! Inca MPI communicator (from module mod_inca_mpi_data) INTEGER, INTENT(in) :: year, month, day, ini_an, ini_mois, ini_jour !! Current date information REAL, INTENT(in) :: hour, ini_heure REAL,INTENT(IN) :: io_lat(:) ! latitudes (of global grid) REAL,INTENT(IN) :: io_lon(:) ! longitudes (of global grid) REAL, INTENT(in) :: timestep REAL, INTENT(in) :: presnivs(PLEV) ! !! 0.2 Local variables ! LOGICAL :: find INTEGER :: i INTEGER :: it,la CHARACTER(LEN=30) :: start_str , time_orig !! Current date as character string TYPE(xios_duration) :: dtime = xios_duration(0, 0, 0, 0, 0, 0) LOGICAL :: mask(iim_glo,jj_nb) !Masque pour les problèmes de recouvrement MPI REAL, DIMENSION(nbveget) :: veget REAL, DIMENSION(nbsurf) :: surf REAL, DIMENSION(PLEV+1) :: paprsniv REAL, DIMENSION(PLEV) :: klev_value REAL, DIMENSION(12) :: timeco2_value REAL, DIMENSION(2920) :: timeco2h_value INTEGER :: n, length, ni, nj CHARACTER(len=13) :: tmp_name ! variables pour la grille non structuree de dynamico REAL :: lon_mpi(plon_mpi) REAL :: lat_mpi(plon_mpi) REAL :: boundslon_mpi(plon_mpi,nvertex) REAL :: boundslat_mpi(plon_mpi,nvertex) INTEGER :: ind_cell_glo_mpi(plon_mpi) ! =================================================================== ! !! 1. Set date and calendar information on the format needed by 1 ! IF (grid_type == unstructured) THEN ! write(*,*) ' dans xios_inca cell = ', ind_cell_glo ! call flush(6) CALL gather_omp(longitude*180/PI,lon_mpi) CALL gather_omp(latitude*180/PI,lat_mpi) CALL gather_omp(boundslon*180/PI,boundslon_mpi) CALL gather_omp(boundslat*180/PI,boundslat_mpi) CALL gather_omp(ind_cell_glo,ind_cell_glo_mpi) endif !$OMP MASTER ! !! 2. Context initialization ! CALL xios_context_initialize("inca",COMM_LMDZ) CALL xios_get_handle("inca",ctx_hdl_inca) CALL xios_set_current_context(ctx_hdl_inca) ! Groupes pour les restart ! ecriture CALL xios_get_handle("source" , source_hdl ) CALL xios_get_handle("inv_oxy" , invoxy_hdl ) CALL xios_get_handle("tauinca1", tauinca1_hdl ) CALL xios_get_handle("pizinca1", pizinca1_hdl ) CALL xios_get_handle("cginca1" , cginca1_hdl ) CALL xios_get_handle("tauinca2", tauinca2_hdl ) CALL xios_get_handle("pizinca2", pizinca2_hdl ) CALL xios_get_handle("cginca2" , cginca2_hdl ) ! lecture CALL xios_get_handle("source0" , source0_hdl ) CALL xios_get_handle("invoxy0" , invoxy0_hdl ) CALL xios_get_handle("source0_read" , source0_read_hdl ) CALL xios_get_handle("invoxy0_read" , invoxy0_read_hdl ) ! Groupes pour les output du code IF(use_group)THEN CALL xios_get_handle("reac_flux" , reacflux_hdl) CALL xios_get_handle("reac_rate" , reacrate_hdl) CALL xios_get_handle("photo_rate" , phtrate_hdl) CALL xios_get_handle("ext_forc" , extfrc_hdl) CALL xios_get_handle("ext_forc_col" , extfrc_col_hdl) CALL xios_get_handle("conc_species" , conc_spcs_hdl) CALL xios_get_handle("emi_species" , emi_hdl) CALL xios_get_handle("emi_noBioNat" , emiNoBio_hdl) CALL xios_get_handle("emi_FromOrch" , emiOrch_hdl) CALL xios_get_handle("dryvd_species" , dryvd_hdl) CALL xios_get_handle("drydep_species", drydep_hdl) CALL xios_get_handle("henry_const" , hrate_hdl) CALL xios_get_handle("Opt_thick" , od_hdl) CALL xios_get_handle("Opt_thick3D" , od3d_hdl) CALL xios_get_handle("sed_aero" , sed_hdl) CALL xios_get_handle("wet_aero" , wet_hdl) CALL xios_get_handle("load_aero" , load_hdl) CALL xios_get_handle("emialt_aero" , emialt_hdl) CALL xios_get_handle("mdw_aero" , mdw_hdl) CALL xios_get_handle("aerh2o_aero" , aerh2o_hdl) CALL xios_get_handle("oduvvis_aero", tau1_hdl) CALL xios_get_handle("odvisir_aero", tau2_hdl) CALL xios_get_handle("ssauvvis_aero", piz1_hdl) CALL xios_get_handle("ssavisir_aero", piz2_hdl) CALL xios_get_handle("asyuvvis_aero", cg1_hdl) CALL xios_get_handle("asyvisir_aero", cg2_hdl) CALL xios_get_handle("swtoaas_aero",swtoaas_hdl ) CALL xios_get_handle("swtoacs_aero",swtoacs_hdl ) CALL xios_get_handle("swsrfas_aero",swsrfas_hdl ) CALL xios_get_handle("swsrfcs_aero",swsrfcs_hdl ) CALL xios_get_handle("fswtoaas_aero",fswtoaas_hdl ) CALL xios_get_handle("fswtoacs_aero",fswtoacs_hdl ) CALL xios_get_handle("fswsrfas_aero",fswsrfas_hdl ) CALL xios_get_handle("fswsrfcs_aero",fswsrfcs_hdl ) CALL xios_get_handle("wetloss",wetloss_hdl ) ENDIF ! !! 2. Calendar and date definition ! !Réglage du calendrier: SELECT CASE (calend) CASE('earth_360d') CALL xios_define_calendar(TYPE="D360",time_origin=xios_date(year,month,day,INT(hour),0,0),start_date=xios_date(ini_an, ini_mois, ini_jour, INT(ini_heure),0,0)) CASE('earth_365d') CALL xios_define_calendar(TYPE="NoLeap",time_origin=xios_date(year,month,day,INT(hour),0,0),start_date=xios_date(ini_an, ini_mois, ini_jour, INT(ini_heure),0,0)) CASE('gregorian') CALL xios_define_calendar(TYPE="Gregorian",time_origin=xios_date(year,month,day,INT(hour),0,0),start_date=xios_date(ini_an, ini_mois, ini_jour, INT(ini_heure),0,0)) CASE DEFAULT CALL print_err(3, 'wxios_set_cal',' Mauvais choix de calendrier', '', '') END SELECT !! 3. Send the time-step length to 1 ! dtime%second = timestep CALL xios_set_timestep(dtime) ! !! 4. Domain definition ! ! Global domain !On parametrise le domaine: ! write(*,*) 'XIOS INCA initialisation grille ', grid_type, ' regular_lonlat = ', regular_lonlat, ' unstructured = ', unstructured if (grid_type == regular_lonlat) THEN CALL xios_set_domain_attr("dom_chem", ni_glo=iim_glo, ibegin=0, ni=iim_glo, TYPE="rectilinear") CALL xios_set_domain_attr("dom_chem", nj_glo=jjm_glo, jbegin=jj_begin-1, nj=jj_nb, data_dim=2) CALL xios_set_domain_attr("dom_chem", lonvalue_1D=(io_lon(1:iim_glo)+1000)-1000, latvalue_1D=io_lat(jj_begin:jj_end)) IF (.NOT.is_sequential) THEN mask(:,:)=.TRUE. IF (ii_begin>1) mask(1:ii_begin-1,1) = .FALSE. IF (ii_end') ENDIF !$OMP END MASTER END SUBROUTINE write_xml_info END MODULE xios_inca