Changeset 3857
- Timestamp:
- Feb 26, 2021, 8:37:59 PM (4 years ago)
- Location:
- LMDZ6/trunk/libf/phylmd
- Files:
-
- 5 edited
Legend:
- Unmodified
- Added
- Removed
-
LMDZ6/trunk/libf/phylmd/carbon_cycle_mod.F90
r3649 r3857 39 39 LOGICAL, PUBLIC :: carbon_cycle_tr ! 3D transport of CO2 in the atmosphere, parameter read in conf_phys 40 40 !$OMP THREADPRIVATE(carbon_cycle_tr) 41 LOGICAL, PUBLIC :: carbon_cycle_rad ! CO2 interactive radiatively41 LOGICAL, PUBLIC :: carbon_cycle_rad ! flag to activate CO2 interactive radiatively 42 42 !$OMP THREADPRIVATE(carbon_cycle_rad) 43 INTEGER, PUBLIC :: level_coupling_esm ! Level of coupling for the ESM - 0, 1, 2, 343 INTEGER, PUBLIC :: level_coupling_esm ! Level of coupling for the ESM - 0, 1, 2, 3 44 44 !$OMP THREADPRIVATE(level_coupling_esm) 45 LOGICAL, PUBLIC :: read_fco2_ocean_cor ! flag to read corrective oceanic CO2 flux 46 !$OMP THREADPRIVATE(read_fco2_ocean_cor) 47 REAL, PUBLIC :: var_fco2_ocean_cor ! corrective oceanic CO2 flux 48 !$OMP THREADPRIVATE(var_fco2_ocean_cor) 49 REAL, PUBLIC :: ocean_area_tot ! total oceanic area to convert flux 50 !$OMP THREADPRIVATE(ocean_area_tot) 51 LOGICAL, PUBLIC :: read_fco2_land_cor ! flag to read corrective land CO2 flux 52 !$OMP THREADPRIVATE(read_fco2_land_cor) 53 REAL, PUBLIC :: var_fco2_land_cor ! corrective land CO2 flux 54 !$OMP THREADPRIVATE(var_fco2_land_cor) 55 REAL, PUBLIC :: land_area_tot ! total land area to convert flux 56 !$OMP THREADPRIVATE(land_area_tot) 57 45 58 REAL, PUBLIC :: RCO2_glo 46 59 !$OMP THREADPRIVATE(RCO2_glo) … … 95 108 REAL, DIMENSION(:), ALLOCATABLE, PUBLIC :: fco2_ocean ! Net flux from ocean [kgCO2/m2/s] 96 109 !$OMP THREADPRIVATE(fco2_ocean) 110 REAL, DIMENSION(:), ALLOCATABLE, PUBLIC :: fco2_ocean_cor ! Net corrective flux from ocean [kgCO2/m2/s] 111 !$OMP THREADPRIVATE(fco2_ocean_cor) 112 REAL, DIMENSION(:), ALLOCATABLE, PUBLIC :: fco2_land_cor ! Net corrective flux from land [kgCO2/m2/s] 113 !$OMP THREADPRIVATE(fco2_land_cor) 97 114 98 115 REAL, DIMENSION(:,:), ALLOCATABLE :: dtr_add ! Tracer concentration to be injected … … 252 269 IF (.NOT.ALLOCATED(fco2_ocean)) ALLOCATE(fco2_ocean(klon), stat=ierr) 253 270 IF (ierr /= 0) CALL abort_physic('carbon_cycle_init', 'pb in allocation fco2_ocean',1) 254 fco2_bb(1:klon) = 0. 271 fco2_ocean(1:klon) = 0. 272 273 IF (.NOT.ALLOCATED(fco2_ocean_cor)) ALLOCATE(fco2_ocean_cor(klon), stat=ierr) 274 IF (ierr /= 0) CALL abort_physic('carbon_cycle_init', 'pb in allocation fco2_ocean_cor',1) 275 fco2_ocean_cor(1:klon) = 0. 276 IF (.NOT.ALLOCATED(fco2_land_cor)) ALLOCATE(fco2_land_cor(klon), stat=ierr) 277 IF (ierr /= 0) CALL abort_physic('carbon_cycle_init', 'pb in allocation fco2_land_cor',1) 278 fco2_land_cor(1:klon) = 0. 279 255 280 ENDIF 256 281 -
LMDZ6/trunk/libf/phylmd/conf_phys_m.F90
r3815 r3857 27 27 USE phys_cal_mod 28 28 USE carbon_cycle_mod, ONLY: carbon_cycle_tr, carbon_cycle_cpl, carbon_cycle_rad, level_coupling_esm 29 USE carbon_cycle_mod, ONLY: read_fco2_ocean_cor,var_fco2_ocean_cor 30 USE carbon_cycle_mod, ONLY: read_fco2_land_cor,var_fco2_land_cor 29 31 USE mod_grid_phy_lmdz, ONLY: klon_glo 30 32 USE print_control_mod, ONLY: lunout … … 237 239 LOGICAL, SAVE :: carbon_cycle_rad_omp 238 240 INTEGER, SAVE :: level_coupling_esm_omp 241 LOGICAL, SAVE :: read_fco2_ocean_cor_omp 242 REAL, SAVE :: var_fco2_ocean_cor_omp 243 LOGICAL, SAVE :: read_fco2_land_cor_omp 244 REAL, SAVE :: var_fco2_land_cor_omp 239 245 LOGICAL, SAVE :: adjust_tropopause_omp 240 246 LOGICAL, SAVE :: ok_daily_climoz_omp … … 2214 2220 CALL getin('carbon_cycle_rad',carbon_cycle_rad_omp) 2215 2221 2216 ! >> PC 2222 read_fco2_ocean_cor_omp=.FALSE. 2223 CALL getin('read_fco2_ocean_cor',read_fco2_ocean_cor_omp) 2224 2225 var_fco2_ocean_cor_omp=0. ! default value 2226 CALL getin('var_fco2_ocean_cor',var_fco2_ocean_cor_omp) 2227 2228 read_fco2_land_cor_omp=.FALSE. 2229 CALL getin('read_fco2_land_cor',read_fco2_land_cor_omp) 2230 2231 var_fco2_land_cor_omp=0. ! default value 2232 CALL getin('var_fco2_land_cor',var_fco2_land_cor_omp) 2233 2217 2234 ! level_coupling_esm : level of coupling of the biogeochemical fields between LMDZ, ORCHIDEE and NEMO 2218 2235 ! Definitions of level_coupling_esm in physiq.def … … 2227 2244 level_coupling_esm_omp=0 ! default value 2228 2245 CALL getin('level_coupling_esm',level_coupling_esm_omp) 2229 ! << PC2230 2246 2231 2247 !$OMP END MASTER -
LMDZ6/trunk/libf/phylmd/phys_output_ctrlout_mod.F90
r3817 r3857 1321 1321 TYPE(ctrl_out), SAVE :: o_flx_co2_land = ctrl_out((/ 11, 11, 11, 11, 11, 11, 11, 11, 11, 1/), & 1322 1322 'flx_co2_land', 'CO2 flux from the land', '1', (/ ('', i=1, 10) /)) 1323 TYPE(ctrl_out), SAVE :: o_flx_co2_ocean_cor = ctrl_out((/ 11, 11, 11, 11, 11, 11, 11, 11, 11, 1/), & 1324 'flx_co2_ocean_cor', 'correction of the CO2 flux from the ocean', 'kg CO2 m-2 s-1', (/ ('', i=1, 10) /)) 1325 TYPE(ctrl_out), SAVE :: o_flx_co2_land_cor = ctrl_out((/ 11, 11, 11, 11, 11, 11, 11, 11, 11, 1/), & 1326 'flx_co2_land_cor', 'correction of the CO2 flux from the land', 'kg CO2 m-2 s-1', (/ ('', i=1, 10) /)) 1323 1327 1324 1328 #ifdef CPP_StratAer -
LMDZ6/trunk/libf/phylmd/phys_output_write_mod.F90
r3817 r3857 202 202 o_col_O3_strato, o_col_O3_tropo, & 203 203 !--interactive CO2 204 o_flx_co2_ocean, o_flx_co2_land, o_flx_co2_ff, o_flx_co2_bb, & 204 o_flx_co2_ocean, o_flx_co2_ocean_cor, & 205 o_flx_co2_land, o_flx_co2_land_cor, & 206 o_flx_co2_ff, o_flx_co2_bb, & 205 207 o_delta_sst, o_delta_sal, o_ds_ns, o_dt_ns, o_dter, o_dser, o_tkt, & 206 208 o_tks, o_taur, o_sss … … 336 338 337 339 USE carbon_cycle_mod, ONLY: fco2_ff, fco2_bb, fco2_land, fco2_ocean 340 USE carbon_cycle_mod, ONLY: fco2_ocean_cor, fco2_land_cor 338 341 339 342 USE phys_output_var_mod, ONLY: vars_defined, snow_o, zfra_o, bils_diss, & … … 2427 2430 CALL histwrite_phy(o_flx_co2_land, fco2_land) 2428 2431 CALL histwrite_phy(o_flx_co2_ocean, fco2_ocean) 2432 CALL histwrite_phy(o_flx_co2_ocean_cor, fco2_ocean_cor) 2433 CALL histwrite_phy(o_flx_co2_land_cor, fco2_land_cor) 2429 2434 CALL histwrite_phy(o_flx_co2_ff, fco2_ff) 2430 2435 CALL histwrite_phy(o_flx_co2_bb, fco2_bb) -
LMDZ6/trunk/libf/phylmd/tracco2i_mod.F90
r3651 r3857 34 34 USE carbon_cycle_mod, ONLY: id_CO2, nbcf_in, fields_in, cfname_in 35 35 USE carbon_cycle_mod, ONLY: fco2_ocn_day, fco2_ff, fco2_bb, fco2_land, fco2_ocean 36 USE carbon_cycle_mod, ONLY: read_fco2_ocean_cor,var_fco2_ocean_cor,fco2_ocean_cor 37 USE carbon_cycle_mod, ONLY: read_fco2_land_cor,var_fco2_land_cor,fco2_land_cor 38 USE carbon_cycle_mod, ONLY: co2_send 36 39 USE carbon_cycle_mod, ONLY: fco2_land_nbp, fco2_land_nep, fco2_land_fLuc 37 40 USE carbon_cycle_mod, ONLY: fco2_land_fwoodharvest, fco2_land_fHarvest 38 41 USE carbon_cycle_mod, ONLY: carbon_cycle_cpl, carbon_cycle_tr, carbon_cycle_rad, RCO2_glo, RCO2_tot 42 USE carbon_cycle_mod, ONLY: ocean_area_tot 43 USE carbon_cycle_mod, ONLY: land_area_tot 39 44 USE mod_grid_phy_lmdz 40 45 USE mod_phys_lmdz_mpi_data, ONLY: is_mpi_root 41 46 USE mod_phys_lmdz_para, ONLY: gather, bcast, scatter 47 USE mod_phys_lmdz_omp_data, ONLY: is_omp_root 42 48 USE phys_cal_mod 43 49 USE phys_state_var_mod, ONLY: pctsrf … … 75 81 REAL, DIMENSION(klon_glo,klev) :: co2_glo ! variable temporaire sur la grille global 76 82 REAL, DIMENSION(klon_glo,klev) :: m_air_glo ! variable temporaire sur la grille global 83 REAL, DIMENSION(klon_glo,nbsrf):: pctsrf_glo !--fractions de maille sur la grille globale 84 REAL, DIMENSION(klon_glo) :: pctsrf_ter_glo 85 REAL, DIMENSION(klon_glo) :: pctsrf_oce_glo 86 REAL, DIMENSION(klon_glo) :: pctsrf_sic_glo 87 REAL, DIMENSION(klon_glo) :: cell_area_glo !--aire des mailles sur la grille globale 77 88 78 89 LOGICAL, SAVE :: check_fCO2_nbp_in_cfname … … 80 91 INTEGER, SAVE :: day_pre=-1 81 92 !$OMP THREADPRIVATE(day_pre) 93 94 REAL, PARAMETER :: secinday=86400. 82 95 83 96 IF (is_mpi_root) THEN … … 100 113 IF (cfname_in(nb)=="fCO2_nbp") check_fCO2_nbp_in_cfname=.TRUE. 101 114 ENDDO 115 116 CALL gather(pctsrf,pctsrf_glo) 117 CALL gather(pctsrf(:,is_ter),pctsrf_ter_glo) 118 CALL gather(pctsrf(:,is_oce),pctsrf_oce_glo) 119 CALL gather(pctsrf(:,is_sic),pctsrf_sic_glo) 120 CALL gather(cell_area(:),cell_area_glo) 102 121 103 122 ENDIF … … 146 165 ENDDO 147 166 167 PRINT *, 'tracco2i_mod.F90 --- read_fco2_ocean_cor ',read_fco2_ocean_cor 168 PRINT *, 'tracco2i_mod.F90 --- read_fco2_land_cor ',read_fco2_land_cor 169 170 IF (debutphy) THEN 171 172 IF (read_fco2_ocean_cor) THEN 173 !$OMP MASTER 174 IF (is_mpi_root .AND. is_omp_root) THEN 175 ocean_area_tot=0. 176 PRINT *, 'tracco2i_mod.F90 --- var_fco2_ocean_cor (PgC/yr) ',var_fco2_ocean_cor 177 DO i=1, klon_glo 178 ocean_area_tot = ocean_area_tot + (pctsrf_oce_glo(i)+pctsrf_sic_glo(i))*cell_area_glo(i) 179 ENDDO 180 ENDIF !--is_mpi_root and is_omp_root 181 !$OMP END MASTER 182 CALL bcast(ocean_area_tot) 183 PRINT *, 'tracco2i_mod.F90 --- ocean_area_tot (debutphy) ',ocean_area_tot 184 ENDIF 185 186 IF (read_fco2_land_cor) THEN 187 !$OMP MASTER 188 IF (is_mpi_root .AND. is_omp_root) THEN 189 land_area_tot=0. 190 PRINT *, 'tracco2i_mod.F90 --- var_fco2_land_cor (PgC/yr) ',var_fco2_land_cor 191 DO i=1, klon_glo 192 land_area_tot = land_area_tot + pctsrf_ter_glo(i)*cell_area_glo(i) 193 ENDDO 194 ENDIF !--is_mpi_root and is_omp_root 195 !$OMP END MASTER 196 CALL bcast(land_area_tot) 197 PRINT *, 'tracco2i_mod.F90 --- land_area_tot (debutphy) ',land_area_tot 198 ENDIF 199 200 ENDIF !-- debutphy 201 202 PRINT *, 'tracco2i_mod.F90 --- ocean_area_tot (m2) ',ocean_area_tot 203 PRINT *, 'tracco2i_mod.F90 --- land_area_tot (m2) ',land_area_tot 204 205 IF (read_fco2_ocean_cor) THEN 206 ! var_fco2_ocean_cor: correction of the surface downward CO2 flux into the ocean fgco2 (PgC/yr) 207 ! This is the correction of the the net air to ocean carbon flux. Positive flux is into the ocean. 208 ! PRINT *, 'tracco2i_mod.F90 --- var_fco2_ocean_cor (PgC/yr) ',var_fco2_ocean_cor 209 210 !var_fco2_ocean_cor: correction of the net air to ocean carbon flux (input data is a scalar in PgC/yr and must be converted in kg CO2 m-2 s-1) 211 212 ! Factors for carbon and carbon dioxide 213 ! 1 mole CO2 = 44.009 g CO2 = 12.011 g C 214 ! 1 ppm by volume of atmosphere CO2 = 2.13 Gt C 215 ! 1 gC = 44.009/12.011 gCO2 216 217 ! ocean_area_tot: ocean area (m2) 218 219 ! year_len: year length (in days) 220 221 ! conversion: PgC/yr --> kg CO2 m-2 s-1 222 ! fco2_ocean_cor / (86400.*year_len): PgC/yr to PgC/s 223 ! fco2_ocean_cor / (86400.*year_len)*(pctsrf(i,is_oce)+pctsrf(i,is_sic))/ocean_area_tot: PgC/s to PgC/s/m2 224 ! (fco2_ocean_cor / (86400.*year_len)*(pctsrf(i,is_oce)+pctsrf(i,is_sic))/ocean_area_tot) *1e12: PgC/s/m2 to kgC/s/m2 225 ! (fco2_ocean_cor / (86400.*year_len)*(pctsrf(i,is_oce)+pctsrf(i,is_sic))/ocean_area_tot) * 1e12 * (RMCO2/RMC): kgC/s/m2 to kgCO2/s/m2 226 227 DO i=1, klon 228 fco2_ocean_cor(i)=(var_fco2_ocean_cor*(RMCO2/RMC)*(pctsrf(i,is_oce)+pctsrf(i,is_sic))/ocean_area_tot/(secinday*year_len))*1.e12 229 ENDDO 230 231 PRINT *, 'tracco2i_mod.F90 --- MINVAL(fco2_ocean_cor) ',MINVAL(fco2_ocean_cor) 232 PRINT *, 'tracco2i_mod.F90 --- MAXVAL(fco2_ocean_cor) ',MAXVAL(fco2_ocean_cor) 233 234 ELSE 235 fco2_ocean_cor(:)=0. 236 ENDIF 237 238 IF (read_fco2_land_cor) THEN 239 ! var_fco2_land_cor: correction of the carbon Mass Flux out of Atmosphere Due to Net Biospheric Production on Land (PgC/yr) 240 ! This is the correction of the net mass flux of carbon between land and atmosphere calculated as 241 ! photosynthesis MINUS the sum of plant and soil respiration, carbon fluxes from 242 ! fire, harvest, grazing and land use change. Positive flux is into the land. 243 ! PRINT *, 'tracco2i_mod.F90 --- var_fco2_land_cor (m2) ',var_fco2_land_cor 244 245 !var_fco2_land_cor: correction of the et air to land carbon flux (input data is a scalar in PgC/yr and must be converted in kg CO2 m-2 s-1) 246 247 ! Factors for carbon and carbon dioxide 248 ! 1 mole CO2 = 44.009 g CO2 = 12.011 g C 249 ! 1 ppm by volume of atmosphere CO2 = 2.13 Gt C 250 ! 1 gC = 44.009/12.011 gCO2 251 252 ! land_area_tot: land area (m2) 253 254 ! year_len: year length (in days) 255 256 ! conversion: PgC/yr --> kg CO2 m-2 s-1 257 ! fco2_land_cor / (86400.*year_len): PgC/yr to PgC/s 258 ! fco2_land_cor / (86400.*year_len)*pctsrf(i,is_ter)/land_area_tot: PgC/s to PgC/s/m2 259 ! (fco2_land_cor / (86400.*year_len)*pctsrf(i,is_ter)/land_area_tot) *1e12: PgC/s/m2 to kgC/s/m2 260 ! (fco2_land_cor / (86400.*year_len)*pctsrf(i,is_ter)/land_area_tot) * 1e12 * (RMCO2/RMC): kgC/s/m2 to kgCO2/s/m2 261 262 DO i=1, klon 263 fco2_land_cor(i)=var_fco2_land_cor*RMCO2/RMC*pctsrf(i,is_ter)/land_area_tot/(secinday*year_len)*1.e12 264 ENDDO 265 266 PRINT *, 'tracco2i_mod.F90 --- MINVAL(fco2_land_cor) ',MINVAL(fco2_land_cor) 267 PRINT *, 'tracco2i_mod.F90 --- MAXVAL(fco2_land_cor) ',MAXVAL(fco2_land_cor) 268 269 ELSE 270 fco2_land_cor(:)=0. 271 ENDIF 272 148 273 !--if fCO2_nbp is transferred we use it, otherwise we use the sum of what has been passed from ORCHIDEE 149 274 IF (check_fCO2_nbp_in_cfname) THEN … … 167 292 ! 168 293 !--build final source term for CO2 169 source(:,id_CO2)=fco2_ff(:)+fco2_bb(:)+fco2_land(:)+fco2_ocean(:) 294 source(:,id_CO2)=fco2_ff(:)+fco2_bb(:)+fco2_land(:)+fco2_ocean(:)-fco2_ocean_cor(:)-fco2_land_cor(:) 170 295 171 296 !--computing global mean CO2 for radiation … … 195 320 ENDIF 196 321 322 PRINT *, 'tracco2i_mod.F90 --- MINVAL(tr_seri(:,1,id_CO2)*1.e6*RMD/RMCO2): L1: ',MINVAL(tr_seri(:,1,id_CO2)*1.e6*RMD/RMCO2) 323 PRINT *, 'tracco2i_mod.F90 --- MAXVAL(tr_seri(:,1,id_CO2)*1.e6*RMD/RMCO2): L1: ',MAXVAL(tr_seri(:,1,id_CO2)*1.e6*RMD/RMCO2) 324 325 PRINT *, 'tracco2i_mod.F90 --- MINVAL(tr_seri(:,79,id_CO2)*1.e6*RMD/RMCO2): L79: ',MINVAL(tr_seri(:,79,id_CO2)*1.e6*RMD/RMCO2) 326 PRINT *, 'tracco2i_mod.F90 --- MAXVAL(tr_seri(:,79,id_CO2)*1.e6*RMD/RMCO2): L79: ',MAXVAL(tr_seri(:,79,id_CO2)*1.e6*RMD/RMCO2) 327 328 co2_send(:) = tr_seri(:,1,id_CO2)*1.e6*RMD/RMCO2 329 330 PRINT *, 'tracco2i_mod.F90 --- MINVAL(co2_send) ',MINVAL(co2_send) 331 PRINT *, 'tracco2i_mod.F90 --- MAXVAL(co2_send) ',MAXVAL(co2_send) 332 197 333 END SUBROUTINE tracco2i 198 334 … … 252 388 IF (readco2ff) THEN 253 389 254 ! ... Open the CO Zff file390 ! ... Open the CO2ff file 255 391 CALL nf95_open("sflx_lmdz_co2_ff.nc", nf90_nowrite, ncid_in) 256 392
Note: See TracChangeset
for help on using the changeset viewer.