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_stomate/stomate_prescribe.f90

    r64 r257  
    1919  USE pft_parameters 
    2020  USE constantes 
    21  
    2221 
    2322  IMPLICIT NONE 
     
    8988      ! only when the DGVM is not activated or agricultural PFT. 
    9089 
    91       IF ( ( .NOT. control%ok_dgvm ) .OR. ( .NOT. natural(j) ) ) THEN 
     90      IF ( ( .NOT. control%ok_dgvm .AND. lpj_gap_const_mort ) .OR. ( .NOT. natural(j) ) ) THEN 
    9291 
    9392        ! 
     
    9594        ! 
    9695 
    97         cn_ind(:,j) = 0.0 
     96        cn_ind(:,j) = zero 
    9897 
    9998        IF ( tree(j) ) THEN 
     
    103102          ! 
    104103 
    105           dia(:) = 0.0 
     104          dia(:) = zero 
    106105 
    107106          DO i = 1, npts 
    108107 
    109             IF ( veget_max(i,j) .GT. 0.0 ) THEN 
     108            IF ( veget_max(i,j) .GT. zero ) THEN 
    110109 
    111110              ! 1.1.1 calculate total wood mass 
     
    128127 
    129128                dia(i) = ( woodmass_ind(i) / ( pipe_density * pi/4. * pipe_tune2 ) ) ** & 
    130                          ( 1. / ( 2. + pipe_tune3 ) ) 
     129                         ( un / ( 2. + pipe_tune3 ) ) 
    131130 
    132131                ! 1.1.5 crown area, provisional 
     
    149148 
    150149                  dia(i) = ( woodmass_ind(i) / ( pipe_density * pi/4. * pipe_tune2 ) ) ** & 
    151                            ( 1. / ( 2. + pipe_tune3 ) ) 
     150                           ( un / ( 2. + pipe_tune3 ) ) 
    152151 
    153152                  ! final crown area 
     
    176175          ! 
    177176 
    178           WHERE ( veget_max(:,j) .GT. 0.0 ) 
    179             cn_ind(:,j) = 1.0 
     177          WHERE ( veget_max(:,j) .GT. zero ) 
     178            cn_ind(:,j) = un 
    180179          ENDWHERE 
    181180 
     
    186185        ! 
    187186 
    188         WHERE ( veget_max(:,j) .GT. 0.0 ) 
     187        WHERE ( veget_max(:,j) .GT. zero ) 
    189188 
    190189          ind(:,j) = veget_max(:,j) / cn_ind(:,j) 
     
    192191        ELSEWHERE 
    193192 
    194           ind(:,j) = 0.0 
     193          ind(:,j) = zero 
    195194 
    196195        ENDWHERE 
     
    247246              IF ( pheno_model(j) .NE. 'none' ) THEN 
    248247 
    249                 biomass(i,j,ileaf) = 0.0 
    250                 leaf_frac(i,j,1) = 0.0 
     248                biomass(i,j,ileaf) = zero 
     249                leaf_frac(i,j,1) = zero 
    251250 
    252251              ENDIF 
     
    265264 
    266265              ! set leaf age classes 
    267               leaf_frac(i,j,:) = 0.0 
    268               leaf_frac(i,j,1) = 1.0 
     266              leaf_frac(i,j,:) = zero 
     267              leaf_frac(i,j,1) = un 
    269268 
    270269              ! set time since last beginning of growing season 
     
    279278            IF ( veget_max(i,j) .GT. min_stomate ) THEN 
    280279              PFTpresent(i,j) = .TRUE. 
    281               everywhere(i,j) = 1. 
     280              everywhere(i,j) = un 
    282281            ENDIF 
    283282 
Note: See TracChangeset for help on using the changeset viewer.