Ignore:
Timestamp:
2011-06-17T14:02:17+02:00 (13 years ago)
Author:
didier.solyga
Message:

Externalized version merged with the trunk

File:
1 edited

Legend:

Unmodified
Added
Removed
  • branches/ORCHIDEE_EXT/ORCHIDEE/src_sechiba/hydrol.f90

    r112 r257  
    33!! 
    44!! @author Marie-Alice Foujols and Jan Polcher 
    5 !! @Version : $Revision: 1.36 $, $Date: 2009/01/07 13:39:45 $ 
     5!! @Version : $Revision: 45 $, $Date: 2011-01-01 21:30:44 +0100 (Sat, 01 Jan 2011) $ 
    66!! 
    7 !! $Header: /home/ssipsl/CVSREP/ORCHIDEE/src_sechiba/hydrol.f90,v 1.36 2009/01/07 13:39:45 ssipsl Exp $ 
     7!< $HeadURL: http://forge.ipsl.jussieu.fr/orchidee/svn/trunk/ORCHIDEE/src_sechiba/hydrol.f90 $ 
     8!< $Date: 2011-01-01 21:30:44 +0100 (Sat, 01 Jan 2011) $ 
     9!< $Author: mmaipsl $ 
     10!< $Revision: 45 $ 
    811!! IPSL (2006) 
    912!!  This software is governed by the CeCILL licence see ORCHIDEE/ORCHIDEE_CeCILL.LIC 
     
    224227    !! We consider that any water on the ice is snow and we only peforme a water balance to have consistency. 
    225228    !! The water balance is limite to + or - 10^6 so that accumulation is not endless 
     229    REAL(r_std),DIMENSION (kjpindex), INTENT (inout)     :: runoff           !! Complete runoff 
     230    REAL(r_std),DIMENSION (kjpindex), INTENT (inout)     :: drainage         !! Drainage 
     231    REAL(r_std),DIMENSION (kjpindex,nbdl), INTENT (inout):: shumdiag         !! relative soil moisture 
    226232    ! output fields 
    227     REAL(r_std),DIMENSION (kjpindex), INTENT (out)     :: runoff           !! Complete runoff 
    228     REAL(r_std),DIMENSION (kjpindex), INTENT (out)     :: drainage         !! Drainage 
    229233    REAL(r_std),DIMENSION (kjpindex,nvm), INTENT (out) :: humrel           !! Relative humidity 
    230234    REAL(r_std),DIMENSION (kjpindex,nvm), INTENT (out) :: vegstress        !! Veg. moisture stress (only for vegetation growth) 
    231235    REAL(r_std),DIMENSION (kjpindex), INTENT (out)     :: drysoil_frac     !! function of litter wetness 
    232     REAL(r_std),DIMENSION (kjpindex,nbdl), INTENT (out):: shumdiag         !! relative soil moisture 
    233236    REAL(r_std),DIMENSION (kjpindex), INTENT (out)     :: litterhumdiag    !! litter humidity 
    234237    REAL(r_std),DIMENSION (kjpindex), INTENT (out)     :: tot_melt         !! Total melt     
     
    10821085       ! 
    10831086       DO jsl=1,nslm 
    1084           CALL setvar_p (us(:,:,:,jsl), val_exp, 'US_INIT', 0.0_r_std) 
     1087          CALL setvar_p (us(:,:,:,jsl), val_exp, 'US_INIT', zero) 
    10851088       ENDDO 
    10861089       ! 
     
    11011104       !Config        started without a restart file. 
    11021105       ! 
    1103        CALL setvar_p (ae_ns, val_exp, 'EVAPNU_SOIL', 0.0_r_std) 
     1106       CALL setvar_p (ae_ns, val_exp, 'EVAPNU_SOIL', zero) 
    11041107       ! 
    11051108       !Config Key  = HYDROL_SNOW 
     
    11101113       !Config        started without a restart file. 
    11111114       ! 
    1112        CALL setvar_p (snow, val_exp, 'HYDROL_SNOW', 0.0_r_std) 
     1115       CALL setvar_p (snow, val_exp, 'HYDROL_SNOW', zero) 
    11131116       ! 
    11141117       !Config Key  = HYDROL_SNOWAGE 
     
    11191122       !Config        started without a restart file. 
    11201123       ! 
    1121        CALL setvar_p (snow_age, val_exp, 'HYDROL_SNOWAGE', 0.0_r_std) 
     1124       CALL setvar_p (snow_age, val_exp, 'HYDROL_SNOWAGE', zero) 
    11221125       ! 
    11231126       !Config Key  = HYDROL_SNOW_NOBIO 
     
    11281131       !Config        started without a restart file. 
    11291132       ! 
    1130        CALL setvar_p (snow_nobio, val_exp, 'HYDROL_SNOW_NOBIO', 0.0_r_std) 
     1133       CALL setvar_p (snow_nobio, val_exp, 'HYDROL_SNOW_NOBIO', zero) 
    11311134       ! 
    11321135       !Config Key  = HYDROL_SNOW_NOBIO_AGE 
     
    11371140       !Config        started without a restart file. 
    11381141       ! 
    1139        CALL setvar_p (snow_nobio_age, val_exp, 'HYDROL_SNOW_NOBIO_AGE', 0.0_r_std) 
     1142       CALL setvar_p (snow_nobio_age, val_exp, 'HYDROL_SNOW_NOBIO_AGE', zero) 
    11401143       ! 
    11411144       ! 
     
    11481151       !Config        the model is started without a restart file.  
    11491152       ! 
    1150        CALL setvar_p (qsintveg, val_exp, 'HYDROL_QSV', 0.0_r_std) 
     1153       CALL setvar_p (qsintveg, val_exp, 'HYDROL_QSV', zero) 
    11511154       ! 
    11521155       ! There is no need to configure the initialisation of resdist. If not available it is the vegetation map 
     
    17171720          IF (snow(ji).GT.sneige) THEN 
    17181721             ! 
    1719              snowmelt(ji) = (1. - frac_nobio(ji,iice))*(temp_sol_new(ji) - tp_00) * soilcap(ji) / chalfu0 
     1722             snowmelt(ji) = (un - frac_nobio(ji,iice))*(temp_sol_new(ji) - tp_00) * soilcap(ji) / chalfu0 
    17201723             ! 
    17211724             ! 1.3.1.1 enough snow for melting or not 
     
    18901893    REAL(r_std), DIMENSION (kjpindex,nvm)          :: zqsintvegnew 
    18911894    LOGICAL, SAVE                                  :: firstcall=.TRUE. 
    1892 !    REAL(r_std), SAVE, DIMENSION(nvm)              :: throughfall_by_pft 
    18931895 
    18941896    IF ( firstcall ) THEN 
     
    20782080    DO jv = 1, nvm 
    20792081      DO ji = 1, kjpindex 
    2080          IF ( ABS(qsintveg(ji,jv)) > 0. .AND. ABS(qsintveg(ji,jv)) < EPS1 ) THEN 
     2082         IF ( ABS(qsintveg(ji,jv)) > zero .AND. ABS(qsintveg(ji,jv)) < EPS1 ) THEN 
    20812083            qsintveg(ji,jv) = EPS1 
    20822084         ENDIF 
Note: See TracChangeset for help on using the changeset viewer.