Ignore:
Timestamp:
Feb 27, 2020, 6:03:57 PM (5 years ago)
Author:
abierjon
Message:

Mars GCM:
Resolved ticket #32 : 1) dsodust is now calculated only once in the InfraRed? by aeropacity_mod (used to be wrongly calculated twice, such as dsodust=IR_part+Visible_part) ; 2) dsords is now calculated in the IR by aeropacity_mod (used to be calculated in the Visible) ; 3) dsotop is added and calculated in the IR in aeropacity_mod
+ some cleaning and commenting of the code
AB

Location:
trunk/LMDZ.MARS/libf/phymars
Files:
5 edited

Legend:

Unmodified
Added
Removed
  • trunk/LMDZ.MARS/libf/phymars/aeropacity_mod.F

    r2199 r2246  
    88     &    pq,tauscaling,tauref,tau,taucloudtes,aerosol,dsodust,reffrad,
    99     &    QREFvis3d,QREFir3d,omegaREFir3d,
    10      &    totstormfract,clearatm,dsords,
     10     &    totstormfract,clearatm,dsords,dsotop,
    1111     &    alpha_hmons,nohmons,
    1212     &    clearsky,totcloudfrac)
     
    9090      REAL, INTENT(OUT) :: aerosol(ngrid,nlayer,naerkind)
    9191      REAL, INTENT(OUT) ::  dsodust(ngrid,nlayer)
    92       REAL, INTENT(OUT) ::  dsords(ngrid,nlayer) !dso of stormdust 
     92      REAL, INTENT(OUT) ::  dsords(ngrid,nlayer) !dso of stormdust
     93      REAL, INTENT(OUT) ::  dsotop(ngrid,nlayer) !dso of topdust 
    9394      REAL, INTENT(INOUT) :: reffrad(ngrid,nlayer,naerkind)
    9495      REAL, INTENT(IN) :: QREFvis3d(ngrid,nlayer,naerkind)
     
    171172      dsords(:,:)=0. !CW17: initialize dsords
    172173      dsodust(:,:)=0.
     174      dsotop(:,:)=0.
    173175
    174176! identify tracers
     
    376378
    377379c==================================================================
    378         CASE("dust_doubleq") aerkind! Two-moment scheme for dust
     380        CASE("dust_doubleq") aerkind! Two-moment scheme for background dust
    379381c        (transport of mass and number mixing ratio)
    380382c==================================================================
     
    385387c             avoid unrealistic values due to constant lifting:
    386388              DO ig=1,ngrid
     389              ! OPTICAL DEPTH for the computation of tauref,
     390              ! which is to be compared with tauref_scenario
     391              ! => visible wavelength
    387392                aerosol(ig,l,iaer) =
    388393     &          (  0.75 * QREFvis3d(ig,cstdustlevel,iaer) /
     
    390395     &          pq(ig,cstdustlevel,igcm_dust_mass) *
    391396     &          ( pplev(ig,l) - pplev(ig,l+1) ) / g
    392                 ! DENSITY SCALED OPACITY IN THE INFRARED:
     397              ! DENSITY SCALED OPACITY :
     398              ! GCM output to be compared with observations
     399              ! => infrared wavelength
    393400                dsodust(ig,l) =
    394401     &          (  0.75 * QREFir3d(ig,cstdustlevel,iaer) /
     
    398405            ELSE
    399406              DO ig=1,ngrid
    400                 aerosol(ig,l,iaer) =
     407              ! OPTICAL DEPTH for the computation of tauref,
     408              ! which is to be compared with tauref_scenario
     409              ! => visible wavelength
     410                aerosol(ig,l,iaer) =
    401411     &          (  0.75 * QREFvis3d(ig,l,iaer) /
    402412     &          ( rho_dust * reffrad(ig,l,iaer) )  ) *
    403413     &          pq(ig,l,igcm_dust_mass) *
    404414     &          ( pplev(ig,l) - pplev(ig,l+1) ) / g
    405                 ! DENSITY SCALED OPACITY IN THE INFRARED:
     415              ! DENSITY SCALED OPACITY :
     416              ! GCM output to be compared with observations
     417              ! => infrared wavelength
    406418                dsodust(ig,l) =
    407419     &          (  0.75 * QREFir3d(ig,l,iaer) /
     
    505517c           avoid unrealistic values due to constant lifting:
    506518               DO ig=1,ngrid
    507                   aerosol(ig,l,iaer) =
     519               ! OPTICAL DEPTH for the computation of tauref,
     520               ! which is to be compared with tauref_scenario
     521               ! => visible wavelength
     522                 aerosol(ig,l,iaer) =
    508523     &           (  0.75 * QREFvis3d(ig,cstdustlevel,iaer) /
    509524     &           ( rho_dust * reffrad(ig,cstdustlevel,iaer) )  ) *
    510525     &           pq(ig,cstdustlevel,igcm_stormdust_mass) *
    511526     &           ( pplev(ig,l) - pplev(ig,l+1) ) / g
     527               ! DENSITY SCALED OPACITY :
     528               ! GCM output to be compared with observations
     529               ! => infrared wavelength
     530                 dsords(ig,l) =
     531     &           (  0.75 * QREFir3d(ig,cstdustlevel,iaer) /
     532     &           ( rho_dust * reffrad(ig,cstdustlevel,iaer) )  ) *
     533     &           pq(ig,cstdustlevel,igcm_stormdust_mass)
    512534               ENDDO
    513535             ELSE
    514               DO ig=1,ngrid
     536               DO ig=1,ngrid
     537               ! OPTICAL DEPTH for the computation of tauref,
     538               ! which is to be compared with tauref_scenario
     539               ! => visible wavelength
    515540                 aerosol(ig,l,iaer) =
    516541     &           (  0.75 * QREFvis3d(ig,l,iaer) /
     
    518543     &           pq(ig,l,igcm_stormdust_mass) *
    519544     &           ( pplev(ig,l) - pplev(ig,l+1) ) / g
    520               ENDDO
     545               ! DENSITY SCALED OPACITY :
     546               ! GCM output to be compared with observations
     547               ! => infrared wavelength
     548                 dsords(ig,l) =
     549     &           (  0.75 * QREFir3d(ig,l,iaer) /
     550     &           ( rho_dust * reffrad(ig,l,iaer) )  ) *
     551     &           pq(ig,l,igcm_stormdust_mass)
     552               ENDDO
    521553             ENDIF
    522554          ENDDO
     
    533565        ELSE  ! part of the mesh with concentred dust storm
    534566          DO l=1,nlayer
    535 !             IF (l.LE.cstdustlevel) THEN
    536 !c          Opacity in the first levels is held constant to
    537 !c           avoid unrealistic values due to constant lifting:
    538 !               DO ig=1,ngrid
    539 !                  aerosol(ig,l,iaer) =
    540 !     &           (  0.75 * QREFvis3d(ig,cstdustlevel,iaer) /
    541 !     &           ( rho_dust * reffrad(ig,cstdustlevel,iaer) )  ) *
    542 !     &           pq(ig,cstdustlevel,igcm_topdust_mass) *
    543 !     &           ( pplev(ig,l) - pplev(ig,l+1) ) / g
    544 !               ENDDO
    545 !             ELSE
    546               DO ig=1,ngrid
    547                  aerosol(ig,l,iaer) =
     567             IF (l.LE.cstdustlevel) THEN
     568c          Opacity in the first levels is held constant to
     569c           avoid unrealistic values due to constant lifting:
     570               DO ig=1,ngrid
     571                  aerosol(ig,l,iaer) =
     572     &           (  0.75 * QREFvis3d(ig,cstdustlevel,iaer) /
     573     &           ( rho_dust * reffrad(ig,cstdustlevel,iaer) )  ) *
     574     &           pq(ig,cstdustlevel,igcm_topdust_mass) *
     575     &           ( pplev(ig,l) - pplev(ig,l+1) ) / g
     576               ! DENSITY SCALED OPACITY :
     577               ! GCM output to be compared with observations
     578               ! => infrared wavelength
     579                 dsotop(ig,l) =
     580     &           (  0.75 * QREFir3d(ig,cstdustlevel,iaer) /
     581     &           ( rho_dust * reffrad(ig,cstdustlevel,iaer) )  ) *
     582     &           pq(ig,cstdustlevel,igcm_topdust_mass)
     583               ENDDO
     584             ELSE
     585               DO ig=1,ngrid
     586               ! OPTICAL DEPTH for the computation of tauref,
     587               ! which is to be compared with tauref_scenario
     588               ! => visible wavelength
     589                 aerosol(ig,l,iaer) =
    548590     &           (  0.75 * QREFvis3d(ig,l,iaer) /
    549591     &           ( rho_dust * reffrad(ig,l,iaer) )  ) *
    550592     &           pq(ig,l,igcm_topdust_mass) *
    551593     &           ( pplev(ig,l) - pplev(ig,l+1) ) / g
    552               ENDDO
    553 !             ENDIF
    554 
     594               ! DENSITY SCALED OPACITY :
     595               ! GCM output to be compared with observations
     596               ! => infrared wavelength
     597                 dsotop(ig,l) =
     598     &           (  0.75 * QREFir3d(ig,l,iaer) /
     599     &           ( rho_dust * reffrad(ig,l,iaer) )  ) *
     600     &           pq(ig,l,igcm_topdust_mass)
     601               ENDDO
     602             ENDIF
    555603          ENDDO
    556604        ENDIF
     
    852900#endif
    853901
    854 c -----------------------------------------------------------------
    855 c Density scaled opacity and column opacity output
    856 c -----------------------------------------------------------------
    857           IF (rdstorm) then
    858             DO l=1,nlayer
    859               IF (l.LE.cstdustlevel) THEN
    860                 DO ig=1,ngrid
    861                   dsodust(ig,l)=dsodust(ig,l) +
    862      &                      aerosol(ig,l,iaer_dust_doubleq) * g /
    863      &                      (pplev(ig,l) - pplev(ig,l+1))
    864 
    865                   dsords(ig,l) = dsords(ig,l) +
    866      &              aerosol(ig,l,iaer_stormdust_doubleq)* g/
    867      &              (pplev(ig,l) - pplev(ig,l+1))
    868                 ENDDO
    869               ELSE
    870                 DO ig=1,ngrid
    871                   dsodust(ig,l) =dsodust(ig,l) +
    872      &                      aerosol(ig,l,iaer_dust_doubleq) * g /
    873      &                      (pplev(ig,l) - pplev(ig,l+1))
    874                    dsords(ig,l) = dsords(ig,l) +
    875      &                        aerosol(ig,l,iaer_stormdust_doubleq)* g/
    876      &                        (pplev(ig,l) - pplev(ig,l+1))
    877                 ENDDO
    878               ENDIF
    879             ENDDO
    880           ENDIF
    881902
    882903c -----------------------------------------------------------------
  • trunk/LMDZ.MARS/libf/phymars/callradite_mod.F

    r2199 r2246  
    1010     $     fluxtop_sw,tauref,tau,aerosol,dsodust,tauscaling,
    1111     $     taucloudtes,rdust,rice,nuice,co2ice,rstormdust,rtopdust,
    12      $     totstormfract,clearatm,dsords,alpha_hmons,nohmons,
     12     $     totstormfract,clearatm,dsords,dsotop,alpha_hmons,nohmons,
    1313     $     clearsky,totcloudfrac)
    1414
     
    3535c
    3636c   These calculations are only valid on the part of the atmosphere
    37 c   where Local Thermal Equilibrium (NLTE) is verified. In practice
    38 c   The calculations are only performed for the first "nlaylte"
     37c   where Local Thermal Equilibrium (LTE) is verified. In practice
     38c   the calculations are only performed for the first "nlaylte"
    3939c   parameters (nlaylte is calculated by subroutine "nlthermeq"
    4040c   and stored in module "yomlw_h").
     
    203203      REAL,INTENT(IN) :: totstormfract(ngrid) ! dust storm mesh fraction
    204204      REAL,INTENT(OUT) :: rstormdust(ngrid,nlayer)  ! Storm dust geometric mean radius (m)
    205       REAL dsords(ngrid,nlayer) ! density scaled opacity for rocket dust storm dust
    206 
     205      REAL,INTENT(OUT) :: dsords(ngrid,nlayer) ! density scaled opacity for rocket dust storm dust
     206     
    207207c     entrainment by slope wind
    208208      LOGICAL, INTENT(IN) :: nohmons ! true for background dust
    209209      REAL, INTENT(IN) :: alpha_hmons(ngrid) ! sub-grid scale topography mesh fraction
    210210      REAL,INTENT(OUT) :: rtopdust(ngrid,nlayer)  ! Topdust geometric mean radius (m)
    211 
     211      REAL,INTENT(OUT) :: dsotop(ngrid,nlayer) ! density scaled opacity for topmons dust
     212     
    212213c     sub-grid scale water ice clouds
    213214      LOGICAL,INTENT(IN) :: clearsky
     
    269270
    270271      REAL :: QREFvis3d(ngrid,nlayer,naerkind)
     272      ! QREFvis3d : Extinction efficiency at the VISible reference wavelength
    271273      REAL :: QREFir3d(ngrid,nlayer,naerkind)
     274      ! QREFir3d : Extinction efficiency at the InfraRed reference wavelength
    272275
    273276      REAL :: omegaREFvis3d(ngrid,nlayer,naerkind)
     
    421424     &    pq,tauscaling,tauref,tau,taucloudtes,aerosol,dsodust,reffrad,
    422425     &    QREFvis3d,QREFir3d,omegaREFir3d,
    423      &    totstormfract,clearatm,dsords,
     426     &    totstormfract,clearatm,dsords,dsotop,
    424427     &    alpha_hmons,nohmons,
    425428     &    clearsky,totcloudfrac)
  • trunk/LMDZ.MARS/libf/phymars/physiq_mod.F

    r2226 r2246  
    407407      REAL dsodust(ngrid,nlayer)
    408408      REAL dsords(ngrid,nlayer)
     409      REAL dsotop(ngrid,nlayer)
    409410      REAL wtop(ngrid,nlayer+1) ! vertical velocity topdust tracer
    410411
     
    855856     &     fluxtop_sw,tauref,tau,aerosol,dsodust,tauscaling,
    856857     &     taucloudtes,rdust,rice,nuice,co2ice,rstormdust,rtopdust,
    857      &     totstormfract,clearatm,dsords,alpha_hmons,nohmons,
     858     &     totstormfract,clearatm,dsords,dsotop,alpha_hmons,nohmons,
    858859     &     clearsky,totcloudfrac)
    859860
     
    871872     &              tau,aerosol,dsodust,tauscaling,taucloudtesclf,rdust,
    872873     &              rice,nuice,co2ice,rstormdust,rtopdust,totstormfract,
    873      &              clearatm,dsords,alpha_hmons,nohmons,
     874     &              clearatm,dsords,dsotop,alpha_hmons,nohmons,
    874875     &              clearsky,totcloudfrac)
    875876               clearsky = .false.  ! just in case.
     
    10691070     &                      nohmons,alpha_hmons,
    10701071c               output
    1071      &                      pdqrds,wspeed,dsodust,dsords,
     1072     &                      pdqrds,wspeed,dsodust,dsords,dsotop,
    10721073     &                      tauref)
    10731074                   
     
    11291130     &                zzlay,zdtsw,zdtlw,
    11301131     &                icount,zday,zls,tsurf,igout,aerosol,
    1131      &                tauscaling,totstormfract,clearatm,dsords,
     1132     &                tauscaling,totstormfract,clearatm,
    11321133     &                clearsky,totcloudfrac,
    11331134     &                nohmons,hsummit,
    1134      &                pdqtop,wtop,dsodust,
     1135     &                pdqtop,wtop,dsodust,dsords,dsotop,
    11351136     &                tauref)
    11361137     
     
    29242925     &                        'part/kg',3,ndust)
    29252926             call WRITEDIAGFI(ngrid,'dsodust',
    2926      &                       'density scaled optical depth in the IR',
    2927      &                       'm2.kg-1',3,dsodust)
     2927     &                        'density scaled optical depth in the IR',
     2928     &                        'm2.kg-1',3,dsodust)
    29282929             call WRITEDIAGFI(ngrid,'dso',
    2929      &                       'density scaled optical depth in the IR',
    2930      &                       'm2.kg-1',3,dsodust+dsords)
    2931            else
     2930     &                        'density scaled optical depth in the IR',
     2931     &                        'm2.kg-1',3,dsodust+dsords+dsotop)
     2932             
     2933           else ! (doubleq=.false.)
    29322934             do iq=1,dustbin
    29332935               write(str2(1:2),'(i2.2)') iq
     
    29902992           endif ! (rdstorm)
    29912993
     2994           if (slpwind) then
     2995             call WRITEDIAGFI(ngrid,'dsotop',
     2996     &                       'density scaled opacity of topdust',
     2997     &                       'm2.kg-1',3,dsotop)
     2998           endif ! (slpwind)
     2999           
    29923000           if (scavenging) then
    29933001             call WRITEDIAGFI(ngrid,'ccnq','CCN mass mr',
  • trunk/LMDZ.MARS/libf/phymars/rocketduststorm_mod.F90

    r2226 r2246  
    3030                                 nohmons,alpha_hmons,                  &
    3131!             output
    32                                  pdqrds,wrad,dsodust,dsords,           &
     32                                 pdqrds,wrad,dsodust,dsords,dsotop,    &
    3333                                 tauref)
    3434
     
    9494      REAL, INTENT(OUT) :: dsodust(ngrid,nlayer) ! density scaled opacity of env. dust
    9595      REAL, INTENT(OUT) :: dsords(ngrid,nlayer) ! density scaled opacity of storm dust
     96      REAL, INTENT(OUT) :: dsotop(ngrid,nlayer) ! density scaled opacity of topmons dust
    9697      REAL, INTENT(OUT) :: tauref(ngrid)
    9798
     
    247248                 fluxtop_sw1,tauref,tau,aerosol,dsodust,tauscaling,       &
    248249                 taucloudtes,rdust,rice,nuice,co2ice,rstormdust,rtopdust, &
    249                  totstormfract,clearatm,dsords,alpha_hmons,nohmons,       &
     250                 totstormfract,clearatm,dsords,dsotop,alpha_hmons,nohmons,&
    250251                 clearsky,totcloudfrac)
    251252
  • trunk/LMDZ.MARS/libf/phymars/topmons_mod.F90

    r2226 r2246  
    2626                                 tauscaling,                           &
    2727!             input sub-grid scale rocket dust storm
    28                                  totstormfract,clearatm,dsords,        &
     28                                 totstormfract,clearatm,               &
    2929!             input sub-grid scale cloud
    3030                                 clearsky,totcloudfrac,                &
     
    3232                                 nohmons,hsummit,                      &
    3333!             output
    34                                  pdqtop,wfin,dsodust,                   &
     34                                 pdqtop,wfin,dsodust,dsords,dsotop,    &
    3535                                 tauref)
    3636
     
    9898      REAL, INTENT(OUT) :: aerosol(ngrid,nlayer,naerkind)
    9999      REAL, INTENT(OUT) :: dsords(ngrid,nlayer)
     100      REAL, INTENT(OUT) :: dsotop(ngrid,nlayer)
    100101      REAL, INTENT(OUT) :: tauref(ngrid)
    101102
     
    211212      dsodust(:,:)=0.
    212213      dsords(:,:)=0.
     214      dsotop(:,:)=0.
    213215      pdqtop(:,:,:) = 0.
    214216      dqvl_topdust_mass(:,:)=0.
     
    274276                 fluxtop_sw1,tauref,tau,aerosol,dsodust,tauscaling,    &
    275277                 taucloudtes,rdust,rice,nuice,co2ice,rstormdust,rtopdust, &
    276                  totstormfract,clearatm,dsords,alpha_hmons,nohmons,    &
     278                 totstormfract,clearatm,dsords,dsotop,alpha_hmons,nohmons,&
    277279                 clearsky,totcloudfrac)
    278280       ! **********************************************************************
Note: See TracChangeset for help on using the changeset viewer.