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/lpj_fire.f90

    r136 r257  
    9999    !MM Shilong ?? 
    100100!!$    REAL(r_std), PARAMETER                                           :: tau_fire = 365.  ! GKtest 
    101  
    102101    ! fire perturbation 
    103102    REAL(r_std), DIMENSION(npts)                                     :: fire_disturb 
     
    273272       IF(.NOT.disable_fire.AND.natural(j))THEN 
    274273          WHERE ( aff(:) .GT. 0.1 ) 
    275              firefrac(:,j) = 1. - ( 1. - aff(:) ) ** (dt/one_year) 
     274             firefrac(:,j) = un - ( un - aff(:) ) ** (dt/one_year) 
    276275          ELSEWHERE 
    277276             firefrac(:,j) = aff(:) * dt/one_year 
     
    315314          ! 4.2.1 Trees: always disturbed 
    316315 
    317           fire_disturb(:) = ( 1. - resist(j) ) * firefrac(:,j) 
     316          fire_disturb(:) = ( un - resist(j) ) * firefrac(:,j) 
    318317 
    319318       ELSE 
     
    323322          WHERE ( biomass(:,j,ileaf) .GT. min_stomate ) 
    324323 
    325              fire_disturb(:) = ( 1. - resist(j) ) * firefrac(:,j) 
     324             fire_disturb(:) = ( un - resist(j) ) * firefrac(:,j) 
    326325 
    327326          ELSEWHERE 
     
    353352             ! 4.3.2 Determine the residue, in gC/m**2 of ground. 
    354353 
    355              residue(:) = biomass(:,j,k) * fire_disturb(:) * ( 1. - co2frac(k) ) 
    356              !MM in SZ ???        residue(:) = fire_disturb(:) * ( 1. - co2frac(k) ) 
     354             residue(:) = biomass(:,j,k) * fire_disturb(:) * ( un - co2frac(k) ) 
     355             !MM in SZ ???        residue(:) = fire_disturb(:) * ( un - co2frac(k) ) 
    357356 
    358357             ! 4.3.2.1 determine fraction of black carbon. Only for plant parts above the 
     
    400399          IF ( .NOT. ( ( .NOT. tree(j) ) .AND. ( ( k.EQ.iroot ) .OR. ( k.EQ.icarbres) ) ) ) THEN 
    401400 
    402              biomass(:,j,k) = ( 1. - fire_disturb(:) ) * biomass(:,j,k) 
     401             biomass(:,j,k) = ( un - fire_disturb(:) ) * biomass(:,j,k) 
    403402 
    404403          ENDIF 
     
    409408       !       individuals. 
    410409 
    411        IF ( control%ok_dgvm .AND. tree(j) ) THEN 
     410       IF ( (control%ok_dgvm .OR. .NOT.lpj_gap_const_mort) .AND. tree(j) ) THEN 
    412411 
    413412          ! fraction of plants that dies each day. 
     
    415414          firedeath(:,j) = fire_disturb(:) / dt 
    416415 
    417           ind(:,j) = ( 1. - fire_disturb(:) ) * ind(:,j) 
     416          ind(:,j) = ( un - fire_disturb(:) ) * ind(:,j) 
    418417 
    419418       ENDIF 
     
    440439 
    441440       litter(:,imetabolic,j,iabove) = litter(:,imetabolic,j,iabove) * & 
    442             ( 1. - firefrac(:,j) ) 
     441            ( un - firefrac(:,j) ) 
    443442 
    444443       ! 
     
    455454       co2_fire(:,j) = co2_fire(:,j) + & 
    456455            litter(:,istructural,j,iabove) * firefrac(:,j) * & 
    457             ( 1. - struc_residual(:) )/ dt 
     456            ( un - struc_residual(:) )/ dt 
    458457 
    459458       ! 5.2.3 determine residue (litter that undergoes fire, but is not transformed 
    460459       !       into CO2) 
    461460 
    462        residue(:) = litter(:,istructural,j,iabove) * firefrac(:,j) * & 
    463             struc_residual(:) 
     461!NV,MM : We add this test to keep coherence with CMIP5 computations without DGVM. 
     462!        It has to be removed in trunk version after CMIP5. 
     463       IF (control%ok_dgvm .OR. .NOT.lpj_gap_const_mort) THEN 
     464          residue(:) = firefrac(:,j) * struc_residual(:) 
     465       ELSE 
     466          residue(:) = litter(:,istructural,j,iabove) * firefrac(:,j) * & 
     467               struc_residual(:) 
     468       ENDIF 
     469 
     470!       residue(:) = litter(:,istructural,j,iabove) * firefrac(:,j) * & 
     471!            struc_residual(:) 
    464472       !MM in SZ        residue(:) = firefrac(:,j) * struc_residual(:) 
    465473 
     
    482490 
    483491       litter(:,istructural,j,iabove) = & 
    484             litter(:,istructural,j,iabove) * ( 1. - firefrac(:,j) ) + & 
    485             residue(:) * ( 1. - bcfrac(:) ) 
    486        !MM in SZ            residue(:) * ( 1. - bcfrac(:) ) * litter(:,iwoody,j,iabove) 
     492            litter(:,istructural,j,iabove) * ( un - firefrac(:,j) ) + & 
     493            residue(:) * ( un - bcfrac(:) ) 
     494       !MM in SZ            residue(:) * ( un - bcfrac(:) ) * litter(:,iwoody,j,iabove) 
    487495 
    488496    ENDDO  !  ground 
     
    496504 
    497505       DO k = 1, nlitt 
    498           dead_leaves(:,j,k) = dead_leaves(:,j,k) * ( 1. - firefrac(:,j) ) 
     506          dead_leaves(:,j,k) = dead_leaves(:,j,k) * ( un - firefrac(:,j) ) 
    499507       ENDDO 
    500508 
     
    543551 
    544552    firefrac_result(:) = & 
    545 !         x(:) * EXP( xm1(:) / ( -.13*xm1(:)*xm1(:)*xm1(:) + .6*xm1(:)*xm1(:) + .8*xm1(:) + .45 ) ) 
    546553         x(:) * EXP( xm1(:) / ( -firefrac_coeff(4)*xm1(:)*xm1(:)*xm1(:) + firefrac_coeff(3)*xm1(:)*xm1(:) + firefrac_coeff(2)*xm1(:) + firefrac_coeff(1) ) ) 
    547554 
    548  
    549555  END FUNCTION firefrac_func 
    550556 
Note: See TracChangeset for help on using the changeset viewer.