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

    r116 r257  
    77!! 
    88!! @call sechiba_main 
    9 !! @Version : $Revision: 1.85 $, $Date: 2010/07/29 15:58:19 $ 
     9!! @Version : $Revision: 221 $, $Date: 2011-05-16 17:26:17 +0200 (Mon, 16 May 2011) $ 
    1010!! 
    1111!! @author Marie-Alice Foujols and Jan Polcher 
    1212!!  
    13 !! $Header: /home/ssipsl/CVSREP/ORCHIDEE/src_sechiba/intersurf.f90,v 1.85 2010/07/29 15:58:19 ssipsl Exp $ 
     13!< $HeadURL: http://forge.ipsl.jussieu.fr/orchidee/svn/trunk/ORCHIDEE/src_sechiba/intersurf.f90 $ 
     14!< $Date: 2011-05-16 17:26:17 +0200 (Mon, 16 May 2011) $ 
     15!< $Author: martial.mancip $ 
     16!< $Revision: 221 $ 
    1417!! IPSL (2006) 
    1518!!  This software is governed by the CeCILL licence see ORCHIDEE/ORCHIDEE_CeCILL.LIC 
     
    181184    ! 
    182185    CALL ipslnlf(new_number=numout,old_number=old_fileout) 
    183  
    184186    ! 
    185187    IF (l_first_intersurf) THEN 
     
    225227       IF ( ok_watchout ) THEN 
    226228          IF (is_root_prc) THEN 
    227              zlev_mean = 0. 
     229             zlev_mean = zero 
    228230             DO ik=1, nbp_glo 
    229231                j = ((index_g(ik)-1)/iim_g) + 1 
     
    391393!!$               dt_split_watch,dt_watch,one_day 
    392394!!$          CALL solarang (julian_watch, julian0, iim, jjm, lon, lat, sinang) 
    393 !!$          WHERE ( sinang(:,:) .LT. EPSILON(1.) )  
     395!!$          WHERE ( sinang(:,:) .LT. EPSILON(un) )  
    394396!!$             isinang(:,:) = isinang(:,:) - 1 
    395397!!$          ENDWHERE 
     
    529531          CALL histwrite (hist_id, 'riverflow',itau_sechiba, driver, kjpindex, kindex) 
    530532       !  
    531           CALL histwrite (hist_id, 'temp_sol', itau_sechiba, temp_sol_NEW, iim*jjm, kindex) 
    532           CALL histwrite (hist_id, 'tsol_max', itau_sechiba, temp_sol_NEW, iim*jjm, kindex) 
    533           CALL histwrite (hist_id, 'tsol_min', itau_sechiba, temp_sol_NEW, iim*jjm, kindex) 
    534           CALL histwrite (hist_id, 'fluxsens', itau_sechiba, fluxsens, iim*jjm, kindex) 
    535           CALL histwrite (hist_id, 'fluxlat',  itau_sechiba, fluxlat, iim*jjm, kindex) 
    536           CALL histwrite (hist_id, 'swnet',    itau_sechiba, dswnet, iim*jjm, kindex) 
    537           CALL histwrite (hist_id, 'swdown',   itau_sechiba, dswdown, iim*jjm, kindex) 
    538           CALL histwrite (hist_id, 'alb_vis',  itau_sechiba, albedo(:,:,1), iim*jjm, kindex) 
    539           CALL histwrite (hist_id, 'alb_nir',  itau_sechiba, albedo(:,:,2), iim*jjm, kindex) 
    540           CALL histwrite (hist_id, 'tair',     itau_sechiba, temp_air, iim*jjm, kindex) 
    541           CALL histwrite (hist_id, 'qair',     itau_sechiba, qair, iim*jjm, kindex) 
     533          CALL histwrite (hist_id, 'temp_sol', itau_sechiba, temp_sol_NEW, kjpindex, kindex) 
     534          CALL histwrite (hist_id, 'tsol_max', itau_sechiba, temp_sol_NEW, kjpindex, kindex) 
     535          CALL histwrite (hist_id, 'tsol_min', itau_sechiba, temp_sol_NEW, kjpindex, kindex) 
     536          CALL histwrite (hist_id, 'fluxsens', itau_sechiba, fluxsens, kjpindex, kindex) 
     537          CALL histwrite (hist_id, 'fluxlat',  itau_sechiba, fluxlat, kjpindex, kindex) 
     538          CALL histwrite (hist_id, 'swnet',    itau_sechiba, dswnet, kjpindex, kindex) 
     539          CALL histwrite (hist_id, 'swdown',   itau_sechiba, dswdown, kjpindex, kindex) 
     540          CALL histwrite (hist_id, 'alb_vis',  itau_sechiba, albedo(:,:,1), kjpindex, kindex) 
     541          CALL histwrite (hist_id, 'alb_nir',  itau_sechiba, albedo(:,:,2), kjpindex, kindex) 
     542          CALL histwrite (hist_id, 'tair',     itau_sechiba, temp_air, kjpindex, kindex) 
     543          CALL histwrite (hist_id, 'qair',     itau_sechiba, qair, kjpindex, kindex) 
    542544          ! Ajout Nathalie - Juin 2006 - on conserve q2m/t2m 
    543           CALL histwrite (hist_id, 'q2m',     itau_sechiba, qair, iim*jjm, kindex) 
    544           CALL histwrite (hist_id, 't2m',     itau_sechiba, temp_air, iim*jjm, kindex) 
     545          CALL histwrite (hist_id, 'q2m',     itau_sechiba, qair, kjpindex, kindex) 
     546          CALL histwrite (hist_id, 't2m',     itau_sechiba, temp_air, kjpindex, kindex) 
    545547          IF ( hist2_id > 0 ) THEN 
    546548             CALL histwrite (hist2_id, 'evap',     itau_sechiba, zvevapp, kjpindex, kindex) 
     
    548550             CALL histwrite (hist2_id, 'riverflow',itau_sechiba, driver, kjpindex, kindex) 
    549551             !  
    550              CALL histwrite (hist2_id, 'temp_sol', itau_sechiba, temp_sol_NEW, iim*jjm, kindex) 
    551              CALL histwrite (hist2_id, 'tsol_max', itau_sechiba, temp_sol_NEW, iim*jjm, kindex) 
    552              CALL histwrite (hist2_id, 'tsol_min', itau_sechiba, temp_sol_NEW, iim*jjm, kindex) 
    553              CALL histwrite (hist2_id, 'fluxsens', itau_sechiba, fluxsens, iim*jjm, kindex) 
    554              CALL histwrite (hist2_id, 'fluxlat',  itau_sechiba, fluxlat, iim*jjm, kindex) 
    555              CALL histwrite (hist2_id, 'swnet',    itau_sechiba, dswnet, iim*jjm, kindex) 
    556              CALL histwrite (hist2_id, 'swdown',   itau_sechiba, dswdown, iim*jjm, kindex) 
    557              CALL histwrite (hist2_id, 'alb_vis',  itau_sechiba, albedo(:,:,1), iim*jjm, kindex) 
    558              CALL histwrite (hist2_id, 'alb_nir',  itau_sechiba, albedo(:,:,2), iim*jjm, kindex) 
    559              CALL histwrite (hist2_id, 'tair',     itau_sechiba, temp_air, iim*jjm, kindex) 
    560              CALL histwrite (hist2_id, 'qair',     itau_sechiba, qair, iim*jjm, kindex) 
    561              CALL histwrite (hist2_id, 'q2m',     itau_sechiba, qair, iim*jjm, kindex) 
    562              CALL histwrite (hist2_id, 't2m',     itau_sechiba, temp_air, iim*jjm, kindex) 
     552             CALL histwrite (hist2_id, 'temp_sol', itau_sechiba, temp_sol_NEW, kjpindex, kindex) 
     553             CALL histwrite (hist2_id, 'tsol_max', itau_sechiba, temp_sol_NEW, kjpindex, kindex) 
     554             CALL histwrite (hist2_id, 'tsol_min', itau_sechiba, temp_sol_NEW, kjpindex, kindex) 
     555             CALL histwrite (hist2_id, 'fluxsens', itau_sechiba, fluxsens, kjpindex, kindex) 
     556             CALL histwrite (hist2_id, 'fluxlat',  itau_sechiba, fluxlat, kjpindex, kindex) 
     557             CALL histwrite (hist2_id, 'swnet',    itau_sechiba, dswnet, kjpindex, kindex) 
     558             CALL histwrite (hist2_id, 'swdown',   itau_sechiba, dswdown, kjpindex, kindex) 
     559             CALL histwrite (hist2_id, 'alb_vis',  itau_sechiba, albedo(:,:,1), kjpindex, kindex) 
     560             CALL histwrite (hist2_id, 'alb_nir',  itau_sechiba, albedo(:,:,2), kjpindex, kindex) 
     561             CALL histwrite (hist2_id, 'tair',     itau_sechiba, temp_air, kjpindex, kindex) 
     562             CALL histwrite (hist2_id, 'qair',     itau_sechiba, qair, kjpindex, kindex) 
     563             CALL histwrite (hist2_id, 'q2m',     itau_sechiba, qair, kjpindex, kindex) 
     564             CALL histwrite (hist2_id, 't2m',     itau_sechiba, temp_air, kjpindex, kindex) 
    563565          ENDIF 
    564566       ELSE 
    565567          CALL histwrite (hist_id, 'Evap', itau_sechiba, zvevapp, kjpindex, kindex) 
    566           CALL histwrite (hist_id, 'SWnet',    itau_sechiba, dswnet, iim*jjm, kindex) 
    567           CALL histwrite (hist_id, 'Qh', itau_sechiba, fluxsens, iim*jjm, kindex) 
    568           CALL histwrite (hist_id, 'Qle',  itau_sechiba, fluxlat, iim*jjm, kindex) 
    569           CALL histwrite (hist_id, 'AvgSurfT', itau_sechiba, temp_sol_NEW, iim*jjm, kindex) 
    570           CALL histwrite (hist_id, 'RadT', itau_sechiba, temp_sol_NEW, iim*jjm, kindex) 
     568          CALL histwrite (hist_id, 'SWnet',    itau_sechiba, dswnet, kjpindex, kindex) 
     569          CALL histwrite (hist_id, 'Qh', itau_sechiba, fluxsens, kjpindex, kindex) 
     570          CALL histwrite (hist_id, 'Qle',  itau_sechiba, fluxlat, kjpindex, kindex) 
     571          CALL histwrite (hist_id, 'AvgSurfT', itau_sechiba, temp_sol_NEW, kjpindex, kindex) 
     572          CALL histwrite (hist_id, 'RadT', itau_sechiba, temp_sol_NEW, kjpindex, kindex) 
    571573          IF ( hist2_id > 0 ) THEN 
    572574             CALL histwrite (hist2_id, 'Evap', itau_sechiba, zvevapp, kjpindex, kindex) 
    573              CALL histwrite (hist2_id, 'SWnet',    itau_sechiba, dswnet, iim*jjm, kindex) 
    574              CALL histwrite (hist2_id, 'Qh', itau_sechiba, fluxsens, iim*jjm, kindex) 
    575              CALL histwrite (hist2_id, 'Qle',  itau_sechiba, fluxlat, iim*jjm, kindex) 
    576              CALL histwrite (hist2_id, 'AvgSurfT', itau_sechiba, temp_sol_NEW, iim*jjm, kindex) 
    577              CALL histwrite (hist2_id, 'RadT', itau_sechiba, temp_sol_NEW, iim*jjm, kindex) 
     575             CALL histwrite (hist2_id, 'SWnet',    itau_sechiba, dswnet, kjpindex, kindex) 
     576             CALL histwrite (hist2_id, 'Qh', itau_sechiba, fluxsens, kjpindex, kindex) 
     577             CALL histwrite (hist2_id, 'Qle',  itau_sechiba, fluxlat, kjpindex, kindex) 
     578             CALL histwrite (hist2_id, 'AvgSurfT', itau_sechiba, temp_sol_NEW, kjpindex, kindex) 
     579             CALL histwrite (hist2_id, 'RadT', itau_sechiba, temp_sol_NEW, kjpindex, kindex) 
    578580          ENDIF 
    579581       ENDIF 
     
    780782       ! 
    781783       IF ( ok_watchout ) THEN 
    782           zlev_mean = 0. 
     784          zlev_mean = zero 
    783785          DO ik=1, kjpindex 
    784786 
     
    905907!!$          julian_watch = date0_shifted+((itau_sechiba-0.5)/dt_split_watch)*dt_watch/one_day 
    906908!!$          CALL solarang (julian_watch, julian0, iim, jjm, lon, lat, sinang) 
    907 !!$          WHERE ( sinang(:,:) .LT. EPSILON(1.) )  
     909!!$          WHERE ( sinang(:,:) .LT. EPSILON(un) )  
    908910!!$             isinang(:,:) = isinang(:,:) - 1 
    909911!!$          ENDWHERE 
     
    14481450       IF ( ok_watchout ) THEN 
    14491451          IF (is_root_prc) THEN 
    1450              zlev_mean = 0. 
     1452             zlev_mean = zero 
    14511453             DO ik=1, nbp_glo 
    14521454                j = ((index_g(ik)-1)/iim_g) + 1 
     
    16021604!!$          julian_watch = date0_shifted+((itau_sechiba-0.5)/dt_split_watch)*dt_watch/one_day 
    16031605!!$          CALL solarang (julian_watch, julian0, iim, jjm, tmp_lon, tmp_lat, sinang) 
    1604 !!$          WHERE ( sinang(:,:) .LT. EPSILON(1.) )  
     1606!!$          WHERE ( sinang(:,:) .LT. EPSILON(un) )  
    16051607!!$             isinang(:,:) = isinang(:,:) - 1 
    16061608!!$          ENDWHERE 
     
    21782180       IF ( ok_watchout ) THEN 
    21792181          IF (is_root_prc) THEN 
    2180              zlev_mean = 0. 
     2182             zlev_mean = zero 
    21812183             DO ik=1, nbp_glo 
    21822184                j = ((index_g(ik)-1)/iim_g) + 1 
     
    23322334!!$          julian_watch = date0_shifted+((itau_sechiba-0.5)/dt_split_watch)*dt_watch/one_day 
    23332335!!$          CALL solarang (julian_watch, julian0, iim, jjm, tmp_lon, tmp_lat, sinang) 
    2334 !!$          WHERE ( sinang(:,:) .LT. EPSILON(1.) ) 
     2336!!$          WHERE ( sinang(:,:) .LT. EPSILON(un) ) 
    23352337!!$             isinang(:,:) = isinang(:,:) - 1 
    23362338!!$          ENDWHERE 
     
    25862588       CALL tlen2itau('1Y',dt,date0,year_length) 
    25872589       IF ( TRIM(calendar_str) .EQ. 'gregorian' ) THEN   
    2588           year_spread=1.0 
     2590          year_spread=un 
    25892591       ELSE 
    25902592          year_spread = one_year/365.2425 
     
    26102612       ! Real date 
    26112613       CALL ju2ymds (in_julian, year, month, day, sec) 
    2612 !!$       jur=0. 
     2614!!$       jur=zero 
    26132615!!$       julian_diff = in_julian 
    26142616!!$       month_len = ioget_mon_len (year,month) 
     
    26302632       ENDIF 
    26312633    ELSE  
    2632 !!$       in_julian = itau2date(istp-1, 0., dt) 
     2634!!$       in_julian = itau2date(istp-1, zero, dt) 
    26332635!!$       CALL ju2ymds (in_julian, year, month, day, sec) 
    2634 !!$       jur=0. 
     2636!!$       jur=zero 
    26352637!!$       julian_diff = in_julian 
    26362638!!$       month_len = ioget_mon_len (year,month) 
     
    26932695    CALL getin_p('NVM',nvm) 
    26942696    WRITE(numout,*)'the number of pfts is : ', nvm 
    2695 !!$DS Debug 28/01/2011 
    26962697    ! 
    26972698    !Config Key  = LONGPRINT 
     
    27232724       ! 
    27242725       dt_watch = dt 
    2725        CALL getin('DT_WATCHOUT',dt_watch) 
     2726       CALL getin_p('DT_WATCHOUT',dt_watch) 
    27262727       dt_split_watch = dt_watch / dt 
    27272728       ! 
     
    27402741    ENDIF 
    27412742 
    2742  
    27432743!!$    DS : reading of IMPOSE_PARAM 
    27442744    ! Option : do you want to change the values of the parameters 
    27452745    CALL getin_p('IMPOSE_PARAM',impose_param) 
    2746     ! Calling pft_parameters 
    27472746    CALL pft_parameters_main   
    27482747    ! 
     
    27842783    IF ( control_flags%hydrol_cwrr ) THEN 
    27852784       CALL getin_hydrol_cwrr_parameters 
     2785    ELSE 
     2786       CALL getin_hydrolc_parameters 
     2787       ! we read the parameters for the choisnel hydrology 
    27862788    ENDIF 
    27872789 
     
    28002802       CALL getin_co2_parameters 
    28012803    ENDIF 
    2802  
    2803  
    2804  
    2805 !!$    DS : reading of IMPOSE_PARAM 
    2806 !!$    ! Option : do you want to change the values of the parameters 
    2807 !!$    CALL getin_p('IMPOS_PARAM',impos_param) 
    2808 !!$    ! Calling pft_parameters 
    2809 !!$    CALL pft_main   
    28102804 
    28112805    ! 
     
    28442838       WRITE(numout,*) 'It is not possible because it has to be modified ', & 
    28452839            ' to give correct values.' 
    2846        CALL ipslerr (3,'intsurf_config', & 
    2847          &          'Use of STOMATE_OK_DGVM not allowed with this version.',& 
    2848          &          'ORCHIDEE will stop.', & 
     2840       CALL ipslerr (2,'intsurf_config', & 
     2841         &          'Use of STOMATE_OK_DGVM is not stable for this version.',& 
     2842         &          'ORCHIDEE should not give correct results with this option activated.', & 
    28492843         &          'Please disable DGVM to use this version of ORCHIDEE.') 
    28502844    ENDIF 
     
    29652959    CALL getin_p('SECHIBA_reset_time', overwrite_time) 
    29662960    ! 
    2967     lev(:) = 0. 
     2961    lev(:) = zero 
    29682962    itau_dep = istp 
    29692963    in_julian = itau2date(istp, date0, dt) 
     
    31863180    !Config  Key  = WRITE_STEP 
    31873181    !Config  Desc = Frequency in seconds at which to WRITE output 
    3188     !Config  Def  = 86400.0 
     3182    !Config  Def  = one_day 
    31893183    !Config  Help = This variables gives the frequency the output of 
    31903184    !Config         the model should be written into the netCDF file. 
     
    31983192    ! 
    31993193    veg(1:nvm)   = (/ (REAL(i,r_std),i=1,nvm) /) 
    3200 !$$ DS DEBUG 
    3201     WRITE(numout,*)'nvm : = ', nvm 
    3202     WRITE(numout,*)'veg : =', veg 
    3203 !$$ nvm =13 (put the calling to getin before) 
    32043194    sol(1:ngrnd) = (/ (REAL(i,r_std),i=1,ngrnd) /)    
    32053195    soltyp(1:nstm) = (/ (REAL(i,r_std),i=1,nstm) /) 
     
    32163206    WRITE(flux_sc,'("ave(X*",F8.1,")")') one_day/dt 
    32173207    !WRITE(flux_sc,'("(ave(X)*",F8.1,")")') one_day/dt 
    3218     WRITE(flux_insec,'("ave(X*",F8.6,")")') 1.0/dt 
    3219     WRITE(flux_scinsec,'("ave(scatter(X*",F8.6,"))")') 1.0/dt 
     3208    WRITE(flux_insec,'("ave(X*",F8.6,")")') un/dt 
     3209    WRITE(flux_scinsec,'("ave(scatter(X*",F8.6,"))")') un/dt 
    32203210    WRITE(numout,*) flux_op, one_day/dt, dt, dw 
    32213211    !- 
     
    33713361               & iim,jjm, hori_id, 1,1,1, -99, 32, once(1), dt,dw)   
    33723362       ENDIF 
    3373        IF ( control_flags%ok_stomate .OR. control_flags%stomate_watchout ) THEN 
    3374           CALL histdef (hist_id,'CO2FLUX','Total output CO2 flux', 'gC/day/(m^2 tot)', & 
    3375                & iim,jjm, hori_id, nvm, 1, nvm, vegax_id, 32, avescatter(1), dt, dw) 
    3376        ENDIF 
    33773363       !- 
    33783364       !- SECHIBA_HISTLEVEL = 2 
     
    36923678       CALL histdef(hist_id, 'nobiofrac', 'Fraction of other surface types', '1', & 
    36933679            & iim,jjm, hori_id, nnobio, 1, nnobio, nobioax_id, 32, avescatter(3), dt,dw) 
    3694        IF ( control_flags%ok_stomate .OR. control_flags%stomate_watchout ) THEN 
    3695           ! Total output CO2 flux                              
    3696           CALL histdef (hist_id,'CO2FLUX','Total output CO2 flux', 'gC/day/(m^2 tot)', & 
    3697                & iim,jjm, hori_id, nvm, 1, nvm, vegax_id, 32, avescatter(1), dt, dw) 
    3698        ENDIF 
    36993680     !-  
    37003681     !-  General energy balance 
     
    40334014          CALL histdef(hist2_id, 'emis', 'Surface emissivity', '?', & 
    40344015               & iim,jjm, hori_id2, 1,1,1, -99, 32, fluxop2(2), dt, dw2) 
    4035           IF ( control_flags%ok_stomate .OR. control_flags%stomate_watchout ) THEN 
    4036              CALL histdef (hist2_id,'CO2FLUX','Total output CO2 flux', 'gC/day/(m^2 tot)', & 
    4037                   & iim,jjm, hori_id2, nvm, 1, nvm, vegax_id2, 32, avescatter2(2), dt, dw2) 
    4038           ENDIF 
    40394016          !- 
    40404017          !- SECHIBA_HISTLEVEL2 = 3 
     
    42984275          CALL histdef(hist2_id, 'nobiofrac', 'Fraction of other surface types', '1', & 
    42994276               & iim,jjm, hori_id2, nnobio, 1, nnobio, nobioax_id2, 32, avescatter2(3), dt, dw2) 
    4300           IF ( control_flags%ok_stomate .OR. control_flags%stomate_watchout ) THEN 
    4301              CALL histdef (hist2_id,'CO2FLUX','Total output CO2 flux', 'gC/day/(m^2 tot)', & 
    4302                   & iim,jjm, hori_id2, nvm, 1, nvm, vegax_id2, 32, avescatter2(1), dt, dw2) 
    4303           ENDIF 
    43044277          !-  
    43054278          !-  General energy balance 
     
    44654438       hist_days_stom = 10. 
    44664439       CALL getin_p('STOMATE_HIST_DT', hist_days_stom)        
    4467        IF ( hist_days_stom == -1. ) THEN 
    4468           hist_dt_stom = -1. 
     4440       IF ( hist_days_stom == moins_un ) THEN 
     4441          hist_dt_stom = moins_un 
    44694442          WRITE(numout,*) 'output frequency for STOMATE history file (d): one month.' 
    44704443       ELSE 
     
    44774450       dt_slow_ = one_day 
    44784451       CALL getin_p('DT_SLOW', dt_slow_) 
    4479        IF ( hist_days_stom /= -1. ) THEN 
     4452       IF ( hist_days_stom /= moins_un ) THEN 
    44804453          IF (dt_slow_ > hist_dt_stom) THEN 
    44814454             WRITE(numout,*) "DT_SLOW = ",dt_slow_,"  , STOMATE_HIST_DT = ",hist_dt_stom 
     
    45674540       !Config  Help = Time step of the STOMATE IPCC history file 
    45684541       !- 
    4569        hist_days_stom_ipcc = 0. 
     4542       hist_days_stom_ipcc = zero 
    45704543       CALL getin_p('STOMATE_IPCC_HIST_DT', hist_days_stom_ipcc)        
    4571        IF ( hist_days_stom_ipcc == -1. ) THEN 
    4572           hist_dt_stom_ipcc = -1. 
     4544       IF ( hist_days_stom_ipcc == moins_un ) THEN 
     4545          hist_dt_stom_ipcc = moins_un 
    45734546          WRITE(numout,*) 'output frequency for STOMATE IPCC history file (d): one month.' 
    45744547       ELSE 
     
    45814554       dt_slow_ = one_day 
    45824555       CALL getin_p('DT_SLOW', dt_slow_) 
    4583        IF ( hist_days_stom_ipcc > 0. ) THEN 
     4556       IF ( hist_days_stom_ipcc > zero ) THEN 
    45844557          IF (dt_slow_ > hist_dt_stom_ipcc) THEN 
    45854558             WRITE(numout,*) "DT_SLOW = ",dt_slow_,"  , STOMATE_IPCC_HIST_DT = ",hist_dt_stom_ipcc 
     
    48224795         &               1,1,1, -99,32, ave(5), dt, hist_dt) 
    48234796 
    4824     ! Monthly CO2 flux                                   
    4825     CALL histdef (hist_id_stom, & 
    4826          &               TRIM("CO2FLUX_MONTHLY     "), & 
    4827          &               TRIM("Monthly CO2 flux                                  "), & 
     4797    ! CO2 flux                                   
     4798    CALL histdef (hist_id_stom, & 
     4799         &               TRIM("CO2FLUX             "), & 
     4800         &               TRIM("CO2 flux                                          "), & 
    48284801         &               TRIM("gC/m^2/pft/mth      "), iim,jjm, hist_hori_id, & 
    48294802         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(1), dt, hist_dt) 
    48304803 
    4831     CALL histdef(hist_id_stom, & 
    4832          &               TRIM("CO2FLUX_MONTHLY_SUM "), & 
    4833          &               TRIM("Monthly CO2 flux                                  "), & 
    4834          &               TRIM("PgC/m^2/mth          "), 1,1, hist_hori_id, & 
    4835          &               1,1,1, -99, 32, ave(1), dt, hist_dt) 
     4804!!$    CALL histdef(hist_id_stom, & 
     4805!!$         &               TRIM("CO2FLUX_MONTHLY_SUM "), & 
     4806!!$         &               TRIM("Monthly CO2 flux Sum                              "), & 
     4807!!$         &               TRIM("PgC/m^2/mth         "), iim,jjm, hist_hori_id, & 
     4808!!$         &               1,1,1, -99, 32, 'inst(scatter(X))', dt, hist_dt) 
    48364809 
    48374810    ! Output CO2 flux from fire                          
     
    51215094         &               TRIM("1/day               "), iim,jjm, hist_hori_id, & 
    51225095         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(6), dt, hist_dt) 
     5096 
     5097    ! Establish tree 
     5098    CALL histdef (hist_id_stom, & 
     5099         &               TRIM("ESTABTREE           "), & 
     5100         &               TRIM("Rate of tree establishement                       "), & 
     5101         &               TRIM("1/day               "), iim,jjm, hist_hori_id, & 
     5102         &               1,1,1, -99,32, ave(6), dt, hist_dt) 
     5103 
     5104    ! Establish grass 
     5105    CALL histdef (hist_id_stom, & 
     5106         &               TRIM("ESTABGRASS          "), & 
     5107         &               TRIM("Rate of grass establishement                      "), & 
     5108         &               TRIM("1/day               "), iim,jjm, hist_hori_id, & 
     5109         &               1,1,1, -99,32, ave(6), dt, hist_dt) 
    51235110 
    51245111    ! Fraction of plants that dies (light competition)   
Note: See TracChangeset for help on using the changeset viewer.