Ignore:
Timestamp:
Jul 13, 2021, 10:45:06 AM (3 years ago)
Author:
romain.vande
Message:

MARS GCM:

Update of the revision 2545, physiq_mod is corrected to contain the modifications that were previously deleted by error
RV

File:
1 edited

Legend:

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

    r2545 r2551  
    7474      use compute_dtau_mod, only: compute_dtau
    7575      use nonoro_gwd_ran_mod, only: nonoro_gwd_ran
     76      use check_fields_mod, only: check_physics_fields
    7677#ifdef MESOSCALE
    7778      use comsoil_h, only: mlayer,layer
     
    9697#endif
    9798      USE mod_grid_phy_lmdz, ONLY: grid_type, unstructured
     99      use ioipsl_getin_p_mod, only: getin_p
    98100
    99101      IMPLICIT NONE
     
    396398      REAL mdusttot(ngrid)      ! Total mass of dust tracer (kg/m2)
    397399      REAL icetot(ngrid)        ! Total mass of water ice (kg/m2)
    398       REAL mtotco2       ! Total mass of co2, including ice at the surface (kg/m2)
    399       REAL vaptotco2     ! Total mass of co2 vapor (kg/m2)
    400       REAL icetotco2     ! Total mass of co2 ice (kg/m2)
     400      REAL mtotco2(ngrid)      ! Total mass of co2, including ice at the surface (kg/m2)
     401      REAL vaptotco2(ngrid)     ! Total mass of co2 vapor (kg/m2)
     402      REAL icetotco2(ngrid)     ! Total mass of co2 ice (kg/m2)
    401403      REAL Nccntot(ngrid)       ! Total number of ccn (nbr/m2)
    402404      REAL NccnCO2tot(ngrid)    ! Total number of ccnCO2 (nbr/m2)
     
    433435      REAL dsords(ngrid,nlayer) ! density scaled opacity for stormdust
    434436      REAL dsotop(ngrid,nlayer) ! density scaled opacity for topdust
    435 
    436       REAL nccnco2(ngrid,nlayer)   ! true n ccnco2 (kg/kg)
    437       REAL qccnco2(ngrid,nlayer)  ! true q ccnco2 (kg/kg)
    438437
    439438c Test 1d/3d scavenging
     
    509508      integer iloop
    510509
    511 !      LOGICAL startphy_file
     510      ! flags to trigger extra sanity checks
     511      logical,save :: check_physics_inputs=.false.
     512      logical,save :: check_physics_outputs=.false.
    512513
    513514c=======================================================================
     
    520521
    521522      IF (firstcall) THEN
     523
     524         call getin_p("check_physics_inputs",check_physics_inputs)
     525         call getin_p("check_physics_outputs",check_physics_outputs)
    522526
    523527c        variables set to 0
     
    736740      ENDIF        !  (end of "if firstcall")
    737741
     742      if (check_physics_inputs) then
     743        ! Check the validity of input fields coming from the dynamics
     744        call check_physics_fields("begin physiq:",pt,pu,pv,pplev)
     745      endif
     746
    738747c ---------------------------------------------------
    739748c 1.2   Initializations done at every physical timestep:
     
    16551664               pdt(1:ngrid,1:nlayer) =
    16561665     &              pdt(1:ngrid,1:nlayer) +
    1657      &              zdtcloudco2(1:ngrid,1:nlayer)! --> in co2condens
     1666     &              zdtcloudco2(1:ngrid,1:nlayer)
    16581667           
    16591668
     
    19501959     $                  zdtc,zdtsurfc,pdpsrf,zduc,zdvc,zdqc,
    19511960     $                  fluxsurf_sw,zls,
    1952      $                  zdqssed_co2,zcondicea_co2microp,
    1953      &                  zdtcloudco2)
     1961     $                  zdqssed_co2,zcondicea_co2microp)
    19541962         ! no scavenging yet
    19551963         zdqsc(:,:) = 0.
     
    19621970     $              fluxsurf_sw,zls,
    19631971     $              zdqssed_co2,zcondicea_co2microp,
    1964      &              zdtcloudco2,zdqsc)
     1972     &              zdqsc)
    19651973           DO iq=1, nq
    19661974           DO ig=1,ngrid
     
    19681976           ENDDO  ! (ig)
    19691977           ENDDO    ! (iq)
    1970         end if
     1978        end if 
    19711979        DO l=1,nlayer
    19721980           DO ig=1,ngrid
     
    24122420              enddo
    24132421           endif !(rdstorm)
    2414 
    2415            if (co2clouds) then
    2416               do ig=1,ngrid
    2417                  nccnco2(ig,:) =
    2418      &                zq(ig,:,igcm_ccnco2_number)*tauscaling(ig)
    2419                  qccnco2(ig,:) =
    2420      &                zq(ig,:,igcm_ccnco2_mass)*tauscaling(ig)
    2421               enddo
    2422            endif ! of if (co2clouds)
    24232422                             
    24242423           if (water) then
     
    25172516
    25182517           endif ! of if (water)
     2518
     2519          if (co2clouds) then
     2520            mtotco2(1:ngrid) = 0.
     2521            icetotco2(1:ngrid) = 0.
     2522            vaptotco2(1:ngrid) = 0.
     2523            do ig=1,ngrid
     2524              do l=1,nlayer
     2525                vaptotco2(ig) = vaptotco2(ig) +
     2526     &                          zq(ig,l,igcm_co2) *
     2527     &                          (zplev(ig,l) - zplev(ig,l+1)) / g
     2528                icetotco2(ig) = icetot(ig) +
     2529     &                          zq(ig,l,igcm_co2_ice) *
     2530     &                          (zplev(ig,l) - zplev(ig,l+1)) / g
     2531              end do
     2532              mtotco2(ig) = icetotco2(ig) + vaptotco2(ig)
     2533            end do
     2534          end if
    25192535        endif                   ! of if (tracer)
    25202536#ifndef MESOSCALE
     
    26412657
    26422658             endif ! of if (water)
     2659
     2660             if (co2clouds) then
     2661               call wstats(ngrid,"mtotco2",
     2662     &                    "total mass atm of co2","kg/m2",
     2663     &                    2,mtotco2)
     2664               call wstats(ngrid,"icetotco2",
     2665     &                    "total mass atm of co2 ice","kg/m2",
     2666     &                    2,icetotco2)
     2667               call wstats(ngrid,"vaptotco2",
     2668     &                    "total mass atm of co2 vapor","kg/m2",
     2669     &                    2,icetotco2)
     2670             end if
    26432671             
    26442672             
     
    29242952
    29252953      if (tracer.and.(igcm_co2.ne.0)) then
    2926 !       call WRITEDIAGFI(ngrid,"co2_l1","co2 mix. ratio in 1st layer",
    2927 !    &                   "kg/kg",2,zq(1,1,igcm_co2))
    29282954        call WRITEDIAGFI(ngrid,"co2","co2 mass mixing ratio",
    2929      &                   "kg/kg",3,zq(:,:,igcm_co2))
     2955     &                   "kg.kg-1",3,zq(:,:,igcm_co2))
    29302956
    29312957        if (co2clouds) then
    2932           call WRITEDIAGFI(ngrid,'zdtcloudco2',
    2933      &                     'temperature variation of CO2 latent heat',
    2934      &                     'K/s',3,zdtcloudco2)
    2935  
    2936           call WRITEDIAGFI(ngrid,'ccnqco2','CCNco2 mass mr',
    2937      &                     'kg/kg',3,qccnco2)
     2958          call WRITEDIAGFI(ngrid,'ccnqco2','CCNco2 mmr',
     2959     &                     'kg.kg-1',3,zq(:,:,igcm_ccnco2_mass))
    29382960
    29392961          call WRITEDIAGFI(ngrid,'ccnNco2','CCNco2 number',
    2940      &                     'part/kg',3,nccnco2)
    2941 
    2942           call WRITEDIAGFI(ngrid,'co2_ice','co2_ice','kg/kg',
    2943      &                     3,zq(:,:,igcm_co2_ice))
    2944 
    2945           call WRITEDIAGFI(ngrid,'precip_co2_ice',
    2946      &                     'surface deposition of co2 ice',
    2947      &                     'kg.m-2.s-1',2,
    2948      &                     zdqssed(1:ngrid,igcm_co2_ice))
     2962     &                     'part.kg-1',3,zq(:,:,igcm_ccnco2_number))
     2963
     2964          call WRITEDIAGFI(ngrid,'co2_ice','co2_ice mmr in atm',
     2965     &                     'kg.kg-1', 3, zq(:,:,igcm_co2_ice))
     2966
     2967         call WRITEDIAGFI(ngrid,"mtotco2","total mass atm of co2",
     2968     &                    "kg.m-2",2, mtotco2)
     2969         call WRITEDIAGFI(ngrid,"icetotco2","total mass atm of co2 ice",
     2970     &                    "kg.m-2", 2, icetotco2)
     2971         call WRITEDIAGFI(ngrid,"vaptotco2","total mass atm of co2
     2972     &                    vapor","kg.m-2", 2, vaptotco2)
     2973         call WRITEDIAGFI(ngrid,"emis","Surface emissivity","w.m-1",2,
     2974     &                  emis)
    29492975        end if ! of if (co2clouds)
    29502976      end if ! of if (tracer.and.(igcm_co2.ne.0))
     
    38013827
    38023828        ENDIF ! of IF (water)
    3803 
    3804 
    3805       ! co2clouds
    3806       if (co2clouds) then
    3807         call WRITEDIAGFI(ngrid,'zdtcloudco2',
    3808      &                   'temperature variation of CO2 latent heat',
    3809      &                   'K/s',3,zdtcloudco2)
    3810          call WRITEDIAGFI(ngrid,"emis","Surface emissivity","w.m-1",2,
    3811      &                  emis)
    3812 
    3813       end if
    38143829         
    38153830ccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccc
     
    38613876
    38623877      CALL send_xios_field("phisinit",phisfi)
    3863 
    3864 ! ap,bp (interlayer),aps,bps (altitude)
    38653878     
    38663879      CALL send_xios_field("ps",ps)
    38673880      CALL send_xios_field("area",cell_area)
    38683881
    3869       CALL send_xios_field("ISR",fluxtop_sw_tot)
     3882!      CALL send_xios_field("ISR",fluxtop_sw_tot)
    38703883      CALL send_xios_field("OLR",fluxtop_lw)
    38713884
    38723885      CALL send_xios_field("tsurf",tsurf)
    3873       CALL send_xios_field("inertiedat",inertiedat)
     3886!      CALL send_xios_field("inertiedat",inertiedat)
    38743887      CALL send_xios_field("tsoil",tsoil)
    38753888      CALL send_xios_field("co2ice",co2ice)
    38763889     
    3877       CALL send_xios_field("temp",zt)
     3890!      CALL send_xios_field("temp",zt)
    38783891      CALL send_xios_field("u",zu)
    38793892      CALL send_xios_field("v",zv)
    38803893
    3881       CALL send_xios_field("rho",rho)
     3894!      CALL send_xios_field("rho",rho)
    38823895      ! Orographic Gravity waves tendencies
    3883       if (calllott) then
    3884       CALL send_xios_field("dugw",zdugw/ptimestep)
    3885       CALL send_xios_field("dvgw",zdvgw/ptimestep)
    3886       CALL send_xios_field("dtgw",zdtgw/ptimestep)
    3887       endif
     3896!      if (calllott) then
     3897!      CALL send_xios_field("dugw",zdugw/ptimestep)
     3898!      CALL send_xios_field("dvgw",zdvgw/ptimestep)
     3899!      CALL send_xios_field("dtgw",zdtgw/ptimestep)
     3900!      endif
    38883901      !CREATE IF CO2CYCLE
    3889       if (tracer.and.(igcm_co2.ne.0)) then
    3890          CALL send_xios_field("co2",zq(:,:,igcm_co2))
    3891       endif
     3902!      if (tracer.and.(igcm_co2.ne.0)) then
     3903!         CALL send_xios_field("co2",zq(:,:,igcm_co2))
     3904!      endif
    38923905      ! Water cycle
    3893       if (water) then
    3894          CALL send_xios_field("watercap",watercap)
     3906!      if (water) then
     3907!         CALL send_xios_field("watercap",watercap)
    38953908         !CALL send_xios_field("watercaptag",watercaptag)
    3896          CALL send_xios_field("mtot",mtot)
    3897          CALL send_xios_field("icetot",icetot)
    3898          if (igcm_h2o_vap.ne.0 .and. igcm_h2o_ice.ne.0) then
    3899             CALL send_xios_field("h2o_vap",zq(:,:,igcm_h2o_vap))
    3900             CALL send_xios_field("h2o_ice",zq(:,:,igcm_h2o_ice))
    3901          endif
    3902       endif
    3903             if (.not.activice) then
     3909!         CALL send_xios_field("mtot",mtot)
     3910!         CALL send_xios_field("icetot",icetot)
     3911!         if (igcm_h2o_vap.ne.0 .and. igcm_h2o_ice.ne.0) then
     3912!            CALL send_xios_field("h2o_vap",zq(:,:,igcm_h2o_vap))
     3913!            CALL send_xios_field("h2o_ice",zq(:,:,igcm_h2o_ice))
     3914!         endif
     3915!      endif
     3916!            if (.not.activice) then
    39043917!      CALL send_xios_field("tauTESap",tauTES)
    3905              else
    3906       CALL send_xios_field("tauTES",taucloudtes)
    3907              endif
    3908 
    3909       CALL send_xios_field("h2o_ice_s",qsurf(:,igcm_h2o_ice))
     3918!             else
     3919!      CALL send_xios_field("tauTES",taucloudtes)
     3920!             endif
     3921
     3922!      CALL send_xios_field("h2o_ice_s",qsurf(:,igcm_h2o_ice))
    39103923
    39113924
     
    39163929#endif
    39173930
     3931      if (check_physics_outputs) then
     3932        ! Check the validity of updated fields at the end of the physics step
     3933        call check_physics_fields("end of physiq:",zt,zu,zv,zplev)
     3934      endif
    39183935
    39193936      icount=icount+1
Note: See TracChangeset for help on using the changeset viewer.