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_crown.f90

    r64 r257  
    66  !--------------------------------------------------------------------- 
    77  !- calculate individual crown area from stem mass. 
     8  !- SZ, I've put the woodmass calculation out of this routine 
     9  !      because after the very first establishment, woodmass 
     10  !      could not be calculated here as veget_max = zero and  
     11  !      d_ind not known... 
    812  !--------------------------------------------------------------------- 
    913  USE ioipsl 
     
    2428  !- 
    2529  SUBROUTINE crown & 
    26        &  (npts, PFTpresent, ind, biomass, veget_max, cn_ind, height) 
     30       &  (npts, PFTpresent, ind, biomass, woodmass_ind, veget_max, cn_ind, height) 
    2731    !--------------------------------------------------------------------- 
    2832    ! 0 declarations 
     
    3842    ! biomass (gC/(m**2 of ground)) 
    3943    REAL(r_std),DIMENSION(npts,nvm,nparts),INTENT(in) :: biomass 
     44    ! woodmass of the individual, needed to calculate crownarea in lpj_crownarea 
     45    REAL(r_std),DIMENSION(npts,nvm),INTENT(in) :: woodmass_ind 
    4046    !- 
    4147    ! 0.2 modified fields 
     
    5965    ! wood mass of an individual 
    6066    !- 
    61     REAL(r_std),DIMENSION(npts) :: woodmass 
     67!!$    REAL(r_std),DIMENSION(npts) :: woodmass 
    6268    !- 
    6369    ! index 
     
    7581    ! 1.1 check if DGVM activated 
    7682    !- 
    77     IF (.NOT.control%ok_dgvm) THEN 
     83    IF (.NOT.control%ok_dgvm .AND. lpj_gap_const_mort) THEN 
    7884       STOP 'crown: not to be called with static vegetation.' 
    7985    ENDIF 
     
    8187    ! 1.2 initialize output to zero 
    8288    !- 
    83     cn_ind(:,:) = 0.0 
     89    cn_ind(:,:) = zero 
    8490    ! no convertion, just cop 
    8591    height_presc_12(1:nvm) = height_presc(1:nvm) 
     
    94100          IF (natural(j)) THEN 
    95101             !------ 2.1.1 natural 
    96              WHERE (PFTpresent(:,j) .AND.ind(:,j).GT.min_stomate) 
    97                 !-------- 2.1.1.1 calculate individual wood mass 
    98                 woodmass(:) = & 
    99                      &         (biomass(:,j,isapabove)+biomass(:,j,isapbelow) & 
    100                      &         +biomass(:,j,iheartabove)+biomass(:,j,iheartbelow))/ind(:,j) 
     102             !WHERE (PFTpresent(:,j) .AND.ind(:,j).GT.min_stomate) 
     103             WHERE (PFTpresent(:,j) .AND.woodmass_ind(:,j).GT.min_stomate) 
     104!!$SZ note that woodmass_ind needs to be defined on the individual, hence 
     105!!$ biomass*veget_max/ind, not as stated here, correction MERGE 
     106!!$!-------- 2.1.1.1 calculate individual wood mass 
     107!!$          woodmass(:) = & 
     108!!$ &         (biomass(:,j,isapabove)+biomass(:,j,isapbelow) & 
     109!!$ &         +biomass(:,j,iheartabove)+biomass(:,j,iheartbelow))/ind(:,j) 
    101110                !-------- 2.1.1.2 stem diameter (pipe model) 
    102                 dia(:) = (woodmass(:)/(pipe_density*pi/4.*pipe_tune2)) & 
     111!!$          dia(:) = (woodmass(:)/(pipe_density*pi/4.*pipe_tune2)) & 
     112                dia(:) = (woodmass_ind(:,j)/(pipe_density*pi/4.*pipe_tune2)) & 
    103113                     &                **(1./(2.+pipe_tune3)) 
    104114                !-------- 2.1.1.3 height 
    105115                height(:,j) = pipe_tune2*(dia(:)**pipe_tune3) 
    106                 WHERE (height(:,j) > height_presc_12(j)) 
    107                    dia(:) = (height_presc_12(j)/pipe_tune2)**(1./pipe_tune3) 
    108                    height(:,j) = height_presc_12(j) 
    109                 ENDWHERE 
     116!!$SZ: The constraint on height has nothing to do with LPJ (for that purpose there's dia_max 
     117!!$ cannot see why this is necessary - it also blurrs the output, hence I leave it commented 
     118!!$                WHERE (height(:,j) > height_presc_12(j)) 
     119!!$                   dia(:) = (height_presc_12(j)/pipe_tune2)**(1./pipe_tune3) 
     120!!$                   height(:,j) = height_presc_12(j) 
     121!!$                ENDWHERE 
    110122                !-------- 2.1.1.4 crown area: for large truncs, crown area cannot 
    111123                !--------         exceed a certain value, prescribed through maxdia. 
     
    122134          WHERE (PFTpresent(:,j)) 
    123135             !------ 2.2.1 an "individual" is 1 m**2 of grass 
    124              cn_ind(:,j) = 1. 
     136             cn_ind(:,j) = un 
    125137          ENDWHERE 
    126138       ENDIF 
     
    129141       !       ind and cn_ind are 0 if not present 
    130142       !--- 
    131        !SZ isn't this physically inconsistent with the assumptions of sechiba?? 
    132        ! the actual LPJ formulation calculates fpc from maximum LAI, and fpar from actual LAI=veget 
    133        IF (natural(j).AND.control%ok_dgvm) THEN 
    134           veget_max(:,j) = ind(:,j) * cn_ind(:,j) 
    135        ENDIF 
     143!!$SZ: since now all state variables are defined on veget_max it is very 
     144!!$ dangerous to change this several times in stomate_lpj, as then GPP, turnover and allocated  
     145!!$ biomass are not defined on the same space! Hence, veget_max is now kept constant 
     146!!$ and updated at the end of stomate_lpj in lpj_cover.f90 
     147!!$ Eventually, this routine should only be called once at the beginning and the end of stomate_lpj 
     148!!$ or prefereably cn_ind made a saved state variable! 
     149!!$    IF (natural(j).AND.control%ok_dgvm) THEN 
     150!!$      veget_max(:,j) = ind(:,j) * cn_ind(:,j) 
     151!!$    ENDIF 
    136152    ENDDO 
    137153    !------------------- 
Note: See TracChangeset for help on using the changeset viewer.