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/enerbil.f90

    r113 r257  
    33!! 
    44!! @author Marie-Alice Foujols and Jan Polcher 
    5 !! @Version : $Revision: 1.24 $, $Date: 2009/01/07 13:39:45 $ 
     5!! @Version : $Revision: 47 $, $Date: 2011-01-01 21:34:45 +0100 (Sat, 01 Jan 2011) $ 
    66!!  
    7 !! $Header: /home/ssipsl/CVSREP/ORCHIDEE/src_sechiba/enerbil.f90,v 1.24 2009/01/07 13:39:45 ssipsl Exp $ 
     7!< $HeadURL: http://forge.ipsl.jussieu.fr/orchidee/svn/trunk/ORCHIDEE/src_sechiba/enerbil.f90 $ 
     8!< $Date: 2011-01-01 21:34:45 +0100 (Sat, 01 Jan 2011) $ 
     9!< $Author: mmaipsl $ 
     10!< $Revision: 47 $ 
    811!! IPSL (2006) 
    912!!  This software is governed by the CeCILL licence see ORCHIDEE/ORCHIDEE_CeCILL.LIC 
     
    121124    REAL(r_std),DIMENSION (kjpindex), INTENT (inout)   :: evapot           !! Soil Potential Evaporation 
    122125    REAL(r_std),DIMENSION (kjpindex), INTENT (inout)   :: evapot_corr !! Soil Potential Evaporation Correction 
     126    REAL(r_std),DIMENSION (kjpindex), INTENT (inout)   :: temp_sol         !! Soil temperature 
     127    REAL(r_std),DIMENSION (kjpindex), INTENT (inout)   :: qsurf            !! Surface specific humidity 
     128    REAL(r_std),DIMENSION (kjpindex), INTENT (inout)   :: fluxsens         !! Sensible chaleur flux 
     129    REAL(r_std),DIMENSION (kjpindex), INTENT (inout)   :: fluxlat          !! Latent chaleur flux 
     130    REAL(r_std),DIMENSION (kjpindex), INTENT (inout)   :: tsol_rad         !! Tsol_rad 
     131    REAL(r_std),DIMENSION (kjpindex), INTENT (inout)   :: vevapp           !! Total of evaporation 
     132    REAL(r_std),DIMENSION (kjpindex,nvm), INTENT (inout) :: gpp              !! Assimilation, gC/m**2 total area. 
     133    REAL(r_std),DIMENSION (kjpindex), INTENT (inout)   :: temp_sol_new     !! New soil temperature 
    123134    ! output fields 
    124     REAL(r_std),DIMENSION (kjpindex), INTENT (out)     :: fluxsens         !! Sensible chaleur flux 
    125     REAL(r_std),DIMENSION (kjpindex), INTENT (out)     :: fluxlat          !! Latent chaleur flux 
    126     REAL(r_std),DIMENSION (kjpindex), INTENT (out)     :: vevapp           !! Total of evaporation 
    127135    REAL(r_std),DIMENSION (kjpindex), INTENT (out)     :: vevapnu          !! Bare soil evaporation 
    128136    REAL(r_std),DIMENSION (kjpindex), INTENT (out)     :: vevapsno         !! Snow evaporation 
    129     REAL(r_std),DIMENSION (kjpindex), INTENT (out)     :: tsol_rad         !! Tsol_rad 
    130     REAL(r_std),DIMENSION (kjpindex), INTENT (out)     :: temp_sol_new     !! New soil temperature 
    131     REAL(r_std),DIMENSION (kjpindex), INTENT (out)     :: temp_sol         !! Soil temperature 
    132     REAL(r_std),DIMENSION (kjpindex), INTENT (out)     :: qsurf            !! Surface specific humidity 
    133137    REAL(r_std),DIMENSION (kjpindex,nvm), INTENT (out) :: transpir         !! Transpiration 
    134     REAL(r_std),DIMENSION (kjpindex,nvm), INTENT (out) :: gpp              !! Assimilation, gC/m**2 total area. 
    135138    REAL(r_std),DIMENSION (kjpindex,nvm), INTENT (out) :: vevapwet         !! Interception  
    136139    REAL(r_std),DIMENSION (kjpindex), INTENT (out)     :: t2mdiag          !! 2-meter temperature 
     
    281284    ! output fields, they need to initialized somehow for the model forcing ORCHIDEE. 
    282285    ! 
    283     REAL(r_std),DIMENSION (kjpindex), INTENT (out)           :: temp_sol           !! Soil temperature 
     286    REAL(r_std),DIMENSION (kjpindex), INTENT (inout)         :: temp_sol           !! Soil temperature 
    284287    REAL(r_std),DIMENSION (kjpindex), INTENT (out)           :: temp_sol_new       !! New soil temperature 
    285288    REAL(r_std),DIMENSION (kjpindex), INTENT (out)           :: qsurf              !! near surface specific humidity 
     
    423426        !Config        the model is started without a restart file.  
    424427        ! 
    425         CALL setvar_p (evapot, val_exp, 'ENERBIL_EVAPOT', 0.0_r_std) 
     428        CALL setvar_p (evapot, val_exp, 'ENERBIL_EVAPOT', zero) 
    426429        IF ( ok_var("evapot_corr") ) THEN 
    427            CALL setvar_p (evapot_corr, val_exp, 'ENERBIL_EVAPOT', 0.0_r_std) 
     430           CALL setvar_p (evapot_corr, val_exp, 'ENERBIL_EVAPOT', zero) 
    428431        ENDIF 
    429432        ! 
     
    778781    REAL(r_std)                                     :: correction 
    779782    REAL(r_std)                                     :: speed, qc 
     783    LOGICAL,DIMENSION (kjpindex)                   :: warning_correction 
    780784    ! initialisation 
    781785 
     
    840844!    grad_qsat(:)= (qsol_sat_new(:)- qsat_air(:)) / ((psnew(:) - epot_air(:)) / cp_air) ! * dtradia 
    841845    !- Penser a sortir evapot en meme temps qu'evapot_corr tdo. 
     846    warning_correction(:)=.FALSE. 
    842847    DO ji=1,kjpindex 
    843848 
     
    852857             correction = chalev0 * rau(ji) * qc * grad_qsat(ji) * (un - vevapp(ji)/evapot(ji)) / correction 
    853858          ELSE 
    854              WRITE(numout,*) "Denominateur de la correction de milly nul! Aucune correction appliquee" 
     859             warning_correction(ji)=.TRUE. 
    855860          ENDIF 
    856861       ELSE 
     
    862867        
    863868    ENDDO 
    864  
     869    IF ( ANY(warning_correction) ) THEN 
     870       DO ji=1,kjpindex 
     871          IF ( warning_correction(ji) ) THEN 
     872             WRITE(numout,*) ji,"Denominateur de la correction de milly nul! Aucune correction appliquee" 
     873          ENDIF 
     874       ENDDO 
     875    ENDIF 
    865876    IF (long_print) WRITE (numout,*) ' enerbil_flux done ' 
    866877 
     
    886897    REAL(r_std),DIMENSION (kjpindex), INTENT (in)            :: evapot           !! Soil Potential Evaporation 
    887898    REAL(r_std),DIMENSION (kjpindex, nvm), INTENT (in)       :: humrel           !! Relative humidity 
    888 !!$ DS 15022011 humrel was used in a previuos version of Orchidee, developped by Nathalie. Need to be discussed if it should be introduces again 
     899!!$ DS 15022011 humrel was used in a previous version of Orchidee, developped by Nathalie. Need to be discussed if it should be introduces again 
    889900    REAL(r_std),DIMENSION (kjpindex,nvm), INTENT (in)        :: vbeta2           !! Interception resistance 
    890901    REAL(r_std),DIMENSION (kjpindex,nvm), INTENT (in)        :: vbeta3           !! Vegetation resistance 
     
    969980    ELSEIF ( control%stomate_watchout ) THEN 
    970981 
    971       gpp(:,:) = 0.0 
     982      gpp(:,:) = zero 
    972983 
    973984    ENDIF 
     
    10011012 
    10021013    ! initialisation 
    1003    IF (long_print) WRITE (numout,*) ' enerbil_fusion start ', MINVAL(soilcap), MINLOC(soilcap),& 
     1014    IF (long_print) WRITE (numout,*) ' enerbil_fusion start ', MINVAL(soilcap), MINLOC(soilcap),& 
    10041015         & MAXVAL(soilcap), MAXLOC(soilcap) 
    10051016    ! 
Note: See TracChangeset for help on using the changeset viewer.