Ignore:
Timestamp:
May 15, 2024, 8:29:23 PM (6 months ago)
Author:
afalco
Message:

Pluto PCM:
Include cooling, hazes in radiative module
AF

File:
1 edited

Legend:

Unmodified
Added
Removed
  • trunk/LMDZ.PLUTO/libf/phypluto/physiq_mod.F90

    r3275 r3329  
    5454                              fast,fasthaze,haze,metcloud,monoxcloud,&
    5555                              n2cond,nearn2cond,noseason_day,conservn2, &
    56                               kbo,triton,paleo,paleoyears, &
     56                              convergeps,kbo,triton,paleo,paleoyears, &
    5757                              carbox, methane, oldplutovdifc, oldplutocorrk, &
    5858                              aerohaze,haze_proffix,source_haze, &
     
    6767      use phys_state_var_mod
    6868      use callcorrk_mod, only: callcorrk
    69     !   use callcorrk_pluto_mod, only: callcorrk_pluto
     69      use callcorrk_pluto_mod, only: callcorrk_pluto
    7070      use vdifc_mod, only: vdifc
    7171      use vdifc_pluto_mod, only: vdifc_pluto
     
    260260      REAL,save  :: tcond1p4Pa
    261261      DATA tcond1p4Pa/38/
     262      real :: tidat(ngrid,nsoilmx)    ! thermal inertia soil
    262263
    263264
     
    306307      real zlss                      ! Sub solar point longitude (radians).
    307308      real zday                      ! Date (time since Ls=0, calculated in sols).
     309      REAL,save :: saveday           ! saved date
     310      REAL,save :: savedeclin        ! saved declin
    308311      real zzlay(ngrid,nlayer)       ! Altitude at the middle of the atmospheric layers.
    309312      real zzlev(ngrid,nlayer+1)     ! Altitude at the atmospheric layer boundaries.
     
    619622         call iniorbit(apoastr,periastr,year_day,peri_day,obliquit)
    620623
     624         savedeclin=0.
     625         saveday=pday
     626         !adjust=0. ! albedo adjustment for convergeps
    621627
    622628!        Initialize soil.
     
    871877         if ((ngrid.eq.1).and.(global1d)) then ! Fixed zenith angle 'szangle' in 1D simulations w/ globally-averaged sunlight.
    872878            mu0 = cos(pi*szangle/180.0)
     879            fract= 1/(4*mu0) ! AF24: from pluto.old
    873880         endif
    874881
    875882      endif
    876883
    877       ! AF24: TODO insert surfprop for pluto & triton around here
     884
     885!     Pluto albedo /IT changes depending on surface ices (only in 3D)
     886!     ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
     887      if (ngrid.ne.1) then
     888
     889         !! Specific to change albedo of N2 so that Psurf
     890         !! converges toward 1.4 Pa in "1989" seasons for Triton
     891         !! converges toward 1.1 Pa in "2015" seasons for Pluto
     892         if (convergeps) then
     893            if (triton) then
     894               ! 1989 declination
     895               if (declin*180./pi.gt.-46..and.declin*180./pi.lt.-45.   &
     896            .and.zday.gt.saveday+1000.   &
     897            .and.declin.lt.savedeclin) then
     898               call globalaverage2d(ngrid,pplev(:,1),globave)
     899               if (globave.gt.1.5) then
     900                     adjust=adjust+0.005
     901               else if (globave.lt.1.3) then
     902                     adjust=adjust-0.005
     903               endif
     904               saveday=zday
     905               endif
     906            else
     907               ! Pluto : 2015 declination current epoch
     908               if (declin*180./pi.gt.50.and.declin*180./pi.lt.51.  &
     909            .and.zday.gt.saveday+10000.  &
     910            .and.declin.gt.savedeclin) then
     911               call globalaverage2d(ngrid,pplev(:,1),globave)
     912               if (globave.gt.1.2) then
     913                     adjust=adjust+0.005
     914               else if (globave.lt.1.) then
     915                     adjust=adjust-0.005
     916               endif
     917               saveday=zday
     918               endif
     919            endif
     920         end if
     921      end if ! if ngrid ne 1
     922
     923      call surfprop(ngrid,nq,fract,qsurf,tsurf,tidat,   &
     924      capcal,adjust,dist_star,albedo,emis,flusurfold,ptimestep,   &
     925      zls)
     926      ! do i=2,ngrid
     927      !    albedo(i,:) = albedo(1,:)
     928      ! enddo
    878929
    879930      if (callrad) then
     
    920971
    921972               ! standard callcorrk
    922                ! clearsky=.false.
    923             !    if (oldplutocorrk) then
    924             !       call callcorrk_pluto(icount,ngrid,nlayer,pq,nq,qsurf,          &
    925             !                    albedo,emis,mu0,pplev,pplay,pt,                   &
    926             !                    tsurf,fract,dist_star,aerosol, &
    927             !                    zdtlw,zdtsw,fluxsurf_lw,fluxsurf_sw,fluxtop_lw,  &
    928             !                    fluxabs_sw,fluxtop_dn,reffrad,tau_col,ptime,pday, &
    929             !                    firstcall,lastcall,zzlay)
    930             !    else
    931                 call callcorrk(ngrid,nlayer,pq,nq,qsurf,                          &
     973               if (oldplutocorrk) then
     974                  call callcorrk_pluto(icount,ngrid,nlayer,pq,nq,qsurf,          &
     975                               albedo(:,1),emis,mu0,pplev,pplay,pt,                   &
     976                               zzlay,tsurf,fract,dist_star,aerosol,              &
     977                               zdtlw,zdtsw,fluxsurf_lw,fluxsurf_sw,fluxtop_lw,  &
     978                               fluxabs_sw,fluxtop_dn,reffrad,tau_col,ptime,pday, &
     979                               cloudfrac,totcloudfrac,.false.,                  &
     980                               firstcall,lastcall)
     981               else
     982                call callcorrk(ngrid,nlayer,pq,nq,qsurf,  &
    932983                              albedo,albedo_equivalent,emis,mu0,pplev,pplay,pt,   &
    933984                              zzlay,tsurf,fract,dist_star,aerosol,muvar,                &
     
    938989                              tau_col,cloudfrac,totcloudfrac,                     &
    939990                              .false.,firstcall,lastcall)
    940             !    endif ! oldplutocorrk
     991               endif ! oldplutocorrk
    941992                !GG (feb2021): Option to "artificially" decrease the raditive time scale in
    942993                !the deep atmosphere  press > 0.1 bar. Suggested by MT.
     
    9561007
    9571008                ! AF24: removed CLFvarying Option
    958 
    959                ! if(ok_slab_ocean) then
    960                !    tsurf(:)=tsurf2(:)
    961                ! endif
    962 
    9631009
    9641010               ! Radiative flux from the sky absorbed by the surface (W.m-2).
     
    10521098
    10531099         if (oldplutovdifc) then
    1054             zflubid(1:ngrid)=fluxrad(1:ngrid)+fluxgrd(1:ngrid)
    10551100            zdum1(:,:) = 0
    10561101            zdum2(:,:) = 0
     
    10661111                    zdqdif,zdqsdif,qsat_ch4,qsat_ch4_l1) !,zq1temp_ch4,qsat_ch4)
    10671112
    1068             pdv(1:ngrid,1:nlayer)=pdv(1:ngrid,1:nlayer)+zdvdif(1:ngrid,1:nlayer)
    1069             pdu(1:ngrid,1:nlayer)=pdu(1:ngrid,1:nlayer)+zdudif(1:ngrid,1:nlayer)
    1070             pdt(1:ngrid,1:nlayer)=pdt(1:ngrid,1:nlayer)+zdhdif(1:ngrid,1:nlayer)*zpopsk(1:ngrid,1:nlayer)
    1071 
    10721113            zdtdif(1:ngrid,1:nlayer)=zdhdif(1:ngrid,1:nlayer)*zpopsk(1:ngrid,1:nlayer) ! for diagnostic only
    1073             zdtsurf(1:ngrid)=zdtsurf(1:ngrid)+zdtsdif(1:ngrid)
    10741114
    10751115            bcond=1./tcond1p4Pa
    10761116            acond=r/lw_n2
    1077 
    1078             if (tracer) then
    1079                pdq(1:ngrid,1:nlayer,1:nq)=pdq(1:ngrid,1:nlayer,1:nq)+ zdqdif(1:ngrid,1:nlayer,1:nq)
    1080                dqsurf(1:ngrid,1:nq)=dqsurf(1:ngrid,1:nq) + zdqsdif(1:ngrid,1:nq)
    1081             end if ! of if (tracer)
    10821117
    10831118            !------------------------------------------------------------------
     
    13791414         zdqphot_prec(:,:)=0.
    13801415         zdqphot_ch4(:,:)=0.
     1416         zdqhaze(:,:,:)=0
    13811417         ! Forcing to a fixed haze profile if haze_proffix
    13821418         if (haze_proffix.and.i_haze.gt.0.) then
    1383          call haze_prof(ngrid,nlayer,zzlay,pplay,pt,  &
    1384                                   reffrad,profmmr)
    1385          zdqhaze(:,:,i_haze)=(profmmr(:,:)-pq(:,:,igcm_haze))  &
    1386                                                   /ptimestep
     1419            call haze_prof(ngrid,nlayer,zzlay,pplay,pt,  &
     1420                           reffrad,profmmr)
     1421            zdqhaze(:,:,i_haze)=(profmmr(:,:)-pq(:,:,igcm_haze))  &
     1422                                 /ptimestep
    13871423         else
    1388          call hazecloud(ngrid,nlayer,nq,ptimestep, &
    1389             pplay,pplev,pq,pdq,dist_star,mu0,zfluxuv,zdqhaze,   &
    1390             zdqphot_prec,zdqphot_ch4,zdqconv_prec,declin)
     1424            call hazecloud(ngrid,nlayer,nq,ptimestep, &
     1425               pplay,pplev,pq,pdq,dist_star,mu0,zfluxuv,zdqhaze,   &
     1426               zdqphot_prec,zdqphot_ch4,zdqconv_prec,declin)
    13911427         endif
    13921428
     
    15891625      ! todo: should be placed in haze and use tendency of n2 instead of flusurf
    15901626      IF (source_haze) THEN
     1627         write(*,*) "Source haze not supported yet."
     1628         stop
    15911629            !  call hazesource(ngrid,nlayer,nq,ptimestep,  &
    15921630            !                 pplev,flusurf,mu0,zdq_source)
Note: See TracChangeset for help on using the changeset viewer.