Ignore:
Timestamp:
2011-08-01T11:25:14+02:00 (13 years ago)
Author:
didier.solyga
Message:

Synchronize the externalized version with revisions 353, 355 and 356 of the trunk

File:
1 edited

Legend:

Unmodified
Added
Removed
  • branches/ORCHIDEE_EXT/ORCHIDEE_OL/forcesoil.f90

    r313 r367  
    2020  IMPLICIT NONE 
    2121  !- 
    22   CHARACTER(LEN=80) :: sto_restname_in,sto_restname_out,var_name 
     22  CHARACTER(LEN=80) :: sto_restname_in,sto_restname_out 
    2323  INTEGER(i_std)                             :: iim,jjm 
     24 
    2425  INTEGER(i_std),PARAMETER                   :: llm = 1 
    2526  INTEGER(i_std)                             :: kjpindex 
     27 
    2628  INTEGER(i_std)                             :: itau_dep,itau_len 
    2729  CHARACTER(LEN=30)                         :: time_str 
    28   INTEGER(i_std)                             :: ier,iret 
    2930  REAL(r_std)                                :: dt_files 
    3031  REAL(r_std)                                :: date0 
    3132  INTEGER(i_std)                             :: rest_id_sto 
    32   INTEGER(i_std)                             :: ncfid 
    33   REAL(r_std)                                :: dt_force,dt_forcesoil 
     33 
     34  !- 
     35  CHARACTER(LEN=100) :: Cforcing_name 
     36  INTEGER            :: Cforcing_id 
     37  INTEGER            :: v_id 
     38  REAL(r_std)                                :: dt_forcesoil 
    3439  INTEGER                                   :: nparan 
    35   INTEGER,PARAMETER                         :: nparanmax=36 
    36   REAL(r_std)                                :: xbid1,xbid2 
    37   INTEGER(i_std)                             :: ibid 
     40 
    3841  INTEGER(i_std),DIMENSION(:),ALLOCATABLE    :: indices 
     42  INTEGER(i_std),DIMENSION(:),ALLOCATABLE    :: indices_g 
     43  REAL(r_std),DIMENSION(:),ALLOCATABLE       :: x_indices_g 
     44  REAL(r_std),DIMENSION(:,:),ALLOCATABLE     :: lon, lat 
    3945  REAL(r_std),DIMENSION(llm)                 :: lev 
    40   REAL(r_std),DIMENSION(:,:,:,:),ALLOCATABLE :: soilcarbon_input 
    41   REAL(r_std),DIMENSION(:,:,:),ALLOCATABLE   :: & 
    42        &  carbon,control_moist,control_temp 
    43   REAL(r_std),DIMENSION(:,:),ALLOCATABLE     :: & 
    44        &  lon,lat,resp_hetero_soil,var_3d 
    45   REAL(r_std),DIMENSION(:),ALLOCATABLE       :: & 
    46        &  x_indices 
    47   REAL(r_std)                                :: time 
    48   INTEGER                                   :: i,j,m,iatt,iv 
     46 
     47 
     48  INTEGER                                   :: i,m,iatt,iv 
     49 
     50  CHARACTER(LEN=80)                         :: var_name 
    4951  CHARACTER(LEN=400)                        :: taboo_vars 
    5052  REAL(r_std),DIMENSION(1)                   :: xtmp 
     
    5658  INTEGER,DIMENSION(varnbdim_max)           :: vardims 
    5759  LOGICAL                                   :: l1d 
     60  REAL(r_std),DIMENSION(:,:),ALLOCATABLE     :: var_3d 
    5861  REAL(r_std)                                :: x_tmp 
    59   ! clay fraction 
    60   REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:)  :: clay 
    61   !- 
    6262  ! string suffix indicating an index 
    6363  CHARACTER(LEN=10)  :: part_str 
    6464  ! 
    65   CHARACTER(LEN=100) :: Cforcing_name 
    66   INTEGER            :: Cforcing_id 
    67   INTEGER            :: v_id 
    68  
    69   REAL(r_std),ALLOCATABLE :: clay_loc(:) 
    70   REAL(r_std),ALLOCATABLE :: soilcarbon_input_loc(:,:,:,:) 
    71   REAL(r_std),ALLOCATABLE :: control_temp_loc(:,:,:) 
    72   REAL(r_std),ALLOCATABLE :: control_moist_loc(:,:,:) 
    73   REAL(r_std),ALLOCATABLE :: carbon_loc(:,:,:) 
    74   INTEGER :: ierr 
     65  ! clay fraction 
     66  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:)  :: clay_g 
     67  REAL(r_std),DIMENSION(:,:,:,:),ALLOCATABLE :: soilcarbon_input_g 
     68  REAL(r_std),DIMENSION(:,:,:),ALLOCATABLE   :: control_temp_g 
     69  REAL(r_std),DIMENSION(:,:,:),ALLOCATABLE   :: control_moist_g 
     70  REAL(r_std),DIMENSION(:,:,:),ALLOCATABLE   :: carbon_g 
     71 
     72  REAL(r_std),ALLOCATABLE :: clay(:) 
     73  REAL(r_std),ALLOCATABLE :: soilcarbon_input(:,:,:,:) 
     74  REAL(r_std),ALLOCATABLE :: control_temp(:,:,:) 
     75  REAL(r_std),ALLOCATABLE :: control_moist(:,:,:) 
     76  REAL(r_std),ALLOCATABLE :: carbon(:,:,:) 
     77  REAL(r_std),DIMENSION(:,:),ALLOCATABLE     :: resp_hetero_soil 
     78 
     79  INTEGER(i_std)                             :: ier,iret 
     80 
     81  LOGICAL :: debug 
     82 
    7583  !>> DS add for externalization 
    7684  LOGICAL  :: l_error 
     
    7886 
    7987  CALL Init_para(.FALSE.)  
    80  
     88  CALL init_timer 
    8189  ! 
    8290  ! DS : For externalization cause we decoupled forcesoil from ORCHIDEE 
     
    8492   
    8593  ! 1. Read the number of PFTs 
    86   CALL getin('NVM',nvm) 
     94  ! 
     95  !Config Key  = NVM 
     96  !Config Desc = number of PFTs   
     97  !Config  if  = ANYTIME 
     98  !Config  Def  = 13 
     99  !Config  Help = The number of vegetation types define by the user 
     100  !Config  Units = NONE 
     101  CALL getin_p('NVM',nvm) 
     102 
    87103  ! 2. Allocation 
    88104  l_error = .FALSE. 
     
    97113   
    98114  ! 4.Reading of the conrrespondance table in the .def file 
    99   CALL getin('PFT_TO_MTC',pft_to_mtc) 
     115  ! 
     116  !Config  Key  = PFT_TO_MTC 
     117  !Config  Desc = correspondance array linking a PFT to MTC 
     118  !Config  if  = ANYTIME 
     119  !Config  Def  = 1, 2, 3, 4, 5, 6, 7, 8, 9, 10, 11, 12, 13 
     120  !Config  Help = 
     121  !Config  Units = NONE 
     122  CALL getin_p('PFT_TO_MTC',pft_to_mtc) 
    100123 
    101124  ! 4.1 if nothing is found, we use the standard configuration 
     
    147170 
    148171  ! 7.2 Initialisation 
    149   DO j= 1, nvm 
    150      natural(j) = natural_mtc(pft_to_mtc(j)) 
    151      is_c4(j) = is_c4_mtc(pft_to_mtc(j)) 
     172  DO i= 1, nvm 
     173     natural(i) = natural_mtc(pft_to_mtc(i)) 
     174     is_c4(i) = is_c4_mtc(pft_to_mtc(i)) 
    152175  ENDDO 
    153176 
     177!--------------------------------------------------------------------- 
     178!- 
     179! set debug to have more information 
     180!- 
     181  !Config  Key  = DEBUG_INFO 
     182  !Config  Desc = Flag for debug information 
     183  !Config  Def  = n 
     184  !Config  Help = This option allows to switch on the output of debug 
     185  !Config         information without recompiling the code. 
     186!- 
     187  debug = .FALSE. 
     188  CALL getin_p('DEBUG_INFO',debug) 
     189  ! 
     190  !Config Key  = LONGPRINT 
     191  !Config Desc = ORCHIDEE will print more messages 
     192  !Config Def  = n 
     193  !Config Help = This flag permits to print more debug messages in the run. 
     194  ! 
     195  long_print = .FALSE. 
     196  CALL getin_p('LONGPRINT',long_print) 
    154197  !- 
    155198  ! Stomate's restart files 
     
    158201     sto_restname_in = 'stomate_start.nc' 
    159202     CALL getin ('STOMATE_RESTART_FILEIN',sto_restname_in) 
    160      WRITE(*,*) 'STOMATE INPUT RESTART_FILE: ',TRIM(sto_restname_in) 
    161      sto_restname_out = 'stomate_restart.nc' 
     203     WRITE(numout,*) 'STOMATE INPUT RESTART_FILE: ',TRIM(sto_restname_in) 
     204     sto_restname_out = 'stomate_rest_out.nc' 
    162205     CALL getin ('STOMATE_RESTART_FILEOUT',sto_restname_out) 
    163      WRITE(*,*) 'STOMATE OUTPUT RESTART_FILE: ',TRIM(sto_restname_out) 
    164      !- 
    165      ! We need to know iim, jjm. 
     206     WRITE(numout,*) 'STOMATE OUTPUT RESTART_FILE: ',TRIM(sto_restname_out) 
     207     !- 
     208     ! We need to know iim_g, jjm. 
    166209     ! Get them from the restart files themselves. 
    167210     !- 
    168      iret = NF90_OPEN (sto_restname_in, NF90_NOWRITE, ncfid) 
    169      iret = NF90_INQUIRE_DIMENSION (ncfid,1,len=iim) 
    170      iret = NF90_INQUIRE_DIMENSION (ncfid,2,len=jjm) 
    171      iret = NF90_CLOSE (ncfid) 
     211     iret = NF90_OPEN (sto_restname_in, NF90_NOWRITE, rest_id_sto) 
     212     iret = NF90_INQUIRE_DIMENSION (rest_id_sto,1,len=iim_g) 
     213     iret = NF90_INQUIRE_DIMENSION (rest_id_sto,2,len=jjm_g) 
     214     iret = NF90_CLOSE (rest_id_sto) 
    172215     !- 
    173216     ! Allocate longitudes and latitudes 
    174217     !- 
    175      ALLOCATE (lon(iim,jjm)) 
    176      ALLOCATE (lat(iim,jjm)) 
     218     ALLOCATE (lon(iim_g,jjm_g)) 
     219     ALLOCATE (lat(iim_g,jjm_g)) 
    177220     lon(:,:) = 0.0 
    178221     lat(:,:) = 0.0 
     
    180223     !- 
    181224     CALL restini & 
    182           & (sto_restname_in, iim, jjm, lon, lat, llm, lev, & 
     225          & (sto_restname_in, iim_g, jjm_g, lon, lat, llm, lev, & 
    183226          &  sto_restname_out, itau_dep, date0, dt_files, rest_id_sto) 
    184227  ENDIF 
     
    188231  CALL bcast(date0) 
    189232!!! MM : à revoir : choix du calendrier dans forcesoil ?? Il est dans le restart de stomate ! 
    190   CALL ioconf_calendar ('noleap') 
     233  CALL ioconf_calendar ('noleap') 
    191234  CALL ioget_calendar  (one_year,one_day) 
    192235 
     
    197240     ! open FORCESOIL's forcing file to read some basic info 
    198241     !- 
    199      Cforcing_name = 'stomate_Cforcing.nc' 
     242     Cforcing_name = 'NONE' 
    200243     CALL getin ('STOMATE_CFORCING_NAME',Cforcing_name) 
    201244     !- 
    202      ier = NF90_OPEN (TRIM(Cforcing_name),NF90_NOWRITE,Cforcing_id) 
     245     iret = NF90_OPEN (TRIM(Cforcing_name),NF90_NOWRITE,Cforcing_id) 
     246     IF (iret /= NF90_NOERR) THEN 
     247        CALL ipslerr (3,'forcesoil', & 
     248             &        'Could not open file : ', & 
     249             &          Cforcing_name,'(Do you have forget it ?)') 
     250     ENDIF 
    203251     !- 
    204252     ier = NF90_GET_ATT (Cforcing_id,NF90_GLOBAL,'kjpindex',x_tmp) 
    205      kjpindex = NINT(x_tmp) 
     253     nbp_glo = NINT(x_tmp) 
    206254     ier = NF90_GET_ATT (Cforcing_id,NF90_GLOBAL,'nparan',x_tmp) 
    207255     nparan = NINT(x_tmp) 
    208256     !- 
    209      ALLOCATE (indices(kjpindex)) 
    210      ALLOCATE (clay(kjpindex)) 
    211      !- 
    212      ALLOCATE (x_indices(kjpindex),stat=ier) 
     257     ALLOCATE (indices_g(nbp_glo)) 
     258     ALLOCATE (clay_g(nbp_glo)) 
     259     !- 
     260     ALLOCATE (x_indices_g(nbp_glo),stat=ier) 
    213261     ier = NF90_INQ_VARID (Cforcing_id,'index',v_id) 
    214      ier = NF90_GET_VAR   (Cforcing_id,v_id,x_indices) 
    215      indices(:) = NINT(x_indices(:)) 
    216      DEALLOCATE (x_indices) 
     262     ier = NF90_GET_VAR   (Cforcing_id,v_id,x_indices_g) 
     263     indices_g(:) = NINT(x_indices_g(:)) 
     264     WRITE(numout,*) mpi_rank,"indices globaux : ",indices_g 
     265     DEALLOCATE (x_indices_g) 
    217266     !- 
    218267     ier = NF90_INQ_VARID (Cforcing_id,'clay',v_id) 
    219      ier = NF90_GET_VAR   (Cforcing_id,v_id,clay) 
     268     ier = NF90_GET_VAR   (Cforcing_id,v_id,clay_g) 
    220269     !- 
    221270     ! time step of forcesoil 
    222271     !- 
    223272     dt_forcesoil = one_year / FLOAT(nparan) 
    224      WRITE(*,*) 'time step (d): ',dt_forcesoil 
     273     WRITE(numout,*) 'time step (d): ',dt_forcesoil 
    225274     !- 
    226275     ! read (and partially write) the restart file 
     
    258307           l1d = ALL(vardims(1:varnbdim) == 1) 
    259308           !---- 
    260            ALLOCATE( var_3d(kjpindex,vardims(3)), stat=ier) 
     309           ALLOCATE( var_3d(nbp_glo,vardims(3)), stat=ier) 
    261310           IF (ier /= 0) STOP 'ALLOCATION PROBLEM' 
    262311           !---- read it 
     
    267316           ELSE 
    268317              CALL restget & 
    269                    &        (rest_id_sto, TRIM(varnames(iv)), kjpindex, vardims(3), & 
    270                    &         1, itau_dep, .TRUE., var_3d, "gather", kjpindex, indices) 
     318                   &        (rest_id_sto, TRIM(varnames(iv)), nbp_glo, vardims(3), & 
     319                   &         1, itau_dep, .TRUE., var_3d, "gather", nbp_glo, indices_g) 
    271320           ENDIF 
    272321           !---- write it 
     
    277326           ELSE 
    278327              CALL restput & 
    279                    &        (rest_id_sto, TRIM(varnames(iv)), kjpindex, vardims(3), & 
    280                    &         1, itau_dep, var_3d, 'scatter',  kjpindex, indices) 
     328                   &        (rest_id_sto, TRIM(varnames(iv)), nbp_glo, vardims(3), & 
     329                   &         1, itau_dep, var_3d, 'scatter',  nbp_glo, indices_g) 
    281330           ENDIF 
    282331           !---- 
     
    287336     ! read soil carbon 
    288337     !- 
    289      ALLOCATE(carbon(kjpindex,ncarb,nvm)) 
    290      carbon(:,:,:) = val_exp 
     338     ALLOCATE(carbon_g(nbp_glo,ncarb,nvm)) 
     339     carbon_g(:,:,:) = val_exp 
    291340     DO m = 1, nvm 
    292341        WRITE (part_str, '(I2)') m 
    293342        IF (m<10) part_str(1:1)='0' 
    294343        var_name = 'carbon_'//part_str(1:LEN_TRIM(part_str)) 
    295         CALL restget_p & 
    296              &    (rest_id_sto, var_name, kjpindex, ncarb , 1, itau_dep, & 
    297              &     .TRUE., carbon(:,:,m), 'gather', kjpindex, indices) 
    298         IF (ALL(carbon(:,:,m) == val_exp)) carbon(:,:,m) = zero 
     344        CALL restget & 
     345             &    (rest_id_sto, var_name, nbp_glo, ncarb , 1, itau_dep, & 
     346             &     .TRUE., carbon_g(:,:,m), 'gather', nbp_glo, indices_g) 
     347        IF (ALL(carbon_g(:,:,m) == val_exp)) carbon_g(:,:,m) = zero 
    299348        !-- do not write this variable: it will be modified. 
    300349     ENDDO 
     
    304353     WRITE(time_str,'(a)') '10000Y' 
    305354     CALL getin('TIME_LENGTH', time_str) 
     355     write(numout,*) 'Number of years for carbon spinup : ',time_str 
    306356     ! transform into itau 
    307357     CALL tlen2itau(time_str, dt_forcesoil*one_year, date0, itau_len) 
    308      write(*,*) 'Number of time steps to do: ',itau_len 
     358     write(numout,*) 'Number of time steps to do: ',itau_len 
    309359     !- 
    310360     ! read the rest of the forcing file and store forcing in an array. 
    311361     ! We read an average year. 
    312362     !- 
    313      ALLOCATE(soilcarbon_input(kjpindex,ncarb,nvm,nparan)) 
    314      ALLOCATE(control_temp(kjpindex,nlevs,nparan)) 
    315      ALLOCATE(control_moist(kjpindex,nlevs,nparan)) 
     363     ALLOCATE(soilcarbon_input_g(nbp_glo,ncarb,nvm,nparan)) 
     364     ALLOCATE(control_temp_g(nbp_glo,nlevs,nparan)) 
     365     ALLOCATE(control_moist_g(nbp_glo,nlevs,nparan)) 
    316366     !- 
    317367     ier = NF90_INQ_VARID (Cforcing_id,'soilcarbon_input',v_id) 
    318      ier = NF90_GET_VAR   (Cforcing_id,v_id,soilcarbon_input) 
     368     ier = NF90_GET_VAR   (Cforcing_id,v_id,soilcarbon_input_g) 
    319369     ier = NF90_INQ_VARID (Cforcing_id,   'control_moist',v_id) 
    320      ier = NF90_GET_VAR   (Cforcing_id,v_id,control_moist) 
     370     ier = NF90_GET_VAR   (Cforcing_id,v_id,control_moist_g) 
    321371     ier = NF90_INQ_VARID (Cforcing_id,    'control_temp',v_id) 
    322      ier = NF90_GET_VAR   (Cforcing_id,v_id,control_temp) 
     372     ier = NF90_GET_VAR   (Cforcing_id,v_id,control_temp_g) 
    323373     !- 
    324374     ier = NF90_CLOSE (Cforcing_id) 
    325375     !- 
    326      !MM Problem here with dpu which depends on soil type            
    327      DO iv = 1, nbdl-1 
    328         ! first 2.0 is dpu  
    329         ! second 2.0 is average 
    330         diaglev(iv) = 2.0/(2**(nbdl-1) -1) * ( ( 2**(iv-1) -1) + ( 2**(iv) -1) ) / 2.0 
    331      ENDDO 
    332      diaglev(nbdl) = 2.0 
    333      !- 
    334      ! For sequential use only, we must initialize data_para : 
     376  ENDIF 
     377  CALL bcast(nparan) 
     378  CALL bcast(dt_forcesoil) 
     379  CALL bcast(iim_g) 
     380  CALL bcast(jjm_g) 
     381  call bcast(nbp_glo) 
     382  CALL bcast(itau_len) 
     383  ! 
     384  ! We must initialize data_para : 
    335385     ! 
    336386     ! 
    337   ENDIF 
    338  
    339   CALL bcast(iim) 
    340   CALL bcast(jjm) 
    341   call bcast(kjpindex) 
    342   CALL init_data_para(iim,jjm,kjpindex,indices) 
    343  
     387  CALL init_data_para(iim_g,jjm_g,nbp_glo,indices_g) 
     388 
     389  kjpindex=nbp_loc 
     390  jjm=jj_nb 
     391  iim=iim_g 
     392  IF (debug) WRITE(numout,*) "Local grid : ",kjpindex,iim,jjm 
     393 
     394  !--- 
     395  !--- Create the index table 
     396  !--- 
     397  !--- This job return a LOCAL kindex 
     398  !--- 
     399  ALLOCATE (indices(kjpindex),stat=ier) 
     400  CALL scatter(indices_g,indices) 
     401  indices(1:kjpindex)=indices(1:kjpindex)-(jj_begin-1)*iim_g 
     402  WRITE(numout,*) mpi_rank,"indices locaux = ",indices(1:kjpindex) 
    344403  !- 
    345404  !- 
    346405  ! there we go: time loop 
    347406  !- 
    348   CALL bcast(nparan) 
    349   ALLOCATE(clay_loc(nbp_loc)) 
    350   ALLOCATE(soilcarbon_input_loc(nbp_loc,ncarb,nvm,nparan)) 
    351   ALLOCATE(control_temp_loc(nbp_loc,nlevs,nparan)) 
    352   ALLOCATE(control_moist_loc(nbp_loc,nlevs,nparan)) 
    353   ALLOCATE(carbon_loc(nbp_loc,ncarb,nvm)) 
    354   ALLOCATE(resp_hetero_soil(nbp_loc,nvm)) 
     407  ALLOCATE(clay(kjpindex)) 
     408  ALLOCATE(soilcarbon_input(kjpindex,ncarb,nvm,nparan)) 
     409  ALLOCATE(control_temp(kjpindex,nlevs,nparan)) 
     410  ALLOCATE(control_moist(kjpindex,nlevs,nparan)) 
     411  ALLOCATE(carbon(kjpindex,ncarb,nvm)) 
     412  ALLOCATE(resp_hetero_soil(kjpindex,nvm)) 
    355413  iatt = 0 
    356414 
    357   CALL bcast(itau_len) 
    358   CALL bcast(nparan) 
    359   CALL bcast(dt_forcesoil) 
    360   CALL Scatter(clay,clay_loc) 
    361   CALL Scatter(soilcarbon_input,soilcarbon_input_loc) 
    362   CALL Scatter(control_temp,control_temp_loc) 
    363   CALL Scatter(control_moist,control_moist_loc) 
    364   CALL Scatter(carbon,carbon_loc) 
    365  
    366 !!$ DS 16/06/2011 : calling the new_values of soilcarbon parameters before loop 
    367      ! 
    368      CALL getin_p('FRAC_CARB_AA',frac_carb_aa) 
    369      CALL getin_p('FRAC_CARB_AP',frac_carb_ap)    
    370      CALL getin_p('FRAC_CARB_SS',frac_carb_ss) 
    371      CALL getin_p('FRAC_CARB_SA',frac_carb_sa) 
    372      CALL getin_p('FRAC_CARB_SP',frac_carb_sp) 
    373      CALL getin_p('FRAC_CARB_PP',frac_carb_pp) 
    374      CALL getin_p('FRAC_CARB_PA',frac_carb_pa) 
    375      CALL getin_p('FRAC_CARB_PS',frac_carb_ps) 
    376      ! 
    377      CALL getin_p('ACTIVE_TO_PASS_CLAY_FRAC',active_to_pass_clay_frac) 
    378      CALL getin_p('CARBON_TAU_IACTIVE',carbon_tau_iactive) 
    379      CALL getin_p('CARBON_TAU_ISLOW',carbon_tau_islow) 
    380      CALL getin_p('CARBON_TAU_IPASSIVE',carbon_tau_ipassive) 
    381      CALL getin_p('FLUX_TOT_COEFF',flux_tot_coeff) 
     415  CALL Scatter(clay_g,clay) 
     416  CALL Scatter(soilcarbon_input_g,soilcarbon_input) 
     417  CALL Scatter(control_temp_g,control_temp) 
     418  CALL Scatter(control_moist_g,control_moist) 
     419  CALL Scatter(carbon_g,carbon) 
     420 
     421!!$ DS 16/06/2011 : for externalization 
     422  ! 
     423  !Config Key  = FRAC_CARB_AA 
     424  !Config Desc = frac carb coefficients from active pool: depends on clay content  
     425  !Config if  = OK_STOMATE  
     426  !Config Def  = 0.0 
     427  !Config Help = fraction of the active pool going to the active pool 
     428  !Config Units = NONE 
     429  CALL getin_p('FRAC_CARB_AA',frac_carb_aa) 
     430  ! 
     431  !Config Key  = FRAC_CARB_AP 
     432  !Config Desc = frac carb coefficients from active pool: depends on clay content 
     433  !Config if  = OK_STOMATE  
     434  !Config Def  = 0.004 
     435  !Config Help = fraction of the active pool going to the passive pool 
     436  !Config Units = NONE 
     437  CALL getin_p('FRAC_CARB_AP',frac_carb_ap)   
     438  ! 
     439  !Config Key  = FRAC_CARB_SS 
     440  !Config Desc = frac_carb_coefficients from slow pool 
     441  !Config if  = OK_STOMATE  
     442  !Config Def  = 0.0  
     443  !Config Help = fraction of the slow pool going to the slow pool 
     444  !Config Units = NONE 
     445  CALL getin_p('FRAC_CARB_SS',frac_carb_ss) 
     446  ! 
     447  !Config Key  = FRAC_CARB_SA 
     448  !Config Desc = frac_carb_coefficients from slow pool 
     449  !Config if  = OK_STOMATE  
     450  !Config Def  = 0.42 
     451  !Config Help = fraction of the slow pool going to the active pool 
     452  !Config Units = NONE  
     453  CALL getin_p('FRAC_CARB_SA',frac_carb_sa) 
     454  ! 
     455  !Config Key  = FRAC_CARB_SP 
     456  !Config Desc = frac_carb_coefficients from slow pool 
     457  !Config if  = OK_STOMATE  
     458  !Config Def  =  0.03 
     459  !Config Help = fraction of the slow pool going to the passive pool 
     460  !Config Units = NONE  
     461  CALL getin_p('FRAC_CARB_SP',frac_carb_sp) 
     462  ! 
     463  !Config Key  = FRAC_CARB_PP 
     464  !Config Desc = frac_carb_coefficients from passive pool 
     465  !Config if  = OK_STOMATE  
     466  !Config Def  = 0.0 
     467  !Config Help = fraction of the passive pool going to the passive pool 
     468  !Config Units = NONE 
     469  CALL getin_p('FRAC_CARB_PP',frac_carb_pp) 
     470  ! 
     471  !Config Key  = FRAC_CARB_PA 
     472  !Config Desc = frac_carb_coefficients from passive pool 
     473  !Config if  = OK_STOMATE  
     474  !Config Def  = 0.45 
     475  !Config Help = fraction of the passive pool going to the passive pool 
     476  !Config Units = NONE  
     477  CALL getin_p('FRAC_CARB_PA',frac_carb_pa) 
     478  ! 
     479  !Config Key  = FRAC_CARB_PS 
     480  !Config Desc = frac_carb_coefficients from passive pool 
     481  !Config if  = OK_STOMATE  
     482  !Config Def  = 0.0 
     483  !Config Help = fraction of the passive pool going to the passive pool 
     484  !Config Units = NONE 
     485  CALL getin_p('FRAC_CARB_PS',frac_carb_ps) 
     486  ! 
     487  !Config Key  = ACTIVE_TO_PASS_CLAY_FRAC 
     488  !Config Desc =  
     489  !Config if  = OK_STOMATE  
     490  !Config Def  =  .68   
     491  !Config Help = 
     492  !Config Units = NONE 
     493  CALL getin_p('ACTIVE_TO_PASS_CLAY_FRAC',active_to_pass_clay_frac) 
     494  ! 
     495  !Config Key  = CARBON_TAU_IACTIVE 
     496  !Config Desc = residence times in carbon pools 
     497  !Config if  = OK_STOMATE  
     498  !Config Def  =  0.149 
     499  !Config Help = 
     500  !Config Units = days [d]  
     501  CALL getin_p('CARBON_TAU_IACTIVE',carbon_tau_iactive) 
     502  ! 
     503  !Config Key  = CARBON_TAU_ISLOW 
     504  !Config Desc = residence times in carbon pools 
     505  !Config if  = OK_STOMATE  
     506  !Config Def  =  5.48 
     507  !Config Help = 
     508  !Config Units = days [d] 
     509  CALL getin_p('CARBON_TAU_ISLOW',carbon_tau_islow) 
     510  ! 
     511  !Config Key  = CARBON_TAU_IPASSIVE 
     512  !Config Desc = residence times in carbon pools 
     513  !Config if  = OK_STOMATE  
     514  !Config Def  =  241. 
     515  !Config Help = 
     516  !Config Units = days [d]  
     517  CALL getin_p('CARBON_TAU_IPASSIVE',carbon_tau_ipassive) 
     518  ! 
     519  !Config Key  = FLUX_TOT_COEFF 
     520  !Config Desc = 
     521  !Config if  = OK_STOMATE  
     522  !Config Def  = 1.2, 1.4,.75 
     523  !Config Help = 
     524  !Config Units = days [d]  
     525  CALL getin_p('FLUX_TOT_COEFF',flux_tot_coeff) 
    382526 
    383527  DO i=1,itau_len 
     
    385529     IF (iatt > nparan) iatt = 1 
    386530     CALL soilcarbon & 
    387           &    (nbp_loc, dt_forcesoil, clay_loc, & 
    388           &     soilcarbon_input_loc(:,:,:,iatt), & 
    389           &     control_temp_loc(:,:,iatt), control_moist_loc(:,:,iatt), & 
    390           &     carbon_loc, resp_hetero_soil) 
     531          &    (kjpindex, dt_forcesoil, clay, & 
     532          &     soilcarbon_input(:,:,:,iatt), & 
     533          &     control_temp(:,:,iatt), control_moist(:,:,iatt), & 
     534          &     carbon, resp_hetero_soil) 
    391535  ENDDO 
    392536 
    393   CALL Gather(carbon_loc,carbon) 
     537  CALL Gather(carbon,carbon_g) 
    394538  !- 
    395539  ! write new carbon into restart file 
     
    400544        IF (m<10) part_str(1:1)='0' 
    401545        var_name = 'carbon_'//part_str(1:LEN_TRIM(part_str)) 
    402         CALL restput_p & 
    403              &    (rest_id_sto, var_name, kjpindex, ncarb , 1, itau_dep, & 
    404              &     carbon(:,:,m), 'scatter', kjpindex, indices) 
     546        CALL restput & 
     547             &    (rest_id_sto, var_name, nbp_glo, ncarb , 1, itau_dep, & 
     548             &     carbon_g(:,:,m), 'scatter', nbp_glo, indices_g) 
    405549     ENDDO 
    406550     !- 
     
    409553  ENDIF 
    410554#ifdef CPP_PARA 
    411   CALL MPI_FINALIZE(ierr) 
     555  CALL MPI_FINALIZE(ier) 
    412556#endif 
     557  WRITE(numout,*) "End of forcesoil." 
    413558  !-------------------- 
    414559END PROGRAM forcesoil 
Note: See TracChangeset for help on using the changeset viewer.