Ignore:
Timestamp:
Jul 10, 2020, 11:50:17 PM (4 years ago)
Author:
oboucher
Message:

The fraction of SW down radiation that is diffuse is extracted from radlwsw.F90 and passed on to pbl_surface for inclusion in fields_out for transfer to ORCHIDEE if it requested in input file coupling_fields.def. Hence there is nothing automatic here. The fraction of SW down radiation is also added as a diagnostic. To satisfy the case when this new quantity is used in ORCHIDEE, then it is added in the restart (and read in case it is there).

File:
1 edited

Legend:

Unmodified
Added
Removed
  • LMDZ6/trunk/libf/phylmd/pbl_surface_mod.F90

    r3435 r3756  
    164164       rlon,      rlat,      rugoro,   rmu0,          &
    165165       zsig,      lwdown_m,  pphi,     cldt,          &
    166        rain_f,    snow_f,    solsw_m,  sollw_m,       &
     166       rain_f,    snow_f,    solsw_m,  solswfdiff_m, sollw_m,       &
    167167       gustiness,                                     &
    168168       t,         q,         u,        v,             &
     
    318318    REAL, DIMENSION(klon),        INTENT(IN)        :: snow_f  ! snow fall
    319319    REAL, DIMENSION(klon),        INTENT(IN)        :: solsw_m ! net shortwave radiation at mean surface
     320    REAL, DIMENSION(klon),        INTENT(IN)        :: solswfdiff_m ! diffuse fraction fordownward shortwave radiation at mean surface
    320321    REAL, DIMENSION(klon),        INTENT(IN)        :: sollw_m ! net longwave radiation at mean surface
    321322    REAL, DIMENSION(klon,klev),   INTENT(IN)        :: t       ! temperature (K)
     
    453454    REAL, DIMENSION(klon, klev),  INTENT(OUT)       :: zxfluxu    ! u wind tension, mean for each grid point
    454455    REAL, DIMENSION(klon, klev),  INTENT(OUT)       :: zxfluxv    ! v wind tension, mean for each grid point
    455     REAL, DIMENSION(klon, nbsrf+1), INTENT(INOUT)     :: z0m,z0h      ! rugosity length (m)
    456     REAL, DIMENSION(klon, nbsrf), INTENT(INOUT)       :: agesno   ! age of snow at surface
     456    REAL, DIMENSION(klon, nbsrf+1), INTENT(INOUT)   :: z0m,z0h      ! rugosity length (m)
     457    REAL, DIMENSION(klon, nbsrf), INTENT(INOUT)     :: agesno   ! age of snow at surface
    457458    REAL, DIMENSION(klon, nbsrf), INTENT(OUT)       :: solsw      ! net shortwave radiation at surface
    458459    REAL, DIMENSION(klon, nbsrf), INTENT(OUT)       :: sollw      ! net longwave radiation at surface
    459460    REAL, DIMENSION(klon, nbsrf), INTENT(OUT)       :: d_ts       ! change in temperature at surface
    460     REAL, DIMENSION(klon, nbsrf), INTENT(INOUT)       :: evap     ! evaporation at surface
     461    REAL, DIMENSION(klon, nbsrf), INTENT(INOUT)     :: evap     ! evaporation at surface
    461462    REAL, DIMENSION(klon, nbsrf), INTENT(OUT)       :: fluxlat    ! latent flux
    462463    REAL, DIMENSION(klon, nbsrf), INTENT(OUT)       :: t2m        ! temperature at 2 meter height
     
    965966    yqsurf = 0.0  ; yalb = 0.0 ; yalb_vis = 0.0
    966967!albedo SB <<<
    967     yrain_f = 0.0 ; ysnow_f = 0.0    ; yfder = 0.0     ; ysolsw = 0.0   
     968    yrain_f = 0.0 ; ysnow_f = 0.0    ; yfder = 0.0     ; ysolsw = 0.0
    968969    ysollw = 0.0  ; yz0m = 0.0 ; yz0h = 0.0    ; yu1 = 0.0   
    969970    yv1 = 0.0     ; ypaprs = 0.0     ; ypplay = 0.0
     
    11831184!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
    11841185
     1186!--OB this line is not satisfactory because alb is the direct albedo not total albedo
    11851187          solsw(i,nsrf) = solsw_m(i) * (1.-alb(i,nsrf)) / (1.-alb_m(i))
    11861188       ENDDO
     
    12051207!>al1
    12061208
     1209!--OB add diffuse fraction of SW down
     1210   DO n=1,nbcf_out
     1211       IF (cfname_out(n) == "swdownfdiff" ) fields_out(:,n) = solswfdiff_m(:)
     1212   ENDDO
    12071213! >> PC
    12081214   IF (carbon_cycle_cpl .AND. carbon_cycle_tr .AND. nbcf_out.GT.0 ) THEN
Note: See TracChangeset for help on using the changeset viewer.