Changeset 7337


Ignore:
Timestamp:
2021-11-06T08:24:04+01:00 (3 years ago)
Author:
agnes.ducharne
Message:

Simplification of soil texture processing, cf ticket #416: when using the Zobler map, the soil parameters are no more taken from 3-value "FAO" vectors in constantes_soil_var.f90, but from 13-value USDA vectors, owing to a pointer fao2usda. A 5-day running test with the Zobler map shows no changes, but over Greenland (class 6=ice in Zobler map).

Location:
branches/ORCHIDEE_2_2/ORCHIDEE
Files:
4 edited

Legend:

Unmodified
Added
Removed
  • branches/ORCHIDEE_2_2/ORCHIDEE/src_parameters/constantes_soil_var.f90

    r7199 r7337  
    2020!!                   for clay oxisols (cf. Tafasca, 2020, PhD thesis; Tafasca et al., in prep for GRL). 
    2121!!                   It makes no change if we read a soil texture map with only 12 USDA classes. 
     22!!                   Lookup tables for Zobler replaces by pointer to read the corresponding values in the 
     23!!                   13-value USDA tables 
    2224!! 
    2325!! REFERENCE(S) : 
     
    106108!$OMP THREADPRIVATE(mx_eau_nobio) 
    107109 
    108  
    109110  !! Parameters specific for the CWRR hydrology. 
    110111 
    111   !!  1. Parameters for FAO Classification 
    112  
    113   !! Parameters for soil type distribution 
    114  
    115   REAL(r_std),DIMENSION(nscm_fao),SAVE :: soilclass_default_fao = &   !! Default soil texture distribution for fao : 
    116  & (/ 0.28, 0.52, 0.20 /)                                             !! in the following order : COARSE, MEDIUM, FINE (unitless) 
    117 !$OMP THREADPRIVATE(soilclass_default_fao) 
    118  
    119   REAL(r_std),PARAMETER,DIMENSION(nscm_fao) :: nvan_fao = &            !! Van Genuchten coefficient n (unitless) 
    120  & (/ 1.89_r_std, 1.56_r_std, 1.31_r_std /)                             !  RK: 1/n=1-m 
    121  
    122   REAL(r_std),PARAMETER,DIMENSION(nscm_fao) :: avan_fao = &            !! Van Genuchten coefficient a  
    123   & (/ 0.0075_r_std, 0.0036_r_std, 0.0019_r_std /)                     !!  @tex $(mm^{-1})$ @endtex 
    124  
    125   REAL(r_std),PARAMETER,DIMENSION(nscm_fao) :: mcr_fao = &             !! Residual volumetric water content  
    126  & (/ 0.065_r_std, 0.078_r_std, 0.095_r_std /)                         !!  @tex $(m^{3} m^{-3})$ @endtex 
    127  
    128   REAL(r_std),PARAMETER,DIMENSION(nscm_fao) :: mcs_fao = &             !! Saturated volumetric water content  
    129  & (/ 0.41_r_std, 0.43_r_std, 0.41_r_std /)                            !!  @tex $(m^{3} m^{-3})$ @endtex 
    130  
    131   REAL(r_std),PARAMETER,DIMENSION(nscm_fao) :: ks_fao = &              !! Hydraulic conductivity at saturation  
    132  & (/ 1060.8_r_std, 249.6_r_std, 62.4_r_std /)                         !!  @tex $(mm d^{-1})$ @endtex 
     112  !!  1. Parameters for FAO-Zobler Map 
     113 
     114  INTEGER(i_std), PARAMETER,DIMENSION(nscm_fao) :: fao2usda = (/ 3,6,9 /) !! To find the values of Coarse, Medium, Fine in Zobler map 
     115  !! from the USDA lookup tables 
     116   
     117!!$  REAL(r_std),DIMENSION(nscm_fao),SAVE :: soilclass_default_fao = &   !! Default soil texture distribution for fao : 
     118!!$ & (/ 0.28, 0.52, 0.20 /)                                             !! in the following order : COARSE, MEDIUM, FINE (unitless) 
     119!!$!$OMP THREADPRIVATE(soilclass_default_fao) 
     120 
     121  !!  2. Parameters for USDA Classification 
     122 
     123  !! Parameters for soil type distribution : 
     124  !! Sand, Loamy Sand, Sandy Loam, Silt Loam, Silt, Loam, Sandy Clay Loam, Silty Clay Loam, Clay Loam, Sandy Clay, Silty Clay, Clay 
     125 
     126  ! AD-Warning: I don't understand correctly the use of soilclass_default; when removing the _fao vectors, the default texture in 
     127  ! Greenland, where the Zobler map has no data, were changed, even when having 0.28 at the 3rd place below 
     128  ! I kept the original soilclass_default_usda to keep the Reynolds map unchanged 
     129   
     130  REAL(r_std),DIMENSION(nscm_usda),SAVE :: soilclass_default_usda = &    !! Default soil texture distribution in the above order : 
     131 & (/ 0.28, 0.52, 0.20, 0.0, 0.0, 0.0, 0.0, 0.0, 0.0, 0.0, 0.0, 0.0, 0.0 /)   !! Thus different from "FAO"'s COARSE, MEDIUM, FINE 
     132  !! which have indices 3,6,9 in the 12-texture vector 
     133  !$OMP THREADPRIVATE(soilclass_default_usda) 
     134 
     135!!$  REAL(r_std),DIMENSION(nscm_usda),SAVE :: soilclass_default_usda = &       !! Default soil texture distribution, to be coherent with the  
     136!!$ & (/ 0.0, 0.0, 0.28, 0.0, 0.0, 0.52, 0.0, 0.0, 0.20, 0.0, 0.0, 0.0, 0.0 /) !! original FAO/Zobler values 
     137!!$  !$OMP THREADPRIVATE(soilclass_default_usda)   
     138 
     139  REAL(r_std),PARAMETER,DIMENSION(nscm_usda) :: nvan_usda = &            !! Van Genuchten coefficient n (unitless) 
     140 & (/ 2.68_r_std, 2.28_r_std, 1.89_r_std, 1.41_r_std, &                   !  RK: 1/n=1-m 
     141 &    1.37_r_std, 1.56_r_std, 1.48_r_std, 1.23_r_std, & 
     142 &    1.31_r_std, 1.23_r_std, 1.09_r_std, 1.09_r_std, & 
     143 &    1.552_r_std    /) ! oxisols 
     144 
     145  REAL(r_std),PARAMETER,DIMENSION(nscm_usda) :: avan_usda = &            !! Van Genuchten coefficient a  
     146 & (/ 0.0145_r_std, 0.0124_r_std, 0.0075_r_std, 0.0020_r_std, &          !!  @tex $(mm^{-1})$ @endtex 
     147 &    0.0016_r_std, 0.0036_r_std, 0.0059_r_std, 0.0010_r_std, & 
     148 &    0.0019_r_std, 0.0027_r_std, 0.0005_r_std, 0.0008_r_std, & 
     149 &    0.0132_r_std /) ! oxisols 
     150 
     151  REAL(r_std),PARAMETER,DIMENSION(nscm_usda) :: mcr_usda = &             !! Residual volumetric water content  
     152 & (/ 0.045_r_std, 0.057_r_std, 0.065_r_std, 0.067_r_std, &              !!  @tex $(m^{3} m^{-3})$ @endtex 
     153 &    0.034_r_std, 0.078_r_std, 0.100_r_std, 0.089_r_std, & 
     154 &    0.095_r_std, 0.100_r_std, 0.070_r_std, 0.068_r_std, & 
     155 &    0.068_r_std /) ! oxisols 
     156 
     157  REAL(r_std),PARAMETER,DIMENSION(nscm_usda) :: mcs_usda = &             !! Saturated volumetric water content  
     158 & (/ 0.43_r_std, 0.41_r_std, 0.41_r_std, 0.45_r_std, &                  !!  @tex $(m^{3} m^{-3})$ @endtex 
     159 &    0.46_r_std, 0.43_r_std, 0.39_r_std, 0.43_r_std, & 
     160 &    0.41_r_std, 0.38_r_std, 0.36_r_std, 0.38_r_std, & 
     161 &    0.503_r_std  /) ! oxisols 
     162 
     163  REAL(r_std),PARAMETER,DIMENSION(nscm_usda) :: ks_usda = &              !! Hydraulic conductivity at saturation 
     164 & (/ 7128.0_r_std, 3501.6_r_std, 1060.8_r_std, 108.0_r_std, &           !!  @tex $(mm d^{-1})$ @endtex 
     165 &    60.0_r_std, 249.6_r_std, 314.4_r_std, 16.8_r_std, & 
     166 &    62.4_r_std, 28.8_r_std, 4.8_r_std, 48.0_r_std, & 
     167 &    6131.4_r_std  /) ! oxisols 
    133168 
    134169! The max available water content is smaller when mcw and mcf depend on texture, 
    135 ! so we increase pcent to a classical value of 80% 
    136   REAL(r_std),PARAMETER,DIMENSION(nscm_fao) :: pcent_fao = &           !! Fraction of saturated volumetric soil moisture  
    137  & (/ 0.8_r_std, 0.8_r_std, 0.8_r_std /)                               !! above which transpir is max (0-1, unitless) 
    138  
    139   REAL(r_std),PARAMETER,DIMENSION(nscm_fao) :: free_drain_max_fao = &  !! Max=default value of the permeability coeff   
    140  & (/ 1.0_r_std, 1.0_r_std, 1.0_r_std /)                               !! at the bottom of the soil (0-1, unitless) 
    141  
     170! so we increase pcent to a classical value of 80%   
     171  REAL(r_std),PARAMETER,DIMENSION(nscm_usda) :: pcent_usda = &           !! Fraction of saturated volumetric soil moisture 
     172 & (/ 0.8_r_std, 0.8_r_std, 0.8_r_std, 0.8_r_std, &                      !! above which transpir is max (0-1, unitless) 
     173 &    0.8_r_std, 0.8_r_std, 0.8_r_std, 0.8_r_std, & 
     174 &    0.8_r_std, 0.8_r_std, 0.8_r_std, 0.8_r_std, & 
     175 &    0.8_r_std /) ! oxisols 
     176 
     177  REAL(r_std),PARAMETER,DIMENSION(nscm_usda) :: free_drain_max_usda = &  !! Max=default value of the permeability coeff  
     178 & (/ 1.0_r_std, 1.0_r_std, 1.0_r_std, 1.0_r_std, &                      !! at the bottom of the soil (0-1, unitless) 
     179 &    1.0_r_std, 1.0_r_std, 1.0_r_std, 1.0_r_std, & 
     180 &    1.0_r_std, 1.0_r_std, 1.0_r_std, 1.0_r_std,  & 
     181 &    1.0_r_std /) 
     182   
    142183!! We use the VG relationships to derive mcw and mcf depending on soil texture 
    143184!! assuming that the matric potential for wilting point and field capacity is 
     
    145186!! (-1m for FC for the three sandy soils following Richards, L.A. and Weaver, L.R. (1944) 
    146187!! Note that mcw GE mcr 
    147   REAL(r_std),PARAMETER,DIMENSION(nscm_fao) :: mcf_fao = &             !! Volumetric water content at field capacity  
    148  & (/ 0.1218_r_std, 0.1654_r_std, 0.2697_r_std /)                      !!  @tex $(m^{3} m^{-3})$ @endtex 
    149  
    150   REAL(r_std),PARAMETER,DIMENSION(nscm_fao) :: mcw_fao = &             !! Volumetric water content at wilting point  
    151  & (/ 0.0657_r_std,  0.0884_r_std, 0.1496_r_std/)                      !!  @tex $(m^{3} m^{-3})$ @endtex 
    152  
    153   REAL(r_std),PARAMETER,DIMENSION(nscm_fao) :: mc_awet_fao = &         !! Vol. wat. cont. above which albedo is cst  
    154  & (/ 0.25_r_std, 0.25_r_std, 0.25_r_std /)                            !!  @tex $(m^{3} m^{-3})$ @endtex 
    155  
    156   REAL(r_std),PARAMETER,DIMENSION(nscm_fao) :: mc_adry_fao = &         !! Vol. wat. cont. below which albedo is cst 
    157  & (/ 0.1_r_std, 0.1_r_std, 0.1_r_std /)                               !!  @tex $(m^{3} m^{-3})$ @endtex 
    158  
    159   REAL(r_std),PARAMETER,DIMENSION(nscm_fao) :: QZ_fao = &              !! QUARTZ CONTENT (SOIL TYPE DEPENDENT) 
    160  & (/ 0.60_r_std, 0.40_r_std, 0.35_r_std /)                            !! Peters et al [1998] 
    161  
    162   REAL(r_std),PARAMETER,DIMENSION(nscm_fao) :: so_capa_dry_ns_fao = &  !! Dry soil Heat capacity of soils,J.m^{-3}.K^{-1} 
    163  & (/ 1.34e+6_r_std, 1.21e+6_r_std, 1.23e+6_r_std /)                   !! Pielke [2002, 2013] 
    164  
    165   !!  2. Parameters for USDA Classification 
    166  
    167   !! Parameters for soil type distribution : 
    168   !! Sand, Loamy Sand, Sandy Loam, Silt Loam, Silt, Loam, Sandy Clay Loam, Silty Clay Loam, Clay Loam, Sandy Clay, Silty Clay, Clay 
    169  
    170   REAL(r_std),DIMENSION(nscm_usda),SAVE :: soilclass_default_usda = &    !! Default soil texture distribution in the above order : 
    171  & (/ 0.28, 0.52, 0.20, 0.0, 0.0, 0.0, 0.0, 0.0, 0.0, 0.0, 0.0, 0.0, 0.0 /)   !! Thus different from "FAO"'s COARSE, MEDIUM, FINE 
    172                                                                          !! which have indices 3,6,9 in the 12-texture vector 
    173   !$OMP THREADPRIVATE(soilclass_default_usda) 
    174  
    175   REAL(r_std),PARAMETER,DIMENSION(nscm_usda) :: nvan_usda = &            !! Van Genuchten coefficient n (unitless) 
    176  & (/ 2.68_r_std, 2.28_r_std, 1.89_r_std, 1.41_r_std, &                   !  RK: 1/n=1-m 
    177  &    1.37_r_std, 1.56_r_std, 1.48_r_std, 1.23_r_std, & 
    178  &    1.31_r_std, 1.23_r_std, 1.09_r_std, 1.09_r_std, & 
    179  &    1.552_r_std    /) ! oxisols 
    180  
    181   REAL(r_std),PARAMETER,DIMENSION(nscm_usda) :: avan_usda = &            !! Van Genuchten coefficient a  
    182  & (/ 0.0145_r_std, 0.0124_r_std, 0.0075_r_std, 0.0020_r_std, &          !!  @tex $(mm^{-1})$ @endtex 
    183  &    0.0016_r_std, 0.0036_r_std, 0.0059_r_std, 0.0010_r_std, & 
    184  &    0.0019_r_std, 0.0027_r_std, 0.0005_r_std, 0.0008_r_std, & 
    185  &    0.0132_r_std /) ! oxisols 
    186  
    187   REAL(r_std),PARAMETER,DIMENSION(nscm_usda) :: mcr_usda = &             !! Residual volumetric water content  
    188  & (/ 0.045_r_std, 0.057_r_std, 0.065_r_std, 0.067_r_std, &              !!  @tex $(m^{3} m^{-3})$ @endtex 
    189  &    0.034_r_std, 0.078_r_std, 0.100_r_std, 0.089_r_std, & 
    190  &    0.095_r_std, 0.100_r_std, 0.070_r_std, 0.068_r_std, & 
    191  &    0.068_r_std /) ! oxisols 
    192  
    193   REAL(r_std),PARAMETER,DIMENSION(nscm_usda) :: mcs_usda = &             !! Saturated volumetric water content  
    194  & (/ 0.43_r_std, 0.41_r_std, 0.41_r_std, 0.45_r_std, &                  !!  @tex $(m^{3} m^{-3})$ @endtex 
    195  &    0.46_r_std, 0.43_r_std, 0.39_r_std, 0.43_r_std, & 
    196  &    0.41_r_std, 0.38_r_std, 0.36_r_std, 0.38_r_std, & 
    197  &    0.503_r_std  /) ! oxisols 
    198  
    199   REAL(r_std),PARAMETER,DIMENSION(nscm_usda) :: ks_usda = &              !! Hydraulic conductivity at saturation 
    200  & (/ 7128.0_r_std, 3501.6_r_std, 1060.8_r_std, 108.0_r_std, &           !!  @tex $(mm d^{-1})$ @endtex 
    201  &    60.0_r_std, 249.6_r_std, 314.4_r_std, 16.8_r_std, & 
    202  &    62.4_r_std, 28.8_r_std, 4.8_r_std, 48.0_r_std, & 
    203  &    6131.4_r_std  /) ! oxisols 
    204  
    205   REAL(r_std),PARAMETER,DIMENSION(nscm_usda) :: pcent_usda = &           !! Fraction of saturated volumetric soil moisture 
    206  & (/ 0.8_r_std, 0.8_r_std, 0.8_r_std, 0.8_r_std, &                      !! above which transpir is max (0-1, unitless) 
    207  &    0.8_r_std, 0.8_r_std, 0.8_r_std, 0.8_r_std, & 
    208  &    0.8_r_std, 0.8_r_std, 0.8_r_std, 0.8_r_std, & 
    209  &    0.8_r_std /) ! oxisols 
    210  
    211   REAL(r_std),PARAMETER,DIMENSION(nscm_usda) :: free_drain_max_usda = &  !! Max=default value of the permeability coeff  
    212  & (/ 1.0_r_std, 1.0_r_std, 1.0_r_std, 1.0_r_std, &                      !! at the bottom of the soil (0-1, unitless) 
    213  &    1.0_r_std, 1.0_r_std, 1.0_r_std, 1.0_r_std, & 
    214  &    1.0_r_std, 1.0_r_std, 1.0_r_std, 1.0_r_std,  & 
    215  &    1.0_r_std /) 
    216  
    217188  REAL(r_std),PARAMETER,DIMENSION(nscm_usda) :: mcf_usda = &             !! Volumetric water content at field capacity 
    218189 & (/ 0.0493_r_std, 0.0710_r_std, 0.1218_r_std, 0.2402_r_std, &          !!  @tex $(m^{3} m^{-3})$ @endtex 
  • branches/ORCHIDEE_2_2/ORCHIDEE/src_sechiba/hydrol.f90

    r7255 r7337  
    14491449    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable mc_adry','','') 
    14501450        
    1451     !! 2.2 Soil texture choose 
    1452  
    1453     SELECTCASE (nscm) 
    1454     CASE (3)               
    1455        pcent(:) = pcent_fao(:)  
    1456        mc_awet(:) = mc_awet_fao(:) 
    1457        mc_adry(:) = mc_adry_fao(:) 
    1458     CASE (13)            
    1459        pcent(:) = pcent_usda(:)  
    1460        mc_awet(:) = mc_awet_usda(:) 
    1461        mc_adry(:) = mc_adry_usda(:)        
    1462     CASE DEFAULT 
    1463        WRITE (numout,*) 'Unsupported soil type classification. Choose between zobler and usda according to the map' 
    1464        CALL ipslerr_p(3,'hydrol_init','Unsupported soil type classification. ',& 
    1465             'Choose between zobler and usda according to the map','') 
    1466     ENDSELECT 
    1467  
     1451    !! 2.2 Soil texture parameters 
     1452          
     1453    pcent(:) = pcent_usda(:)  
     1454    mc_awet(:) = mc_awet_usda(:) 
     1455    mc_adry(:) = mc_adry_usda(:)  
    14681456 
    14691457    !! 2.3 Read in the run.def the parameters values defined by the user 
  • branches/ORCHIDEE_2_2/ORCHIDEE/src_sechiba/slowproc.f90

    r7326 r7337  
    30323032             IF (ALLOC_ERR/=0) CALL ipslerr_p(3,'slowproc_soilt','Error in allocation for textfrac_table','','') 
    30333033             DO ib=1, nbpt 
    3034                 soilclass(ib,:) = soilclass_default_fao 
     3034                soilclass(ib,:) = soilclass_default_usda  
    30353035                clayfraction(ib) = clayfraction_default 
    30363036             ENDDO 
     
    30383038          CASE('zobler') 
    30393039             ! 
    3040              soilclass_default=soilclass_default_fao ! FAO means here 3 final texture classes 
     3040             soilclass_default=soilclass_default_usda ! USDA means here 13 final texture classes, owing to fao2usda 
    30413041             ! 
    30423042             IF (printlev_loc>=2) WRITE(numout,*) "Using a soilclass map with Zobler classification, to be read using XIOS" 
     
    30573057             !             ! 
    30583058             DO ib =1, nbpt 
    3059                 soilclass(ib,1)=textrefrac(ib,1) 
    3060                 soilclass(ib,2)=textrefrac(ib,2)+textrefrac(ib,3)+textrefrac(ib,4)+textrefrac(ib,7) 
    3061                 soilclass(ib,3)=textrefrac(ib,5) 
     3059                soilclass(ib,:)=0. 
     3060                soilclass(ib,fao2usda(1))=textrefrac(ib,1) 
     3061                soilclass(ib,fao2usda(2))=textrefrac(ib,2)+textrefrac(ib,3)+textrefrac(ib,4)+textrefrac(ib,7) 
     3062                soilclass(ib,fao2usda(3))=textrefrac(ib,5) 
    30623063 
    30633064                ! clayfraction is the sum of the % of clay (as a mineral of small granulometry, and not as a texture) 
     
    30753076                     textfrac_table(5,1) * textrefrac(ib,5)+textfrac_table(7,1) * textrefrac(ib,7) 
    30763077 
    3077                 sgn=SUM(soilclass(ib,1:3)) 
    3078  
    3079                 IF (sgn < min_sechiba) THEN 
     3078                sgn=SUM(soilclass(ib,1:3)) ! grid-cell fraction with texture info 
     3079 
     3080                IF (sgn < min_sechiba) THEN ! if no texture info in this grid-point, we assume 28%/52%, 20% of texture classes 3/6/9 
    30803081                   soilclass(ib,:) = soilclass_default(:) 
    30813082                   clayfraction(ib) = clayfraction_default 
     
    31353136                ENDDO 
    31363137 
    3137                 sgn=SUM(soilclass(ib,:)) 
    3138  
    3139                 IF (sgn < min_sechiba) THEN 
     3138                sgn=SUM(soilclass(ib,:)) ! grid-cell fraction with texture info 
     3139 
     3140                IF (sgn < min_sechiba) THEN ! if no texture info in this grid-point, we assume 28%/52%, 20% of texture classes 3/6/9 
    31403141                   soilclass(ib,:) = soilclass_default(:) 
    31413142                   clayfraction(ib) = clayfraction_default 
     
    32343235             IF (ALLOC_ERR/=0) CALL ipslerr_p(3,'slowproc_soilt','Error in allocation for textfrac_table','','') 
    32353236             DO ib=1, nbpt 
    3236                 soilclass(ib,:) = soilclass_default_fao 
     3237                soilclass(ib,:) = soilclass_default_usda 
    32373238                clayfraction(ib) = clayfraction_default 
    32383239                sandfraction(ib) = sandfraction_default 
     
    32413242          CASE('zobler') 
    32423243             ! 
    3243              soilclass_default=soilclass_default_fao ! FAO means here 3 final texture classes 
     3244             soilclass(ib,:) = soilclass_default_usda ! USDA means here 13 final texture classes, owing to fao2usda 
    32443245             ! 
    32453246             IF (printlev_loc>=2) WRITE(numout,*) "Using a soilclass map with Zobler classification" 
     
    32943295                         SELECT CASE(solt(ilf)) 
    32953296                         CASE(1) 
    3296                             soilclass(ib,1) = soilclass(ib,1) + textrefrac(ib,solt(ilf)) 
     3297                            soilclass(ib,fao2usda(1)) = soilclass(ib,fao2usda(1)) + textrefrac(ib,solt(ilf)) 
    32973298                         CASE(2) 
    3298                             soilclass(ib,2) = soilclass(ib,2) + textrefrac(ib,solt(ilf)) 
     3299                            soilclass(ib,fao2usda(2)) = soilclass(ib,fao2usda(2)) + textrefrac(ib,solt(ilf)) 
    32993300                         CASE(3) 
    3300                             soilclass(ib,2) = soilclass(ib,2) + textrefrac(ib,solt(ilf)) 
     3301                            soilclass(ib,fao2usda(2)) = soilclass(ib,fao2usda(2)) + textrefrac(ib,solt(ilf)) 
    33013302                         CASE(4) 
    3302                             soilclass(ib,2) = soilclass(ib,2) + textrefrac(ib,solt(ilf)) 
     3303                            soilclass(ib,fao2usda(2)) = soilclass(ib,fao2usda(2)) + textrefrac(ib,solt(ilf)) 
    33033304                         CASE(5) 
    3304                             soilclass(ib,3) = soilclass(ib,3) + textrefrac(ib,solt(ilf)) 
     3305                            soilclass(ib,fao2usda(3)) = soilclass(ib,fao2usda(3)) + textrefrac(ib,solt(ilf)) 
    33053306                         CASE(7) 
    3306                             soilclass(ib,2) = soilclass(ib,2) + textrefrac(ib,solt(ilf)) 
     3307                            soilclass(ib,fao2usda(2)) = soilclass(ib,fao2usda(2)) + textrefrac(ib,solt(ilf)) 
    33073308                         CASE DEFAULT 
    33083309                            WRITE(numout,*) 'We should not be here, an impossible case appeared' 
     
    34513452       njsc(:) = 0 
    34523453       DO ib = 1, nbpt 
    3453           njsc(ib) = MAXLOC(soilclass(ib,:),1) 
     3454          njsc(ib) = MAXLOC(soilclass(ib,:),1) ! Here we get 3/6/9 for the Zobler classes Coarse/Medium/Fine 
    34543455       ENDDO 
    34553456 
     
    35453546 
    35463547       ELSE ! spmipexp is not maps nor unif, then it must be texture 
    3547          IF (spmipexp == 'texture') THEN 
    3548             IF (soil_classif == 'usda') THEN 
    3549                ! Texture map from SP-MIP, thus Soilgrids modified 
    3550                nvan(:) = nvan_usda(njsc(:)) 
    3551                avan(:) = avan_usda(njsc(:)) 
    3552                mcr(:) = mcr_usda(njsc(:)) 
    3553                mcs(:) = mcs_usda(njsc(:)) 
    3554                ks(:) = ks_usda(njsc(:)) 
    3555                mcfc(:) = mcf_usda(njsc(:)) 
    3556                mcw(:) = mcw_usda(njsc(:)) 
    3557                ! on aura pcent(:) = pcent(njsc(:)) dans hydrol 
    3558             ELSE ! soil_classif == 'zobler' or 'none' 
    3559                ! salma: here we are in exp3 -- Zobler map 
    3560                nvan(:) = nvan_fao(njsc(:)) 
    3561                avan(:) = avan_fao(njsc(:)) 
    3562                mcr(:) = mcr_fao(njsc(:)) 
    3563                mcs(:) = mcs_fao(njsc(:)) 
    3564                ks(:) = ks_fao(njsc(:)) 
    3565                mcfc(:) = mcf_fao(njsc(:)) 
    3566                mcw(:) = mcw_fao(njsc(:)) 
    3567             ENDIF !if spmipexp is texture        
     3548          IF (spmipexp == 'texture') THEN 
     3549             ! Whichever the soil texture map, we can use the USDA parameter vectors with 13 values  
     3550             nvan(:) = nvan_usda(njsc(:)) 
     3551             avan(:) = avan_usda(njsc(:)) 
     3552             mcr(:) = mcr_usda(njsc(:)) 
     3553             mcs(:) = mcs_usda(njsc(:)) 
     3554             ks(:) = ks_usda(njsc(:)) 
     3555             mcfc(:) = mcf_usda(njsc(:)) 
     3556             mcw(:) = mcw_usda(njsc(:))     
    35683557         ELSE ! if spmipexp is not among texture or maps or unif 
    35693558            WRITE(numout,*) "Unsupported spmipexp=",spmipexp 
  • branches/ORCHIDEE_2_2/ORCHIDEE/src_sechiba/thermosoil.f90

    r7207 r7337  
    379379 
    380380 
    381 !! Soil texture choose 
    382     SELECTCASE (nscm) 
    383     CASE (3) 
    384        QZ(:) = QZ_fao(:) 
    385        so_capa_dry_ns(:) = so_capa_dry_ns_fao(:) 
    386     CASE (13) !Salma changed from 12 to 13 for the new class Oxisols 
    387        QZ(:) = QZ_usda(:) 
    388        so_capa_dry_ns(:) = so_capa_dry_ns_usda(:) 
    389     CASE DEFAULT 
    390        WRITE (numout,*) 'Unsupported soil type classification. Choose between zobler, fao and usda according to the map' 
    391        STOP 'thermosoil_initialize' 
    392     ENDSELECT 
    393  
     381    !! Soil texture choose : Now useless since njsc defines the dominant texture within 13 classes whichever the soil map 
     382    QZ(:) = QZ_usda(:) 
     383    so_capa_dry_ns(:) = so_capa_dry_ns_usda(:) 
    394384     
    395385    !! 2. Initialize variable from restart file or with default values  
     
    13301320          ! Eq 11 in Peters-Lidard et al., 1998 
    13311321          IF ( satratio(ji,jg) >  0.1 ) THEN 
    1332             IF ((jst < 4 .AND. soil_classif == 'usda') .OR. (jst == 1 .AND. soil_classif == 'zobler') )  THEN 
     1322            IF (jst < 4 )  THEN 
    13331323                ! Coarse  
    13341324                ake(ji,jg) = 0.7 * LOG10 (SATRATIO(ji,jg)) + 1.0 
     
    13381328            ENDIF 
    13391329          ELSEIF ( satratio(ji,jg) >  0.05 .AND. satratio(ji,jg) <=  0.1 ) THEN 
    1340             IF ((jst < 4 .AND. soil_classif == 'usda') .OR. (jst == 1 .AND. soil_classif == 'zobler') )  THEN 
     1330            IF (jst < 4 )  THEN 
    13411331                ! Coarse  
    13421332                ake(ji,jg) = 0.7 * LOG10 (satratio(ji,jg)) + 1.0 
Note: See TracChangeset for help on using the changeset viewer.