Changeset 3335 for trunk/LMDZ.GENERIC


Ignore:
Timestamp:
May 18, 2024, 8:21:24 PM (6 months ago)
Author:
emillour
Message:

Generic PCM:
Add reading/writing of surface albedo in (re)startfi.nc to
improve model restartability. For now only the simpler case
of non-spectral dependent surface albedo is handled.
Turned "surfini" in a module in the process.
Unrelated: added missing delarations in kcm1d so it compiles one again.
EM

Location:
trunk/LMDZ.GENERIC
Files:
9 edited

Legend:

Unmodified
Added
Removed
  • trunk/LMDZ.GENERIC/changelog.txt

    r3332 r3335  
    19301930not 1 this extra computation of radiative tendencies will break
    19311931model restartability (the famous "1+1=2" requirement).
     1932
     1933== 18/05/2024 == EM
     1934Add reading/writing of surface albedo in (re)startfi.nc to
     1935improve model restartability. For now only the simpler case
     1936of non-spectral dependent surface albedo is handled.
     1937Turned "surfini" in a module in the process.
     1938Unrelated: added missing delarations in kcm1d so it compiles one again.
  • trunk/LMDZ.GENERIC/libf/dynphy_lonlat/phystd/newstart.F

    r3116 r3335  
    2121      USE tracer_h, ONLY: igcm_co2_ice, igcm_h2o_vap, igcm_h2o_ice
    2222      USE comsoil_h, ONLY: nsoilmx, layer, mlayer, inertiedat
     23      USE radinc_h, only : L_NSPECTV ! number of spectral bands in the visible
    2324      USE surfdat_h, ONLY: phisfi, albedodat,
    2425     &                     zmea, zstd, zsig, zgam, zthe
     
    112113      REAL q2(ngridmx,llm+1)
    113114!      REAL rnaturfi(ngridmx)
    114       real alb(iip1,jjp1),albfi(ngridmx) ! albedos
     115      real alb(iip1,jjp1),albfi(ngridmx) ! bare ground albedos
     116      real albedodyn(iip1,jjp1),albedofi(ngridmx) ! surface albedos
     117      real spectral_albedofi(ngridmx,L_NSPECTV) ! spectral surface albedo
    115118      real,ALLOCATABLE :: ith(:,:,:),ithfi(:,:) ! thermal inertia (3D)
    116119      real surfith(iip1,jjp1),surfithfi(ngridmx) ! surface thermal inertia (2D)
     
    361364        fichnom = 'startfi.nc'
    362365        CALL phyetat0(.true.,ngridmx,llm,fichnom,tab0,Lmodif,nsoilmx,
    363      .        nqtot,day_ini,time,
    364      .        tsurf,tsoil,emis,q2,qsurf,   !) ! temporary modif by RDW
    365      .        cloudfrac,totalfrac,hice,rnat,pctsrf_sic,tslab,tsea_ice,
    366      .        sea_ice)
     366     &        nqtot,day_ini,time,
     367     &        tsurf,tsoil,emis,spectral_albedofi,q2,qsurf,
     368     &        cloudfrac,totalfrac,hice,rnat,pctsrf_sic,tslab,tsea_ice,
     369     &        sea_ice)
    367370
    368371        ! copy albedo and soil thermal inertia on (local) physics grid
    369372        do i=1,ngridmx
    370373          albfi(i) = albedodat(i)
     374          albedofi(i)= spectral_albedofi(i,1) ! assume same albedo at all wavelenghts
    371375          do j=1,nsoilmx
    372376           ithfi(i,j) = inertiedat(i,j)
     
    380384        ! to correctly recast things on physics grid)
    381385        call gr_fi_dyn(1,ngridmx,iip1,jjp1,albfi,alb)
     386        call gr_fi_dyn(1,ngridmx,iip1,jjp1,albedofi,albedodyn)
    382387        call gr_fi_dyn(nsoilmx,ngridmx,iip1,jjp1,ithfi,ith)
    383388        call gr_fi_dyn(1,ngridmx,iip1,jjp1,surfithfi,surfith)
     
    16621667      call physdem1("restartfi.nc",nsoilmx,ngridmx,llm,nqtot,
    16631668     &                dtphys,real(day_ini),
    1664      &                tsurf,tsoil,emis,q2,qsurf,
     1669     &                tsurf,tsoil,emis,spectral_albedofi,q2,qsurf,
    16651670     &                cloudfrac,totalfrac,hice,
    16661671     &                rnat,pctsrf_sic,tslab,tsea_ice,sea_ice)
  • trunk/LMDZ.GENERIC/libf/dynphy_lonlat/phystd/start2archive.F

    r3100 r3335  
    2121      use infotrac, only: infotrac_init, nqtot, tname
    2222      USE comsoil_h
    23      
     23      USE radinc_h, only : L_NSPECTV ! number of spectral bands in the visible
    2424!      use slab_ice_h, only: noceanmx
    2525      USE ocean_slab_mod, ONLY: nslay
     
    7373      REAL,ALLOCATABLE :: qsurf(:,:)
    7474      REAL emis(ngridmx)
     75      REAL :: albedo(ngridmx,L_NSPECTV) ! spectral surface albedo
    7576      INTEGER start,length
    7677      PARAMETER (length = 100)
     
    99100      REAL,ALLOCATABLE :: qsurfS(:,:)
    100101      REAL emisS(ip1jmp1)
     102      REAL :: albedoS(ngridmx) ! surface albedo assumed same at all wavelengths
    101103
    102104!     added by FF for cloud fraction setup
     
    245247      CALL phyetat0(.true.,ngridmx,llm,fichnom,0,Lmodif,nsoilmx,nqtot,
    246248     .      day_ini_fi,timefi,
    247      .      tsurf,tsoil,emis,q2,qsurf,
     249     .      tsurf,tsoil,emis,albedo,q2,qsurf,
    248250!       change FF 05/2011
    249251     .       cloudfrac,totalcloudfrac,hice,
     
    351353      call gr_fi_dyn(nsoilmx,ngridmx,iip1,jjp1,inertiedat,ithS)
    352354      call gr_fi_dyn(1,ngridmx,iip1,jjp1,emis,emisS)
     355      call gr_fi_dyn(1,ngridmx,iip1,jjp1,albedo(1,1),albedoS)
    353356      call gr_fi_dyn(llm+1,ngridmx,iip1,jjp1,q2,q2S)
    354357      call gr_fi_dyn(nqtot,ngridmx,iip1,jjp1,qsurf,qsurfS)
     
    455458!     &  'kg/m2',2,co2iceS)
    456459      call write_archive(nid,ntime,'emis','grd emis',' ',2,emisS)
     460      call write_archive(nid,ntime,'albedo','surface albedo',' ',
     461     &                   2,albedoS)
    457462      call write_archive(nid,ntime,'ps','Psurf','Pa',2,ps)
    458463      call write_archive(nid,ntime,'tsurf','surf T','K',2,tsurfS)
  • trunk/LMDZ.GENERIC/libf/phystd/dyn1d/kcm1d.F90

    r3233 r3335  
    106106  LOGICAL :: moderntracdef=.false. ! JVO, YJ : modern traceur.def
    107107
     108  character(len=100) :: dt_file
     109  integer :: ios
     110  integer :: k
     111 
    108112  ! --------------
    109113  ! Initialisation
  • trunk/LMDZ.GENERIC/libf/phystd/dyn1d/rcm1d.F

    r3105 r3335  
    77      use infotrac, only: nqtot, tname
    88      use tracer_h, only: noms, is_condensable
     9      use radinc_h, only : L_NSPECTV
    910      use surfdat_h, only: albedodat, phisfi, dryness,
    1011     &                     zmea, zstd, zsig, zgam, zthe,
     
    9495      integer :: i_h2o_ice=0     ! tracer index of h2o ice
    9596      integer :: i_h2o_vap=0     ! tracer index of h2o vapor
    96       REAL emis(1)               ! surface layer
     97      REAL emis(1)               ! emissivity of surface
     98      real :: albedo(1,L_NSPECTV) ! surface albedo in various spectral bands
    9799      REAL q2(llm+1)             ! Turbulent Kinetic Energy
    98100      REAL zlay(llm)             ! altitude estimee dans les couches (km)
     
    883885      call getin("albedo",albedodat(1))
    884886      write(*,*) " albedo = ",albedodat(1)
     887      ! Initialize surface albedo to that of bare ground
     888      albedo(1,:)=albedodat(1)
    885889
    886890      inertiedat(1,1)=400 ! default value for inertiedat
     
    954958      call physdem1("startfi.nc",nsoilmx,1,llm,nq,
    955959     &                dtphys,time,
    956      &                tsurf,tsoil,emis,q2,qsurf,
     960     &                tsurf,tsoil,emis,albedo,q2,qsurf,
    957961     &                cloudfrac,totcloudfrac,hice,
    958962     &                rnat,pctsrf_sic,tslab,tsea_ice,sea_ice)
  • trunk/LMDZ.GENERIC/libf/phystd/phyetat0_mod.F90

    r3100 r3335  
    77subroutine phyetat0 (startphy_file, &
    88                     ngrid,nlayer,fichnom,tab0,Lmodif,nsoil,nq, &
    9                      day_ini,time,tsurf,tsoil, &
    10                      emis,q2,qsurf,cloudfrac,totcloudfrac,hice, &
     9                     day_ini,time,tsurf,tsoil,emis,albedo, &
     10                     q2,qsurf,cloudfrac,totcloudfrac,hice, &
    1111                     rnat,pctsrf_sic,tslab,tsea_ice,sea_ice)
    1212
     
    1818  use tabfi_mod, only: tabfi
    1919  USE tracer_h, ONLY: noms, igcm_h2o_vap
     20  USE radinc_h, ONLY: L_NSPECTV
    2021  USE surfdat_h, only: phisfi, albedodat, zmea, zstd, zsig, zgam, zthe
    2122  use iostart, only: nid_start, open_startphy, close_startphy, &
     
    4849  real,intent(out) :: tsoil(ngrid,nsoil) ! soil temperature
    4950  real,intent(out) :: emis(ngrid) ! surface emissivity
     51  real,intent(out) :: albedo(ngrid,L_NSPECTV) ! albedo of the surface
    5052  real,intent(out) :: q2(ngrid,nlayer+1) !
    5153  real,intent(out) :: qsurf(ngrid,nq) ! tracers on surface
     
    129131
    130132if (startphy_file) then
    131   ! Load bare ground albedo:
     133  ! Load bare ground albedo: (will be stored in surfdat_h)
    132134  call get_field("albedodat",albedodat,found)
    133135  if (.not.found) then
     
    143145write(*,*) "phyetat0: Bare ground albedo <albedodat> range:", &
    144146             minval(albedodat), maxval(albedodat)
     147
     148if (startphy_file) then
     149  ! Load surface albedo (for now assume it is spectrally homogeneous)
     150  call get_field("albedo",albedo(:,1),found)
     151  if (.not.found) then
     152    write(*,*) modname//": Failed loading <albedo>"
     153    write(*,*) " setting it to bare ground albedo"
     154    albedo(1:ngrid,1)=albedodat(1:ngrid)
     155  endif
     156  ! copy value to all spectral bands
     157  do i=2,L_NSPECTV
     158    albedo(1:ngrid,i)=albedo(1:ngrid,1)
     159  enddo
     160else
     161  ! If no startfi file, use bare ground value
     162  do i=1,L_NSPECTV
     163    albedo(1:ngrid,i)=albedodat(1:ngrid)
     164  enddo
     165endif ! of if (startphy_file)
     166write(*,*) "phyetat0: Surface albedo <albedo> range:", &
     167             minval(albedo), maxval(albedo)
    145168
    146169! ZMEA
  • trunk/LMDZ.GENERIC/libf/phystd/phyredem.F90

    r3311 r3335  
    134134
    135135subroutine physdem1(filename,nsoil,ngrid,nlay,nq, &
    136                     phystep,time,tsurf,tsoil,emis,q2,qsurf, &
     136                    phystep,time,tsurf,tsoil,emis,albedo,q2,qsurf, &
    137137                    cloudfrac,totcloudfrac,hice, &
    138138                    rnat,pctsrf_sic,tslab,tsea_ice,sea_ice)
     
    141141                      put_var, put_field
    142142  use tracer_h, only: noms
     143  USE radinc_h, ONLY: L_NSPECTV
    143144!  use slab_ice_h, only: noceanmx
    144145  USE ocean_slab_mod, ONLY: nslay
     
    159160  real,intent(in) :: tsoil(ngrid,nsoil)
    160161  real,intent(in) :: emis(ngrid)
     162  real,intent(in) :: albedo(ngrid,L_NSPECTV)
    161163  real,intent(in) :: q2(ngrid,nlay+1)
    162164  real,intent(in) :: qsurf(ngrid,nq)
     
    189191  call put_field("emis","Surface emissivity",emis)
    190192 
     193  ! Surface albedo (assume homegeneous spectral albedo for now)
     194  call put_field("albedo","Surface albedo",albedo(:,1))
     195 
    191196  ! Planetary Boundary Layer
    192197  call put_field("q2","pbl wind variance",q2)
  • trunk/LMDZ.GENERIC/libf/phystd/physiq_mod.F90

    r3332 r3335  
    3939      use time_phylmdz_mod, only: ecritphy, iphysiq, nday
    4040      use phyetat0_mod, only: phyetat0
     41      use surfini_mod, only: surfini
    4142      use wstats_mod, only: callstats, wstats, mkstats
    4243      use phyredem, only: physdem0, physdem1
     
    592593         call phyetat0(startphy_file,                                 &
    593594                       ngrid,nlayer,"startfi.nc",0,0,nsoilmx,nq,      &
    594                        day_ini,time_phys,tsurf,tsoil,emis,q2,qsurf,   &
    595                        cloudfrac,totcloudfrac,hice,                   &
     595                       day_ini,time_phys,tsurf,tsoil,emis,albedo,     &
     596                       q2,qsurf,cloudfrac,totcloudfrac,hice,          &
    596597                       rnat,pctsrf_sic,tslab, tsea_ice,sea_ice)
    597598
     
    626627!        Initialize albedo calculation.
    627628!        ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
    628          albedo(:,:)=0.0
    629          albedo_bareground(:)=0.0
    630          albedo_snow_SPECTV(:)=0.0
    631          albedo_co2_ice_SPECTV(:)=0.0
    632          call surfini(ngrid,nq,qsurf,albedo,albedo_bareground,albedo_snow_SPECTV,albedo_co2_ice_SPECTV)
     629         call surfini(ngrid,nq,qsurf,albedo,albedo_bareground,&
     630                      albedo_snow_SPECTV,albedo_co2_ice_SPECTV)
    633631
    634632!        Initialize orbital calculation.
     
    23722370            call physdem1("restartfi.nc",nsoilmx,ngrid,nlayer,nq, &
    23732371                          ptimestep,ztime_fin,                    &
    2374                           tsurf,tsoil,emis,q2,qsurf_hist,         &
     2372                          tsurf,tsoil,emis,albedo,q2,qsurf_hist,  &
    23752373                          cloudfrac,totcloudfrac,hice,            &
    23762374                          rnat,pctsrf_sic,tslab,tsea_ice,sea_ice)
  • trunk/LMDZ.GENERIC/libf/phystd/surfini.F

    r1482 r3335  
     1      MODULE surfini_mod
     2     
     3      IMPLICIT NONE
     4     
     5      CONTAINS
     6
    17      SUBROUTINE surfini(ngrid,nq,qsurf,albedo,albedo_bareground,
    28     &                   albedo_snow_SPECTV,albedo_co2_ice_SPECTV)
    39
    4       USE surfdat_h, only: albedodat
    5       USE tracer_h, only: igcm_co2_ice
     10      USE surfdat_h, only: albedodat ! bare ground albedo
    611      use planetwide_mod, only: planetwide_maxval, planetwide_minval
    7       use radinc_h, only : L_NSPECTV
     12      use radinc_h, only : L_NSPECTV ! number of spectral bands in the visible
    813      use callkeys_mod, only : albedosnow, albedoco2ice
    914
     
    2429      INTEGER,INTENT(IN) :: ngrid
    2530      INTEGER,INTENT(IN) :: nq
    26       REAL,INTENT(OUT) :: albedo(ngrid,L_NSPECTV)
     31      REAL,INTENT(IN) :: albedo(ngrid,L_NSPECTV)
    2732      REAL,INTENT(OUT) :: albedo_bareground(ngrid)
    2833      REAL,INTENT(OUT) :: albedo_snow_SPECTV(L_NSPECTV)
     
    4550      DO ig=1,ngrid
    4651         albedo_bareground(ig)=albedodat(ig)
    47          DO nw=1,L_NSPECTV
    48             albedo(ig,nw)=albedo_bareground(ig)
    49          ENDDO
    5052      ENDDO
    5153      call planetwide_minval(albedo_bareground,min_albedo)
     
    5557
    5658
    57       ! Step 3 : We modify the albedo considering some CO2 at the surface. We dont take into account water ice (this is made in hydrol after the first timestep) ...
    58       if (igcm_co2_ice.ne.0) then
    59          DO ig=1,ngrid
    60             IF (qsurf(ig,igcm_co2_ice) .GT. 1.) THEN ! This was changed by MT2015. Condition for ~1mm of CO2 ice deposit.
    61                DO nw=1,L_NSPECTV
    62                   albedo(ig,nw)=albedo_co2_ice_SPECTV(nw)
    63                ENDDO
    64             END IF   
    65          ENDDO   
    66       else
    67          write(*,*) "surfini: No CO2 ice tracer on surface  ..."
    68          write(*,*) "         and therefore no albedo change."
    69       endif     
     59      ! Step 3 : Surface albedo already loaded from startfi.nc
     60      ! merely report vmin/max values here
     61
    7062      call planetwide_minval(albedo,min_albedo)
    7163      call planetwide_maxval(albedo,max_albedo)
     
    7466
    7567
    76       END
     68      END SUBROUTINE surfini
     69     
     70      END MODULE surfini_mod
Note: See TracChangeset for help on using the changeset viewer.