Changeset 1617


Ignore:
Timestamp:
Oct 10, 2016, 11:26:09 AM (8 years ago)
Author:
jaudouard
Message:

Added modifications for CO2 clouds scheme in physiq_mod.F and added several routines and variables for CO2 microphysics. October 2016 Joachim Audouard

Location:
trunk/LMDZ.MARS
Files:
5 added
9 edited
1 copied

Legend:

Unmodified
Added
Removed
  • trunk/LMDZ.MARS/README

    r1594 r1617  
    23282328- Further cleanup to harmonize with LMDZ.COMMON turn "idissip" into
    23292329  "dissip_period".
     2330
     2331== 10/10/16 == J. Audouard
     2332- Added CO2 clouds : if co2clouds is set to .true., physiq_mod will call co2cloud.F which contains a co2 clouds microphysics scheme (improvedCO2clouds.F). 3 tracers are needed: co2_ice, ccnco2_mass and ccnco2_number.
     2333- Routines added:
     2334 co2cloud.F (called by physiq_mod.F, contains the microtimestep)
     2335 co2sat.F
     2336 improvedCO2clouds.F (called inside the microtimestep, contains the microphysics)
     2337 massflowrateCO2.F (CO2 ice growth rate)
     2338 nucleaCO2.F (CO2 ice nucleation)
     2339 
     2340- The following routines/files have been modified to take co2 clouds into account :
     2341 callkeys.h (added logicals co2clouds and microphysco2)
     2342 callsedim.F (CO2 clouds tracers are ignored : their sedimentation is done in the microtimestep inside co2cloud.F)
     2343 conf_phys.F (added CO2 clouds logicals and some variables needed by the CO2 microphysics)
     2344 initracer.F (added CO2 clouds tracers)
     2345 microphys.H (added some values needed by the CO2 microphysic scheme)
     2346 physiq_mod.F (now calls co2cloud.F if co2cloud is set to .true.)
     2347 tracer_mod.F90 (added some variables needed by CO2 microphysics)
     2348 updaterad.F90 (added a routine for CO2 clouds)
  • trunk/LMDZ.MARS/libf/phymars/callkeys.h

    r1467 r1617  
    1313     &   ,lifting,freedust,callddevil,scavenging,sedimentation          &
    1414     &   ,activice,water,tifeedback,microphys,supersat,caps,photochem   &
    15      &   ,calltherm,callrichsl,callslope,tituscap,callyamada4
     15     &   ,calltherm,callrichsl,callslope,tituscap,callyamada4,co2clouds,&
     16     &   microphysco2
    1617     
    1718      COMMON/callkeys_i/iradia,iaervar,iddist,ilwd,ilwb,ilwn,ncouche    &
     
    5758      logical active,doubleq,submicron,lifting,callddevil,scavenging
    5859      logical sedimentation
    59       logical water,activice,tifeedback,microphys,supersat,caps
     60      logical activice,tifeedback,supersat,caps
     61      logical co2clouds
     62      logical water
     63      logical microphys
    6064      logical photochem
     65      logical microphysco2
    6166      integer nltemodel
    6267      integer nircorr
  • trunk/LMDZ.MARS/libf/phymars/callsedim.F

    r1266 r1617  
    1010     &                      rho_dust, rho_q, radius, varian,
    1111     &                      igcm_ccn_mass, igcm_ccn_number,
    12      &                      igcm_h2o_ice, nuice_sed, nuice_ref
     12     &                      igcm_h2o_ice, nuice_sed, nuice_ref,
     13     &                      igcm_ccnco2_mass, igcm_ccnco2_number,
     14     &                      igcm_co2_ice
    1315      USE comcstfi_h
    1416      IMPLICIT NONE
     
    2325c        technique in order to have only one call to callsedim in
    2426c        physiq.F.
     27c
     28c      Modified by J. Audouard 09/16: Now includes the co2clouds case
     29c        If the co2 microphysics is on, then co2 theice & ccn tracers
     30c        are being sedimented in the microtimestep (co2cloud.F), not
     31c        in this routine.
    2532c
    2633c=======================================================================
     
    119126      INTEGER,SAVE :: iccn_number ! index of tracer containing CCN number
    120127                                  !   mix. ratio
     128      INTEGER,SAVE :: iccnco2_number ! index of tracer containing CCN number
     129      INTEGER,SAVE :: iccnco2_mass ! index of tracer containing CCN number
     130      INTEGER,SAVE :: ico2_ice ! index of tracer containing CCN number
     131
    121132
    122133      LOGICAL,SAVE :: firstcall=.true.
     
    194205        ENDIF !of if (microphys)
    195206
     207        IF (microphysco2) THEN
     208          iccnco2_mass=0
     209          iccnco2_number=0
     210          ico2_ice=0
     211          do iq=1,nq
     212            if (noms(iq).eq."ccnco2_mass") then
     213              iccnco2_mass=iq
     214              write(*,*)"callsedim: iccnco2_mass=",iccnco2_mass
     215            endif
     216            if (noms(iq).eq."co2_ice") then
     217              ico2_ice=iq
     218              write(*,*)"callsedim: ico2_ice=",ico2_ice
     219            endif
     220            if (noms(iq).eq."ccnco2_number") then
     221              iccnco2_number=iq
     222              write(*,*)"callsedim: iccnco2_number=",iccnco2_number
     223            endif
     224          enddo
     225          ! check that we did find the tracers
     226          if ((iccnco2_mass.eq.0).or.(iccnco2_number.eq.0)) then
     227            write(*,*) 'callsedim: error! could not identify'
     228            write(*,*) ' tracers for ccn co2 mass and number mixing'
     229            write(*,*) ' ratio and microphysco2 is activated!'
     230            stop
     231          endif
     232       ENDIF                    !of if (microphysco2)
     233
     234
    196235        IF (water) THEN
    197236         write(*,*) "correction for the shape of the ice particles ?"
     
    252291c =================================================================
    253292      do iq=1,nq
    254         if(radius(iq).gt.1.e-9) then   ! no sedim for gaz
     293        if(radius(iq).gt.1.e-9 .and.(iq.ne.ico2_ice) .and.
     294     &        (iq .ne. iccnco2_mass) .and. (iq .ne.
     295     &        iccnco2_number)) then   ! no sedim for gaz or CO2 clouds  (done in microtimestep)
    255296
    256297c -----------------------------------------------------------------
  • trunk/LMDZ.MARS/libf/phymars/conf_phys.F

    r1579 r1617  
    3535! to use  'getin'
    3636      USE ioipsl_getincom, only : getin
    37       use tracer_mod, only : nuice_sed, ccn_factor
     37      use tracer_mod, only : nuice_sed, ccn_factor, nuiceco2_sed,
     38     &                       nuice_ref,nuiceco2_ref
    3839      use surfdat_h, only: albedo_h2o_ice, inert_h2o_ice,
    3940     &                     frost_albedo_threshold
     
    5354 
    5455      CHARACTER ch1*12
    55 
    5656#ifndef MESOSCALE
    5757      ! read in some parameters from "run.def" for physics,
     
    436436         write(*,*) " water = ",water
    437437
     438!CO2 clouds scheme?
     439         write(*,*) "Compute CO2 clouds ?"
     440         co2clouds=.false. ! default value
     441         call getin("co2clouds",co2clouds)
     442         write(*,*) " co2clouds = ",co2clouds
    438443! thermal inertia feedback
    439444         write(*,*) "Activate the thermal inertia feedback ?"
     
    467472         
    468473! water ice clouds effective variance distribution for sedimentaion       
    469         write(*,*) "effective variance for water ice clouds ?"
     474        write(*,*) "Sed effective variance for water ice clouds ?"
    470475        nuice_sed=0.45
    471476        call getin("nuice_sed",nuice_sed)
    472477        write(*,*) "water_param nueff Sedimentation:", nuice_sed
    473          
     478             
     479        write(*,*) "Sed effective variance for CO2 clouds ?"
     480        nuiceco2_sed=0.45
     481        call getin("nuiceco2_sed",nuiceco2_sed)
     482        write(*,*) "CO2 nueff Sedimentation:", nuiceco2_sed
     483 
     484        write(*,*) "REF effective variance for CO2 clouds ?"
     485        nuiceco2_ref=0.45
     486        call getin("nuiceco2_ref",nuiceco2_ref)
     487        write(*,*) "CO2 nueff Sedimentation:", nuiceco2_ref
     488
     489        write(*,*) "REF effective variance for water clouds ?"
     490        nuice_ref=0.45
     491        call getin("nuice_ref",nuice_ref)
     492        write(*,*) "CO2 nueff Sedimentation:", nuice_ref
     493
     494
    474495! ccn factor if no scavenging         
    475         write(*,*) "water param CCN reduc. factor ?", ccn_factor
     496        write(*,*) "water param CCN reduc. factor ?"
    476497        ccn_factor = 4.5
    477498        call getin("ccn_factor",ccn_factor)
     
    486507         write(*,*)" microphys = ",microphys
    487508
     509         write(*,*)"Microphysical scheme for CO2 clouds?"
     510         microphysco2=.false. ! default value
     511         call getin("microphysco2",microphysco2)
     512         write(*,*)" microphysco2 = ",microphysco2
    488513! supersat
    489514         write(*,*)"Allow super-saturation of water vapor?"
    490          supersat=.true. ! default value
     515         supersat=.false. ! default value
    491516         call getin("supersat",supersat)
    492517         write(*,*)"supersat = ",supersat
     
    522547         endif
    523548
    524          if ((scavenging.and..not.microphys).or.
    525      &       (scavenging.and.(dustbin.lt.1))) then
     549         if ((scavenging.and..not.microphys.and..not. microphysco2).or.
     550     &       (scavenging.and.(dustbin.lt.1)))then
    526551             print*,'if scavenging is used, then microphys'
    527552             print*,'must be used!'
  • trunk/LMDZ.MARS/libf/phymars/initracer.F

    r1455 r1617  
    6969!                 or new convention (full tracer names)
    7070      ! check if tracers have 'old' names
     71
    7172      count=0
    7273      do iq=1,nq
     
    8889      do iq=1,nq
    8990        noms(iq)=tname(iq)
     91        write(*,*) "initracer names : ", noms(iq)
    9092      enddo
    9193#endif
     
    98100      ! 0. initialize tracer indexes to zero:
    99101      igcm_dustbin(1:nq)=0
    100 
     102      igcm_co2_ice=0
     103      igcm_ccnco2_mass=0
     104      igcm_ccnco2_number=0
    101105      igcm_dust_mass=0
    102106      igcm_dust_number=0
     
    335339          count=count+1
    336340        endif
     341        if (noms(iq).eq."co2_ice") then
     342          igcm_co2_ice=iq
     343          mmol(igcm_co2_ice)=44.
     344          count=count+1
     345        endif
    337346        if (noms(iq).eq."h2o_ice") then
    338347          igcm_h2o_ice=iq
     
    346355          count=count+1
    347356        endif
    348 
    349       enddo ! of do iq=1,nq
    350      
     357        if (microphysco2) then
     358           if (noms(iq).eq."ccnco2_mass") then
     359              igcm_ccnco2_mass=iq
     360              count=count+1
     361           endif
     362           if (noms(iq).eq."ccnco2_number") then
     363              igcm_ccnco2_number=iq
     364              count=count+1
     365           endif
     366        endif
     367      enddo                     ! of do iq=1,nq
     368     
    351369      ! check that we identified all tracers:
    352370      if (count.ne.nq) then
     
    392410      rho_dust=2500.  ! Mars dust density (kg.m-3)
    393411      rho_ice=920.    ! Water ice density (kg.m-3)
     412      rho_ice_co2=1500. !dry ice density (kg.m-3), varies with T from 0.98 to 1.5 see Satorre et al., PSS 2008
    394413      nuice_ref=0.1   ! Effective variance nueff of the
    395414                      ! water-ice size distribution
     
    528547
    529548      end if  ! (water)
    530 
     549     
     550! Initialisation for CO2 clouds
     551      if (co2clouds ) then
     552        radius(igcm_ccnco2_mass) = radius(igcm_dust_mass)
     553        alpha_lift(igcm_ccnco2_mass) = 1e-30
     554        alpha_devil(igcm_ccnco2_mass) = 1e-30
     555        rho_q(igcm_ccnco2_mass) = rho_dust
     556        radius(igcm_ccnco2_number) = radius(igcm_ccnco2_mass)
     557        alpha_lift(igcm_ccnco2_number) = alpha_lift(igcm_ccnco2_mass)
     558        alpha_devil(igcm_ccnco2_number) = alpha_devil(igcm_ccnco2_mass)
     559        rho_q(igcm_ccnco2_number) = rho_q(igcm_ccnco2_mass)
     560     
     561        radius(igcm_co2)=0.
     562        alpha_lift(igcm_co2) =0.
     563        alpha_devil(igcm_co2)=0.
     564        radius(igcm_co2_ice)=1.e-6
     565        rho_q(igcm_co2_ice)=rho_ice_co2
     566        alpha_lift(igcm_co2_ice) =0.
     567        alpha_devil(igcm_co2_ice)=0.
     568
     569      endif
     570     
    531571c     Output for records:
    532572c     ~~~~~~~~~~~~~~~~~~
     
    597637       endif
    598638
     639       if (co2clouds) then
     640          !verify that we have co2_ice and co2 tracers
     641          if (igcm_co2 .eq. 0) then
     642             write(*,*) "initracer: error !!"
     643             write(*,*) "  cannot use co2 clouds option without ",
     644     &            "a co2 tracer !"
     645          stop
     646          endif
     647          if (igcm_co2_ice .eq. 0) then
     648             write(*,*) "initracer: error !!"
     649             write(*,*) "  cannot use co2 clouds option without ",
     650     &            "a co2_ice tracer !"
     651             stop
     652          endif
     653       endif
     654       
    599655       if (callnlte) then ! NLTE requirements
    600656         if (nltemodel.ge.1) then
     
    625681       if (scavenging) then
    626682       ! verify that we indeed have ccn_mass and ccn_number tracers
    627          if (igcm_ccn_mass.eq.0) then
     683         if (igcm_ccn_mass.eq.0 .and. igcm_ccnco2_mass.eq.0) then
    628684           write(*,*) "initracer: error !!"
    629685           write(*,*) "  cannot use scavenging option without ",
    630      &                "a ccn_mass tracer !"
     686     &                "a ccn_mass or ccnco2_mass tracer !"
    631687           stop
    632688         endif
    633          if (igcm_ccn_number.eq.0) then
     689         if (igcm_ccn_number.eq.0 .and. igcm_ccnco2_number.eq.0 ) then
    634690           write(*,*) "initracer: error !!"
    635691           write(*,*) "  cannot use scavenging option without ",
    636      &                "a ccn_number tracer !"
     692     &                "a ccn_number or ccnco2_number tracer !"
    637693           stop
    638694         endif
  • trunk/LMDZ.MARS/libf/phymars/microphys.h

    r520 r1617  
    1919!     Molecular weight of CO2 (kg.mol-1)
    2020      DOUBLE PRECISION, PARAMETER :: mco2 = 44.d-3
     21!     Molecular weight of N2 (kg.mol-1)
     22      DOUBLE PRECISION, PARAMETER :: mn2 = 28.01d-3
    2123!     Effective CO2 gas molecular radius (m)
    2224      DOUBLE PRECISION, PARAMETER :: molco2 = 2.2d-10
     
    4850
    4951
     52
     53
     54!CO2 part
     55!      number of bins for nucleation
     56      INTEGER, PARAMETER :: nbinco2_cld=40
     57!     Surface tension of ice/vapor (J.m-2)
     58      DOUBLE PRECISION, PARAMETER :: sigco2 = 0.08
     59!     Activation energy for desorption of
     60!       water on a dust-like substrate
     61!       (J/molecule)
     62      DOUBLE PRECISION, PARAMETER :: desorpco2 = 3.25e-20
     63!     Jump frequency of a co2 molecule (s-1)
     64      DOUBLE PRECISION, PARAMETER :: nusco2 =  2.9e+12
     65!     Estimated activation energy for
     66!       surface diffusion of co2 molecules
     67!       (J/molecule)
     68      DOUBLE PRECISION, PARAMETER :: surfdifco2 = desorpco2 / 10.
     69!     Weight of a co2 molecule (kg)
     70      DOUBLE PRECISION, PARAMETER :: m0co2 = mco2 / nav
     71!     Contact parameter ( m=cos(theta) )
     72!       (initialized in improvedCO2clouds.F)
     73       REAL, parameter :: mtetaco2 = 0.952
     74!     Volume of a co2 molecule (m3)
     75       DOUBLE PRECISION :: vo1co2
     76!     Radius used by the microphysical scheme (m)
     77      DOUBLE PRECISION :: rad_cldco2(nbinco2_cld)
     78       REAL, parameter :: threshJA = 1.0
     79!     COMMON/microphys/vo1co2,rad_cldco2
     80
    5081! NB: to keep commons aligned:
    5182!     split them in groups (reals, integers and characters)
    5283
    53       COMMON/microphys/rad_cld,vo1
    54      
    55       COMMON/microphys_2/mteta
     84      COMMON/microphys/rad_cld,vo1,rad_cldco2,vo1co2
     85                  COMMON/microphys_2/mteta
    5686     
    5787!     EXAMPLE:
  • trunk/LMDZ.MARS/libf/phymars/physiq_mod.F

    r1590 r1617  
    1414     $            ,pdu,pdv,pdt,pdq,pdpsrf)
    1515
    16       use tracer_mod, only: noms, mmol, igcm_co2, igcm_n2,
     16      use tracer_mod, only: noms, mmol, igcm_co2, igcm_n2, igcm_co2_ice,
    1717     &                      igcm_co, igcm_o, igcm_h2o_vap, igcm_h2o_ice,
    1818     &                      igcm_ccn_mass, igcm_ccn_number,
     19     &                      igcm_ccnco2_mass, igcm_ccnco2_number,
     20     &                      rho_ice_co2,nuiceco2_sed,nuiceco2_ref,
    1921     &                      igcm_dust_mass, igcm_dust_number, igcm_h2o2,
    2022     &                      nuice_ref, rho_ice, rho_dust, ref_r0
     
    8284c      6. Condensation and sublimation of carbon dioxide.
    8385c      7.  TRACERS :
    84 c       7a. water and water ice
     86c       7a. water, water ice, co2 ice (clouds)
    8587c       7b. call for photochemistry when tracers are chemical species
    8688c       7c. other scheme for tracer (dust) transport (lifting, sedimentation)
     
    108110c           Mesoscale lines: Aymeric Spiga (2007 - 2011) -- check MESOSCALE flags
    109111c           jul 2011 malv+fgg: Modified calls to NIR heating routine and 15 um cooling parameterization
    110 c           
     112c
     113c           10/16 J. Audouard: modifications for CO2 clouds scheme
     114
    111115c   arguments:
    112116c   ----------
     
    208212                                      ! thermal inertia (J.s-1/2.m-2.K-1)
    209213                                      ! (used only when tifeedback=.true.)
     214c     Variables used by the CO2 clouds microphysical scheme:
     215      REAL riceco2(ngrid,nlayer)   ! co2 ice geometric mean radius (m)
     216      real rsedcloudco2(ngrid,nlayer) !CO2 Cloud sedimentation radius
     217      real rhocloudco2(ngrid,nlayer) !co2 Cloud density (kg.m-3)
     218      real zdqssed_co2(ngrid)  ! CO2 flux at the surface  (kg.m-2.s-1)
    210219c     Variables used by the photochemistry
    211220      logical :: asis             ! true  : adaptative semi-implicit symmetric (asis) chemical solver
     
    255264      REAL zdtnlte(ngrid,nlayer)   ! (K/s)
    256265      REAL zdtsurf(ngrid)            ! (K/s)
    257       REAL zdtcloud(ngrid,nlayer)
     266      REAL zdtcloud(ngrid,nlayer),zdtcloudco2(ngrid,nlayer)
    258267      REAL zdvdif(ngrid,nlayer),zdudif(ngrid,nlayer)  ! (m.s-2)
    259268      REAL zdhdif(ngrid,nlayer), zdtsdif(ngrid)         ! (K/s)
     
    270279      REAL zdqadj(ngrid,nlayer,nq)
    271280      REAL zdqc(ngrid,nlayer,nq)
    272       REAL zdqcloud(ngrid,nlayer,nq)
     281      REAL zdqcloud(ngrid,nlayer,nq),zdqcloudco2(ngrid,nlayer,nq)
    273282      REAL zdqscloud(ngrid,nq)
    274283      REAL zdqchim(ngrid,nlayer,nq)
     
    320329      REAL mtot(ngrid)          ! Total mass of water vapor (kg/m2)
    321330      REAL icetot(ngrid)        ! Total mass of water ice (kg/m2)
     331      REAL mtotco2(ngrid)       ! Total mass of co2 vapor (kg/m2)
     332      REAL icetotco2(ngrid)        ! Total mass of co2 ice (kg/m2)
    322333      REAL Nccntot(ngrid)       ! Total number of ccn (nbr/m2)
    323334      REAL Mccntot(ngrid)       ! Total mass of ccn (kg/m2)
    324335      REAL rave(ngrid)          ! Mean water ice effective radius (m)
     336      REAL raveco2(ngrid)       ! Mean co2 ice effective radius (m)
    325337      REAL opTES(ngrid,nlayer)  ! abs optical depth at 825 cm-1
    326338      REAL tauTES(ngrid)        ! column optical depth at 825 cm-1
     
    342354      REAL satu(ngrid,nlayer)  ! satu ratio for output
    343355      REAL zqsat(ngrid,nlayer) ! saturation
    344 
     356      REAL satuco2(ngrid,nlayer)  ! co2 satu ratio for output
     357      REAL zqsatco2(ngrid,nlayer) ! saturation co2
    345358      REAL,SAVE :: time_phys
    346359
     
    531544
    532545      zday=pday+ptime ! compute time, in sols (and fraction thereof)
    533 
     546   
    534547c     Compute Solar Longitude (Ls) :
    535548c     ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
     
    11381151         END IF  ! of IF (water)
    11391152
     1153c   6a bis. CO2 clouds (CL & JA)
     1154
     1155c        ---------------------------------------
     1156c        CO2 ice cloud condensation in the atmosphere
     1157c        ----------------------------------------
     1158
     1159         
     1160         IF (co2clouds) THEN
     1161           
     1162            call co2cloud(ngrid,nlayer,ptimestep,
     1163     &           zplev,zplay,pdpsrf,zzlay,pt,pdt,
     1164     &           pq,pdq,zdqcloudco2,zdtcloudco2,
     1165     &           nq,tau,tauscaling,rdust,rice,riceco2,nuice,
     1166     &           rsedcloudco2,rhocloudco2,zzlev,zdqssed_co2)
     1167           
     1168           
     1169            call WRITEdiagfi(ngrid,"rhocloudco2","rho cloud co2","kk",1,
     1170     &           rhocloudco2)
     1171           
     1172
     1173c Temperature variation due to latent heat release
     1174            if (activice) then  !Maybe create activice_co2 ?
     1175               pdt(1:ngrid,1:nlayer) =
     1176     &              pdt(1:ngrid,1:nlayer) +
     1177     &              zdtcloudco2(1:ngrid,1:nlayer)
     1178            endif
     1179           
     1180
     1181! increment dust and ccn masses and numbers
     1182! We need to check that we have Nccn & Ndust > 0
     1183! This is due to single precision rounding problems
     1184           if (microphysco2) then
     1185             
     1186              pdq(1:ngrid,1:nlayer,igcm_co2) =
     1187     &             pdq(1:ngrid,1:nlayer,igcm_co2) +
     1188     &             zdqcloudco2(1:ngrid,1:nlayer,igcm_co2)
     1189              pdq(1:ngrid,1:nlayer,igcm_co2_ice) =
     1190     &             pdq(1:ngrid,1:nlayer,igcm_co2_ice) +
     1191     &             zdqcloudco2(1:ngrid,1:nlayer,igcm_co2_ice)
     1192              pdq(1:ngrid,1:nlayer,igcm_ccnco2_mass) =
     1193     &             pdq(1:ngrid,1:nlayer,igcm_ccnco2_mass) +
     1194     &             zdqcloudco2(1:ngrid,1:nlayer,igcm_ccnco2_mass)
     1195             pdq(1:ngrid,1:nlayer,igcm_ccnco2_number) =
     1196     &             pdq(1:ngrid,1:nlayer,igcm_ccnco2_number) +
     1197     &             zdqcloudco2(1:ngrid,1:nlayer,igcm_ccnco2_number)
     1198c Negative values?
     1199             where (pq(:,:,igcm_ccnco2_mass) +
     1200     &            ptimestep*pdq(:,:,igcm_ccnco2_mass) < 0.)
     1201             pdq(:,:,igcm_ccnco2_mass) =
     1202     &            - pq(:,:,igcm_ccnco2_mass)/ptimestep + 1.e-30
     1203             pdq(:,:,igcm_ccnco2_number) =
     1204     &            - pq(:,:,igcm_ccnco2_number)/ptimestep + 1.e-30
     1205          end where
     1206              where (pq(:,:,igcm_ccnco2_number) +
     1207     &             ptimestep*pdq(:,:,igcm_ccnco2_number) < 0.)
     1208              pdq(:,:,igcm_ccnco2_mass) =
     1209     &             - pq(:,:,igcm_ccnco2_mass)/ptimestep + 1.e-30
     1210              pdq(:,:,igcm_ccnco2_number) =
     1211     &             - pq(:,:,igcm_ccnco2_number)/ptimestep + 1.e-30
     1212           end where
     1213       endif !(of if micropĥysco2)
     1214
     1215! increment dust tracers tendancies
     1216       if (scavenging) then
     1217          pdq(1:ngrid,1:nlayer,igcm_dust_mass) =
     1218     &         pdq(1:ngrid,1:nlayer,igcm_dust_mass) +
     1219     &         zdqcloudco2(1:ngrid,1:nlayer,igcm_dust_mass)         
     1220          pdq(1:ngrid,1:nlayer,igcm_dust_number) =
     1221     &         pdq(1:ngrid,1:nlayer,igcm_dust_number) +
     1222     &         zdqcloudco2(1:ngrid,1:nlayer,igcm_dust_number)
     1223c     Negative values?
     1224          where (pq(:,:,igcm_dust_mass) +
     1225     &         ptimestep*pdq(:,:,igcm_dust_mass) < 0.)
     1226          pdq(:,:,igcm_dust_mass) =
     1227     &         - pq(:,:,igcm_dust_mass)/ptimestep + 1.e-30
     1228          pdq(:,:,igcm_dust_number) =
     1229     &         - pq(:,:,igcm_dust_number)/ptimestep + 1.e-30
     1230       end where
     1231       where (pq(:,:,igcm_dust_number) +
     1232     &      ptimestep*pdq(:,:,igcm_dust_number) < 0.)
     1233       pdq(:,:,igcm_dust_mass) =
     1234     &      - pq(:,:,igcm_dust_mass)/ptimestep + 1.e-30
     1235       pdq(:,:,igcm_dust_number) =
     1236     &      - pq(:,:,igcm_dust_number)/ptimestep + 1.e-30
     1237      end where
     1238      endif                     ! of if scavenging
     1239      END IF                    ! of IF (co2clouds)
     1240
     1241
    11401242c   6b. Aerosol particles
    11411243c     -------------------
     
    11721274           zdqssed(1:ngrid,1:nq)=0
    11731275
     1276cSedimentation for co2 clouds tracers are inside co2cloud microtimestep
     1277cZdqssed isn't
    11741278           call callsedim(ngrid,nlayer, ptimestep,
    11751279     &                zplev,zzlev, zzlay, pt, pdt, rdust, rice,
     
    11771281     &                pq, pdq, zdqsed, zdqssed,nq,
    11781282     &                tau,tauscaling)
     1283   !Flux at the surface of co2 ice computed in co2cloud microtimestep
     1284           DO ig=1,ngrid
     1285              zdqssed(ig,igcm_co2_ice)=zdqssed_co2(ig)
     1286           enddo
    11791287
    11801288           DO iq=1, nq
     
    17391847
    17401848           endif ! of if (water)
     1849
     1850
     1851
     1852           if (co2clouds) then
     1853              mtotco2(:)=0
     1854              icetotco2(:)=0
     1855              raveco2(:)=0
     1856              do ig=1,ngrid
     1857                 do l=1,nlayer
     1858                    mtotco2(ig) = mtotco2(ig) +
     1859     &                   zq(ig,l,igcm_co2) *
     1860     &                   (zplev(ig,l) - zplev(ig,l+1)) / g
     1861                    icetotco2(ig) = icetotco2(ig) +
     1862     &                   zq(ig,l,igcm_co2_ice) *
     1863     &                    (zplev(ig,l) - zplev(ig,l+1)) / g
     1864
     1865c      Computing abs optical depth at 825 cm-1 in each   ! for now commented for CO2 - listo  layer to simulate NEW TES retrieval
     1866                    Qabsice = min( max(0.4e6*riceco2(ig,l)*
     1867     &                   (1.+nuiceco2_ref)-0.05 ,0.),1.2)
     1868c                    opTESco2(ig,l)= 0.75 * Qabsice *
     1869c     &                   zq(ig,l,igcm_co2_ice) *
     1870c     &                   (zplev(ig,l) - zplev(ig,l+1)) / g
     1871c     &                   / (rho_ice_co2 * riceco2(ig,l)
     1872c     &                   * (1.+nuiceco2_ref))
     1873c                    tauTESco2(ig)=tauTESco2(ig)+ opTESco2(ig,l)
     1874                 enddo
     1875              enddo
     1876              call co2sat(ngrid*nlayer,zt,zplay,zqsatco2)
     1877              do ig=1,ngrid
     1878                 do l=1,nlayer
     1879                    satuco2(ig,l) = zq(ig,l,igcm_co2)*
     1880     &                   (mmean(ig,l)/44.01)*zplay(ig,l)/zqsatco2(ig,l)
     1881                 enddo
     1882              enddo
     1883
     1884              if (scavenging) then
     1885                 Nccntot(:)= 0
     1886                 Mccntot(:)= 0
     1887                 raveco2(:)=0
     1888                 icetotco2(:)=0
     1889                 do ig=1,ngrid
     1890                    do l=1,nlayer
     1891                       icetotco2(ig) = icetotco2(ig) +
     1892     &                   zq(ig,l,igcm_co2_ice) *
     1893     &                    (zplev(ig,l) - zplev(ig,l+1)) / g
     1894                       Nccntot(ig) = Nccntot(ig) +
     1895     &                      zq(ig,l,igcm_ccnco2_number)*tauscaling(ig)
     1896     &                      *(zplev(ig,l) - zplev(ig,l+1)) / g
     1897                       Mccntot(ig) = Mccntot(ig) +
     1898     &                      zq(ig,l,igcm_ccnco2_mass)*tauscaling(ig)
     1899     &                      *(zplev(ig,l) - zplev(ig,l+1)) / g
     1900cccc  Column integrated effective ice radius
     1901cccc is weighted by total ice surface area (BETTER than total ice mass)
     1902                       raveco2(ig) = raveco2(ig) +
     1903     &                      tauscaling(ig) *
     1904     &                      zq(ig,l,igcm_ccnco2_number) *
     1905     &                      (zplev(ig,l) - zplev(ig,l+1)) / g *
     1906     &                      riceco2(ig,l) * riceco2(ig,l)*
     1907     &                      (1.+nuiceco2_ref)
     1908                    enddo
     1909                    raveco2(ig)=(icetotco2(ig)/rho_ice_co2+Mccntot(ig)/
     1910     &                   rho_dust)*0.75
     1911     &                   /max(pi*raveco2(ig),1.e-30) ! surface weight
     1912                    if (icetotco2(ig)*1e3.lt.0.01) raveco2(ig)=0.
     1913                 enddo
     1914              else              ! of if (scavenging)
     1915                 raveco2(:)=0
     1916                 do ig=1,ngrid
     1917                    do l=1,nlayer
     1918                       raveco2(ig) = raveco2(ig) +
     1919     &                      zq(ig,l,igcm_co2_ice) *
     1920     &                      (zplev(ig,l) - zplev(ig,l+1)) / g *
     1921     &                      riceco2(ig,l) * (1.+nuiceco2_ref)
     1922                    enddo
     1923                    raveco2(ig) = max(raveco2(ig) /
     1924     &                   max(icetotco2(ig),1.e-30),1.e-30) ! mass weight
     1925                 enddo
     1926              endif   ! of if (scavenging)
     1927           endif    ! of if (co2clouds)
    17411928         endif ! of if (tracer)
    17421929
     
    19112098     $               noms(iq) .ne. "dust_number" .and.
    19122099     $               noms(iq) .ne. "ccn_mass" .and.
    1913      $               noms(iq) .ne. "ccn_number") then
     2100     $               noms(iq) .ne. "ccn_number" .and.
     2101     $               noms(iq) .ne. "ccnco2_mass" .and.
     2102     $               noms(iq) .ne. "ccnco2_number") then
    19142103
    19152104!                   volume mixing ratio
     
    20772266         call WRITEDIAGFI(ngrid,"fluxtop_sw","fluxtop_sw","W.m-2",2,
    20782267     &                  fluxtop_sw_tot)
    2079          call WRITEDIAGFI(ngrid,"temp","temperature","K",3,zt)
     2268c         call WRITEDIAGFI(ngrid,"temp","temperature","K",3,zt)
    20802269         call WRITEDIAGFI(ngrid,"u","Zonal wind","m.s-1",3,zu)
    20812270         call WRITEDIAGFI(ngrid,"v","Meridional wind","m.s-1",3,zv)
     
    24212610c         CALL writeg1d(ngrid,1,tsurf,'tsurf','K')
    24222611c         CALL writeg1d(ngrid,1,ps,'ps','Pa')
    2423          
     2612       
    24242613c         CALL writeg1d(ngrid,nlayer,zt,'T','K')
    24252614c        CALL writeg1d(ngrid,nlayer,pu,'u','m.s-1')
     
    24772666     &                                   ,"kg.m-2",0,co2ice)
    24782667
     2668      call co2sat(ngrid*nlayer,zt,zplay,zqsatco2)
     2669         do ig=1,ngrid
     2670            do l=1,nlayer
     2671               satuco2(ig,l) = zq(ig,l,igcm_co2)*
     2672     &              (mmean(ig,l)/44.01)*zplay(ig,l)/zqsatco2(ig,l)
     2673                 
     2674c               write(*,*) "In PHYSIQMOD, pt,zt,time ",pt(ig,l)
     2675c     &              ,zt(ig,l),ptime
     2676            enddo
     2677         enddo
     2678
     2679c         CALL writeg1d(ngrid,nlayer,zt,'temp','K')
     2680c         CALL writeg1d(ngrid,nlayer,riceco2,'riceco2','m')
     2681c         CALL writeg1d(ngrid,nlayer,satuco2,'satuco2','satu')
     2682         
     2683         
     2684         call WRITEDIAGFI(ngrid,"satuco2","vap in satu","kg/kg",1,
     2685     &        satuco2(1,:))
     2686         call WRITEdiagfi(ngrid,"riceco2","ice radius","m"
     2687     &        ,1,riceco2(1,:))
    24792688! or output in diagfi.nc (for testphys1d)
    24802689         call WRITEDIAGFI(ngrid,'ps','Surface pressure','Pa',0,ps)
    2481          call WRITEDIAGFI(ngrid,'temp','Temperature',
    2482      &                       'K',1,zt)
    2483      
     2690         call WRITEDIAGFI(ngrid,'temp','Temperature ',
     2691     &                       'K JA',1,zt(1,:))
     2692c         call WRITEDIAGFI(ngrid,'temp2','Temperature ',
     2693c     &        'K JA2',1,pt)
     2694
    24842695         if(tracer) then
    24852696c           CALL writeg1d(ngrid,1,tau,'tau','SI')
     
    26012812           endif ! of if (scavenging)
    26022813
     2814          if (scavenging) then
     2815             Nccntot(:)= 0
     2816             Mccntot(:)= 0
     2817             raveco2(:)=0
     2818             icetotco2(:)=0
     2819             do ig=1,ngrid
     2820                do l=1,nlayer
     2821                   icetotco2(ig) = icetotco2(ig) +
     2822     &                  zq(ig,l,igcm_co2_ice) *
     2823     &                  (zplev(ig,l) - zplev(ig,l+1)) / g
     2824                   Nccntot(ig) = Nccntot(ig) +
     2825     &                  zq(ig,l,igcm_ccnco2_number)*tauscaling(ig)
     2826     &                  *(zplev(ig,l) - zplev(ig,l+1)) / g
     2827                   Mccntot(ig) = Mccntot(ig) +
     2828     &                  zq(ig,l,igcm_ccnco2_mass)*tauscaling(ig)
     2829     &                  *(zplev(ig,l) - zplev(ig,l+1)) / g
     2830cccc  Column integrated effective ice radius
     2831cccc is weighted by total ice surface area (BETTER than total ice mass)
     2832                   raveco2(ig) = raveco2(ig) +
     2833     &                  tauscaling(ig) *
     2834     &                  zq(ig,l,igcm_ccnco2_number) *
     2835     &                  (zplev(ig,l) - zplev(ig,l+1)) / g *
     2836     &                  riceco2(ig,l) * riceco2(ig,l)*
     2837     &                  (1.+nuiceco2_ref)
     2838                enddo
     2839                raveco2(ig)=(icetotco2(ig)/rho_ice_co2+Mccntot(ig)/
     2840     &               rho_dust)*0.75
     2841     &               /max(pi*raveco2(ig),1.e-30) ! surface weight
     2842                if (icetotco2(ig)*1e3.lt.0.01) raveco2(ig)=0.
     2843             enddo
     2844          else                  ! of if (scavenging)
     2845             raveco2(:)=0
     2846             do ig=1,ngrid
     2847                do l=1,nlayer
     2848                   raveco2(ig) = raveco2(ig) +
     2849     &                  zq(ig,l,igcm_co2_ice) *
     2850     &                  (zplev(ig,l) - zplev(ig,l+1)) / g *
     2851     &                  riceco2(ig,l) * (1.+nuiceco2_ref)
     2852                enddo
     2853                raveco2(ig) = max(raveco2(ig) /
     2854     &               max(icetotco2(ig),1.e-30),1.e-30) ! mass weight
     2855             enddo
     2856          endif                 ! of if (scavenging)
     2857         
     2858             
     2859         call WRITEdiagfi(ngrid,"raveco2","ice eff radius","m",0
     2860     &        ,raveco2)
     2861
    26032862           CALL WRITEDIAGFI(ngrid,'reffice',
    26042863     &                      'reffice',
  • trunk/LMDZ.MARS/libf/phymars/tracer_mod.F90

    r1224 r1617  
    55      ! number of tracers:
    66      integer,save :: nqmx ! initialized in conf_phys
    7       
     7   
    88      character*20,allocatable,save ::  noms(:)  ! name of the tracer
    99      real,allocatable,save :: mmol(:)           ! mole mass of tracer (g/mol-1)
     
    2020      real,save :: nuice_sed   ! Sedimentation effective variance of the water ice dist.
    2121      real,save :: ref_r0        ! for computing reff=ref_r0*r0 (in log.n. distribution)
    22      
     22      real,save :: rho_ice_co2     ! co2 ice density (kg.m-3)
     23      real,save :: nuiceco2_sed   ! Sedimentation effective variance of the co2 ice dist.
     24      real,save :: nuiceco2_ref   ! Effective variance of the co2 ice dist.
     25
    2326      real,save :: ccn_factor  ! ratio of nuclei for water ice particles
    2427
    2528      INTEGER,ALLOCATABLE,SAVE :: nqdust(:) ! to store the indexes of dust tracers (cf aeropacity)
     29      real,allocatable,save :: dryness(:)!"Dryness coefficient" for grnd water ice sublimation
     30
    2631
    2732! tracer indexes: these are initialized in initracer and should be 0 if the
     
    3742      integer,save :: igcm_ccn_number ! CCN number mixing ratio
    3843      integer,save :: igcm_dust_submicron ! submicron dust mixing ratio
    39                                      !   (transported dust)
     44   
     45      integer,save :: igcm_ccnco2_mass   ! CCN (dust and/or water ice) for CO2 mass mixing ratio
     46      integer,save :: igcm_ccnco2_number ! CCN (dust and/or water ice) for CO2 number mixing ratio
     47
    4048      ! water
    4149      integer,save :: igcm_h2o_vap ! water vapour
    4250      integer,save :: igcm_h2o_ice ! water ice
     51      integer,save :: igcm_co2_ice ! co2 ice
     52
    4353      ! chemistry:
    4454      integer,save :: igcm_co2
  • trunk/LMDZ.MARS/libf/phymars/updaterad.F90

    r1307 r1617  
    1 module updaterad
     1                module updaterad
    22
    33
     
    1212
    1313! T. Navarro, June 2012
    14 
    15 
     14! CO2 clouds added 09/16 by J. Audouard
    1615
    1716! For instance, if R^3 is lower than r3icemin, then R is set to ricemin.
     
    2423real, parameter :: ricemax  = 500.e-6
    2524
     25real, parameter :: r3iceco2min = 1.e-30
     26real, parameter :: riceco2min  = 1.e-10
     27
     28real, parameter :: r3iceco2max = 125.e-12
     29real, parameter :: riceco2max  = 500.e-6
     30
     31
     32real, parameter :: qice_threshold  = 1.e-15 ! 1.e-10
     33real, parameter :: qice_co2_threshold  = 1.e-30 ! 1.e-10
    2634
    2735real, parameter :: nccn_threshold  =  1.
    28 real, parameter :: qccn_threshold  =  1.e-20
    29 
    30 real, parameter :: r3ccnmin = 1.e-21    ! ie rccnmin = 0.1 microns
    31 real, parameter :: rccnmin  = 0.1e-6
    32 
    33 real, parameter :: r3ccnmax = 125.e-12  ! ie rccnmax  = 500 microns
    34 real, parameter :: rccnmax  = 500.e-6 
     36real, parameter :: qccn_threshold  =  1.e-30
     37
     38real, parameter :: r3ccnmin = 1.e-24    ! ie rccnmin = 10n m
     39real, parameter :: rccnmin  = 1.e-8
     40
     41real, parameter :: r3ccnmax = 125.e-18  ! ie rccnmax  = 5 microns
     42real, parameter :: rccnmax  = 5.e-6
    3543
    3644
     
    3947real, parameter :: qdust_threshold  = 1.e-20
    4048
    41 real, parameter :: r3dustmin = 1.e-24  ! ie rdustmin = 0.1 microns
    42 real, parameter :: rdustmin  = 0.01e-6
     49real, parameter :: r3dustmin = 1.e-24  ! ie rdustmin = 0.01 microns
     50real, parameter :: rdustmin  = 1.e-8
    4351
    4452real, parameter :: r3dustmax = 125.e-12 ! ie rdustmax  = 500 microns
     
    96104!============================================================================
    97105
    98 
     106subroutine updaterice_microco2(qice,qccn,nccn,coeff,rice,rhocloudco2)
     107use tracer_mod, only: rho_dust, rho_ice_co2
     108USE comcstfi_h, only:  pi
     109implicit none
     110!By CL and JA 09/16
     111
     112real, intent(in)  :: qice,qccn,nccn
     113real, intent(in)  :: coeff         ! this coeff is tauscaling if microphy = T (possibly ccn_factor^-1 otherwise)
     114real, intent(out) :: rice,rhocloudco2 ! rhocloud is needed for sedimentation and is also a good diagnostic variable
     115real nccn_true,qccn_true ! nombre et masse de CCN
     116   
     117nccn_true = max(nccn * coeff, 1.e-30)
     118qccn_true = max(qccn * coeff, 1.e-30)
     119
     120
     121  rhocloudco2 = (qice *rho_ice_co2 + qccn_true*rho_dust) / (qice + qccn_true)
     122
     123  rhocloudco2 = min(max(rhocloudco2,rho_ice_co2),rho_dust)
     124
     125  rice = (qice + qccn_true) * 0.75 / pi / rhocloudco2 / nccn_true
     126
     127  if (rice .le. r3iceco2min) then !r3icemin radius power 3 ?
     128    rice = riceco2min
     129  else if (rice .ge. r3iceco2max) then !r3icemin radius power 3 ?
     130    rice = riceco2max
     131  else
     132    rice = rice**(1./3.) ! here rice is always positive
     133  endif
     134
     135
     136end subroutine updaterice_microco2
    99137
    100138
Note: See TracChangeset for help on using the changeset viewer.