Ignore:
Timestamp:
2011-06-20T15:28:40+02:00 (13 years ago)
Author:
didier.solyga
Message:

Correct forcesoil.f90 and teststomate.f90 for working with the externalized version (branche ORCHIDEE_EXT)

File:
1 edited

Legend:

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

    r258 r272  
    5353  REAL(r_std),DIMENSION(:,:),ALLOCATABLE    :: qsintmax_x 
    5454  REAL(r_std),DIMENSION(:,:),ALLOCATABLE    :: co2_flux 
    55 !!$   DS add for externalised version 
     55!!$ >>  DS add for externalised version 
    5656  REAL(r_std),DIMENSION(:),ALLOCATABLE      :: hist_PFTaxis 
    57 !!$   DS 
     57!!$ >>  DS 
    5858 
    5959 
     
    7575  CHARACTER(LEN=30)                :: time_str 
    7676  REAL                             :: hist_days_stom,hist_dt_stom 
    77 !!$  REAL,DIMENSION(nvm)              :: hist_PFTaxis 
    7877  REAL(r_std),DIMENSION(10)         :: hist_pool_10axis      
    7978  REAL(r_std),DIMENSION(100)        :: hist_pool_100axis      
     
    176175  write(*,*) 'ATTENTION',dtradia,dt_force 
    177176 
    178 !!$ DS added for the externalised version 
    179 !!$we need to know the pft parameters values used for stomate 
     177!!$ >> DS added for the externalised version 
     178!!$ we need to know the pft parameters values used for stomate 
     179 
     180  ! 1. Read the number of PFTs 
     181  CALL getin('NVM',nvm) 
     182  ! 2. Allocate and read the pft parameters stomate specific 
    180183  CALL pft_parameters_main 
    181184  CALL getin_stomate_pft_parameters 
     
    186189!- 
    187190  a_er = .FALSE. 
    188 !!$ DS added for the externalised version 
    189 !!$  ALLOCATE (pft_to_mtc(nvm),stat=ier) 
    190 !!$  a_er = a_er .OR. (ier.NE.0)  
     191!!$ >> DS added for the externalised version 
    191192  ALLOCATE (hist_PFTaxis(nvm),stat=ier) 
    192193  a_er = a_er .OR. (ier.NE.0) 
     
    356357  control%ok_co2 = .TRUE. 
    357358  control%ok_stomate = .TRUE. 
    358 !!$DS now we search the values for the scalar parameters in orchidee.def 
     359!!$ >> DS now we search the values for the scalar parameters in  some .def files 
    359360  CALL getin_co2_parameters 
    360361  CALL getin_stomate_parameters 
    361 !!$  CALL getin('CLAYFRACTION_DEFAULT',clayfraction_default) 
     362!!$ >> DS  
    362363!- 
    363364! is DGVM activated? 
     
    366367  CALL getin('STOMATE_OK_DGVM',control%ok_dgvm) 
    367368  WRITE(*,*) 'LPJ is activated: ',control%ok_dgvm 
    368 !!$DS for the externalisation reading the scalar parameters when ok_dgvm is set to true 
     369!!$ >> DS for the externalisation reading the scalar parameters when ok_dgvm is set to true 
    369370  IF (control%ok_dgvm) THEN  
    370371     CALL getin_dgvm_parameters    
    371372  ENDIF 
     373!!$ >> DS  
    372374!- 
    373375! restart files 
     
    542544!- 
    543545   
    544   ! DS : getin the value of slowproc parameters 
     546  ! >> DS : getin the value of slowproc parameters 
    545547  CALL getin('CLAYFRACTION_DEFAULT',clayfraction_default) 
     548  CALL getin('SOILTYPE_DEFAULT',soiltype_default) 
     549  ! >> DS 
    546550 
    547551  CALL slowproc_main & 
Note: See TracChangeset for help on using the changeset viewer.