Ignore:
Timestamp:
Nov 19, 2021, 4:58:59 PM (3 years ago)
Author:
lguez
Message:

Sync latest trunk changes to Ocean_skin

Location:
LMDZ6/branches/Ocean_skin
Files:
2 edited

Legend:

Unmodified
Added
Removed
  • LMDZ6/branches/Ocean_skin

  • LMDZ6/branches/Ocean_skin/libf/phylmd/surf_landice_mod.F90

    r3798 r4013  
    1919       tsoil, z0m, z0h, SFRWL, alb_dir, alb_dif, evap, fluxsens, fluxlat, &
    2020       tsurf_new, dflux_s, dflux_l, &
    21        slope, cloudf, &
     21       alt, slope, cloudf, &
    2222       snowhgt, qsnow, to_ice, sissnow, &
    2323       alb3, runoff, &
     
    2525
    2626    USE dimphy
    27     USE surface_data,     ONLY : type_ocean, calice, calsno, landice_opt, n_dtis
    28     USE fonte_neige_mod,  ONLY : fonte_neige, run_off_lic
     27    USE geometry_mod,     ONLY : longitude,latitude
     28    USE surface_data,     ONLY : type_ocean, calice, calsno, landice_opt, iflag_albcalc
     29    USE fonte_neige_mod,  ONLY : fonte_neige,run_off_lic,fqcalving_global,ffonte_global,fqfonte_global,runofflic_global
    2930    USE cpl_mod,          ONLY : cpl_send_landice_fields
    3031    USE calcul_fluxs_mod
     
    3334    USE ioipsl_getin_p_mod, ONLY : getin_p
    3435
    35 #ifdef CPP_SISVAT
    36     USE surf_sisvat_mod,  ONLY : surf_sisvat
    37 #endif
    3836
    3937#ifdef CPP_INLANDSIS
     
    7573    REAL, DIMENSION(klon), INTENT(IN)             :: albedo  !mean albedo
    7674    REAL, DIMENSION(klon), INTENT(IN)             :: pphi1   
     75    REAL, DIMENSION(klon), INTENT(IN)             :: alt   !mean altitude of the grid box 
    7776    REAL, DIMENSION(klon), INTENT(IN)             :: slope   !mean slope in grid box 
    7877    REAL, DIMENSION(klon), INTENT(IN)             :: cloudf  !total cloud fraction
     
    115114    REAL, DIMENSION(klon)    :: u0, v0, u1_lay, v1_lay, ustar
    116115    INTEGER                  :: i,j,nt
    117 
     116    REAL, DIMENSION(klon)    :: fqfonte,ffonte
    118117    REAL, DIMENSION(klon)    :: emis_new                  !Emissivity
    119118    REAL, DIMENSION(klon)    :: swdown,lwdown
    120     REAL, DIMENSION(klon)    :: precip_snow_adv, snow_adv !Snow Drift precip./advection
    121     REAL, DIMENSION(klon)    :: zsl_height, wind_velo      !surface layer height, wind spd
     119    REAL, DIMENSION(klon)    :: precip_snow_adv, snow_adv !Snow Drift precip./advection (not used in inlandsis)
     120    REAL, DIMENSION(klon)    :: erod                      !erosion of surface snow (flux, kg/m2/s like evap)
     121    REAL, DIMENSION(klon)    :: zsl_height, wind_velo     !surface layer height, wind spd
    122122    REAL, DIMENSION(klon)    :: dens_air,  snow_cont_air  !air density; snow content air
    123123    REAL, DIMENSION(klon)    :: alb_soil                  !albedo of underlying ice
     
    132132
    133133
    134 !albedo SB >>>
    135     real,dimension(klon) :: alb1,alb2
    136 !albedo SB <<<
    137 
     134    REAL,DIMENSION(klon) :: alb1,alb2
     135    REAL, DIMENSION (klon,6) :: alb6
    138136! End definition
    139137!****************************************************************************************
     
    179177!****************************************************************************************
    180178!  landice_opt = 0 : soil_model, calcul_flux, fonte_neige, ... 
    181 !  landice_opt = 1  : prepare and call SISVAT snow model
    182 !  landice_opt = 2  : prepare and call INLANDSIS snow model
     179!  landice_opt = 1  : prepare and call INterace Lmdz SISvat (INLANDSIS)
    183180!****************************************************************************************
    184181
    185182
    186183    IF (landice_opt .EQ. 1) THEN
    187    
    188 !****************************************************************************************
    189 ! CALL to SISVAT interface
    190 !****************************************************************************************
    191 
    192 #ifdef CPP_SISVAT
    193        ! Prepare for calling SISVAT
    194        
    195        ! Calculate incoming flux for SW and LW interval: swdown, lwdown
    196        swdown(:)        = 0.0
    197        lwdown(:)        = 0.0
    198        DO i = 1, knon
    199           swdown(i)        = swnet(i)/(1-albedo(i))
    200           lwdown(i)        = lwdownm(i)
    201        END DO
    202        
    203        ! Set constants and compute some input for SISVAT
    204        snow_adv(:)      = 0.                          ! no snow blown in for now
    205        snow_cont_air(:) = 0.       
    206        alb_soil(:)      = albedo(:)
    207        pref             = 100000.                     ! = 1000 hPa
    208        DO i = 1, knon
    209           wind_velo(i)     = u1(i)**2 + v1(i)**2
    210           wind_velo(i)     = wind_velo(i)**0.5
    211           pexner(i)        = (p1lay(i)/pref)**(RD/RCPD)
    212           dens_air(i)      = p1lay(i)/RD/temp_air(i)  ! dry air density
    213           zsl_height(i)     = pphi1(i)/RG             
    214        END DO
    215 
    216 
    217        ! config: compute everything with SV but temperatures afterwards with soil/calculfluxs
    218        DO i = 1, knon
    219           tsoil0(i,:)=tsoil(i,:)
    220        END DO
    221            ! Martin
    222            PRINT*, 'on appelle surf_sisvat'
    223            ! Martin
    224        CALL surf_sisvat(knon, rlon, rlat, knindex, itime, dtime, debut, lafin, &
    225             rmu0, swdown, lwdown, pexner, ps, p1lay, &
    226             precip_rain, precip_snow, precip_snow_adv, snow_adv, &
    227             zsl_height, wind_velo, temp_air, dens_air, spechum, tsurf, &
    228             rugoro, snow_cont_air, alb_soil, slope, cloudf, &
    229             radsol, qsol, tsoil0, snow, snowhgt, qsnow, to_ice,sissnow, agesno, &
    230             AcoefH, AcoefQ, BcoefH, BcoefQ, cdragh, &
    231             run_off_lic, evap, fluxsens, fluxlat, dflux_s, dflux_l, &       
    232             tsurf_new, alb1, alb2, alb3, &
    233             emis_new, z0m, qsurf)
    234        z0h(1:knon)=z0m(1:knon) ! en attendant mieux
    235        
    236        ! Suppose zero surface speed
    237        u0(:)            = 0.0
    238        v0(:)            = 0.0
    239        ! The calculation of heat/water fluxes, otherwise done by "CALL calcul_fluxs" is
    240        ! integrated in SISVAT, using the same method. It can be found in "sisvat.f", in the
    241        ! subroutine "SISVAT_TS2".
    242        ! u0, v0=0., dif_grnd=0. and beta=1 are assumed there!
    243        
    244        CALL calcul_flux_wind(knon, dtime, &
    245             u0, v0, u1, v1, gustiness, cdragm, &
    246             AcoefU, AcoefV, BcoefU, BcoefV, &
    247             p1lay, temp_air, &
    248             flux_u1, flux_v1)
    249 #else
    250        abort_message='Pb de coherence: landice_opt = 1 mais CPP_SISVAT = .false.'
    251        CALL abort_physic(modname,abort_message,1)
    252 #endif
    253 
    254 !****************************************************************************************
     184
     185!****************************************************************************************   
    255186! CALL to INLANDSIS interface
    256187!****************************************************************************************
    257 
    258     ELSE IF (landice_opt .EQ. 2) THEN
    259188#ifdef CPP_INLANDSIS
    260189
     
    278207       swdown(:)        = 0.0
    279208       lwdown(:)        = 0.0
    280        snow_adv(:)      = 0.  ! no snow blown in for now
    281        snow_cont_air(:) = 0.       
     209       snow_cont_air(:) = 0.  ! the snow content in air is not a prognostic variable of the model     
    282210       alb_soil(:)      = 0.4 ! before albedo(:) but here it is the ice albedo that we have to set
    283211       ustar(:)         = 0.
     
    296224       
    297225
    298        ! Subtimestepping
    299        
    300         dtis=dtime/n_dtis
    301 
    302         DO nt=1,n_dtis
    303 
    304           IF (lafin .and. nt.eq.n_dtis) THEN
     226
     227        dtis=dtime
     228
     229          IF (lafin) THEN
    305230            lafin_is=.true.
    306231          END IF
    307232
    308         !PRINT*,'RENTRE DANS INLANDSIS','itime',itime,'dtime',dtime,'dtis',dtis
    309         CALL surf_inlandsis(knon, rlon, rlat, knindex, itime, dtis, debut_is, lafin_is, &
    310             rmu0, swdown, lwdown, albedo, pexner, ps, p1lay, &
    311             precip_rain, precip_snow, precip_snow_adv, snow_adv, &
    312             zsl_height, wind_velo, ustar, temp_air, dens_air, spechum, tsurf, &
    313             rugoro, snow_cont_air, alb_soil, slope, cloudf, &
    314             radsol, qsol, tsoil0, snow, zfra, snowhgt, qsnow, to_ice,sissnow, agesno, &
     233          CALL surf_inlandsis(knon, rlon, rlat, knindex, itime, dtis, debut_is, lafin_is,&
     234            rmu0, swdown, lwdown, albedo, pexner, ps, p1lay, precip_rain, precip_snow,   &
     235            zsl_height, wind_velo, ustar, temp_air, dens_air, spechum, tsurf,&
     236            rugoro, snow_cont_air, alb_soil, alt, slope, cloudf, &
     237            radsol, qsol, tsoil0, snow, zfra, snowhgt, qsnow, to_ice, sissnow,agesno,   &
    315238            AcoefH, AcoefQ, BcoefH, BcoefQ, cdragm, cdragh, &
    316             run_off_lic, evap, fluxsens, fluxlat, dflux_s, dflux_l, &       
    317             tsurf_new, alb1, alb2, alb3, &
    318             emis_new, z0m, z0h, qsurf)     
    319 
    320          debut_is=.false.
    321 
    322         END DO
     239            run_off_lic, fqfonte, ffonte, evap, erod, fluxsens, fluxlat,dflux_s, dflux_l, &
     240            tsurf_new, alb1, alb2, alb3, alb6, &
     241            emis_new, z0m, z0h, qsurf)
     242
     243          debut_is=.false.
     244
     245
     246        ! Treatment of snow melting and calving
     247
     248        ! for consistency with standard LMDZ, add calving to run_off_lic
     249        run_off_lic(:)=run_off_lic(:) + to_ice(:)
     250
     251        DO i = 1, knon
     252           ffonte_global(knindex(i),is_lic)    = ffonte(i)
     253           fqfonte_global(knindex(i),is_lic)   = fqfonte(i)! net melting= melting - refreezing
     254           fqcalving_global(knindex(i),is_lic) = to_ice(i) ! flux
     255           runofflic_global(knindex(i)) = run_off_lic(i)
     256        ENDDO
     257        ! Here, we assume that the calving term is equal to the to_ice term
     258        ! (no ice accumulation)
    323259
    324260
    325261#else
    326        abort_message='Pb de coherence: landice_opt = 2 mais CPP_INLANDSIS = .false.'
     262       abort_message='Pb de coherence: landice_opt = 1 mais CPP_INLANDSIS = .false.'
    327263       CALL abort_physic(modname,abort_message,1)
    328264#endif
     
    343279    ! use soil model and recalculate properly cal
    344280    IF (soil_model) THEN
    345        CALL soil(dtime, is_lic, knon, snow, tsurf, tsoil, soilcap, soilflux)
     281       CALL soil(dtime, is_lic, knon, snow, tsurf, qsol, &
     282        & longitude(knindex(1:knon)), latitude(knindex(1:knon)), tsoil, soilcap, soilflux)
    346283       cal(1:knon) = RCPD / soilcap(1:knon)
    347284       radsol(1:knon)  = radsol(1:knon) + soilflux(1:knon)
     
    420357
    421358
    422 
    423    
    424 
    425359    END IF ! landice_opt
    426360
     
    428362!****************************************************************************************
    429363! Send run-off on land-ice to coupler if coupled ocean.
    430 ! run_off_lic has been calculated in fonte_neige or surf_sisvat
     364! run_off_lic has been calculated in fonte_neige or surf_inlandsis
    431365!
    432366!****************************************************************************************
     
    476410       alb_dir(1:knon,5)=alb2(1:knon)
    477411       alb_dir(1:knon,6)=alb2(1:knon)
     412
     413       IF ((landice_opt .EQ. 1) .AND. (iflag_albcalc .EQ. 2)) THEN
     414       alb_dir(1:knon,1)=alb6(1:knon,1)
     415       alb_dir(1:knon,2)=alb6(1:knon,2)
     416       alb_dir(1:knon,3)=alb6(1:knon,3)
     417       alb_dir(1:knon,4)=alb6(1:knon,4)
     418       alb_dir(1:knon,5)=alb6(1:knon,5)
     419       alb_dir(1:knon,6)=alb6(1:knon,6)
     420       ENDIF
     421
    478422     end select
    479423alb_dif=alb_dir
    480424!albedo SB <<<
    481425
    482 
    483 
     426 
     427 
    484428
    485429  END SUBROUTINE surf_landice
Note: See TracChangeset for help on using the changeset viewer.