Changeset 1353


Ignore:
Timestamp:
Oct 6, 2014, 6:31:06 PM (10 years ago)
Author:
tnavarro
Message:

New option dustiropacity in callphys.def to change the reference IR opacity of dust + New output dsodust (density-scaled opacity). Without the use of this option, nothing changes for the uninformed user.

Location:
trunk/LMDZ.MARS
Files:
7 edited

Legend:

Unmodified
Added
Removed
  • trunk/LMDZ.MARS/README

    r1331 r1353  
    21402140- Bug fix: Enforce recomputation of reaction rates at every call of
    21412141  routine prodsandlosses (in paramfoto_compact.F)
     2142
     2143== 06/10/2014 == TN
     2144- New option dustiropacity in callphys.def to change the reference IR opacity
     2145  of dust. Default is 'tes' (like before), the new one is 'mcs'. A new output,
     2146  dsodust, is the density scaled opacity of dust, to be compared with MCS
     2147  measurements, along with dustiropacity='mcs'. Future evolutions of this option
     2148  could include other instruments, or be used for water ice.
  • trunk/LMDZ.MARS/libf/phymars/aeropacity.F

    r1278 r1353  
    11      SUBROUTINE aeropacity(ngrid,nlayer,nq,zday,pplay,pplev,ls,
    2      &    pq,tauscaling,tauref,tau,taucloudtes,aerosol,reffrad,nueffrad,
    3      &    QREFvis3d,QREFir3d,omegaREFvis3d,omegaREFir3d)
     2     &    pq,tauscaling,tauref,tau,taucloudtes,aerosol,dsodust,reffrad,
     3     &    nueffrad,QREFvis3d,QREFir3d,omegaREFvis3d,omegaREFir3d)
    44                                                   
    55! to use  'getin'
     
    340340     &          pq(ig,cstdustlevel,igcm_dust_mass) *
    341341     &          ( pplev(ig,l) - pplev(ig,l+1) ) / g
     342                ! DENSITY SCALED OPACITY IN INFRARED:
     343                dsodust(ig,l) =
     344     &          (  0.75 * QREFir3d(ig,cstdustlevel,iaer) /
     345     &          ( rho_dust * reffrad(ig,cstdustlevel,iaer) )  ) *
     346     &          pq(ig,cstdustlevel,igcm_dust_mass)
    342347              ENDDO
    343348            ELSE
     
    348353     &          pq(ig,l,igcm_dust_mass) *
    349354     &          ( pplev(ig,l) - pplev(ig,l+1) ) / g
     355                ! DENSITY SCALED OPACITY IN INFRARED:
     356                dsodust(ig,l) =
     357     &          (  0.75 * QREFir3d(ig,l,iaer) /
     358     &          ( rho_dust * reffrad(ig,l,iaer) )  ) *
     359     &          pq(ig,l,igcm_dust_mass)
    350360              ENDDO
    351361            ENDIF
     
    458468     &                aerosol(ig,l,iaerdust(iaer))* tauscaling(ig))
    459469          ENDDO
     470        ENDDO
     471      ENDDO
     472
     473      DO l=1,nlayer
     474        DO ig=1,ngrid
     475          dsodust(ig,l) = max(1E-20,dsodust(ig,l)* tauscaling(ig))
    460476        ENDDO
    461477      ENDDO
  • trunk/LMDZ.MARS/libf/phymars/callkeys.h

    r1240 r1353  
    1919     
    2020      COMMON/callkeys_r/topdustref,solarcondate,semi,alphan,euveff,     &
    21      &   tke_heat_flux
     21     &   tke_heat_flux,dustrefir
    2222     
    2323      LOGICAL callrad,calldifv,calladj,callcond,callsoil,               &
     
    2828     &   ,calltherm,callrichsl,callslope,tituscap,callyamada4
    2929
     30      COMMON/aeroutput/dustiropacity
    3031
    3132      logical callemis
     
    6162      integer nircorr
    6263
     64      character(len=100) dustiropacity
     65      real               dustrefir
     66 
    6367      integer swrtype ! type of short wave (solar wavelength) radiative
    6468      ! transfer to use 1: Fouquart 2: Toon.
  • trunk/LMDZ.MARS/libf/phymars/callradite.F

    r1266 r1353  
    22     $     emis,mu0,pplev,pplay,pt,tsurf,fract,dist_sol,igout,
    33     $     dtlw,dtsw,fluxsurf_lw,fluxsurf_sw,fluxtop_lw,fluxtop_sw,
    4      &     tauref,tau,aerosol,tauscaling,taucloudtes,rdust,rice,
     4     &     tauref,tau,aerosol,dsodust,tauscaling,taucloudtes,rdust,rice,
    55     &     nuice,co2ice)
    66
     
    180180                               !   (direct comparison with TES)
    181181      REAL,INTENT(OUT) :: aerosol(ngrid,nlayer,naerkind)
     182      REAL,INTENT(OUT) :: dsodust(ngrid,nlayer)
    182183      REAL,INTENT(OUT) :: rdust(ngrid,nlayer)  ! Dust geometric mean radius (m)
    183184      REAL,INTENT(OUT) :: rice(ngrid,nlayer)   ! Ice geometric mean radius (m)
     
    373374c     Computing aerosol optical depth in each layer:
    374375      CALL aeropacity(ngrid,nlayer,nq,zday,pplay,pplev,ls,
    375      &      pq,tauscaling,tauref,tau,taucloudtes,aerosol,reffrad,
    376      &      nueffrad,QREFvis3d,QREFir3d,omegaREFvis3d,omegaREFir3d)
     376     &     pq,tauscaling,tauref,tau,taucloudtes,aerosol,dsodust,reffrad,
     377     &     nueffrad,QREFvis3d,QREFir3d,omegaREFvis3d,omegaREFir3d)
    377378
    378379c     Starting loop on sub-domain
  • trunk/LMDZ.MARS/libf/phymars/conf_phys.F

    r1268 r1353  
    371371#endif
    372372
     373! Dust IR opacity
     374         write(*,*)" Wavelength for infrared opacity of dust ?"
     375         write(*,*)" Choices are:"
     376         write(*,*)" tes  --- > 9.3 microns  [default]"
     377         write(*,*)" mcs  --- > 21.6 microns"
     378         !
     379         ! WARNING WARNING WARNING WARNING WARNING WARNING
     380         !
     381         ! BEFORE ADDING A NEW VALUE, BE SURE THAT THE
     382         ! CORRESPONDING WAVELENGTH IS IN THE LOOKUP TABLE,
     383         ! OR AT LEAST NO TO FAR, TO AVOID FALLACIOUS INTERPOLATIONS.
     384         !
     385         dustiropacity="tes" !default value - is expected to shift to mcs one day
     386         call getin("dustiropacity",dustiropacity)
     387         write(*,*)" dustiropacity = ",trim(dustiropacity)
     388         select case (trim(dustiropacity))
     389           case ("tes")
     390             dustrefir = 9.3E-6
     391           case ("mcs")
     392             dustrefir = 21.6E-6
     393           case default
     394              write(*,*) trim(dustiropacity),
     395     &                  " is not a valid option for dustiropacity"
     396             stop
     397         end select
     398
    373399! callddevil
    374400         write(*,*)" dust lifted by dust devils ?"
  • trunk/LMDZ.MARS/libf/phymars/physiq.F

    r1346 r1353  
    231231      REAL tau(ngrid,naerkind)     ! Column dust optical depth at each point
    232232                                   ! AS: TBD: this one should be in a module !
     233      REAL dsodust(ngrid,nlayer)   ! density-scaled opacity (in infrared)
    233234      REAL zls                       !  solar longitude (rad)
    234235      REAL zday                      ! date (time since Ls=0, in martian days)
     
    669670     $     emis,mu0,zplev,zplay,pt,tsurf,fract,dist_sol,igout,
    670671     $     zdtlw,zdtsw,fluxsurf_lw,fluxsurf_sw,fluxtop_lw,fluxtop_sw,
    671      $     tauref,tau,aerosol,tauscaling,taucloudtes,rdust,rice,
     672     $     tauref,tau,aerosol,dsodust,tauscaling,taucloudtes,rdust,rice,
    672673     $     nuice,co2ice)
    673674
     
    21832184             call WRITEDIAGFI(ngrid,'dustN','Dust number',
    21842185     &                        'part/kg',3,ndust)
     2186             call WRITEDIAGFI(ngrid,'dsodust',
     2187     &                        'dust density scaled opacity',
     2188     &                        'm2.kg-1',3,dsodust)
    21852189c             call WRITEDIAGFI(ngrid,"tauscaling",
    21862190c     &                    "dust conversion factor"," ",2,tauscaling)
  • trunk/LMDZ.MARS/libf/phymars/suaer.F90

    r1266 r1353  
    114114!                     For dust: change readtesassim accordingly;
    115115!       Reference wavelength in the infrared:
    116         longrefir(iaer)=9.3E-6
     116        longrefir(iaer)=dustrefir
    117117!==================================================================
    118118        CASE("dust_doubleq") aerkind! Two-moment scheme for dust
     
    127127!       If not equal to 0.67e-6 -> change readtesassim accordingly;
    128128!       Reference wavelength in the infrared:
    129         longrefir(iaer)=9.3E-6
     129        longrefir(iaer)=dustrefir
    130130!==================================================================
    131131        CASE("dust_submicron") aerkind   ! Small dust population
     
    139139!       If not equal to 0.67e-6 -> change readtesassim accordingly;
    140140!       Reference wavelength in the infrared:
    141         longrefir(iaer)=9.3E-6
     141        longrefir(iaer)=dustrefir
    142142!==================================================================
    143143        CASE("h2o_ice") aerkind             ! Water ice crystals
Note: See TracChangeset for help on using the changeset viewer.