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

    r142 r257  
    44!! 
    55!! @author Marie-Alice Foujols and Jan Polcher 
    6 !! @Version : $Revision: 1.46 $, $Date: 2010/05/07 08:28:13 $ 
     6!! @Version : $Revision: 45 $, $Date: 2011-01-01 21:30:44 +0100 (Sat, 01 Jan 2011) $ 
    77!!  
    8 !! $Header: /home/ssipsl/CVSREP/ORCHIDEE/src_sechiba/sechiba.f90,v 1.46 2010/05/07 08:28:13 ssipsl Exp $ 
     8!< $HeadURL: http://forge.ipsl.jussieu.fr/orchidee/svn/trunk/ORCHIDEE/src_sechiba/sechiba.f90 $ 
     9!< $Date: 2011-01-01 21:30:44 +0100 (Sat, 01 Jan 2011) $ 
     10!< $Author: mmaipsl $ 
     11!< $Revision: 45 $ 
    912!! IPSL (2006) 
    1013!!  This software is governed by the CeCILL licence see ORCHIDEE/ORCHIDEE_CeCILL.LIC 
     
    239242    REAL(r_std),DIMENSION (kjpindex), INTENT (out)           :: tsol_rad         !! Radiative surface temperature 
    240243    REAL(r_std),DIMENSION (kjpindex), INTENT (out)           :: vevapp           !! Total of evaporation 
    241     REAL(r_std),DIMENSION (kjpindex), INTENT (out)           :: temp_sol_new     !! New soil temperature 
     244    REAL(r_std),DIMENSION (kjpindex), INTENT (inout)           :: temp_sol_new     !! New soil temperature 
    242245    REAL(r_std),DIMENSION (kjpindex), INTENT (out)           :: qsurf_out        !! Surface specific humidity 
    243246    REAL(r_std),DIMENSION (kjpindex), INTENT (out)           :: z0_out           !! Surface roughness (output diagnostic) 
     
    256259    REAL(r_std), DIMENSION(kjpindex) :: sum_treefrac, sum_grassfrac, sum_cropfrac 
    257260    INTEGER(i_std) :: jv 
    258  
    259  
    260  
    261261 
    262262    IF (long_print) WRITE(numout,*) ' kjpindex =',kjpindex 
     
    636636       ENDIF 
    637637 
    638        histvar(:)=SUM(vevapwet(:,:),dim=2)/86400 
     638       histvar(:)=SUM(vevapwet(:,:),dim=2)/one_day 
    639639       CALL histwrite(hist_id, 'evspsblveg', kjit, histvar, kjpindex, index) 
    640640 
    641        histvar(:)=(vevapnu(:)+vevapsno(:))/86400 
     641       histvar(:)=(vevapnu(:)+vevapsno(:))/one_day 
    642642       CALL histwrite(hist_id, 'evspsblsoi', kjit, histvar, kjpindex, index) 
    643643 
    644        histvar(:)=SUM(transpir(:,:),dim=2)/86400 
     644       histvar(:)=SUM(transpir(:,:),dim=2)/one_day 
    645645       CALL histwrite(hist_id, 'tran', kjit, histvar, kjpindex, index) 
    646  
    647 !------------------------------------ 
    648  
    649 !       histvar(:)=SUM(veget_max(:,2:9),dim=2)*100*contfrac(:) 
    650 !       CALL histwrite(hist_id, 'treeFrac', kjit, histvar, kjpindex, index) 
    651  
    652 !       histvar(:)=SUM(veget_max(:,10:11),dim=2)*100*contfrac(:) 
    653 !       CALL histwrite(hist_id, 'grassFrac', kjit, histvar, kjpindex, index) 
    654  
    655 !       histvar(:)=SUM(veget_max(:,12:13),dim=2)*100*contfrac(:) 
    656 !       CALL histwrite(hist_id, 'cropFrac', kjit, histvar, kjpindex, index) 
    657646 
    658647!$$ 25/10/10 Modif DS & NViovy 
     
    666655       histvar(:)= sum_cropfrac(:)*100*contfrac(:) 
    667656       CALL histwrite(hist_id, 'cropFrac', kjit, histvar, kjpindex, index) 
    668  
    669657 
    670658       histvar(:)=veget_max(:,1)*100*contfrac(:) 
     
    13471335    ENDDO 
    13481336 
    1349  
    13501337    ! 
    13511338    ! 2. restart value 
     
    13721359    ! 
    13731360 
     1361    control%river_routing = control_in%river_routing 
     1362    control%hydrol_cwrr = control_in%hydrol_cwrr 
    13741363    control%ok_co2 = control_in%ok_co2 
    13751364    control%ok_sechiba = control_in%ok_sechiba 
Note: See TracChangeset for help on using the changeset viewer.