Ignore:
Timestamp:
2011-09-08T09:37:26+02:00 (13 years ago)
Author:
didier.solyga
Message:

Correct bcast functions. In sechiba modules, move var_name from save variables to local variables. Correct a save attribute to parameter attribute in constantes_mtc.f90

File:
1 edited

Legend:

Unmodified
Added
Removed
  • branches/ORCHIDEE_EXT/ORCHIDEE/src_sechiba/thermosoil.f90

    r257 r461  
    3535  ! 
    3636  LOGICAL, SAVE                             :: l_first_thermosoil=.TRUE. !! Initialisation has to be done one time 
    37  
    38   CHARACTER(LEN=80) , SAVE                  :: var_name                  !! To store variables names for I/O 
    3937  REAL(r_std), SAVE                          :: lambda, cstgrnd, lskin, fz1, zalph 
    4038 
     
    106104    REAL(r_std),DIMENSION (kjpindex), INTENT (inout)     :: soilflx           
    107105    REAL(r_std),DIMENSION (kjpindex,nbdl), INTENT (inout):: stempdiag        !! diagnostic temp profile 
    108  
     106    ! local 
    109107    REAL(r_std),DIMENSION (kjpindex,ngrnd) :: temp 
    110108    REAL(r_std),DIMENSION (kjpindex,ngrnd-1) :: temp1 
    111109    REAL(r_std),DIMENSION (kjpindex) :: temp2 
     110    CHARACTER(LEN=80)                :: var_name                  !! To store variables names for I/O 
     111 
    112112    ! 
    113113    ! do initialisation 
     
    252252        CALL restput_p(rest_id, var_name, nbp_glo, 1, 1, kjit, z1, 'scatter', nbp_glo, index_g) 
    253253 
    254             var_name= 'pcapa' 
     254        var_name= 'pcapa' 
    255255        CALL restput_p(rest_id, var_name, nbp_glo, ngrnd, 1, kjit, pcapa, 'scatter', nbp_glo, index_g) 
    256256 
    257             var_name= 'pcapa_en' 
     257        var_name= 'pcapa_en' 
    258258        CALL restput_p(rest_id, var_name, nbp_glo, ngrnd, 1, kjit, pcapa_en, 'scatter', nbp_glo, index_g) 
    259259 
    260             var_name= 'pkappa' 
     260        var_name= 'pkappa' 
    261261        CALL restput_p(rest_id, var_name, nbp_glo, ngrnd, 1, kjit, pkappa, 'scatter', nbp_glo, index_g) 
    262262 
    263             var_name= 'zdz1' 
     263        var_name= 'zdz1' 
    264264        CALL restput_p(rest_id, var_name, nbp_glo, ngrnd-1, 1, kjit, zdz1, 'scatter', nbp_glo, index_g) 
    265265 
    266             var_name= 'zdz2' 
     266        var_name= 'zdz2' 
    267267        CALL restput_p(rest_id, var_name, nbp_glo, ngrnd, 1, kjit, zdz2, 'scatter', nbp_glo, index_g) 
    268268 
     
    342342    ! local declaration 
    343343    INTEGER(i_std)                                     :: ier 
     344    CHARACTER(LEN=80)                                  :: var_name            !! To store variables names for I/O 
    344345 
    345346    ! initialisation 
     
    466467        ! 
    467468        ! change restart If they were not found in the restart file 
    468 ! 
    469 !Config Key  = THERMOSOIL_TPRO 
    470 !Config Desc = Initial soil temperature profile if not found in restart 
    471 !Config Def  = 280. 
    472 !Config Help = The initial value of the temperature profile in the soil if  
    473 !Config        its value is not found in the restart file. This should only  
    474 !Config        be used if the model is started without a restart file. Here 
    475 !Config        we only require one value as we will assume a constant  
    476 !Config        throughout the column. 
    477 ! 
     469        ! 
     470        !Config Key  = THERMOSOIL_TPRO 
     471        !Config Desc = Initial soil temperature profile if not found in restart 
     472        !Config Def  = 280. 
     473        !Config Help = The initial value of the temperature profile in the soil if  
     474        !Config        its value is not found in the restart file. This should only  
     475        !Config        be used if the model is started without a restart file. Here 
     476        !Config        we only require one value as we will assume a constant  
     477        !Config        throughout the column. 
     478        ! 
    478479        CALL setvar_p (ptn, val_exp,'THERMOSOIL_TPRO',280._r_std) 
    479480 
Note: See TracChangeset for help on using the changeset viewer.