Changeset 3204


Ignore:
Timestamp:
Feb 8, 2024, 9:38:16 AM (10 months ago)
Author:
emillour
Message:

Generic PCM:
Code cleanup. Remove obsolete "sourceevol" option and related variables.
EM

Location:
trunk/LMDZ.GENERIC
Files:
5 edited

Legend:

Unmodified
Added
Removed
  • trunk/LMDZ.GENERIC/README

    r3194 r3204  
    18381838== 31/01/2024 == NC
    18391839Small corrections to enable compilation with WRF4.
     1840
     1841== 08/02/2024 == EM
     1842Code cleanup. Remove obsolete "sourceevol" option and related variables.
  • trunk/LMDZ.GENERIC/libf/phystd/callkeys_mod.F90

    r2958 r3204  
    5757!$OMP THREADPRIVATE(aerogeneric)
    5858      logical,save :: hydrology
    59       logical,save :: sourceevol
    6059      logical,save :: CLFvarying
    6160      logical,save :: nosurf
    6261      logical,save :: oblate
    63 !$OMP THREADPRIVATE(hydrology,sourceevol,CLFvarying,nosurf,oblate)
     62!$OMP THREADPRIVATE(hydrology,CLFvarying,nosurf,oblate)
    6463      logical,save :: ok_slab_ocean
    6564      logical,save :: ok_slab_sic
     
    143142      real,save :: tau_relax
    144143      real,save :: cloudlvl
    145       real,save :: icetstep
    146144      real,save :: intheat
    147 !$OMP THREADPRIVATE(Tsaldiff,tau_relax,cloudlvl,icetstep,intheat)
     145!$OMP THREADPRIVATE(Tsaldiff,tau_relax,cloudlvl,intheat)
    148146      real,save :: flatten
    149147      real,save :: Rmean
  • trunk/LMDZ.GENERIC/libf/phystd/inifis_mod.F90

    r3100 r3204  
    10221022     if (is_master) write(*,*)trim(rname)//": hydrology = ",hydrology
    10231023
    1024      if (is_master) write(*,*)trim(rname)//": Evolve surface water sources ?"
    1025      sourceevol=.false. ! default value
    1026      call getin_p("sourceevol",sourceevol)
    1027      if (is_master) write(*,*)trim(rname)//": sourceevol = ",sourceevol
    1028 
    1029      if (is_master) write(*,*)trim(rname)//": Ice evolution timestep ?"
    1030      icetstep=100.0 ! default value
    1031      call getin_p("icetstep",icetstep)
    1032      if (is_master) write(*,*)trim(rname)//": icetstep = ",icetstep
    1033          
    10341024     if (is_master) write(*,*)trim(rname)//": Spectral Dependant albedo ?"
    10351025     albedo_spectral_mode=.false. ! default value
  • trunk/LMDZ.GENERIC/libf/phystd/phys_state_var_mod.F90

    r3100 r3204  
    8888      real,allocatable,dimension(:,:,:),save :: nueffrad ! Aerosol effective radius variance. By RW
    8989!$OMP THREADPRIVATE(qsurf_hist,nueffrad)
    90 
    91       real,allocatable,dimension(:),save :: ice_initial
    92       real,allocatable,dimension(:),save :: ice_min
    93 !$OMP THREADPRIVATE(ice_initial,ice_min)
    9490
    9591      real,dimension(:),allocatable,save ::  pctsrf_sic
     
    170166        ALLOCATE(reffrad(klon,klev,naerkind))
    171167        ALLOCATE(nueffrad(klon,klev,naerkind))
    172         ALLOCATE(ice_initial(klon))
    173         ALLOCATE(ice_min(klon))
    174168        ALLOCATE(fluxsurf_lw(klon))
    175169        ALLOCATE(fluxsurf_lw1(klon))
     
    263257        DEALLOCATE(reffrad)
    264258        DEALLOCATE(nueffrad)
    265         DEALLOCATE(ice_initial)
    266         DEALLOCATE(ice_min)
    267259        DEALLOCATE(fluxsurf_lw)
    268260        DEALLOCATE(fluxsurf_lw1)
  • trunk/LMDZ.GENERIC/libf/phystd/physiq_mod.F90

    r3100 r3204  
    6161                              calltherm, CLFvarying, co2cond, corrk, diagdtau, &
    6262                              diurnal, enertest, fat1au, flatten, j2, &
    63                               hydrology, icetstep, intheat, iradia, kastprof, &
     63                              hydrology, intheat, iradia, kastprof, &
    6464                              lwrite, mass_redistrib, massplanet, meanOLR, &
    6565                              nearco2cond, newtonian, noseason_day, oblate, &
    6666                              ok_slab_ocean, photochem, rings_shadow, rmean, &
    6767                              season, sedimentation,generic_condensation, &
    68                               sourceevol, specOLR, &
     68                              specOLR, &
    6969                              startphy_file, testradtimes, tlocked, &
    7070                              tracer, UseTurbDiff, water, watercond, &
     
    454454!$OMP THREADPRIVATE(reffcol)
    455455
    456 !     Sourceevol for 'accelerated ice evolution'. By RW
    457       real delta_ice,ice_tot
    458       integer num_run
    459       logical,save :: ice_update
    460456!  Non-oro GW tendencies
    461457      REAL d_u_hin(ngrid,nlayer), d_v_hin(ngrid,nlayer)
     
    545541                       rnat,pctsrf_sic,tslab, tsea_ice,sea_ice)
    546542
    547 !!         call WriteField_phy("post_phyetat0_qsurf",qsurf(1:ngrid,igcm_h2o_vap),1)
    548543#else   
    549544
     
    582577         call surfini(ngrid,nq,qsurf,albedo,albedo_bareground,albedo_snow_SPECTV,albedo_co2_ice_SPECTV)
    583578
    584 !!        call WriteField_phy("post_surfini1_qsurf",qsurf(1:ngrid,igcm_h2o_vap),1)
    585 !!        call WriteField_phy("post_surfini2_qsurf",qsurf(1:ngrid,igcm_h2o_vap),1)
    586          
    587579!        Initialize orbital calculation.
    588580!        ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
     
    654646           
    655647         endif ! end of 'callsoil'.
    656 
    657 !!         call WriteField_phy("post_callsoil_qsurf",qsurf(1:ngrid,igcm_h2o_vap),1)
    658648         
    659649         icount=1
    660 
    661 !        Decide whether to update ice at end of run.
    662 !        ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
    663          ice_update=.false.
    664          if(sourceevol)then
    665 !$OMP MASTER
    666             open(128,file='num_run',form='formatted', &
    667                      status="old",iostat=ierr)
    668             if (ierr.ne.0) then
    669                write(*,*) "physiq: Error! No num_run file!"
    670                write(*,*) " (which is needed for sourceevol option)"
    671                stop
    672             endif
    673             read(128,*) num_run
    674             close(128)
    675 !$OMP END MASTER
    676 !$OMP BARRIER
    677        
    678             if(num_run.ne.0.and.mod(num_run,2).eq.0)then
    679                print*,'Updating ice at end of this year!'
    680                ice_update=.true.
    681                ice_min(:)=1.e4
    682             endif
    683            
    684          endif ! end of 'sourceevol'.
    685 
    686650
    687651         ! Here is defined the type of the surface : Continent or Ocean.
     
    741705            endif
    742706
    743             if(ice_update)then
    744                ice_initial(:)=qsurf(:,igcm_h2o_ice)
    745             endif
    746 
    747          endif
    748 
    749 !!         call WriteField_phy("post_ice_update_qsurf",qsurf(1:ngrid,igcm_h2o_vap),1)
     707         endif
    750708
    751709!        Set metallicity for GCS
     
    20061964         qsurf_hist(:,:) = qsurf(:,:)
    20071965
    2008          if(ice_update)then
    2009             ice_min(1:ngrid)=min(ice_min(1:ngrid),qsurf(1:ngrid,igcm_h2o_ice))
    2010          endif
    2011 
    20121966      endif! end of if 'tracer'
    20131967
     
    23222276         ztime_fin = ptime + ptimestep/(float(iphysiq)*daysec)
    23232277
    2324          ! Update surface ice distribution to iterate to steady state if requested
    2325          if(ice_update)then
    2326 
    2327             do ig=1,ngrid
    2328 
    2329                delta_ice = (qsurf(ig,igcm_h2o_ice)-ice_initial(ig))
    2330                
    2331                ! add multiple years of evolution
    2332                qsurf_hist(ig,igcm_h2o_ice) = qsurf_hist(ig,igcm_h2o_ice) + delta_ice*icetstep
    2333 
    2334                ! if ice has gone -ve, set to zero
    2335                if(qsurf_hist(ig,igcm_h2o_ice).lt.0.0)then
    2336                   qsurf_hist(ig,igcm_h2o_ice) = 0.0
    2337                endif
    2338 
    2339                ! if ice is seasonal, set to zero (NEW)
    2340                if(ice_min(ig).lt.0.01)then
    2341                   qsurf_hist(ig,igcm_h2o_ice) = 0.0
    2342                endif
    2343 
    2344             enddo
    2345 
    2346             ! enforce ice conservation
    2347             ice_tot= SUM(qsurf_hist(:,igcm_h2o_ice)*cell_area(:) )/SUM(cell_area(:))
    2348             qsurf_hist(:,igcm_h2o_ice) = qsurf_hist(:,igcm_h2o_ice)*(icesrf/ice_tot)
    2349 
    2350          endif
    23512278#ifndef MESOSCALE
    23522279         
     
    26612588            endif
    26622589
    2663             if(ice_update)then
    2664                call writediagfi(ngrid,"ice_min","min annual ice","m",2,ice_min)
    2665                call writediagfi(ngrid,"ice_ini","initial annual ice","m",2,ice_initial)
    2666             endif
    2667 
    2668             ! do ig=1,ngrid
    2669             !    if(tau_col(ig).gt.1.e3)then
    2670             !       print*,'WARNING: tau_col=',tau_col(ig)
    2671             !       print*,'at ig=',ig,'in PHYSIQ'
    2672             !    endif         
    2673             ! end do
    2674 
    26752590            call writediagfi(ngrid,"tau_col","Total aerosol optical depth","[]",2,tau_col)
    26762591
Note: See TracChangeset for help on using the changeset viewer.