Changeset 7239


Ignore:
Timestamp:
2021-06-28T14:38:08+02:00 (3 years ago)
Author:
agnes.ducharne
Message:

Bug correction on the dimension of pcent, mc_awet, and mc_adry, leading to runtime error on irene. The committ of the SP-MIP features initiated with r6954 should now be complete, and the comments have also been cleaned.

File:
1 edited

Legend:

Unmodified
Added
Removed
  • branches/ORCHIDEE_2_2/ORCHIDEE/src_sechiba/hydrol.f90

    r7200 r7239  
    9595  REAL(r_std), PARAMETER                          :: allowed_err =  2.0E-8_r_std 
    9696  REAL(r_std), PARAMETER                          :: EPS1 = EPSILON(un)      !! A small number 
     97   
    9798  ! one dimension array allocated, computed, saved and got in hydrol module 
    9899  ! Values per soil type 
    99                                                                
    100100  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:)   :: pcent               !! Fraction of saturated volumetric soil moisture above  
    101                                                                          !! which transpir is max (0-1, unitless) 
    102 !$OMP THREADPRIVATE(pcent)                                                       
     101                                                                         !! which transpir is max (0-1, unitless)  
     102!$OMP THREADPRIVATE(pcent)                                                                 
    103103  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:)   :: mc_awet             !! Vol. wat. cont. above which albedo is cst 
    104104                                                                         !!  @tex $(m^{3} m^{-3})$ @endtex  
     
    440440                                 kjpindex,       index,     rest_id,                         & 
    441441                                 njsc,           soiltile,  veget,         veget_max,        & 
    442                                  humrel,         vegstress, drysoil_frac,                    & 
     442                                 humrel,    vegstress,  drysoil_frac,        & 
    443443                                 shumdiag_perma,    qsintveg,                        & 
    444444                                 evap_bare_lim,  evap_bare_lim_ns,  snow,      snow_age,      snow_nobio,       & 
     
    450450    !! 0.1 Input variables 
    451451 
    452  
    453     !salma: added soil params as input variables 
     452    INTEGER(i_std), INTENT(in)                         :: kjit             !! Time step number  
     453    INTEGER(i_std), INTENT(in)                         :: kjpindex         !! Domain size 
     454    INTEGER(i_std),DIMENSION (kjpindex), INTENT (in)   :: index            !! Indeces of the points on the map 
     455    INTEGER(i_std),INTENT (in)                         :: rest_id          !! Restart file identifier 
     456    INTEGER(i_std),DIMENSION (kjpindex), INTENT (in)   :: njsc             !! Index of the dominant soil textural class in the 
     457                                                                           !! grid cell (1-nscm, unitless)   
     458    ! 2D soil parameters 
    454459    REAL(r_std),DIMENSION (kjpindex), INTENT (in)      :: ks               !! Hydraulic conductivity at saturation (mm {-1}) 
    455460    REAL(r_std),DIMENSION (kjpindex), INTENT (in)      :: nvan             !! Van Genuchten coeficients n (unitless) 
     
    459464    REAL(r_std),DIMENSION (kjpindex), INTENT (in)      :: mcfc             !! Volumetric water content at field capacity (m^{3} m^{-3}) 
    460465    REAL(r_std),DIMENSION (kjpindex), INTENT (in)      :: mcw              !! Volumetric water content at wilting point (m^{3} m^{-3}) 
    461     !end salma: added soil params as input variables 
    462  
    463     INTEGER(i_std), INTENT(in)                         :: kjit             !! Time step number  
    464     INTEGER(i_std), INTENT(in)                         :: kjpindex         !! Domain size 
    465     INTEGER(i_std),DIMENSION (kjpindex), INTENT (in)   :: index            !! Indeces of the points on the map 
    466     INTEGER(i_std),INTENT (in)                         :: rest_id          !! Restart file identifier 
    467     INTEGER(i_std),DIMENSION (kjpindex), INTENT (in)   :: njsc             !! Index of the dominant soil textural class in the grid cell (1-nscm, unitless) 
     466     
    468467    REAL(r_std),DIMENSION (kjpindex,nstm), INTENT (in) :: soiltile         !! Fraction of each soil tile within vegtot (0-1, unitless) 
    469468    REAL(r_std),DIMENSION (kjpindex,nvm), INTENT (in)  :: veget            !! Fraction of vegetation type            
    470469    REAL(r_std),DIMENSION (kjpindex,nvm), INTENT (in)  :: veget_max        !! Max. fraction of vegetation type (LAI -> infty) 
    471470 
     471     
    472472    !! 0.2 Output variables 
    473473    REAL(r_std),DIMENSION (kjpindex,nvm), INTENT (out)   :: humrel         !! Relative humidity 
     
    492492    REAL(r_std),DIMENSION (kjpindex)                     :: soilwetdummy   !! Temporary variable never used 
    493493 
    494  
    495494    !! 0.4 Local variables 
    496495    INTEGER(i_std)                                       :: jsl 
    497496     
    498     !salma: added soil params which depend on soil texture 
    499     REAL(r_std), DIMENSION (nscm)                        :: nvan_text 
    500     REAL(r_std), DIMENSION (nscm)                        :: avan_text 
    501     REAL(r_std), DIMENSION (nscm)                        :: mcr_text 
    502     REAL(r_std), DIMENSION (nscm)                        :: mcs_text 
    503     REAL(r_std), DIMENSION (nscm)                        :: ks_text 
    504     REAL(r_std), DIMENSION (nscm)                        :: pcent_text 
    505     REAL(r_std), DIMENSION (nscm)                        :: mcfc_text 
    506     REAL(r_std), DIMENSION (nscm)                        :: mcw_text 
    507     REAL(r_std), DIMENSION (nscm)                        :: mc_awet_text 
    508     REAL(r_std), DIMENSION (nscm)                        :: mc_adry_text 
    509      !end salma: added soil params which depend on soil texture 
    510497!_ ================================================================================================================================ 
    511498 
     
    622609    REAL(r_std),DIMENSION (kjpindex), INTENT (in)      :: reinf_slope      !! Slope coef 
    623610 
    624     !salma: added input soil params: 
    625611    REAL(r_std),DIMENSION (kjpindex), INTENT (in)      :: ks               !! Hydraulic conductivity at saturation (mm {-1}) 
    626612    REAL(r_std),DIMENSION (kjpindex), INTENT (in)      :: nvan             !! Van Genuchten coeficients n (unitless) 
     
    630616    REAL(r_std),DIMENSION (kjpindex), INTENT (in)      :: mcfc             !! Volumetric water content at field capacity (m^{3} m^{-3}) 
    631617    REAL(r_std),DIMENSION (kjpindex), INTENT (in)      :: mcw              !! Volumetric water content at wilting point (m^{3} m^{-3}) 
    632     !end salma: added input soil params 
    633618  
    634619    REAL(r_std),DIMENSION (kjpindex), INTENT (in)      :: evapot           !! Soil Potential Evaporation 
     
    695680                                                                           !! at the present time-step @tex ($K$) @endtex 
    696681 
    697  
    698682    !! 0.4 Local variables 
    699     !salma: added variable kfact_root_type 
    700683    INTEGER(i_std)                                     :: jst              !! Index of soil tiles (unitless, 1-3) 
    701684    INTEGER(i_std)                                     :: jsl              !! Index of soil layers (unitless) 
    702685    INTEGER(i_std)                                     :: ji, jv 
    703     CHARACTER(LEN=80)                                  :: kfact_root_type  !! read from run.def: when equal to 'cons', it indicates that ks does not increase 
    704                                                                            !!   in the rootzone, ie, kfact_root=1; else, kfact_root defined as usual 
     686    CHARACTER(LEN=80)                                  :: kfact_root_type  !! read from run.def: when equal to 'cons', it indicates that 
     687                                                                           !! ks does not increase in the rootzone, ie, kfact_root=1;  
     688                                                                           !! else, kfact_root defined as usual 
    705689    REAL(r_std),DIMENSION (kjpindex)                   :: soilwet          !! A temporary diagnostic of soil wetness 
    706690    REAL(r_std),DIMENSION (kjpindex)                   :: snowdepth_diag   !! Depth of snow layer containing default values, only for diagnostics 
    707     REAL(r_std),DIMENSION (kjpindex, nsnow)            :: snowdz_diag      !! Depth of snow layer on all layers containing default values, only for diagnostics 
     691    REAL(r_std),DIMENSION (kjpindex, nsnow)            :: snowdz_diag      !! Depth of snow layer on all layers containing default values, 
     692                                                                           !! only for diagnostics 
    708693    REAL(r_std),DIMENSION (kjpindex)                   :: njsc_tmp         !! Temporary REAL value for njsc to write it 
    709694    REAL(r_std), DIMENSION (kjpindex)                  :: snowmelt         !! Snow melt [mm/dt_sechiba] 
     
    911896    !     mcs etc are identical in all layers (no normalization by vegtot to be comparable to mc) 
    912897    DO jsl=1,nslm 
    913        !salma: replaced mcs(njsc(:)) by mcs(:) and same for other variables 
    914898       land_mcs(:,jsl) = mcs(:) 
    915899       land_mcfc(:,jsl) = mcfc(:) 
     
    13321316!_ ================================================================================================================================ 
    13331317!!_ hydrol_init 
    1334 !salma: added variables and njsc in arguments and input variables 
    13351318 
    13361319  SUBROUTINE hydrol_init(ks, nvan, avan, mcr, mcs, mcfc, mcw, njsc,& 
     
    13441327 
    13451328    !! 0.1 Input variables 
    1346     !salma introduced njsc variable 
    13471329    INTEGER(i_std),DIMENSION (kjpindex), INTENT (in)    :: njsc               !! Index of the dominant soil textural class in the grid cell (1-nscm, unitless) 
    13481330    INTEGER(i_std), INTENT (in)                         :: kjit               !! Time step number  
     
    13551337    !! 0.2 Output variables 
    13561338 
    1357     !salma: added input variables 
    13581339    REAL(r_std),DIMENSION (kjpindex), INTENT (in)         :: ks               !! Hydraulic conductivity at saturation (mm {-1}) 
    13591340    REAL(r_std),DIMENSION (kjpindex), INTENT (in)         :: nvan             !! Van Genuchten coeficients n (unitless) 
     
    13891370    INTEGER(i_std)                                     :: jsc                   !! Index of soil texture (1) 
    13901371    INTEGER(i_std), PARAMETER                          :: error_level = 3       !! Error level for consistency check 
    1391                                                                                 !! Switch to 2 tu turn fatal errors into warnings   
     1372    !! Switch to 2 tu turn fatal errors into warnings 
    13921373    REAL(r_std), ALLOCATABLE, DIMENSION (:)            :: free_drain_max        !! Temporary var for initialization of free_drain_coef  
    13931374    REAL(r_std), ALLOCATABLE, DIMENSION (:)            :: zwt_default           !! Temporary variable for initialization of zwt_force 
    13941375    LOGICAL                                            :: zforce                !! To test if we force the WT in any of the soiltiles 
     1376     
    13951377 
    13961378!_ ================================================================================================================================ 
     
    14631445    !! 2.1 array allocation for soil texture 
    14641446 
    1465     
    1466     ALLOCATE (pcent(kjpindex),stat=ier) 
     1447    ALLOCATE (pcent(nscm),stat=ier) 
    14671448    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable pcent','','') 
    14681449     
    1469     ALLOCATE (mc_awet(kjpindex),stat=ier) 
     1450    ALLOCATE (mc_awet(nscm),stat=ier) 
    14701451    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable mc_awet','','') 
    14711452 
    1472     ALLOCATE (mc_adry(kjpindex),stat=ier) 
     1453    ALLOCATE (mc_adry(nscm),stat=ier) 
    14731454    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable mc_adry','','') 
    14741455        
    1475     !!__2.2 Soil texture choose 
     1456    !! 2.2 Soil texture choose 
    14761457 
    14771458    SELECTCASE (nscm) 
    1478     CASE (3) 
    1479                
    1480        pcent(:) = pcent_fao(njsc(:)) 
    1481        mc_awet(:) = mc_awet_fao(njsc(:)) 
    1482        mc_adry(:) = mc_adry_fao(njsc(:)) 
    1483     CASE (13) 
    1484             
    1485        pcent(:) = pcent_usda(njsc(:)) 
    1486        mc_awet(:) = mc_awet_usda(njsc(:)) 
    1487        mc_adry(:) = mc_adry_usda(njsc(:)) 
    1488         
     1459    CASE (3)               
     1460       pcent(:) = pcent_fao(:)  
     1461       mc_awet(:) = mc_awet_fao(:) 
     1462       mc_adry(:) = mc_adry_fao(:) 
     1463    CASE (13)            
     1464       pcent(:) = pcent_usda(:)  
     1465       mc_awet(:) = mc_awet_usda(:) 
     1466       mc_adry(:) = mc_adry_usda(:)        
    14891467    CASE DEFAULT 
    14901468       WRITE (numout,*) 'Unsupported soil type classification. Choose between zobler and usda according to the map' 
     
    14951473 
    14961474    !! 2.3 Read in the run.def the parameters values defined by the user 
    1497  
    1498  
    1499  
    1500  
    1501  
    1502  
    1503  
    1504  
    15051475 
    15061476    !Config Key   = WETNESS_TRANSPIR_MAX 
     
    15201490            &     "Please, check parameter value in run.def. ") 
    15211491    END IF 
    1522  
    1523  
    15241492    
    15251493 
     
    27162684 
    27172685    !! 0.1 Input variables 
    2718     !salma: added the following soil parameters 
    2719     REAL(r_std),DIMENSION (kjpindex), INTENT (in)      :: ks               !! Hydraulic conductivity at saturation (mm {-1}) 
    2720     REAL(r_std),DIMENSION (kjpindex), INTENT (in)      :: nvan             !! Van Genuchten coeficients n (unitless) 
    2721     REAL(r_std),DIMENSION (kjpindex), INTENT (in)      :: avan             !! Van Genuchten coeficients a (mm-1}) 
    2722     REAL(r_std),DIMENSION (kjpindex), INTENT (in)      :: mcr              !! Residual volumetric water content (m^{3} m^{-3}) 
    2723     REAL(r_std),DIMENSION (kjpindex), INTENT (in)      :: mcs              !! Saturated volumetric water content (m^{3} m^{-3}) 
    2724     REAL(r_std),DIMENSION (kjpindex), INTENT (in)      :: mcfc             !! Volumetric water content at field capacity (m^{3} m^{-3}) 
    2725     REAL(r_std),DIMENSION (kjpindex), INTENT (in)      :: mcw              !! Volumetric water content at wilting point (m^{3} m^{-3}) 
    2726  
    27272686    ! input scalar  
    27282687    INTEGER(i_std), INTENT(in)                          :: kjpindex      !! Domain size (number of grid cells) (1) 
     
    27332692                                                                         !! in the grid cell (1-nscm, unitless)  
    27342693    REAL(r_std), DIMENSION (kjpindex,nstm), INTENT (in) :: soiltile      !! Fraction of each soil tile within vegtot (0-1, unitless) 
    2735  
     2694    
     2695    REAL(r_std),DIMENSION (kjpindex), INTENT (in)      :: ks               !! Hydraulic conductivity at saturation (mm {-1}) 
     2696    REAL(r_std),DIMENSION (kjpindex), INTENT (in)      :: nvan             !! Van Genuchten coeficients n (unitless) 
     2697    REAL(r_std),DIMENSION (kjpindex), INTENT (in)      :: avan             !! Van Genuchten coeficients a (mm-1}) 
     2698    REAL(r_std),DIMENSION (kjpindex), INTENT (in)      :: mcr              !! Residual volumetric water content (m^{3} m^{-3}) 
     2699    REAL(r_std),DIMENSION (kjpindex), INTENT (in)      :: mcs              !! Saturated volumetric water content (m^{3} m^{-3}) 
     2700    REAL(r_std),DIMENSION (kjpindex), INTENT (in)      :: mcfc             !! Volumetric water content at field capacity (m^{3} m^{-3}) 
     2701    REAL(r_std),DIMENSION (kjpindex), INTENT (in)      :: mcw              !! Volumetric water content at wilting point (m^{3} m^{-3}) 
     2702  
    27362703    !! 0.2 Output variables 
    27372704 
     
    27882755                                                                           !! (unitless) 
    27892756                                                                           !! need special treatment 
    2790     !salma: added local variable ii and jiref replaced with iiref 
    27912757    INTEGER(i_std)                                      :: ii 
    27922758    INTEGER(i_std)                                      :: iiref           !! To identify the mc_lins where k_lin and d_lin 
     
    29622928    !! 3 Compute the profile for a and n 
    29632929    !- 
    2964     !salma: for every grid cell 
    29652930    DO ji = 1, kjpindex 
    29662931       DO jsl=1,nslm 
     
    29742939       ENDDO 
    29752940    ENDDO 
    2976     !end salma 
    29772941     
    29782942    ! For every grid cell 
     
    30433007                     (  frac**(-un/m) -un ) ** (-m) 
    30443008             ENDIF 
    3045           ENDDO !Salma end loop over landpoints 
     3009          ENDDO 
    30463010 
    30473011          ! Special case for ii=imin 
     
    31383102          tmc_litter_field(ji,jst) = dz(2) * mcfc(ji) / deux 
    31393103          tmc_litter_sat(ji,jst) = dz(2) * mcs(ji) / deux 
    3140           tmc_litter_awet(ji,jst) = dz(2) * mc_awet(ji) / deux 
    3141           tmc_litter_adry(ji,jst) = dz(2) * mc_adry(ji) / deux 
     3104          tmc_litter_awet(ji,jst) = dz(2) * mc_awet(njsc(ji)) / deux 
     3105          tmc_litter_adry(ji,jst) = dz(2) * mc_adry(njsc(ji)) / deux 
    31423106       ENDDO 
    31433107    END DO 
     
    31633127             tmc_litter_awet(ji,jst) = tmc_litter_awet(ji,jst) + & 
    31643128                  &(dz(jsl)+ dz(jsl+1))* & 
    3165                   & mc_awet(ji)/deux 
     3129                  & mc_awet(njsc(ji))/deux 
    31663130             tmc_litter_adry(ji,jst) = tmc_litter_adry(ji,jst) + & 
    31673131                  & (dz(jsl)+ dz(jsl+1))* & 
    3168                   & mc_adry(ji)/deux 
     3132                  & mc_adry(njsc(ji))/deux 
    31693133          END DO 
    31703134       END DO 
     
    36603624 
    36613625    !! 0.1 Input variables 
    3662     !salma added soil params to arguments and input variables 
     3626     
     3627    INTEGER(i_std), INTENT(in)                               :: kjpindex  
     3628    REAL(r_std), DIMENSION (kjpindex,nvm), INTENT (in)       :: veget_max        !! Map of max vegetation types [-] 
     3629    INTEGER(i_std),DIMENSION (kjpindex), INTENT (in)         :: njsc             !! Index of the dominant soil textural class  
     3630                                                                                 !!   in the grid cell (1-nscm, unitless) 
     3631     
    36633632    REAL(r_std),DIMENSION (kjpindex), INTENT (in)            :: ks               !! Hydraulic conductivity at saturation (mm {-1}) 
    36643633    REAL(r_std),DIMENSION (kjpindex), INTENT (in)            :: nvan             !! Van Genuchten coeficients n (unitless) 
     
    36683637    REAL(r_std),DIMENSION (kjpindex), INTENT (in)            :: mcfc             !! Volumetric water content at field capacity (m^{3} m^{-3}) 
    36693638    REAL(r_std),DIMENSION (kjpindex), INTENT (in)            :: mcw              !! Volumetric water content at wilting point (m^{3} m^{-3}) 
    3670  
    3671  
    3672     INTEGER(i_std), INTENT(in)                               :: kjpindex  
    3673     REAL(r_std), DIMENSION (kjpindex,nvm), INTENT (in)       :: veget_max        !! Map of max vegetation types [-] 
    3674     INTEGER(i_std),DIMENSION (kjpindex), INTENT (in)         :: njsc             !! Index of the dominant soil textural class  
    3675                                                                                  !!   in the grid cell (1-nscm, unitless) 
     3639    
    36763640    REAL(r_std), DIMENSION (kjpindex,nstm), INTENT (in)      :: soiltile         !! Fraction of each soil tile within vegtot (0-1, unitless) 
    36773641    REAL(r_std), DIMENSION (kjpindex,nvm), INTENT(in)        :: transpir         !! Transpiration   
     
    43934357       ! sm_nostress = soil moisture of each layer at which us reaches 1, here at the middle of [smw,smf] 
    43944358       DO jsl = 1,nslm 
    4395           sm_nostress(:,jsl) = smw(:,jsl) + pcent(:) * (smf(:,jsl)-smw(:,jsl)) 
     4359          sm_nostress(:,jsl) = smw(:,jsl) + pcent(njsc(:)) * (smf(:,jsl)-smw(:,jsl)) 
    43964360       END DO 
    43974361 
     
    49794943 
    49804944    ! GLOBAL (in or inout) 
    4981     ! salma added input soil hydraulic parameters 
    4982     REAL(r_std),DIMENSION (kjpindex), INTENT (in)      :: ks               !! Hydraulic conductivity at saturation (mm {-1}) 
    4983     REAL(r_std),DIMENSION (kjpindex), INTENT (in)      :: nvan             !! Van Genuchten coeficients n (unitless) 
    4984     REAL(r_std),DIMENSION (kjpindex), INTENT (in)      :: avan             !! Van Genuchten coeficients a (mm-1}) 
    4985     REAL(r_std),DIMENSION (kjpindex), INTENT (in)      :: mcr              !! Residual volumetric water content (m^{3} m^{-3}) 
    4986     REAL(r_std),DIMENSION (kjpindex), INTENT (in)      :: mcs              !! Saturated volumetric water content (m^{3} m^{-3}) 
    4987     REAL(r_std),DIMENSION (kjpindex), INTENT (in)      :: mcfc             !! Volumetric water content at field capacity (m^{3} m^{-3}) 
    4988     REAL(r_std),DIMENSION (kjpindex), INTENT (in)      :: mcw              !! Volumetric water content at wilting point (m^{3} m^{-3}) 
    4989  
    4990  
    49914945    INTEGER(i_std), INTENT(in)                        :: kjpindex        !! Domain size 
    49924946    INTEGER(i_std), INTENT(in)                        :: ins 
    49934947    INTEGER(i_std),DIMENSION (kjpindex), INTENT (in)  :: njsc            !! Index of the dominant soil textural class in the grid cell 
    49944948                                                                         !!  (1-nscm, unitless) 
     4949    REAL(r_std),DIMENSION (kjpindex), INTENT (in)     :: ks               !! Hydraulic conductivity at saturation (mm {-1}) 
     4950    REAL(r_std),DIMENSION (kjpindex), INTENT (in)     :: nvan             !! Van Genuchten coeficients n (unitless) 
     4951    REAL(r_std),DIMENSION (kjpindex), INTENT (in)     :: avan             !! Van Genuchten coeficients a (mm-1}) 
     4952    REAL(r_std),DIMENSION (kjpindex), INTENT (in)     :: mcr              !! Residual volumetric water content (m^{3} m^{-3}) 
     4953    REAL(r_std),DIMENSION (kjpindex), INTENT (in)     :: mcs              !! Saturated volumetric water content (m^{3} m^{-3}) 
     4954    REAL(r_std),DIMENSION (kjpindex), INTENT (in)     :: mcfc             !! Volumetric water content at field capacity (m^{3} m^{-3}) 
     4955    REAL(r_std),DIMENSION (kjpindex), INTENT (in)     :: mcw              !! Volumetric water content at wilting point (m^{3} m^{-3}) 
    49954956    REAL(r_std), DIMENSION (kjpindex), INTENT (in)    :: flux_infilt     !! Water to infiltrate 
    49964957                                                                         !!  @tex $(kg m^{-2})$ @endtex 
    4997  
    49984958    !! 0.2 Output variables 
    49994959    REAL(r_std), DIMENSION(kjpindex,nstm), INTENT(out) :: check       !! delta SM - flux (mm/dt_sechiba) 
     
    51635123    !! 0.1 Input variables 
    51645124 
    5165     !salma: added parameter mcr 
    5166     REAL(r_std),DIMENSION (kjpindex), INTENT (in)      :: mcr          !! Residual volumetric water content (m^{3} m^{-3}) 
    51675125    INTEGER(i_std), INTENT(in)                         :: kjpindex     !! Domain size 
    51685126    INTEGER(i_std), INTENT(in)                         :: ins          !! Soiltile index (1-nstm, unitless) 
    51695127    INTEGER(i_std),DIMENSION (kjpindex), INTENT (in)   :: njsc         !! Index of the dominant soil textural class in grid cell  
    5170                                                                        !! (1-nscm, unitless)     
     5128                                                                       !! (1-nscm, unitless)   
     5129    REAL(r_std),DIMENSION (kjpindex), INTENT (in)      :: mcr          !! Residual volumetric water content (m^{3} m^{-3})   
    51715130     
    51725131    !! 0.2 Output variables 
     
    53215280 
    53225281    !! 0.1 Input variables  
    5323     !salma: added mcs 
    5324     REAL(r_std),DIMENSION (kjpindex), INTENT (in)        :: mcs             !! Saturated volumetric water content (m^{3} m^{-3}) 
    53255282    INTEGER(i_std), INTENT(in)                           :: kjpindex        !! Domain size 
    53265283    INTEGER(i_std), INTENT(in)                           :: ins             !! Soiltile index (1-nstm, unitless) 
    53275284    INTEGER(i_std),DIMENSION (kjpindex), INTENT (in)     :: njsc            !! Index of the dominant soil textural class in grid cell  
    53285285                                                                            !! (1-nscm, unitless) 
     5286    REAL(r_std),DIMENSION (kjpindex), INTENT (in)        :: mcs             !! Saturated volumetric water content (m^{3} m^{-3}) 
    53295287     
    53305288    !! 0.2 Output variables 
     
    54545412 
    54555413    !! 0.1 Input variables 
    5456     !salma: added mcs 
    5457     REAL(r_std),DIMENSION (kjpindex), INTENT (in)        :: mcs             !! Saturated volumetric water content (m^{3} m^{-3}) 
    54585414    INTEGER(i_std), INTENT(in)                           :: kjpindex        !! Domain size 
    54595415    INTEGER(i_std), INTENT(in)                           :: ins             !! Soiltile index (1-nstm, unitless) 
    54605416    INTEGER(i_std),DIMENSION (kjpindex), INTENT (in)     :: njsc            !! Index of the dominant soil textural class in grid cell  
    54615417                                                                            !! (1-nscm, unitless) 
     5418    REAL(r_std),DIMENSION (kjpindex), INTENT (in)        :: mcs             !! Saturated volumetric water content (m^{3} m^{-3}) 
    54625419     
    54635420    !! 0.2 Output variables 
     
    57405697 
    57415698    !! 0.1 Input variables 
    5742     !salma: added mcr and mcs 
     5699    INTEGER(i_std), INTENT(in)                        :: kjpindex         !! Domain size 
     5700    INTEGER(i_std), INTENT(in)                        :: ins              !! Index of soil type 
     5701    INTEGER(i_std),DIMENSION (kjpindex), INTENT (in)  :: njsc             !! Index of the dominant soil textural class 
     5702                                                                          !! in the grid cell (1-nscm, unitless) 
    57435703    REAL(r_std),DIMENSION (kjpindex), INTENT (in)     :: mcr              !! Residual volumetric water content (m^{3} m^{-3}) 
    57445704    REAL(r_std),DIMENSION (kjpindex), INTENT (in)     :: mcs              !! Saturated volumetric water content (m^{3} m^{-3}) 
    5745     INTEGER(i_std), INTENT(in)                        :: kjpindex         !! Domain size 
    5746     INTEGER(i_std), INTENT(in)                        :: ins              !! Index of soil type 
    5747     INTEGER(i_std),DIMENSION (kjpindex), INTENT (in)  :: njsc             !! Index of the dominant soil textural class in the grid cell (1-nscm, unitless) 
    57485705 
    57495706    !! 0.2 Output variables 
     
    58325789 
    58335790    !! 0.1 Input variables 
    5834     !salma: added the following soil variables 
     5791 
     5792    INTEGER(i_std), INTENT(in)                        :: kjpindex         !! Domain size 
     5793    INTEGER(i_std), INTENT(in)                        :: ins              !! Index of soil type 
     5794    INTEGER(i_std),DIMENSION (kjpindex), INTENT (in)  :: njsc             !! Index of the dominant soil textural class 
     5795                                                                          !! in the grid cell (1-nscm, unitless) 
    58355796    REAL(r_std),DIMENSION (kjpindex), INTENT (in)     :: nvan             !! Van Genuchten coeficients n (unitless) 
    58365797    REAL(r_std),DIMENSION (kjpindex), INTENT (in)     :: avan             !! Van Genuchten coeficients a (mm-1}) 
    58375798    REAL(r_std),DIMENSION (kjpindex), INTENT (in)     :: mcr              !! Residual volumetric water content (m^{3} m^{-3}) 
    58385799    REAL(r_std),DIMENSION (kjpindex), INTENT (in)     :: mcs              !! Saturated volumetric water content (m^{3} m^{-3}) 
    5839  
    5840     INTEGER(i_std), INTENT(in)                        :: kjpindex         !! Domain size 
    5841     INTEGER(i_std), INTENT(in)                        :: ins              !! Index of soil type 
    5842     INTEGER(i_std),DIMENSION (kjpindex), INTENT (in)  :: njsc             !! Index of the dominant soil textural class in the grid cell (1-nscm, unitless) 
    58435800 
    58445801    !! 0.2 Output variables 
     
    63496306 
    63506307    !! 0.1 Input variables 
    6351     !salma: added the following soil variables 
     6308 
     6309    ! input scalar  
     6310    INTEGER(i_std), INTENT(in)                               :: kjpindex  
     6311    REAL(r_std),DIMENSION (kjpindex,nvm), INTENT (in)        :: veget_max       !! Max. vegetation type 
     6312    INTEGER(i_std),DIMENSION (kjpindex), INTENT (in)         :: njsc            !! Index of the dominant soil textural class in the grid cell (1-nscm, unitless) 
     6313    REAL(r_std), DIMENSION (kjpindex,nstm), INTENT (in)      :: soiltile        !! Fraction of each soil tile within vegtot (0-1, unitless) 
    63526314    REAL(r_std),DIMENSION (kjpindex), INTENT (in)            :: ks               !! Hydraulic conductivity at saturation (mm {-1}) 
    63536315    REAL(r_std),DIMENSION (kjpindex), INTENT (in)            :: nvan             !! Van Genuchten coeficients n (unitless) 
     
    63576319    REAL(r_std),DIMENSION (kjpindex), INTENT (in)            :: mcfc             !! Volumetric water content at field capacity (m^{3} m^{-3}) 
    63586320    REAL(r_std),DIMENSION (kjpindex), INTENT (in)            :: mcw              !! Volumetric water content at wilting point (m^{3} m^{-3}) 
    6359  
    6360     ! input scalar  
    6361     INTEGER(i_std), INTENT(in)                               :: kjpindex  
    6362     REAL(r_std),DIMENSION (kjpindex,nvm), INTENT (in)        :: veget_max       !! Max. vegetation type 
    6363     INTEGER(i_std),DIMENSION (kjpindex), INTENT (in)         :: njsc            !! Index of the dominant soil textural class in the grid cell (1-nscm, unitless) 
    6364     REAL(r_std), DIMENSION (kjpindex,nstm), INTENT (in)      :: soiltile        !! Fraction of each soil tile within vegtot (0-1, unitless) 
    63656321    REAL(r_std), DIMENSION (kjpindex), INTENT(in)            :: evapot          !!  
    63666322    REAL(r_std), DIMENSION (kjpindex), INTENT(in)            :: returnflow      !! Water returning to the deep reservoir 
Note: See TracChangeset for help on using the changeset viewer.