Changeset 4013 for trunk


Ignore:
Timestamp:
Jan 19, 2026, 2:31:03 PM (5 days ago)
Author:
debatzbr
Message:

Titan PCM: Minor merge and clean.
BBT

Location:
trunk/LMDZ.TITAN/libf/phytitan
Files:
7 edited

Legend:

Unmodified
Added
Removed
  • trunk/LMDZ.TITAN/libf/phytitan/callcorrk.F90

    r3659 r4013  
    726726
    727727
    728       !  Optical thickness diagnostics (added by JVO)
     728      !  Optical thickness diagnostics
    729729      if (diagdtau) then
    730730         do l=1,L_NLAYRAD
     
    732732               int_dtauv(ig,l,nw) = 0.0d0
    733733               DO k=1,L_NGAUSS
    734                ! Output exp(-tau) because gweight ponderates exp and not tau itself
    735                int_dtauv(ig,l,nw)= int_dtauv(ig,l,nw) + exp(-dtauv(l,nw,k))*gweight(k)
     734                 ! Output exp(-tau) because gweight ponderates exp and not tau itself
     735                 int_dtauv(ig,l,nw)= int_dtauv(ig,l,nw) + exp(-dtauv(l,nw,k))*gweight(k)
    736736               ENDDO
    737737            enddo
     
    739739            int_dtaui(ig,l,nw) = 0.0d0
    740740               DO k=1,L_NGAUSS
    741                ! Output exp(-tau) because gweight ponderates exp and not tau itself
    742                int_dtaui(ig,l,nw)= int_dtaui(ig,l,nw) + exp(-dtaui(l,nw,k))*gweight(k)
     741                 ! Output exp(-tau) because gweight ponderates exp and not tau itself
     742                 int_dtaui(ig,l,nw)= int_dtaui(ig,l,nw) + exp(-dtaui(l,nw,k))*gweight(k)
    743743               ENDDO
    744744            enddo
  • trunk/LMDZ.TITAN/libf/phytitan/evapCH4.F90

    r3497 r4013  
    7979real, parameter :: humCH4 = 0.4 ! Imposed surface humidity for CH4 [-]
    8080
    81 real, parameter :: Flnp = 0.10  ! Fraction occupied by lakes (North Pole)
     81real, parameter :: Flnp = 0.07  ! Fraction occupied by lakes (North Pole)
    8282real, parameter :: Flsp = 0.01  ! Fraction occupied by lakes (South Pole)
    83 real, parameter :: Flml = 1.    ! Fraction not infiltrated into the ground (Mid latitudes)
     83real, parameter :: Flml = 0.75  ! Fraction not infiltrated into the ground (Mid latitudes)
    8484
    8585real, parameter :: mmolair = 28.e-3 ! Molar mass of air [kg.mol-1]
  • trunk/LMDZ.TITAN/libf/phytitan/get_haze_and_cloud_opacity.F90

    r3700 r4013  
    200200  !-------------------------
    201201
    202   IF((m0 .gt. tiny(m0)) .and. (m3 .gt.tiny(m3))) THEN  ! if there are clouds !emoisan tests
     202  IF((m0 .gt. tiny(m0)) .and. (m3 .gt.tiny(m3))) THEN  ! If there are clouds
    203203      rinit = 1.e-9                ! fin = rinit*step**(33-1) = 1.e-5
    204204      if(CTYPE.eq.0) rinit = 1.e-7 ! fin = rinit*step**(33-1) = 1.e-3
     
    324324   
    325325      tauext = tauext * m0
    326   ENDIF !if there are clouds !emoisan tests
    327   !else just return the initialize values of tauext, wbar and gbar =0
     326  ENDIF ! If there are clouds, else return the initialize values tauext=wbar=gbar=0
    328327
    329328  return
  • trunk/LMDZ.TITAN/libf/phytitan/optci.F90

    r3700 r4013  
    289289               call get_haze_and_cloud_opacity(FTYPE,FTYPE,m0ccn,m3ccn,iw,dtau_ccn,ssa_ccn(nw),asf_ccn(nw))
    290290               
    291                ! Clear column (CCN, C2H2, C2H6, HCN, AC6H6) :
     291               ! Clear column (CCN + minor ices):
    292292               IF (CDCOLUMN == 0) THEN
    293293                  DO iq = 2, nice
     
    296296                  call get_haze_and_cloud_opacity(FTYPE,CTYPE,m0ccn,m3cld,iw,dtau_cld,ssa_cld(nw),asf_cld(nw))
    297297               
    298                ! Dark column (CCN, CH4, C2H2, C2H6, HCN, AC6H6) :
     298               ! Dark column (CCN + CH4 ice + minor ices):
    299299               ELSEIF (CDCOLUMN == 1) THEN
    300300                  DO iq = 1, nice
     
    313313               
    314314               ! For small dropplets, opacity of nucleus dominates...
    315                IF ((m3ccn + m3cld) .le. tiny(m3ccn)) THEN !no cloud !emoisan tests
     315               IF ((m3ccn + m3cld) .le. tiny(m3ccn)) THEN ! No cloud
    316316                  dtau_cld = 0.
    317317                  ssa_cld(nw) = 0.
  • trunk/LMDZ.TITAN/libf/phytitan/optcv.F90

    r3700 r4013  
    313313               call get_haze_and_cloud_opacity(FTYPE,FTYPE,m0ccn,m3ccn,iw,dtau_ccn,ssa_ccn(nw),asf_ccn(nw))
    314314
    315                ! Clear column (CCN, C2H2, C2H6, HCN, AC6H6) :
     315               ! Clear column (CCN + minor ices):
    316316               IF (CDCOLUMN == 0) THEN
    317317                  DO iq = 2, nice
     
    320320                  call get_haze_and_cloud_opacity(FTYPE,CTYPE,m0ccn,m3cld,iw,dtau_cld,ssa_cld(nw),asf_cld(nw))
    321321               
    322                ! Dark column (CCN, CH4, C2H2, C2H6, HCN, AC6H6) :
     322               ! Dark column (CCN + CH4 ice + minor ices):
    323323               ELSEIF (CDCOLUMN == 1) THEN
    324324                  DO iq = 1, nice
     
    337337
    338338               ! For small dropplets, opacity of nucleus dominates
    339                IF ((m3ccn + m3cld) .le. tiny(m3ccn)) THEN !no cloud !emoisan tests
     339               IF ((m3ccn + m3cld) .le. tiny(m3ccn)) THEN ! No cloud
    340340                  dtau_cld = 0.
    341341                  ssa_cld(nw) = 0.
     
    586586  !   END DO           
    587587  !END DO                 ! end full gauss loop
    588  
     588
    589589  TAUCUMV(:,:,:) = DTAUKV(:,:,:)
    590590  DO L=1,L_NLAYRAD
  • trunk/LMDZ.TITAN/libf/phytitan/phys_state_var_mod.F90

    r3318 r4013  
    7070      real,dimension(:,:,:),allocatable,save :: int_dtauv   ! VI optical thickness of layers within narrowbands for diags ().
    7171      real,dimension(:,:,:),allocatable,save :: int_dtaui   ! IR optical thickness of layers within narrowbands for diags ().
    72 !$OMP THREADPRIVATE(int_dtaui,int_dtauv) 
     72!$OMP THREADPRIVATE(int_dtaui,int_dtauv)
    7373
    7474      real,dimension(:,:,:,:),allocatable,save :: zpopthi ! IR optical properties [haze] within narrowbands for diags (dtau,tau,k,wbar,gbar,drayaer,taugaz,dcont).
  • trunk/LMDZ.TITAN/libf/phytitan/physiq_mod.F90

    r3682 r4013  
    220220      real zh(ngrid,nlayer)               ! Potential temperature (K).
    221221      real pw(ngrid,nlayer)               ! Vertical velocity (m/s). (NOTE : >0 WHEN DOWNWARDS !!)
     222      real omega(ngrid,nlayer)            ! omega velocity (Pa/s, >0 when downward)
    222223
    223224      integer l,ig,ierr,iq,nw,isoil,ilat,lat_idx,i,j
     
    814815         pw(:,l)=(pw(:,l)*r*pt(:,l)) / (pplay(:,l)*cell_area(:))
    815816      enddo
     817      ! omega in Pa/s
     818      do l=1,nlayer-1
     819         omega(1:ngrid,l)=0.5*(flxw(1:ngrid,l)+flxw(1:ngrid,l+1))
     820       enddo
     821       omega(1:ngrid,nlayer)=0.5*flxw(1:ngrid,nlayer) ! since flxw(nlayer+1)=0
     822       do l=1,nlayer
     823         omega(1:ngrid,l)=g*omega(1:ngrid,l)/cell_area(1:ngrid)
     824       enddo
    816825
    817826!---------------------------------
     
    14371446      enddo
    14381447
    1439       ! [Forcage de la photochimie pour les nuages]
     1448      ! [Temporary: adapted photochemistry for clouds]
    14401449      if (callclouds) then
    14411450         do ig = 1, ngrid
     
    14441453               !-------
    14451454               if(trim(nameOfTracer(gazs_indx(iq))) .eq. "C2H2") then
    1446                   pdq(ig,nlayer-3:,gazs_indx(iq)) = (4.0e-5 * rat_mmol(gazs_indx(iq)) - pq(ig,nlayer-3:,gazs_indx(iq))) / ptimestep
     1455                  pdq(ig,nlayer-3:,gazs_indx(iq)) = (3.0e-5 * rat_mmol(gazs_indx(iq)) - pq(ig,nlayer-3:,gazs_indx(iq))) / ptimestep
    14471456               endif
    14481457               ! C2H6 :
    14491458               !-------
    14501459               if(trim(nameOfTracer(gazs_indx(iq))) .eq. "C2H6") then
    1451                   pdq(ig,nlayer-3:,gazs_indx(iq)) = (8.0e-5 * rat_mmol(gazs_indx(iq)) - pq(ig,nlayer-3:,gazs_indx(iq))) / ptimestep
     1460                  pdq(ig,nlayer-3:,gazs_indx(iq)) = (6.0e-5 * rat_mmol(gazs_indx(iq)) - pq(ig,nlayer-3:,gazs_indx(iq))) / ptimestep
     1461               endif
     1462               ! AC6H6 :
     1463               !--------
     1464               if(trim(nameOfTracer(gazs_indx(iq))) .eq. "AC6H6") then
     1465                  pdq(ig,nlayer-5:,gazs_indx(iq)) = (5.0e-11 * rat_mmol(gazs_indx(iq)) - pq(ig,nlayer-5:,gazs_indx(iq))) / ptimestep
    14521466               endif
    14531467               ! HCN :
    14541468               !------
    14551469               if(trim(nameOfTracer(gazs_indx(iq))) .eq. "HCN") then
    1456                   pdq(ig,nlayer-3:,gazs_indx(iq)) = (2.0e-5 * rat_mmol(gazs_indx(iq)) - pq(ig,nlayer-3:,gazs_indx(iq))) / ptimestep
     1470                  pdq(ig,nlayer-3:,gazs_indx(iq)) = (5.0e-6 * rat_mmol(gazs_indx(iq)) - pq(ig,nlayer-3:,gazs_indx(iq))) / ptimestep
    14571471               endif
    1458                ! AC6H6 :
    1459                !--------
    1460                if(trim(nameOfTracer(gazs_indx(iq))) .eq. "AC6H6") then
    1461                   pdq(ig,nlayer-3:,gazs_indx(iq)) = (2.0e-5 * rat_mmol(gazs_indx(iq)) - pq(ig,nlayer-3:,gazs_indx(iq))) / ptimestep
     1472               ! HC3N :
     1473               !-------
     1474               if(trim(nameOfTracer(gazs_indx(iq))) .eq. "HC3N") then
     1475                  pdq(ig,nlayer-3:,gazs_indx(iq)) = (5.0e-8 * rat_mmol(gazs_indx(iq)) - pq(ig,nlayer-3:,gazs_indx(iq))) / ptimestep
    14621476               endif
    14631477            enddo
     
    17371751      CALL send_xios_field("v",zv)
    17381752      CALL send_xios_field("w",pw)
     1753      CALL send_xios_field("omega",omega)
    17391754
    17401755      CALL send_xios_field("area",cell_area)
     
    19641979         CALL send_xios_field("evapCH4",dycevapCH4(:)) ! Pseudo-evaporation flux (mol/mol/s)
    19651980         CALL send_xios_field("tankCH4",tankCH4(:))    ! CH4 tank at the surface (m)
     1981         CALL send_xios_field("sphumCH4",zq(:,:,7+nmicro)/(1+zq(:,:,7+nmicro))) ! CH4 Specific Humidity (kg/kg)
    19661982
    19671983         ! Atmosphere (3D) :
Note: See TracChangeset for help on using the changeset viewer.