Ignore:
Timestamp:
Nov 28, 2014, 4:36:29 PM (10 years ago)
Author:
Laurent Fairhead
Message:

Merged trunk changes -r2070:2158 into testing branch. Compilation problems introduced by revision r2155 have been corrected by hand

Location:
LMDZ5/branches/testing
Files:
2 edited

Legend:

Unmodified
Added
Removed
  • LMDZ5/branches/testing

  • LMDZ5/branches/testing/libf/phylmd/pbl_surface_mod.F90

    r1999 r2160  
    319319    REAL, DIMENSION(klon),        INTENT(OUT)       :: alb2_m     ! mean albedo in near IR SW interval
    320320    ! Martin
    321         REAL, DIMENSION(klon),        INTENT(OUT)       :: alb3_lic
     321    REAL, DIMENSION(klon),        INTENT(OUT)       :: alb3_lic
    322322    ! Martin
    323323    REAL, DIMENSION(klon),        INTENT(OUT)       :: zxsens     ! sensible heat flux at surface with inversed sign
     
    475475    LOGICAL, PARAMETER                 :: check=.FALSE.
    476476    REAL, DIMENSION(klon)              :: Kech_h       ! Coefficient d'echange pour l'energie
     477    REAL                               :: vent
    477478
    478479! For debugging with IOIPSL
     
    797798            yts, yqsurf, yrugos, &
    798799            ycdragm, ycdragh )
     800! --- special Dice: on force cdragm ( a defaut de forcer ustar) MPL 05082013
     801     IF (ok_prescr_ust) then
     802      DO i = 1, knon
     803       print *,'ycdragm avant=',ycdragm(i)
     804       vent= sqrt(yu(i,1)*yu(i,1)+yv(i,1)*yv(i,1))
     805!      ycdragm(i) = ust*ust/(1.+(yu(i,1)*yu(i,1)+yv(i,1)*yv(i,1)))
     806!      ycdragm(i) = ust*ust/((1.+sqrt(yu(i,1)*yu(i,1)+yv(i,1)*yv(i,1))) &
     807!     *sqrt(yu(i,1)*yu(i,1)+yv(i,1)*yv(i,1)))
     808       ycdragm(i) = ust*ust/(1.+vent)/vent
     809       print *,'ycdragm ust yu yv apres=',ycdragm(i),ust,yu(i,1),yv(i,1)
     810      ENDDO
     811     ENDIF
     812
    799813
    800814!****************************************************************************************
     
    905919               y_flux_u1, y_flux_v1 )
    906920               
     921! Special DICE MPL 05082013
     922       IF (ok_prescr_ust) THEN
     923!         ysnow(:)=0.
     924!         yqsol(:)=0.
     925!         yagesno(:)=50.
     926!         ytsoil(:,:)=300.
     927!         yz0_new(:)=0.001
     928!         yalb1_new(:)=0.22
     929!         yalb2_new(:)=0.22
     930!         yevap(:)=flat/RLVTT
     931!         yfluxlat(:)=-flat
     932!         yfluxsens(:)=-fsens
     933!         yqsurf(:)=0.
     934!         ytsurf_new(:)=tg
     935!         y_dflux_t(:)=0.
     936!         y_dflux_q(:)=0.
     937          y_flux_u1(:)=ycdragm(:)*(1.+sqrt(yu(:,1)*yu(:,1)+yv(:,1)*yv(:,1)))*yu(:,1)*ypplay(:,1)/RD/yt(:,1)
     938          y_flux_v1(:)=ycdragm(:)*(1.+sqrt(yu(:,1)*yu(:,1)+yv(:,1)*yv(:,1)))*yv(:,1)*ypplay(:,1)/RD/yt(:,1)
     939      ENDIF
     940
    907941     
    908942       CASE(is_lic)
Note: See TracChangeset for help on using the changeset viewer.