Changeset 2643 for trunk/LMDZ.MARS/libf/phymars
- Timestamp:
- Mar 17, 2022, 2:36:31 PM (3 years ago)
- Location:
- trunk/LMDZ.MARS/libf/phymars
- Files:
-
- 10 edited
- 1 moved
Legend:
- Unmodified
- Added
- Removed
-
trunk/LMDZ.MARS/libf/phymars/aeropacity_mod.F
r2634 r2643 10 10 11 11 SUBROUTINE aeropacity(ngrid,nlayer,nq,zday,pplay,pplev,ls, 12 & pq,pt,tauscaling,dust_rad_adjust,tau_pref_scenario,13 & 14 & 15 & 16 & 17 & 12 & pq,pt,tauscaling,dust_rad_adjust,IRtoVIScoef,tau_pref_scenario, 13 & tau_pref_gcm,tau,taucloudtes,aerosol,dsodust,reffrad, 14 & QREFvis3d,QREFir3d,omegaREFir3d, 15 & totstormfract,clearatm,dsords,dsotop, 16 & nohmons, 17 & clearsky,totcloudfrac) 18 18 19 19 use ioipsl_getin_p_mod, only: getin_p … … 35 35 & iaer_stormdust_doubleq, 36 36 & iaer_topdust_doubleq 37 use dust_param_mod, only: odpref, freedust 37 use dust_param_mod, only: odpref, freedust, 38 & reff_driven_IRtoVIS_scenario 38 39 use dust_scaling_mod, only: compute_dustscaling 39 40 use density_co2_ice_mod, only: density_co2_ice 40 41 use surfdat_h,only: alpha_hmons,contains_mons 42 use read_dust_scenario_mod, only: read_dust_scenario 41 43 42 44 IMPLICIT NONE … … 89 91 ! (for direct comparison with TES) 90 92 REAL, INTENT(OUT) :: aerosol(ngrid,nlayer,naerkind) ! optical 91 ! depth of each aeros l in each layer93 ! depth of each aerosol in each layer 92 94 REAL, INTENT(OUT) :: dsodust(ngrid,nlayer) ! density scaled opacity 93 95 ! of (background) dust … … 110 112 REAL,INTENT(OUT) :: tauscaling(ngrid) ! Scaling factor for qdust and Ndust 111 113 REAL,INTENT(INOUT) :: dust_rad_adjust(ngrid) ! Radiative adjustment 112 ! factor for dust 114 ! factor for dust 115 REAL,INTENT(INOUT) :: IRtoVIScoef(ngrid) ! conversion coefficient to apply on 116 ! scenario absorption IR (9.3um) CDOD 117 ! = tau_pref_gcm_VIS / tau_pref_gcm_IR 113 118 REAL,INTENT(IN) :: totcloudfrac(ngrid) ! total water ice cloud fraction 114 119 LOGICAL,INTENT(IN) :: clearsky ! true to compute RT without water ice clouds … … 134 139 ! reference wavelength 135 140 REAL topdust0(ngrid) 141 142 REAL aerosol_IRabs(ngrid,nlayer) 143 REAL taudust_IRabs(ngrid) 144 REAL taudust_VISext(ngrid) 136 145 137 146 ! -- CO2 clouds … … 295 304 tau_pref_scenario(ig) = tau_pref_scenario(1) 296 305 end do 306 !!!!!!!!!!!!!!!!!!!!!!!!!!! 307 ! NB: here, IRtoVIScoef=2.6 308 ! ( useful to be here only if iddist=0 (Pollack90 vertical distribution) ) 297 309 ELSE IF ((iaervar.ge.6).and.(iaervar.le.8)) THEN 298 310 ! clim, cold or warm synthetic scenarios 299 311 call read_dust_scenario(ngrid,nlayer,zday,pplev, 300 & tau_pref_scenario)312 & IRtoVIScoef,tau_pref_scenario) 301 313 ELSE IF ((iaervar.ge.24).and.(iaervar.le.35)) 302 314 & THEN ! << MY... dust scenarios >> 303 315 call read_dust_scenario(ngrid,nlayer,zday,pplev, 304 & tau_pref_scenario)316 & IRtoVIScoef,tau_pref_scenario) 305 317 ELSE IF ((iaervar.eq.4).or. 306 318 & ((iaervar.ge.124).and.(iaervar.le.126))) THEN 307 319 ! "old" TES assimation dust scenario (values at 700Pa in files!) 308 320 call read_dust_scenario(ngrid,nlayer,zday,pplev, 309 & tau_pref_scenario) 321 & IRtoVIScoef,tau_pref_scenario) 322 !!!!!!!!!!!!!!!!!!!!!!!!!!! 310 323 ELSE 311 324 call abort_physic("aeropacity","wrong value for iaervar",1) … … 385 398 c (transport of mass and number mixing ratio) 386 399 c================================================================== 387 400 ! Some initialisations for the IRtoVIScoef 401 aerosol_IRabs(:,:)=0. 402 taudust_IRabs(:)=0. 403 taudust_VISext(:)=0. 404 388 405 DO l=1,nlayer 389 406 IF (l.LE.cstdustlevel) THEN … … 405 422 & ( rho_dust * reffrad(ig,cstdustlevel,iaer) ) ) * 406 423 & pq(ig,cstdustlevel,igcm_dust_mass) 424 425 if (reff_driven_IRtoVIS_scenario) then 426 if ((clearatm).and.(nohmons)) then ! the IRtoVIScoef is computed only during the first call to the RT 427 ! OPTICAL DEPTH in IR absorption to compute the IRtoVIScoef 428 aerosol_IRabs(ig,l) = 429 & ( 0.75 * QREFir3d(ig,cstdustlevel,iaer) / 430 & ( rho_dust * reffrad(ig,cstdustlevel,iaer) ) ) * 431 & ( 1. - omegaREFir3d(ig,cstdustlevel,iaer) ) * 432 & pq(ig,cstdustlevel,igcm_dust_mass) * 433 & ( pplev(ig,l) - pplev(ig,l+1) ) / g 434 endif 435 endif 407 436 ENDDO 408 437 ELSE … … 422 451 & ( rho_dust * reffrad(ig,l,iaer) ) ) * 423 452 & pq(ig,l,igcm_dust_mass) 453 454 if (reff_driven_IRtoVIS_scenario) then 455 if ((clearatm).and.(nohmons)) then ! the IRtoVIScoef is computed only during the first call to the RT 456 ! OPTICAL DEPTH in IR absorption to compute the IRtoVIScoef 457 aerosol_IRabs(ig,l) = 458 & ( 0.75 * QREFir3d(ig,l,iaer) / 459 & ( rho_dust * reffrad(ig,l,iaer) ) ) * 460 & ( 1. - omegaREFir3d(ig,l,iaer) ) * 461 & pq(ig,l,igcm_dust_mass) * 462 & ( pplev(ig,l) - pplev(ig,l+1) ) / g 463 endif 464 endif 424 465 ENDDO 425 466 ENDIF 426 ENDDO 467 if (reff_driven_IRtoVIS_scenario) then 468 if ((clearatm).and.(nohmons)) then ! the IRtoVIScoef is computed only during the first call to the RT 469 taudust_VISext(:) = taudust_VISext(:) + aerosol(:,l,iaer) 470 taudust_IRabs(:) = taudust_IRabs(:) + aerosol_IRabs(:,l) 471 endif 472 endif 473 ENDDO 474 475 if (reff_driven_IRtoVIS_scenario) then 476 if ((clearatm).and.(nohmons)) then ! the IRtoVIScoef is computed only during the first call to the RT 477 IRtoVIScoef(:) = taudust_VISext(:) / taudust_IRabs(:) 478 endif 479 endif 427 480 428 481 c================================================================== … … 647 700 ! 3. Specific treatments for the dust aerosols 648 701 702 ! here IRtoVIScoef has been updated, we can call again read_dust_scenario 703 if (reff_driven_IRtoVIS_scenario) then 704 IF ((iaervar.ge.6).and.(iaervar.le.8)) THEN 705 ! clim, cold or warm synthetic scenarios 706 call read_dust_scenario(ngrid,nlayer,zday,pplev, 707 & IRtoVIScoef,tau_pref_scenario) 708 ELSE IF ((iaervar.ge.24).and.(iaervar.le.35)) 709 & THEN ! << MY... dust scenarios >> 710 call read_dust_scenario(ngrid,nlayer,zday,pplev, 711 & IRtoVIScoef,tau_pref_scenario) 712 ELSE IF ((iaervar.eq.4).or. 713 & ((iaervar.ge.124).and.(iaervar.le.126))) THEN 714 ! "old" TES assimation dust scenario (values at 700Pa in files!) 715 call read_dust_scenario(ngrid,nlayer,zday,pplev, 716 & IRtoVIScoef,tau_pref_scenario) 717 ENDIF 718 endif 719 649 720 #ifdef DUSTSTORM 650 721 c ----------------------------------------------------------------- … … 790 861 ! coefficients and adjust aerosol() dust opacities accordingly 791 862 call compute_dustscaling(ngrid,nlayer,naerkind,naerdust,zday,pplev 792 & ,tau_pref_scenario, tauscaling,793 & dust_rad_adjust,aerosol)863 & ,tau_pref_scenario,IRtoVIScoef, 864 & tauscaling,dust_rad_adjust,aerosol) 794 865 795 866 ! 3.2. Recompute tau_pref_gcm, the reference dust opacity, based on dust tracer -
trunk/LMDZ.MARS/libf/phymars/callradite_mod.F
r2634 r2643 9 9 $ dtlw,dtsw,fluxsurf_lw,fluxsurf_sw,fluxtop_lw, 10 10 $ fluxtop_sw,tau_pref_scenario,tau_pref_gcm, 11 & tau,aerosol,dsodust,tauscaling,dust_rad_adjust, 11 & tau,aerosol,dsodust,tauscaling,dust_rad_adjust,IRtoVIScoef, 12 12 $ taucloudtes,rdust,rice,nuice,riceco2,nuiceco2,co2ice, 13 13 $ rstormdust,rtopdust,totstormfract,clearatm,dsords,dsotop, … … 179 179 REAL,INTENT(INOUT) :: dust_rad_adjust(ngrid) ! Radiative adjustment 180 180 ! factor for dust 181 REAL,INTENT(INOUT) :: IRtoVIScoef(ngrid) ! conversion coefficient to apply on 182 ! scenario absorption IR (9.3um) CDOD 183 ! = tau_pref_gcm_VIS / tau_pref_gcm_IR 181 184 REAL,INTENT(IN) :: albedo(ngrid,2),emis(ngrid) 182 185 REAL,INTENT(IN) :: ls,zday … … 443 446 c Computing aerosol optical depth in each layer: 444 447 CALL aeropacity(ngrid,nlayer,nq,zday,pplay,pplev,ls, 445 & pq,pt,tauscaling,dust_rad_adjust,tau_pref_scenario, 446 & tau_pref_gcm,tau,taucloudtes,aerosol,dsodust,reffrad, 448 & pq,pt,tauscaling,dust_rad_adjust,IRtoVIScoef, 449 & tau_pref_scenario,tau_pref_gcm,tau,taucloudtes, 450 & aerosol,dsodust,reffrad, 447 451 & QREFvis3d,QREFir3d,omegaREFir3d, 448 452 & totstormfract,clearatm,dsords,dsotop, -
trunk/LMDZ.MARS/libf/phymars/compute_dtau_mod.F90
r2616 r2643 15 15 SUBROUTINE compute_dtau(ngrid,nlayer, & 16 16 zday,pplev,tau_pref_gcm, & 17 ptimestep,dustliftday,local_time) 17 ptimestep,local_time,IRtoVIScoef, & 18 dustliftday) 18 19 19 20 USE geometry_mod, only: longitude_deg … … 23 24 USE dimradmars_mod, only: tauvis 24 25 USE dust_param_mod, only: odpref, t_scenario_sol 26 USE read_dust_scenario_mod, only: read_dust_scenario 25 27 26 28 IMPLICIT NONE … … 36 38 REAL, INTENT(in) :: ptimestep 37 39 REAL, INTENT(in) :: local_time(ngrid) 40 REAL, INTENT(in) :: IRtoVIScoef(ngrid) ! conversion coefficient to apply on 41 ! scenario absorption IR (9.3um) CDOD 42 ! = tau_pref_gcm_VIS / tau_pref_gcm_IR 38 43 REAL, INTENT(out) :: dustliftday(ngrid) ! Dust injection rate (s-1) 39 44 … … 71 76 zday_scenario=zday_scenario+1 ! opacity of the dust scenario is read the day after 72 77 call read_dust_scenario(ngrid,nlayer,zday_scenario,pplev, & 78 IRtoVIScoef, & 73 79 tau_pref_target) 74 80 endif -
trunk/LMDZ.MARS/libf/phymars/conf_phys.F
r2639 r2643 49 49 use dust_param_mod, only: dustbin, doubleq, submicron, active, 50 50 & lifting, freedust, callddevil, 51 & dustscaling_mode 51 & dustscaling_mode, 52 & reff_driven_IRtoVIS_scenario 52 53 use aeropacity_mod, only: iddist, topdustref 53 54 USE mod_phys_lmdz_transfert_para, ONLY: bcast … … 516 517 ! OR AT LEAST NO TO FAR, TO AVOID FALLACIOUS INTERPOLATIONS. 517 518 ! 518 dustiropacity="tes" !default value - is expected to shift to mcs one day519 dustiropacity="tes" !default value 519 520 call getin_p("dustiropacity",dustiropacity) 520 521 write(*,*)" dustiropacity = ",trim(dustiropacity) … … 530 531 & "invalid dustiropacity option value",1) 531 532 end select 533 ! Dust scenario IR to VIS conversion 534 write(*,*)"Use an IR to VIS conversion coefficient" 535 write(*,*)"for the dust scenario, that is dependent" 536 write(*,*)"on the GCM dust effective radius," 537 write(*,*)"instead of a fixed 2.6 coefficient ?" 538 reff_driven_IRtoVIS_scenario=.false. !default value 539 call getin_p("reff_driven_IRtoVIS_scenario", 540 & reff_driven_IRtoVIS_scenario) 541 write(*,*)" reff_driven_IRtoVIS_scenario = ", 542 & reff_driven_IRtoVIS_scenario 543 ! Test of incompatibility: 544 ! if reff_driven_IRtoVIS_scenario=.true., 545 ! dustrefir must be 9.3E-6 = scenarios' wavelength 546 if (reff_driven_IRtoVIS_scenario .and. 547 & (dustrefir.ne.9.3E-6)) then 548 print*,'if reff_driven_IRtoVIS_scenario is used, then '// 549 & 'the GCM IR reference wavelength should be the one '// 550 & 'of the scenarios (dustiropacity=tes)' 551 call abort_physic(modname, 552 & "reff_driven_IRtoVIS_scenario requires tes wavelength",1) 553 endif 532 554 533 555 ! callddevil … … 539 561 ! Test of incompatibility: 540 562 ! if dustdevil is used, then dustbin should be > 0 541 542 563 if (callddevil.and.(dustbin.lt.1)) then 543 564 print*,'if dustdevil is used, then dustbin should > 0' … … 545 566 & "callddevil requires dustbin > 0",1) 546 567 endif 568 547 569 ! sedimentation 548 570 write(*,*) "Gravitationnal sedimentation ?" -
trunk/LMDZ.MARS/libf/phymars/dust_param_mod.F90
r2578 r2643 8 8 LOGICAL,SAVE :: freedust ! if true: no rescaling (via tauscaling) of the dust mass and number 9 9 LOGICAL,SAVE :: callddevil ! flag to activate dust devil (dust lifing/injection) parametrization 10 LOGICAL,SAVE :: reff_driven_IRtoVIS_scenario ! use GCM dust size to convert IR scenarios to VIS 10 11 11 12 !$OMP THREADPRIVATE(active, doubleq,submicron,lifting,freedust, & … … 28 29 ! tau_pref_scenario is deemed exact 29 30 30 !$OMP THREADPRIVATE(tauscaling, 31 !$OMP THREADPRIVATE(tauscaling,dustscaling_mode,dust_rad_adjust) 31 32 32 33 contains -
trunk/LMDZ.MARS/libf/phymars/dust_rad_adjust_mod.F90
r2634 r2643 13 13 14 14 subroutine compute_dust_rad_adjust(ngrid,nlayer,zday,pplev, & 15 taudust,dust_rad_adjust) 15 taudust,IRtoVIScoef, & 16 dust_rad_adjust) 16 17 17 18 use geometry_mod, only: longitude_deg 18 19 use time_phylmdz_mod, only: dtphys, daysec 19 20 use dust_param_mod, only: odpref, t_scenario_sol 21 use read_dust_scenario_mod, only: read_dust_scenario 20 22 21 23 implicit none … … 26 28 real,intent(in) :: pplev(ngrid,nlayer+1) ! pressure (Pa) at layer boundaries 27 29 real,intent(in) :: taudust(ngrid) ! visible dust columns opacity in the GCM 30 real,intent(in) :: IRtoVIScoef(ngrid) ! conversion coefficient to apply on 31 ! scenario absorption IR (9.3um) CDOD 32 ! = tau_pref_gcm_VIS / tau_pref_gcm_IR 28 33 real,intent(out) :: dust_rad_adjust(ngrid) ! radiative adjustment coefficient 29 34 ! for dust … … 74 79 ! tau_pref_scenario) 75 80 call read_dust_scenario(ngrid,nlayer,zday_scenario_next,pplev, & 81 IRtoVIScoef, & 76 82 tau_pref_scenario_next) 77 83 -
trunk/LMDZ.MARS/libf/phymars/dust_scaling_mod.F90
r2634 r2643 7 7 subroutine compute_dustscaling(ngrid,nlayer,naerkind,naerdust, & 8 8 zday,pplev, & 9 tau_pref_scenario,tauscaling, & 9 tau_pref_scenario,IRtoVIScoef, & 10 tauscaling, & 10 11 dust_rad_adjust,aerosol) 11 12 … … 24 25 real,intent(in) :: tau_pref_scenario(ngrid) ! prescribed visible dust 25 26 ! opacity column at odpref reference pressure 27 real,intent(in) :: IRtoVIScoef(ngrid) ! conversion coefficient to apply on 28 ! scenario absorption IR (9.3um) CDOD 29 ! = tau_pref_gcm_VIS / tau_pref_gcm_IR 26 30 real,intent(out) :: tauscaling(ngrid) ! dust scaling factor 27 31 real,intent(inout) :: dust_rad_adjust(ngrid) ! Radiative adjustment … … 74 78 if (zday/=zday_prev_call) then 75 79 call compute_dust_rad_adjust(ngrid,nlayer,zday,pplev, & 76 taudust,dust_rad_adjust) 77 endif ! of if (zday/=zday_prev_call) 80 taudust,IRtoVIScoef, & 81 dust_rad_adjust) 82 endif ! of if (zday/=zday_prev_call) 78 83 79 84 ! update zday_prev_call -
trunk/LMDZ.MARS/libf/phymars/physiq_mod.F
r2628 r2643 65 65 & tauscaling, odpref, dustbin, 66 66 & dustscaling_mode, dust_rad_adjust, 67 & freedust 67 & freedust, reff_driven_IRtoVIS_scenario 68 68 use turb_mod, only: q2, wstar, ustar, sensibFlux, 69 69 & zmax_th, hfmax_th, turb_resolved … … 301 301 REAL tau_pref_scenario(ngrid) ! prescribed dust column visible opacity 302 302 ! at odpref 303 REAL IRtoVIScoef(ngrid) ! conversion coefficient to apply on 304 ! scenario absorption IR (9.3um) CDOD 305 ! = tau_pref_gcm_VIS / tau_pref_gcm_IR 303 306 REAL tau_pref_gcm(ngrid) ! dust column visible opacity at odpref in the GCM 304 307 c rocket dust storm … … 761 764 dsotop(:,:)=0. 762 765 dwatercap(:)=0 766 767 ! Dust scenario conversion coefficient from IRabs to VISext 768 IRtoVIScoef(1:ngrid)=2.6 ! initialized with former value from Montabone et al 2015 769 ! recomputed in aeropacity if reff_driven_IRtoVIS_scenario=.true. 763 770 764 771 #ifdef DUSTSTORM … … 967 974 & zdtlw,zdtsw,fluxsurf_lw,fluxsurf_sw,fluxtop_lw, 968 975 & fluxtop_sw,tau_pref_scenario,tau_pref_gcm, 969 & tau,aerosol,dsodust,tauscaling,dust_rad_adjust, 976 & tau,aerosol,dsodust,tauscaling,dust_rad_adjust,IRtoVIScoef, 970 977 & taucloudtes,rdust,rice,nuice,riceco2,nuiceco2,co2ice, 971 978 & rstormdust,rtopdust,totstormfract,clearatm,dsords,dsotop, … … 983 990 & dist_sol,igout,zdtlwclf,zdtswclf,fluxsurf_lwclf, 984 991 & fluxsurf_swclf,fluxtop_lwclf,fluxtop_swclf, 985 & tau_pref_scenario,tau_pref_gcm, 986 & tau,aerosol,dsodust,tauscaling,dust_rad_adjust,992 & tau_pref_scenario,tau_pref_gcm,tau,aerosol, 993 & dsodust,tauscaling,dust_rad_adjust,IRtoVIScoef, 987 994 & taucloudtesclf,rdust, 988 995 & rice,nuice,riceco2, nuiceco2,co2ice,rstormdust, … … 1179 1186 & tsurf,igout,totstormfract, 1180 1187 & tauscaling,dust_rad_adjust, 1188 & IRtoVIScoef, 1181 1189 c input sub-grid scale cloud 1182 1190 & clearsky,totcloudfrac, … … 1240 1248 & zzlay,zdtsw,zdtlw, 1241 1249 & icount,zday,zls,tsurf,igout,aerosol, 1242 & tauscaling,dust_rad_adjust, 1250 & tauscaling,dust_rad_adjust,IRtoVIScoef, 1243 1251 & totstormfract,clearatm, 1244 1252 & clearsky,totcloudfrac, … … 1272 1280 CALL compute_dtau(ngrid,nlayer, 1273 1281 & zday,pplev,tau_pref_gcm, 1274 & ptimestep,dustliftday,local_time) 1282 & ptimestep,local_time,IRtoVIScoef, 1283 & dustliftday) 1275 1284 endif ! end of if (dustinjection.gt.0) 1276 1285 … … 3247 3256 & 'Visible dust optical depth at 610Pa in the GCM', 3248 3257 & 'NU',2,tau_pref_gcm) 3258 3259 if (reff_driven_IRtoVIS_scenario) then 3260 call WRITEDIAGFI(ngrid,'IRtoVIScoef', 3261 & 'conversion coeff for dust tau from abs9.3um to ext0.67um', 3262 & '/',2,IRtoVIScoef) 3263 endif 3249 3264 3250 3265 if (tracer.and.(dustbin.ne.0)) then -
trunk/LMDZ.MARS/libf/phymars/read_dust_scenario_mod.F90
r2641 r2643 1 subroutine read_dust_scenario(ngrid,nlayer,zday,pplev,tau_pref_scenario) 1 module read_dust_scenario_mod 2 3 implicit none 4 5 contains 6 7 subroutine read_dust_scenario(ngrid,nlayer,zday,pplev,IRtoVIScoef,tau_pref_scenario) 2 8 3 9 ! Reading of the dust scenario file … … 16 22 real, intent(in) :: zday ! date in martian days 17 23 real, dimension(ngrid,nlayer+1), intent(in) :: pplev 24 real, dimension(ngrid), intent(in) :: IRtoVIScoef ! conversion coefficient to apply on 25 ! scenario absorption IR (9.3um) CDOD 26 ! = tau_pref_gcm_VIS / tau_pref_gcm_IR 18 27 real, dimension(ngrid), intent(out) :: tau_pref_scenario ! visible dust column 19 28 ! opacity at odpref from scenario … … 40 49 integer, save :: timelen,lonlen,latlen 41 50 character(len=33),save :: filename 51 logical,save :: IRscenario ! =true if the scenarios are IR absorption opacity (variable 'cdod') 52 ! and not VIS extinction (variable 'dustop') 42 53 43 54 !$OMP THREADPRIVATE(firstcall,radeg,pi, & 44 !$OMP lat,lon,time,tautes, & 45 !$OMP timelen,lonlen,latlen,filename) 55 !$OMP lat,lon,time,tautes, & 56 !$OMP timelen,lonlen,latlen, & 57 !$OMP filename,IRscenario) 46 58 47 59 realday=mod(zday,669.) … … 126 138 ierr=nf90_inq_varid(nid,"dustop",nvarid) 127 139 if (ierr.eq.nf90_noerr) then 140 IRscenario = .false. 128 141 ierr=nf90_get_var(nid,nvarid,tautes) 129 142 IF (ierr .NE. nf90_noerr) THEN … … 134 147 else 135 148 ! did not find "dustop" , look for "cdod" 149 IRscenario = .true. 136 150 ierr=nf90_inq_varid(nid,"cdod",nvarid) 137 151 ierr=nf90_get_var(nid,nvarid,tautes) … … 141 155 call abort_physic("read_dust_scenario","cdod not found",1) 142 156 ENDIF 143 ! and multiply by 2*1.3=2.6 to convert from IR absorption144 ! to visible extinction opacity145 tautes(:,:,:)=2.6*tautes(:,:,:)146 157 endif 147 158 … … 194 205 call bcast(lat) 195 206 call bcast(lon) 207 call bcast(IRscenario) 196 208 197 209 endif ! of if (firstcall) 210 198 211 199 212 do ig=1,ngrid … … 354 367 tau= dlat*(dlon*(tau1(2)+tau1(3)-tau1(1)-tau1(4))+tau1(1)-tau1(3)) +dlon*(tau1(4)-tau1(3))+tau1(3) 355 368 356 tau_pref_scenario(ig)=tau 369 if (IRscenario) then 370 ! if the scenarios are in infrared, multiply by IRtoVIScoef(ig) 371 ! to convert from IR absorption to visible extinction opacity 372 tau_pref_scenario(ig)=tau * IRtoVIScoef(ig) 373 else 374 tau_pref_scenario(ig)=tau 375 endif 376 357 377 ! 358 378 enddo ! of ig=1,ngrid … … 373 393 endif 374 394 375 end 395 end subroutine read_dust_scenario 396 397 end module read_dust_scenario_mod -
trunk/LMDZ.MARS/libf/phymars/rocketduststorm_mod.F90
r2634 r2643 27 27 tsurf,igout,totstormfract, & 28 28 tauscaling,dust_rad_adjust, & 29 IRtoVIScoef, & 29 30 ! input sub-grid scale cloud 30 31 clearsky,totcloudfrac, & … … 79 80 REAL, INTENT(IN) :: totstormfract(ngrid) 80 81 REAL, INTENT(INOUT) :: tauscaling(ngrid) 81 REAL,INTENT(INOUT) :: dust_rad_adjust(ngrid) 82 REAL,INTENT(INOUT) :: dust_rad_adjust(ngrid) 83 REAL,INTENT(INOUT) :: IRtoVIScoef(ngrid) ! NB: not modified by this call to callradite, 84 ! the OUT is just here because callradite needs it 82 85 83 86 ! subgrid scale water ice clouds … … 254 257 zdtlw1,zdtsw1,fluxsurf_lw1,fluxsurf_sw1,fluxtop_lw1, & 255 258 fluxtop_sw1,tau_pref_scenario,tau_pref_gcm, & 256 tau,aerosol,dsodust,tauscaling,dust_rad_adjust, 259 tau,aerosol,dsodust,tauscaling,dust_rad_adjust,IRtoVIScoef, & 257 260 taucloudtes,rdust,rice,nuice,riceco2,nuiceco2,co2ice,rstormdust,rtopdust, & 258 261 totstormfract,clearatm,dsords,dsotop,nohmons,& -
trunk/LMDZ.MARS/libf/phymars/topmons_mod.F90
r2634 r2643 22 22 icount,zday,zls,tsurf,igout,aerosol, & 23 23 tauscaling,dust_rad_adjust, & 24 IRtoVIScoef, & 24 25 ! input sub-grid scale rocket dust storm 25 26 totstormfract,clearatm, & … … 75 76 REAL, INTENT(INOUT) :: tauscaling(ngrid) 76 77 REAL,INTENT(INOUT) :: dust_rad_adjust(ngrid) 78 REAL,INTENT(INOUT) :: IRtoVIScoef(ngrid) ! NB: not modified by this call to callradite, 79 ! the OUT is just here because callradite needs it 80 77 81 ! input sub-grid scale rocket dust storm 78 82 LOGICAL, INTENT(IN) :: clearatm … … 284 288 zdtlw1,zdtsw1,fluxsurf_lw1,fluxsurf_sw1,fluxtop_lw1, & 285 289 fluxtop_sw1,tau_pref_scenario,tau_pref_gcm, & 286 tau,aerosol,dsodust,tauscaling,dust_rad_adjust, 290 tau,aerosol,dsodust,tauscaling,dust_rad_adjust,IRtoVIScoef, & 287 291 taucloudtes,rdust,rice,nuice,riceco2,nuiceco2,co2ice,rstormdust,rtopdust, & 288 292 totstormfract,clearatm,dsords,dsotop,nohmons,&
Note: See TracChangeset
for help on using the changeset viewer.