Changeset 435


Ignore:
Timestamp:
2011-09-02T10:32:15+02:00 (13 years ago)
Author:
didier.solyga
Message:

Add a new getin_p subroutine for vector of characters. Replace the last getin by getin_p. Use the new function of IOPSL for writing the names of the PFTs defined by the user in the history files

Location:
branches/ORCHIDEE_EXT/ORCHIDEE
Files:
5 edited

Legend:

Unmodified
Added
Removed
  • branches/ORCHIDEE_EXT/ORCHIDEE/src_parallel/ioipsl_para.f90

    r257 r435  
    1515!- 
    1616  INTERFACE getin_p 
    17     MODULE PROCEDURE getin_p_c,                      & 
     17    MODULE PROCEDURE getin_p_c,getin_p_c1,   & 
    1818         getin_p_i,getin_p_i1,getin_p_i2,& 
    1919         getin_p_r,getin_p_r1,getin_p_r2,& 
     
    5151  END SUBROUTINE getin_p_c   
    5252 
     53! DS 02/09/2011 : add for vector of characters 
     54 
     55  SUBROUTINE getin_p_c1(VarIn,VarOut) 
     56    IMPLICIT NONE     
     57    CHARACTER(LEN=*),INTENT(IN) :: VarIn 
     58    CHARACTER(LEN=*),INTENT(INOUT) :: VarOut(:)     
     59 
     60    IF (is_root_prc) CALL getin(VarIn,VarOut) 
     61    CALL bcast(VarOut) 
     62  END SUBROUTINE getin_p_c1  
     63 
    5364!! -- Les entiers -- !! 
    5465   
  • branches/ORCHIDEE_EXT/ORCHIDEE/src_parallel/transfert_para.f90

    r381 r435  
    1616 
    1717  INTERFACE bcast 
    18     MODULE PROCEDURE bcast_c,                                     & 
     18    MODULE PROCEDURE bcast_c, bcast_c1,                           & 
    1919                     bcast_i,bcast_i1,bcast_i2,bcast_i3,bcast_i4, & 
    2020                     bcast_r,bcast_r1,bcast_r2,bcast_r3,bcast_r4, & 
     
    7575#endif 
    7676  END SUBROUTINE bcast_c 
     77 
     78! DS 02/09/2011 : add for vector of characters 
     79 
     80  SUBROUTINE bcast_c1(var1) 
     81  IMPLICIT NONE 
     82    CHARACTER(LEN=*),INTENT(INOUT) :: Var1(:) 
     83    
     84#ifndef CPP_PARA 
     85    RETURN 
     86#else 
     87    CALL bcast_cgen(Var1,size(Var1)) 
     88#endif 
     89  END SUBROUTINE bcast_c1 
    7790 
    7891!! -- Les entiers -- !! 
  • branches/ORCHIDEE_EXT/ORCHIDEE/src_parameters/constantes.f90

    r433 r435  
    11961196           !Config Help = set to TRUE if constant mortality is to be activated 
    11971197           !              ignored if DGVM=true! 
    1198            CALL getin('LPJ_GAP_CONST_MORT', lpj_gap_const_mort) 
     1198           CALL getin_p('LPJ_GAP_CONST_MORT', lpj_gap_const_mort) 
    11991199           ! 
    12001200           !Config  Key  = HARVEST_AGRI 
  • branches/ORCHIDEE_EXT/ORCHIDEE/src_parameters/pft_parameters.f90

    r428 r435  
    481481      !Config  Help = the user can name the new PFTs he/she introducing for new species 
    482482      !Config  Units = NONE 
    483       CALL getin('PFT_NAME',pft_name) 
     483      CALL getin_p('PFT_NAME',pft_name) 
    484484 
    485485      ! 5.2 A useful message to the user: correspondance between the number of the pft 
     
    10671067     !Config  Help = 
    10681068     !Config  Units = NONE 
    1069      CALL getin('TYPE_OF_LAI',type_of_lai) 
     1069     CALL getin_p('TYPE_OF_LAI',type_of_lai) 
    10701070     ! 
    10711071     !Config  Key  = IS_TREE 
     
    10941094     !Config  Help = 
    10951095     !Config  Units = NONE 
    1096      CALL getin('IS_DECIDUOUS',is_deciduous) 
     1096     CALL getin_p('IS_DECIDUOUS',is_deciduous) 
    10971097     ! 
    10981098     !Config  Key  = IS_EVERGREEN 
     
    11021102     !Config  Help = 
    11031103     !Config  Units = NONE  
    1104      CALL getin('IS_EVERGREEN',is_evergreen) 
     1104     CALL getin_p('IS_EVERGREEN',is_evergreen) 
    11051105     ! 
    11061106     !Config  Key  = IS_C3 
     
    16181618     !Config  Help = 
    16191619     !Config  Units = NONE 
    1620      CALL getin('PHENO_MODEL',pheno_model) 
     1620     CALL getin_p('PHENO_MODEL',pheno_model) 
    16211621     ! 
    16221622     !Config  Key  = PHENO_TYPE 
     
    17811781     !Config  Help = 
    17821782     !Config  Units = NONE 
    1783      CALL getin('SENESCENCE_TYPE', senescence_type)  
     1783     CALL getin_p('SENESCENCE_TYPE', senescence_type)  
    17841784     ! 
    17851785     !Config  Key  = SENESCENCE_HUM 
  • branches/ORCHIDEE_EXT/ORCHIDEE/src_sechiba/intersurf.f90

    r433 r435  
    32023202         & fluxop_scinsec2, tmincels2, tmaxcels2, once2, sumscatter2  !! The various operation to be performed 
    32033203!!, tmax2, fluxop_sc2, fluxop_insec2, & 
     3204    ! DS for externalization : write the names of the pfts in the history files 
     3205    ! Warning : works only if you use the trunk of IOIPSL library (02/09/2011) 
     3206    CHARACTER(LEN=80) :: global_attribute 
    32043207    INTEGER(i_std)     :: i, jst 
    32053208    ! SECHIBA AXIS 
     
    39123915    CALL histdef(hist_id, 'Contfrac', 'Continental fraction', '1', & 
    39133916         & iim,jjm, hori_id, 1,1,1, -99, 32, once(1), dt, dw) 
     3917    !- 
     3918    ! DS for externalization : write the names of the pfts in the history files 
     3919    ! Warning : works only if you use the trunk of IOIPSL library (02/09/2011) 
     3920    global_attribute="PFT_name" 
     3921    DO i=1,nvm 
     3922       WRITE(global_attribute(9:10),"(I2.2)") i 
     3923       CALL histglobal_attr(hist_id,global_attribute,PFT_name(i)) 
     3924    ENDDO 
    39143925    !- 
    39153926    CALL histend(hist_id) 
Note: See TracChangeset for help on using the changeset viewer.