Ignore:
Timestamp:
Apr 19, 2018, 3:16:47 PM (7 years ago)
Author:
emillour
Message:

Mars GCM:
CO2 code updates:

  • make co2cloud a module and save mem_* variables (initialized via phys_state_var_init)
  • make improvedCO2cloud a module
  • read/write mem_* variables in phyetat0.F and phyredem.F

DB

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

Legend:

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

    r1921 r1922  
     1      MODULE co2cloud_mod
     2
     3      IMPLICIT NONE
     4
     5      DOUBLE PRECISION,allocatable,save :: mem_Mccn_co2(:,:) ! Memory of CCN mass of H2O and dust used by CO2
     6      DOUBLE PRECISION,allocatable,save :: mem_Mh2o_co2(:,:) ! Memory of H2O mass integred into CO2 crystal
     7      DOUBLE PRECISION,allocatable,save :: mem_Nccn_co2(:,:) ! Memory of CCN number of H2O and dust used by CO2
     8
     9      CONTAINS
     10
    111      SUBROUTINE co2cloud(ngrid,nlay,ptimestep,
    212     &                pplev,pplay,pdpsrf,pzlay,pt,pdt,
     
    2030      USE newsedim_mod, ONLY: newsedim
    2131      USE datafile_mod, ONLY: datadir
     32      USE improvedCO2clouds_mod, ONLY: improvedCO2clouds
    2233
    2334      IMPLICIT NONE
     
    137148      real subpdqsed(ngrid,nlay,nq)
    138149      real sum_subpdqs_sedco2(ngrid) ! CO2 flux at the surface
    139 
    140       DOUBLE PRECISION,allocatable,save :: memdMMccn(:,:) !memory of h2o particles
    141       DOUBLE PRECISION,allocatable,save :: memdMMh2o(:,:) !only if co2useh2o=.true.
    142       DOUBLE PRECISION,allocatable,save :: memdNNccn(:,:) !Nb particules H2O intégré
    143150     
    144151!     What we need for Qext reading and tau computation : size distribution
     
    207214        write(*,*)"Physical timestep is",ptimestep
    208215        write(*,*)"CO2 Microphysics timestep is",microtimestep
    209      
    210    
    211         if (.not. allocated(memdMMccn)) allocate(memdMMccn(ngrid,nlay))
    212         if (.not. allocated(memdNNccn)) allocate(memdNNccn(ngrid,nlay))
    213         if (.not. allocated(memdMMh2o)) allocate(memdMMh2o(ngrid,nlay))
    214        
    215         memdMMccn(:,:)=0.
    216         memdMMh2o(:,:)=0.
    217         memdNNccn(:,:)=0.
    218216
    219217c     Compute the size bins of the distribution of CO2 ice particles
     
    610608     &     pplay,pplev,pteff,sum_subpdt,
    611609     &     pqeff,sum_subpdq,subpdqcloudco2,subpdtcloudco2,
    612      &     nq,tauscaling,memdMMccn,memdMMh2o,memdNNccn)
     610     &     nq,tauscaling,mem_Mccn_co2,mem_Mh2o_co2,mem_Nccn_co2)
    613611c ==============================================================================
    614612c      3.  Updating tendencies after cloud scheme:
     
    960958      call WRITEdiagfi(ngrid,"tau1mic","co2 ice opacity 1 micron"
    961959     &        ," ",2,tau1mic)
    962       call WRITEDIAGFI(ngrid,"memdNNccn","Nombre de CCN de glace d eau"
    963      &        ,"kg/kg ",3,memdNNccn)
    964       call WRITEDIAGFI(ngrid,"memdMMccn","Masse de CCN de glace d eau"
    965      &        ,"kg/kg ",3,memdMMccn)
    966       call WRITEDIAGFI(ngrid,"memdMMh2o","Masse de CCN de glace d eau"
    967      &        ,"kg/kg ",3,memdMMh2o)         
    968       END
     960      call WRITEDIAGFI(ngrid,"mem_Nccn_co2","CCN number used by CO2"
     961     &        ,"kg/kg ",3,mem_Nccn_co2)
     962      call WRITEDIAGFI(ngrid,"mem_Mccn_co2","CCN mass used by CO2"
     963     &        ,"kg/kg ",3,mem_Mccn_co2)
     964      call WRITEDIAGFI(ngrid,"mem_Mh2o_co2","H2O mass in CO2 crystal"
     965     &        ,"kg/kg ",3,mem_Mh2o_co2)         
     966
     967      END SUBROUTINE co2cloud
     968c Subroutines used to write variables of memory in start files       
     969      SUBROUTINE ini_co2cloud(ngrid,nlayer)
     970 
     971      IMPLICIT NONE
     972
     973      INTEGER, INTENT (in) :: ngrid  ! number of atmospheric columns
     974      INTEGER, INTENT (in) :: nlayer ! number of atmospheric layers
     975
     976         allocate(mem_Nccn_co2(ngrid,nlayer))
     977         allocate(mem_Mccn_co2(ngrid,nlayer))
     978         allocate(mem_Mh2o_co2(ngrid,nlayer))
     979
     980      END SUBROUTINE ini_co2cloud
     981
     982      SUBROUTINE end_co2cloud
     983
     984      IMPLICIT NONE
     985
     986         if (allocated(mem_Nccn_co2)) deallocate(mem_Nccn_co2)
     987         if (allocated(mem_Mccn_co2)) deallocate(mem_Mccn_co2)
     988         if (allocated(mem_Mh2o_co2)) deallocate(mem_Mh2o_co2)
     989
     990      END SUBROUTINE end_co2cloud
     991
     992      END MODULE co2cloud_mod
  • trunk/LMDZ.MARS/libf/phymars/improvedCO2clouds.F

    r1921 r1922  
     1      MODULE improvedCO2clouds_mod
     2     
     3      IMPLICIT NONE
     4
     5      CONTAINS
     6 
    17      subroutine improvedCO2clouds(ngrid,nlay,microtimestep,
    28     &             pplay,pplev,pteff,sum_subpdt,
    39     &             pqeff,sum_subpdq,subpdqcloudco2,subpdtcloudco2,
    410     &             nq,tauscaling,
    5      &             memdMMccn,memdMMh2o,memdNNccn)
     11     &             mem_Mccn_co2,mem_Mh2o_co2,mem_Nccn_co2)
    612      USE comcstfi_h, only: pi, g, cpp
    713      USE updaterad, only: updaterice_micro, updaterice_microco2
     
    3642c Memory of the origin of the co2 particles is kept and thus the
    3743c water cycle shouldn't be modified by this.
    38 cWARNING: no sedimentation of the water ice origin is performed
     44c WARNING: no sedimentation of the water ice origin is performed
    3945c in the microphysical timestep in co2cloud.F.
    4046
     
    104110      DOUBLE PRECISION Mo,No,No_dust,Mo_dust
    105111      DOUBLE PRECISION  Rn, Rm, dev2,dev3, n_derf, m_derf
    106       DOUBLE PRECISION memdMMccn(ngrid,nlay)
    107       DOUBLE PRECISION memdMMh2o(ngrid,nlay)
    108       DOUBLE PRECISION memdNNccn(ngrid,nlay)
     112      DOUBLE PRECISION mem_Mccn_co2(ngrid,nlay) ! Memory of CCN mass of H2O and dust used by CO2
     113      DOUBLE PRECISION mem_Mh2o_co2(ngrid,nlay) ! Memory of H2O mass integred into CO2 crystal
     114      DOUBLE PRECISION mem_Nccn_co2(ngrid,nlay) ! Memory of CCN number of H2O and dust used by CO2
    109115     
    110116!     Radius used by the microphysical scheme (m)
     
    506512                zq(ig,l,igcm_h2o_ice) = zq(ig,l,igcm_h2o_ice)-dMh2o_ice
    507513                zq(ig,l,igcm_ccn_mass)= zq(ig,l,igcm_ccn_mass)-dMh2o_ccn
    508                 memdMMh2o(ig,l)=memdMMh2o(ig,l)+dMh2o_ice
    509                 memdMMccn(ig,l)=memdMMccn(ig,l)+dMh2o_ccn
    510                 memdNNccn(ig,l)=memdNNccn(ig,l)+dNNh2o
     514                mem_Mh2o_co2(ig,l)=mem_Mh2o_co2(ig,l)+dMh2o_ice
     515                mem_Mccn_co2(ig,l)=mem_Mccn_co2(ig,l)+dMh2o_ccn
     516                mem_Nccn_co2(ig,l)=mem_Nccn_co2(ig,l)+dNNh2o
    511517             endif ! of if co2useh2o
    512518           ENDIF   ! of is satu >1
     
    566572! On sublime tout
    567573                 if (co2useh2o) then
    568                    if (memdMMccn(ig,l) .gt. 0) then
     574                   if (mem_Mccn_co2(ig,l) .gt. 0) then
    569575                    zq(ig,l,igcm_ccn_mass)=zq(ig,l,igcm_ccn_mass)
    570      &                   +memdMMccn(ig,l)
     576     &                   +mem_Mccn_co2(ig,l)
    571577                   endif
    572                    if (memdMMh2o(ig,l) .gt. 0) then
     578                   if (mem_Mh2o_co2(ig,l) .gt. 0) then
    573579                    zq(ig,l,igcm_h2o_ice)=zq(ig,l,igcm_h2o_ice)
    574      &                   +memdMMh2o(ig,l)
     580     &                   +mem_Mh2o_co2(ig,l)
    575581                   endif
    576582                 
    577                    if (memdNNccn(ig,l) .gt. 0) then
     583                   if (mem_Nccn_co2(ig,l) .gt. 0) then
    578584                    zq(ig,l,igcm_ccn_number)=zq(ig,l,igcm_ccn_number)
    579      &                   +memdNNccn(ig,l)
     585     &                   +mem_Nccn_co2(ig,l)
    580586                   endif
    581587                 endif
     
    583589     &                   zq(ig,l,igcm_dust_mass)
    584590     &                   + zq(ig,l,igcm_ccnco2_mass)-
    585      &                   (memdMMh2o(ig,l)+memdMMccn(ig,l))
     591     &                   (mem_Mh2o_co2(ig,l)+mem_Mccn_co2(ig,l))
    586592                    zq(ig,l,igcm_dust_number) =
    587593     &                   zq(ig,l,igcm_dust_number)
    588      &                   + zq(ig,l,igcm_ccnco2_number)-memdNNccn(ig,l)
     594     &                   + zq(ig,l,igcm_ccnco2_number)
     595     &                   -mem_Nccn_co2(ig,l)
    589596                 
    590597                    zq(ig,l,igcm_co2) = zq(ig,l,igcm_co2)
     
    594601                 zq(ig,l,igcm_co2_ice)=0.
    595602                 zq(ig,l,igcm_ccnco2_number)=0.
    596                  memdNNccn(ig,l)=0.
    597                  memdMMh2o(ig,l)=0.
    598                  memdMMccn(ig,l)=0.
     603                 mem_Nccn_co2(ig,l)=0.
     604                 mem_Mh2o_co2(ig,l)=0.
     605                 mem_Mccn_co2(ig,l)=0.
    599606                 riceco2(ig,l)=0.
    600607
     
    643650
    644651
    645         end
    646      
    647      
    648      
     652c     TEST D.BARDET
     653      call WRITEDIAGFI(ngrid,"No_dust","Nombre particules de poussière"
     654     &        ,"part/kg",3,No_dust)
     655      call WRITEDIAGFI(ngrid,"Mo_dust","Masse particules de poussière"
     656     &        ,"kg/kg ",3,Mo_dust)     
     657
     658        END SUBROUTINE improvedCO2clouds
     659
     660        END MODULE improvedCO2clouds_mod
     661     
     662     
     663     
  • trunk/LMDZ.MARS/libf/phymars/phyetat0.F90

    r1711 r1922  
    11subroutine phyetat0 (fichnom,tab0,Lmodif,nsoil,ngrid,nlay,nq, &
    22                     day_ini,time0,tsurf,tsoil,emis,q2,qsurf,co2ice, &
    3                      tauscaling,totcloudfrac)
    4 !  use netcdf
     3                     tauscaling,totcloudfrac,mem_Mccn_co2,mem_Nccn_co2,&
     4                     mem_Mh2o_co2)
     5
    56  use tracer_mod, only: noms ! tracer names
    67  use surfdat_h, only: phisfi, albedodat, z0, z0_default,&
     
    4748  real,intent(out) :: tauscaling(ngrid) ! dust conversion factor
    4849  real,intent(out) :: totcloudfrac(ngrid) ! total cloud fraction
     50  real,intent(out) :: mem_Mccn_co2(ngrid,nlay) ! Memory of CCN mass of H2O and dust used by CO2
     51  real,intent(out) :: mem_Nccn_co2(ngrid,nlay) ! Memory of CCN number of H2O and dust used by CO2
     52  real,intent(out) :: mem_Mh2o_co2(ngrid,nlay) ! Memory of H2O mass integred into CO2 crystal
    4953!======================================================================
    5054!  Local variables:
     
    230234endif
    231235
     236! Memory of the origin of the co2 particles
     237call get_field("mem_Mccn_co2",mem_Mccn_co2,found,indextime)
     238if (.not.found) then
     239  write(*,*) "phyetat0: <mem_Mccn_co2> not in file"
     240  mem_Mccn_co2(:,:)=0
     241else
     242  write(*,*) "phyetat0: Memory of CCN mass of H2O and dust used by CO2"
     243  write(*,*) " <mem_Mccn_co2> range:", &
     244             minval(mem_Mccn_co2), maxval(mem_Mccn_co2)
     245endif
     246
     247call get_field("mem_Nccn_co2",mem_Nccn_co2,found,indextime)
     248if (.not.found) then
     249  write(*,*) "phyetat0: <mem_Nccn_co2> not in file"
     250  mem_Nccn_co2(:,:)=0
     251else
     252  write(*,*) "phyetat0: Memory of CCN number of H2O and dust used by CO2"
     253  write(*,*) " <mem_Nccn_co2> range:", &
     254             minval(mem_Nccn_co2), maxval(mem_Nccn_co2)
     255endif
     256
     257call get_field("mem_Mh2o_co2",mem_Mh2o_co2,found,indextime)
     258if (.not.found) then
     259  write(*,*) "phyetat0: <mem_Mh2o_co2> not in file"
     260  mem_Mh2o_co2(:,:)=0
     261else
     262  write(*,*) "phyetat0: Memory of H2O mass integred into CO2 crystal"
     263  write(*,*) " <mem_Mh2o_co2> range:", &
     264             minval(mem_Mh2o_co2), maxval(mem_Mh2o_co2)
     265endif
    232266
    233267! Dust conversion factor
  • trunk/LMDZ.MARS/libf/phymars/phyredem.F90

    r1711 r1922  
    145145subroutine physdem1(filename,nsoil,ngrid,nlay,nq, &
    146146                    phystep,time,tsurf,tsoil,co2ice,emis,q2,qsurf,&
    147                     tauscaling,totcloudfrac)
     147                    tauscaling,totcloudfrac,mem_Mccn_co2,mem_Nccn_co2,&
     148                    mem_Mh2o_co2)
    148149  ! write time-dependent variable to restart file
    149150  use iostart, only : open_restartphy, close_restartphy, &
    150151                      put_var, put_field
    151152  use tracer_mod, only: noms ! tracer names
     153
    152154  implicit none
     155 
     156  include "callkeys.h"
     157 
    153158  character(len=*),intent(in) :: filename
    154159  integer,intent(in) :: nsoil
     
    165170  real,intent(in) :: qsurf(ngrid,nq)
    166171  real,intent(in) :: tauscaling(ngrid)
    167   real, intent(in) :: totcloudfrac(ngrid)
     172  real,intent(in) :: totcloudfrac(ngrid)
     173  real,intent(in) :: mem_Mccn_co2(ngrid,nlay) ! CCN mass of H2O and dust used by CO2
     174  real,intent(in) :: mem_Nccn_co2(ngrid,nlay) ! CCN number of H2O and dust used by CO2
     175  real,intent(in) :: mem_Mh2o_co2(ngrid,nlay) ! H2O mass integred into CO2 crystal
    168176 
    169177  integer :: iq
     
    235243    enddo
    236244  endif
     245  ! Memory of the origin of the co2 particles
     246  if (co2useh2o) then
     247     call put_field("mem_Mccn_co2","CCN mass of H2O and dust used by CO2",mem_Mccn_co2,time)
     248     call put_field("mem_Nccn_co2","CCN number of H2O and dust used by CO2",mem_Nccn_co2,time)
     249     call put_field("mem_Mh2o_co2","H2O mass integred into CO2 crystal",mem_Mh2o_co2,time)
     250  endif
    237251 
    238252  ! Close file
  • trunk/LMDZ.MARS/libf/phymars/phys_state_var_init_mod.F90

    r1773 r1922  
    4646      use tracer_mod, only: ini_tracer_mod,end_tracer_mod
    4747      use time_phylmdz_mod, only: init_time
     48      use co2cloud_mod, only: ini_co2cloud,end_co2cloud
    4849
    4950      IMPLICIT NONE
     
    105106      call end_turb_mod
    106107      call ini_turb_mod(ngrid,nlayer)
    107 
     108     
     109      ! allocate arrays in "co2cloud" :
     110      ! Memory of the origin of the co2 particles     
     111      call end_co2cloud
     112      call ini_co2cloud(ngrid,nlayer)
     113     
    108114      END SUBROUTINE phys_state_var_init
    109115
  • trunk/LMDZ.MARS/libf/phymars/physiq_mod.F

    r1921 r1922  
    1515
    1616      use watercloud_mod
     17      use co2cloud_mod, only: co2cloud, mem_Mccn_co2, mem_Mh2o_co2,
     18     &                        mem_Nccn_co2
    1719      use aeropacity_mod
    1820      use callradite_mod
     
    6062      USE vertical_layers_mod, ONLY: ap,bp,aps,bps
    6163#endif
     64
     65
    6266
    6367      IMPLICIT NONE
     
    162166c    ------------------
    163167
    164 #include "callkeys.h"
    165 #include "comg1d.h"
    166 #include "nlteparams.h"
    167 #include "chimiedata.h"
    168 #include "netcdf.inc"
     168      include "callkeys.h"
     169      include "comg1d.h"
     170      include "nlteparams.h"
     171      include "chimiedata.h"
     172      include "netcdf.inc"
    169173
    170174c Arguments :
     
    432436     &         day_ini,time_phys,
    433437     &         tsurf,tsoil,emis,q2,qsurf,co2ice,tauscaling,
    434      &         totcloudfrac)
     438     &         totcloudfrac,mem_Mccn_co2,mem_Nccn_co2,
     439     &         mem_Mh2o_co2)
    435440
    436441         if (pday.ne.day_ini) then
     
    12311236         
    12321237         IF (co2clouds ) THEN
    1233            
     1238
     1239
    12341240            call co2cloud(ngrid,nlayer,ptimestep,
    12351241     &           zplev,zplay,pdpsrf,zzlay,pt,pdt,
     
    12391245     &           rsedcloud,rhocloud,zzlev,zdqssed_co2,
    12401246     &           pdu,pu)
    1241                
     1247
    12421248
    12431249c Temperature variation due to latent heat release
     
    13011307             where (pq(:,:,igcm_ccnco2_mass) +
    13021308     &              ptimestep*pdq(:,:,igcm_ccnco2_mass) < 0.)
    1303                 pdq(:,:,igcm_ccnco2_mass) =
     1309               pdq(:,:,igcm_ccnco2_mass) =
    13041310     &            - pq(:,:,igcm_ccnco2_mass)/ptimestep + 1.e-30
    1305                 pdq(:,:,igcm_ccnco2_number) =
     1311               pdq(:,:,igcm_ccnco2_number) =
    13061312     &            - pq(:,:,igcm_ccnco2_number)/ptimestep + 1.e-30
    13071313             end where
    13081314             where (pq(:,:,igcm_ccnco2_number) +
    13091315     &              ptimestep*pdq(:,:,igcm_ccnco2_number) < 0.)
    1310                 pdq(:,:,igcm_ccnco2_mass) =
     1316               pdq(:,:,igcm_ccnco2_mass) =
    13111317     &            - pq(:,:,igcm_ccnco2_mass)/ptimestep + 1.e-30
    1312                 pdq(:,:,igcm_ccnco2_number) =
     1318               pdq(:,:,igcm_ccnco2_number) =
    13131319     &            - pq(:,:,igcm_ccnco2_number)/ptimestep + 1.e-30
    13141320             end where
     
    13171323             where (pq(:,:,igcm_dust_mass) +
    13181324     &              ptimestep*pdq(:,:,igcm_dust_mass) < 0.)
    1319                 pdq(:,:,igcm_dust_mass) =
    1320      &            - pq(:,:,igcm_dust_mass)/ptimestep + 1.e-30
    1321                 pdq(:,:,igcm_dust_number) =
    1322      &            - pq(:,:,igcm_dust_number)/ptimestep + 1.e-30
     1325               pdq(:,:,igcm_dust_mass) =
     1326     &           - pq(:,:,igcm_dust_mass)/ptimestep + 1.e-30
     1327               pdq(:,:,igcm_dust_number) =
     1328     &           - pq(:,:,igcm_dust_number)/ptimestep + 1.e-30
    13231329             end where
    13241330             where (pq(:,:,igcm_dust_number) +
    13251331     &              ptimestep*pdq(:,:,igcm_dust_number) < 0.)
    1326                 pdq(:,:,igcm_dust_mass) =
    1327      &            - pq(:,:,igcm_dust_mass)/ptimestep + 1.e-30
    1328                 pdq(:,:,igcm_dust_number) =
    1329      &            - pq(:,:,igcm_dust_number)/ptimestep + 1.e-30
     1332               pdq(:,:,igcm_dust_mass) =
     1333     &           - pq(:,:,igcm_dust_mass)/ptimestep + 1.e-30
     1334               pdq(:,:,igcm_dust_number) =
     1335     &           - pq(:,:,igcm_dust_number)/ptimestep + 1.e-30
    13301336             end where
    13311337     
     
    18391845     .                ptimestep,ztime_fin,
    18401846     .                tsurf,tsoil,co2ice,emis,q2,qsurf,tauscaling,
    1841      .               totcloudfrac)
     1847     .                totcloudfrac,mem_Mccn_co2,mem_Nccn_co2,
     1848     .                mem_Mh2o_co2)
    18421849         
    18431850         ENDIF
     
    18951902               enddo
    18961903              enddo
    1897              
    18981904           endif ! of if (co2clouds)
    18991905           
     
    23692375c        Outputs of the CO2 cycle
    23702376c        ----------------------------------------------------------
    2371 
     2377           
    23722378         if (tracer.and.(igcm_co2.ne.0)) then
    23732379!          call WRITEDIAGFI(ngrid,"co2_l1","co2 mix. ratio in 1st layer",
     
    23862392     &                       'total mass of CO2 ice',
    23872393     &                       'kg/m2',2,icetotco2)
    2388 
     2394 
    23892395            call WRITEDIAGFI(ngrid,'ccnqco2','CCNco2 mass mr',
    23902396     &                       'kg/kg',3,qccnco2)
     
    23952401          endif ! of if (co2clouds)
    23962402         endif ! of if (tracer.and.(igcm_co2.ne.0))
    2397 
    2398 
    23992403        ! Output He tracer, if there is one
    24002404        if (tracer.and.(igcm_he.ne.0)) then
     
    24452449     &                       'Mean reff',
    24462450     &                       'm',2,rave)
     2451
    24472452            call WRITEDIAGFI(ngrid,'h2o_ice','h2o_ice','kg/kg',
    24482453     &             3,zq(:,:,igcm_h2o_ice))
    24492454            call WRITEDIAGFI(ngrid,'h2o_vap','h2o_vap','kg/kg',
    24502455     &             3,zq(:,:,igcm_h2o_vap))
     2456
    24512457
    24522458!A. Pottier
Note: See TracChangeset for help on using the changeset viewer.