Changeset 8462 for branches/ORCHIDEE_2_2/ORCHIDEE/src_stomate
- Timestamp:
- 2024-03-07T18:38:03+01:00 (11 months ago)
- Location:
- branches/ORCHIDEE_2_2/ORCHIDEE/src_stomate
- Files:
-
- 3 edited
Legend:
- Unmodified
- Added
- Removed
-
branches/ORCHIDEE_2_2/ORCHIDEE/src_stomate/stomate.f90
r8423 r8462 644 644 rest_id_stom, hist_id_stom, hist_id_stom_IPCC, & 645 645 index, lalo, neighbours, resolution, & 646 contfrac, totfrac_nobio, clay, temp_air,&647 lai, veget, veget_max,&646 contfrac, totfrac_nobio, clay, bulk, & 647 temp_air, lai, veget, veget_max, & 648 648 deadleaf_cover, assim_param, temp_growth ) 649 649 … … 665 665 REAL(r_std),DIMENSION(kjpindex),INTENT(in) :: totfrac_nobio !! Fraction of grid cell covered by lakes, land ice, cities, ... (unitless) 666 666 REAL(r_std),DIMENSION(kjpindex),INTENT(in) :: clay !! Clay fraction of soil (0-1, unitless) 667 REAL(r_std),DIMENSION(kjpindex),INTENT(in) :: bulk !! Bulk density (kg/m**3) 667 668 REAL(r_std),DIMENSION(kjpindex),INTENT(in) :: temp_air !! Air temperature at first atmospheric model layer (K) 668 669 REAL(r_std),DIMENSION(kjpindex,nvm),INTENT(in) :: lai !! Leaf area inex @tex $(m^2 m^{-2})$ @endtex … … 1188 1189 & (kjit, kjpij, kjpindex, & 1189 1190 & index, lalo, neighbours, resolution, contfrac, totfrac_nobio, clay, & 1190 & temp_air, temp_sol, stempdiag, &1191 & humrel, shumdiag, litterhumdiag, precip_rain, precip_snow, &1191 & bulk, temp_air, temp_sol, stempdiag, & 1192 & humrel, shumdiag,shumdiagSAT, litterhumdiag,litterhumdiagSAT, precip_rain, precip_snow, & 1192 1193 & gpp, deadleaf_cover, assim_param, & 1193 1194 & lai, frac_age, height, veget, veget_max, & … … 1225 1226 !! ice, cities, ... (unitless) 1226 1227 REAL(r_std),DIMENSION(kjpindex),INTENT(in) :: clay !! Clay fraction of soil (0-1, unitless) 1228 REAL(r_std),DIMENSION(kjpindex),INTENT(in) :: bulk !! Bulk density (kg/m**3) 1227 1229 REAL(r_std),DIMENSION(kjpindex,nvm),INTENT(in) :: humrel !! Relative humidity ("moisture availability") 1228 1230 !! (0-1, unitless) … … 1231 1233 REAL(r_std),DIMENSION(kjpindex,nslm),INTENT(in) :: stempdiag !! Soil temperature (K) 1232 1234 REAL(r_std),DIMENSION(kjpindex,nslm),INTENT(in) :: shumdiag !! Relative soil moisture (0-1, unitless) 1235 REAL(r_std),DIMENSION(kjpindex,nslm),INTENT(in) :: shumdiagSAT !! Relative soil moisture (0-1, unitless) 1236 !! with respect to(mcs-mcw) 1233 1237 REAL(r_std),DIMENSION(kjpindex),INTENT(in) :: litterhumdiag !! Litter humidity (0-1, unitless) 1238 REAL(r_std),DIMENSION(kjpindex),INTENT(in) :: litterhumdiagSAT !! Litter humidity (0-1, unitless) 1239 !! with respect to(tmc_litter_sat-tmc_litter_wilt) 1234 1240 REAL(r_std),DIMENSION(kjpindex),INTENT(in) :: precip_rain !! Rain precipitation 1235 1241 !! @tex $(mm dt_stomate^{-1})$ @endtex … … 1369 1375 1370 1376 !_ ================================================================================================================================ 1371 1377 1378 1372 1379 !! 1. Initialize variables 1373 1380 … … 1487 1494 CALL littercalc (kjpindex, & 1488 1495 turnover_littercalc, bm_to_littercalc, & 1489 veget_cov_max, temp_sol, stempdiag, shumdiag, litterhumdiag, &1496 veget_cov_max, temp_sol, stempdiag, shumdiag, litterhumdiag,shumdiagSAT,litterhumdiagSAT, & 1490 1497 litterpart, litter, dead_leaves, lignin_struc, & 1491 1498 deadleaf_cover, resp_hetero_litter, & 1492 1499 soilcarbon_input_inst, control_temp_inst, control_moist_inst, & 1493 matrixA, vectorB )1500 matrixA, vectorB, bulk, clay, carbon) 1494 1501 1495 1502 ! Heterothropic litter respiration during time step ::dt_sechiba @tex $(gC m^{-2})$ @endtex … … 1551 1558 & (kjpindex, dt_days, & 1552 1559 & veget_cov, veget_cov_max, & 1553 & humrel_daily, t2m_daily, tsoil_daily, soilhum_daily, lalo, & 1560 & humrel_daily, t2m_daily, tsoil_daily, & 1561 & soilhum_daily, lalo, & 1554 1562 & precip_daily, npp_daily, biomass, & 1555 1563 & turnover_daily, gpp_daily, when_growthinit, & … … 1562 1570 & maxfpc_lastyear, maxfpc_thisyear, & 1563 1571 & humrel_month, humrel_week, t2m_longterm, tau_longterm, & 1564 & t2m_month, t2m_week, tsoil_month, 1572 & t2m_month, t2m_week, tsoil_month,soilhum_month, & 1565 1573 & npp_longterm, turnover_longterm, gpp_week, & 1566 1574 & gdd_m5_dormance, gdd_midwinter, ncd_dormance, ngd_minus5, & … … 1584 1592 & clay, herbivores, & 1585 1593 & tsurf_daily, tsoil_daily, t2m_daily, t2m_min_daily, & 1586 & litterhum_daily, soilhum_daily, &1594 & litterhum_daily, soilhum_daily, & 1587 1595 & maxhumrel_lastyear, minhumrel_lastyear, & 1588 1596 & gdd0_lastyear, precip_lastyear, & … … 2013 2021 !_ ================================================================================================================================ 2014 2022 2015 SUBROUTINE stomate_finalize (kjit, kjpindex, index, clay, assim_param)2023 SUBROUTINE stomate_finalize (kjit, kjpindex, index, clay, bulk, assim_param) 2016 2024 2017 2025 IMPLICIT NONE … … 2023 2031 INTEGER(i_std),DIMENSION(kjpindex),INTENT(in) :: index !! Indices of the terrestrial pixels only (unitless) 2024 2032 REAL(r_std),DIMENSION(kjpindex),INTENT(in) :: clay !! Clay fraction of soil (0-1, unitless) 2033 REAL(r_std),DIMENSION(kjpindex),INTENT(in) :: bulk !! Bulk density (kg/m**3) 2025 2034 REAL(r_std),DIMENSION(kjpindex,nvm,npco2),INTENT(in) :: assim_param !! min+max+opt temperatures (K) & vmax for photosynthesis 2026 2035 … … 2109 2118 dt_days, days_since_beg, & 2110 2119 ind, adapted, regenerate, & 2111 humrel_daily, gdd_init_date, litterhum_daily, 2120 humrel_daily, gdd_init_date, litterhum_daily,& 2112 2121 t2m_daily, t2m_min_daily, tsurf_daily, tsoil_daily, & 2113 2122 soilhum_daily, precip_daily, & -
branches/ORCHIDEE_2_2/ORCHIDEE/src_stomate/stomate_io.f90
r8423 r8462 440 440 & .TRUE., litterhum_daily, 'gather', nbp_glo, index_g) 441 441 IF (ALL(litterhum_daily(:) == val_exp)) litterhum_daily(:) = zero 442 442 443 !- 443 444 t2m_daily(:) = val_exp … … 471 472 & .TRUE., soilhum_daily, 'gather', nbp_glo, index_g) 472 473 IF (ALL(soilhum_daily(:,:) == val_exp)) soilhum_daily(:,:) = zero 474 473 475 !- 474 476 precip_daily(:) = val_exp … … 604 606 & .TRUE., soilhum_month, 'gather', nbp_glo, index_g) 605 607 IF (ALL(soilhum_month(:,:) == val_exp)) soilhum_month(:,:) = zero 608 609 606 610 !- 607 611 ! 6 fire probability … … 993 997 CALL restget_p (rest_id_stomate, var_name, nbp_glo, nlitt , 1, itime, & 994 998 & .TRUE., litter(:,:,m,l,k), 'gather', nbp_glo, index_g) 995 IF (ALL(litter(:,:,m,l,k) == val_exp)) litter(:,:,m,l,k) = zero 999 IF (ok_moyano_soilhumsat)THEN 1000 IF (ALL(litter(:,:,m,l,k) == val_exp)) litter(:,:,m,l,k) = Litterini_Moyano 1001 ELSE 1002 IF (ALL(litter(:,:,m,l,k) == val_exp)) litter(:,:,m,l,k) = zero 1003 ENDIF 996 1004 ENDDO 997 1005 ENDDO … … 1013 1021 CALL restget_p (rest_id_stomate, var_name, nbp_glo, ncarb , 1, itime, & 1014 1022 & .TRUE., carbon(:,:,m), 'gather', nbp_glo, index_g) 1015 IF (ALL(carbon(:,:,m) == val_exp)) carbon(:,:,m) = zero 1023 IF (ok_moyano_soilhumsat)THEN 1024 IF (ALL(carbon(:,:,m) == val_exp)) carbon(:,:,m) = Cini_Moyano 1025 ELSE 1026 IF (ALL(carbon(:,:,m) == val_exp)) carbon(:,:,m) = zero 1027 ENDIF 1016 1028 ENDDO 1017 1029 !- … … 1689 1701 var_name = 't2m_daily' 1690 1702 CALL restput_p (rest_id_stomate, var_name, nbp_glo, 1, 1, itime, & 1691 & t2m_daily, 'scatter', nbp_glo, index_g)1703 & t2m_daily, 'scatter', nbp_glo, index_g) 1692 1704 !- 1693 1705 var_name = 't2m_min_daily' 1694 1706 CALL restput_p (rest_id_stomate, var_name, nbp_glo, 1, 1, itime, & 1695 & t2m_min_daily, 'scatter', nbp_glo, index_g)1707 & t2m_min_daily, 'scatter', nbp_glo, index_g) 1696 1708 !- 1697 1709 var_name = 'tsurf_daily' 1698 1710 CALL restput_p (rest_id_stomate, var_name, nbp_glo, 1, 1, itime, & 1699 & tsurf_daily, 'scatter', nbp_glo, index_g)1711 & tsurf_daily, 'scatter', nbp_glo, index_g) 1700 1712 !- 1701 1713 var_name = 'tsoil_daily' 1702 1714 CALL restput_p (rest_id_stomate, var_name, nbp_glo, nslm, 1, itime, & 1703 & tsoil_daily, 'scatter', nbp_glo, index_g)1715 & tsoil_daily, 'scatter', nbp_glo, index_g) 1704 1716 !- 1705 1717 var_name = 'soilhum_daily' -
branches/ORCHIDEE_2_2/ORCHIDEE/src_stomate/stomate_litter.f90
r8423 r8462 26 26 27 27 ! modules used: 28 28 USE xios_orchidee 29 29 USE ioipsl_para 30 30 USE stomate_data … … 180 180 turnover, bm_to_litter, & 181 181 veget_cov_max, tsurf, tsoil, soilhum, litterhum, & 182 soilhumSAT, litterhumSAT, & 182 183 litterpart, litter, dead_leaves, lignin_struc, & 183 184 deadleaf_cover, resp_hetero_litter, & 184 185 soilcarbon_input, control_temp, control_moist, & 185 MatrixA, VectorB )186 MatrixA, VectorB, bulk, clay, carbon) 186 187 187 188 !! 0. Variable and parameter declaration … … 201 202 REAL(r_std), DIMENSION(npts,nslm), INTENT(in) :: soilhum !! Daily soil humidity of each soil layer 202 203 !! (unitless) 204 REAL(r_std), DIMENSION(npts,nslm), INTENT(in) :: soilhumSAT !! Daily soil humidity of each soil layer 205 !! (unitless) 203 206 REAL(r_std), DIMENSION(npts), INTENT(in) :: litterhum !! Daily litter humidity (unitless) 207 REAL(r_std), DIMENSION(npts), INTENT(in) :: litterhumSAT !! Daily litter humidity (unitless) 208 REAL(r_std), DIMENSION(npts), INTENT(in) :: clay !! Clay fraction (unitless, 0-1) 209 REAL(r_std), DIMENSION(npts),INTENT(in) :: bulk !! Bulk density (kg/m**3) 210 REAL(r_std), DIMENSION(npts,ncarb,nvm), INTENT(in) :: carbon !! Soil carbon pools: active, slow, or passive, \f$(gC m^{2})$\f 204 211 205 212 !! 0.2 Output variables … … 261 268 REAL(r_std), DIMENSION(npts) :: soilhum_decomp !! Humidity used for decompostition in soil 262 269 !! (unitless) 270 REAL(r_std), DIMENSION(npts) :: soilhumSAT_decomp !! Humidity used for decompostition in soil 271 !! (unitless) for Moyano et al 2012 263 272 REAL(r_std), DIMENSION(npts) :: fd !! Fraction of structural or metabolic litter 264 273 !! decomposed (unitless) … … 585 594 586 595 !! 4.1 above the ground: litter humidity 587 control_moist(:,iabove) = control_moist_func (npts, litterhum) 588 596 597 IF (ok_moyano_soilhumsat)THEN !!ok_moyano_soilhumsat is true 598 control_moist(:,iabove) = control_moist_func_moyano (npts,clay,bulk,carbon, litter ,litterhumSAT, veget_cov_max) 599 ELSE !ok_moyano_soilhumsat is false by default 600 control_moist(:,iabove) = control_moist_func (npts, litterhum) 601 ENDIF 602 603 CALL xios_orchidee_send_field("ControlMoistLitter",control_moist(:,iabove)) 604 CALL xios_orchidee_send_field("litterhumSAT",litterhumSAT(:)) 589 605 ! 590 606 !! 4.2 below: convolution of humidity and decomposer profiles … … 596 612 !! 4.2.2 integrate over the nslm levels 597 613 soilhum_decomp(:) = zero 598 599 DO l = 1, nslm !Loop over soil levels 600 601 soilhum_decomp(:) = & 602 soilhum_decomp(:) + soilhum(:,l) * rpc(:) * & 603 ( EXP( -z_soil(l-1)/z_decomp ) - EXP( -z_soil(l)/z_decomp ) ) 604 605 ENDDO 606 607 control_moist(:,ibelow) = control_moist_func (npts, soilhum_decomp) 614 soilhumSAT_decomp(:) = zero 615 616 IF (ok_moyano_soilhumsat)THEN !!ok_moyano_soilhumsat is true 617 DO l = 1, nslm !Loop over soil levels 618 soilhumSAT_decomp(:) = & 619 soilhumSAT_decomp(:) + soilhumSAT(:,l) * rpc(:) * & 620 ( EXP( -z_soil(l-1)/z_decomp ) - EXP( -z_soil(l)/z_decomp ) ) 621 ENDDO 622 control_moist(:,ibelow) = control_moist_func_moyano (npts,clay,bulk,carbon, litter, soilhumSAT_decomp,veget_cov_max) 623 624 ELSE !ok_moyano_soilhumsat is false by default 625 DO l = 1, nslm !Loop over soil levels 626 627 soilhum_decomp(:) = & 628 soilhum_decomp(:) + soilhum(:,l) * rpc(:) * & 629 ( EXP( -z_soil(l-1)/z_decomp ) - EXP( -z_soil(l)/z_decomp ) ) 630 ENDDO 631 control_moist(:,ibelow) = control_moist_func (npts, soilhum_decomp) 632 ENDIF 633 634 CALL xios_orchidee_send_field("ControlMoistSoil",control_moist(:,ibelow)) 635 CALL xios_orchidee_send_field("soilhumSAT",soilhumSAT_decomp(:)) 608 636 609 637 !! 5. fluxes from litter to carbon pools and respiration … … 850 878 851 879 !! ================================================================================================================================ 880 !! FUNCTION : control_moist_func_moyano 881 !! 882 !>\BRIEF Calculate moisture control for litter and soil C decomposition 883 !! 884 !! DESCRIPTION : Calculate moisture control factor applied 885 !! to litter decomposition and to soil carbon decomposition in 886 !! stomate_soilcarbon.f90 using the following equation based on the Moyano et al., 2012 BG paper: \n 887 !! \latexonly 888 !! \input{control_moist_func1.tex} 889 !! \endlatexonly 890 !! \n 891 !! with M the moisture control factor and soilmoisutre, the soil moisture 892 !! calculated in sechiba. 893 !! Then, the function is ranged between Moistcont_min and 1:\n 894 !! \latexonly 895 !! \input{control_moist_func2.tex} 896 !! \endlatexonly 897 !! \n 898 !! RECENT CHANGE(S) : None 899 !! 900 !! RETURN VALUE : ::moistfunc_result 901 !! 902 !! REFERENCE(S) : None 903 !! 904 !! FLOWCHART : None 905 !! \n 906 !_ ================================================================================================================================ 907 908 FUNCTION control_moist_func_moyano (npts,clay,bulk,carbon,litter,moist_in,veget_cov_max) RESULT (moistfunc_result) 909 910 !! 0. Variable and parameter declaration 911 912 !! 0.1 Input variables 913 INTEGER(i_std) :: k,m,n,i,l,e !!indices 914 INTEGER(i_std), INTENT(in) :: npts !! Domain size - number of grid pixel (unitless) 915 REAL(r_std), DIMENSION(npts), INTENT(in) :: moist_in !! relative humidity (unitless) 916 REAL(r_std), DIMENSION(npts), INTENT(in) :: clay !! Clay fraction (unitless, 0-1) 917 REAL(r_std), DIMENSION(npts), INTENT(in) :: bulk !! Bulk density (kg/m**3) 918 REAL(r_std), DIMENSION(npts,ncarb,nvm), INTENT(in) :: carbon !! Soil carbon pools: active, s low, or passive, \f$(gC m^{2})$\f 919 REAL(r_std), DIMENSION(npts,nlitt,nvm,nlevs,nelements), INTENT(inout) ::litter !! Metabolic and structural litter,above and 920 !! below ground. The unit is given by m^2 of ground 921 !! @tex $(gC m^{-2})$ @endtex 922 REAL(r_std),DIMENSION(npts,nvm),INTENT(in):: veget_cov_max !! PFT "Maximal" coverage fraction of a PFT 923 924 !! 0.2 Output variables 925 926 REAL(r_std), DIMENSION(npts) :: moistfunc_result !! Moisture control factor (0.25-1, unitless) 927 928 !! 0.3 Modified variables 929 930 !! 0.4 Local variables 931 REAL(r_std), DIMENSION(101) :: Mint !! range [0,0.01,1] to compute PRSRmax 932 REAL(r_std), DIMENSION(npts,101) :: PRSR !! Proportional Response of Soil Respiration 933 REAL(r_std), DIMENSION(npts,101) :: SR !! Soil respiration compute using Moyano et al 2012 procedure 934 REAL(r_std) :: SRmax !! maximum value of SR 935 REAL(r_std), DIMENSION(npts,101) :: SRnorm !! SR normalized by the SRmax 936 REAL(r_std) :: ind !! i index of maximum SRnorm value 937 REAL(r_std) :: SRmin !! minimum value of SRnorm 938 REAL(r_std), DIMENSION(npts,101) :: SRsc !! Soil respiration rescale between 0 and 1 following Moyano et al 2012 procedure 939 REAL(r_std) :: SRscmax !! maximum value of SRsc 940 REAL(r_std) :: indmc !! i index of maximum mois_round values 941 REAL(r_std) :: moist_round !! moist_in round to 2decimal points 942 REAL(r_std), DIMENSION(npts) :: carbon_gCgs !! total Soil carbon pools: active +slow+ passive, (gC/gsoil) 943 REAL(r_std), DIMENSION(npts) :: carbon_gCm2s !! total Soil carbon pools: active +slow+ passive , (gC/gsoil) 944 REAL(r_std), DIMENSION(npts) :: clay_Moyano !! Clay fraction borned within the values used by Moyano et al., (unitless, 0-1) 945 946 !_ =============================================================================================================================== 947 948 !! In ok_moyano_soilhumsat total soil carbon per grid cells need to be computed and 949 !! converted from gC/m2soil to gC/gsoil 950 carbon_gCm2s(:)=zero 951 carbon_gCgs(:)=zero 952 DO n = 1, npts ! loop over grids 953 DO m = 1, nvm ! Loop over # PFTs 954 DO k = 1, ncarb ! Loop over carbon pools 955 carbon_gCm2s(n)=carbon_gCm2s(n)+carbon(n,k,m)*veget_cov_max(n,m) 956 ENDDO 957 ENDDO 958 ENDDO 959 960 IF (ok_orga) THEN 961 DO n = 1, npts ! loop over grids 962 carbon_gCgs(n)=carbon_gCm2s(n) / (bulk(n) * 1E3 * soilheight) 963 carbon_gCgs(n)= MAX(min_carbon_moyano,MIN(max_carbon_moyano,carbon_gCgs(n))) 964 clay_Moyano(n) = MAX(min_clay_moyano,MIN(max_clay_moyano,clay(n))) 965 ENDDO 966 967 !!1. compute Max(Prsr(M[0,0.01,1])); Prsr:Proportional Response of Soil 968 !!Respiration (PRSR) and Soil respiration(SR): SR(M)=SRo x Prsr(M)/Max(Prsr(M[0,0.01,1])) 969 !! M:soilhumSAT, SRo=1 (arbitrary) 970 DO n = 1,npts 971 Mint(:)= zero 972 SRmax = zero 973 DO i = 1,101 974 Mint(i)=0.01*(i-1) 975 IF (carbon_gCgs(n) .LT. limit_carbon_orga) THEN 976 PRSR(n,i) = beta1 * Mint(i) + beta2 * Mint(i)**2.0 + beta3 * Mint(i)**3.0 & 977 & + beta4 * clay_Moyano(n) + beta5 * clay_Moyano(n) * Mint(i) & 978 & + beta6 * carbon_gCgs(n) + intercept 979 ELSE 980 PRSR(n,i) = beta1_orga * Mint(i) + beta2_orga * Mint(i)**2.0 + & 981 & beta3_orga * Mint(i)**3.0 + intercept_orga 982 ENDIF 983 984 IF (i.LT.2) THEN 985 SR(n,i) = PRSR(n,i) 986 SRmax = MAX(SR(n,i),SRmax) 987 ELSE 988 SR(n,i) = PRSR(n,i) * SR(n,i-1) 989 SRmax = MAX(SR(n,i),SRmax) 990 ENDIF 991 ENDDO 992 SRnorm(n,:)= SRo * SR(n,:)/SRmax 993 ENDDO 994 ELSE 995 DO n = 1, npts ! loop over grids 996 carbon_gCgs(n)=carbon_gCm2s(n) / (bulk(n) * 1E3 * soilheight) 997 carbon_gCgs(n)= MAX(min_carbon_moyano,MIN(limit_carbon_orga,carbon_gCgs(n))) 998 clay_Moyano(n) = MAX(min_clay_moyano,MIN(max_clay_moyano,clay(n))) 999 ENDDO 1000 1001 !!1. compute Max(Prsr(M[0,0.01,1])); Prsr:Proportional Response of Soil 1002 !!Respiration (PRSR) and Soil respiration(SR): SR(M)=SRo x 1003 !Prsr(M)/Max(Prsr(M[0,0.01,1])) 1004 !! M:soilhumSAT, SRo=1 (arbitrary) 1005 DO n = 1,npts 1006 Mint(:)= zero 1007 SRmax = zero 1008 DO i = 1,101 1009 Mint(i)=0.01*(i-1) 1010 PRSR(n,i) = beta1 * Mint(i) + beta2 * Mint(i)**2.0 + beta3 * Mint(i)**3.0 & 1011 & + beta4 * clay_Moyano(n) + beta5 * clay_Moyano(n) * Mint(i) & 1012 & + beta6 * carbon_gCgs(n) + intercept 1013 1014 IF (i.LT.2) THEN 1015 SR(n,i) = PRSR(n,i) 1016 SRmax = MAX(SR(n,i),SRmax) 1017 ELSE 1018 SR(n,i) = PRSR(n,i) * SR(n,i-1) 1019 SRmax = MAX(SR(n,i),SRmax) 1020 ENDIF 1021 ENDDO 1022 SRnorm(n,:)= SRo * SR(n,:)/SRmax 1023 ENDDO 1024 ENDIF 1025 1026 !!2. Rescale SR values between 0 and 1 and defined SR for moist_in 1027 DO n = 1,npts 1028 ind = 1.0 1029 indmc = zero 1030 moist_round = zero 1031 SRscmax = zero 1032 SRsc(n,:) = zero 1033 SRmin = 1.0 1034 1035 ind = MAXLOC(SRnorm(n,:),1) 1036 DO i = 1,ind 1037 SRmin = MIN(SRnorm(n,i),SRmin) 1038 ENDDO 1039 DO i = 1,101 1040 SRsc(n,i) = SRnorm(n,i)- SRmin 1041 IF (i.LE.ind)THEN 1042 SRscmax = MAX(SRsc(n,i),SRscmax) 1043 ENDIF 1044 ENDDO 1045 SRsc(n,:)=SRsc(n,:)/SRscmax 1046 1047 moist_round=(NINT(moist_in(n)*100.))/100. 1048 indmc=INT(moist_round/0.01) + un 1049 1050 moistfunc_result(n) = SRsc(n,indmc) 1051 moistfunc_result(n) = MAX( moistcontSAT_min, MIN( un, moistfunc_result(n) )) 1052 ENDDO 1053 1054 END FUNCTION control_moist_func_moyano 1055 1056 !! ================================================================================================================================ 852 1057 !! FUNCTION : control_moist_func 853 1058 !! … … 861 1066 !! \endlatexonly 862 1067 !! \n 863 !! with M the moisture control factor and soilmoisutre, the soil moisture 1068 !! with M the moisture control factor and soilmoisutre, the soil moisture 864 1069 !! calculated in sechiba. 865 1070 !! Then, the function is ranged between Moistcont_min and 1:\n … … 871 1076 !! 872 1077 !! RETURN VALUE : ::moistfunc_result 873 !! 1078 !! 874 1079 !! REFERENCE(S) : None 875 1080 !! … … 877 1082 !! \n 878 1083 !_ ================================================================================================================================ 879 1084 880 1085 FUNCTION control_moist_func (npts, moist_in) RESULT (moistfunc_result) 881 1086 882 1087 !! 0. Variable and parameter declaration 883 884 !! 0.1 Input variables 885 886 INTEGER(i_std), INTENT(in) :: npts !! Domain size - number of grid pixel (unitless) 887 REAL(r_std), DIMENSION(npts), INTENT(in) :: moist_in !! relative humidity (unitless) 888 889 !! 0.2 Output variables 1088 1089 !! 0.1 Input variables 1090 1091 INTEGER(i_std), INTENT(in) :: npts !! Domain size - number of grid pixel (unitless) 1092 REAL(r_std), DIMENSION(npts), INTENT(in) :: moist_in !! relative humidity (unitless) 1093 1094 !! 0.2 Output variables 1095 1096 REAL(r_std), DIMENSION(npts) :: moistfunc_result !! Moisture control factor (0.25-1, unitless) 890 1097 891 REAL(r_std), DIMENSION(npts) :: moistfunc_result !! Moisture control factor (0.25-1, unitless) 892 893 !! 0.3 Modified variables 894 895 !! 0.4 Local variables 896 1098 !! 0.3 Modified variables 1099 1100 !! 0.4 Local variables 1101 897 1102 !_ ================================================================================================================================ 898 1103 899 1104 moistfunc_result(:) = -moist_coeff(1) * moist_in(:) * moist_in(:) + moist_coeff(2)* moist_in(:) - moist_coeff(3) 900 1105 moistfunc_result(:) = MAX( moistcont_min, MIN( un, moistfunc_result(:) ) ) 901 1106 902 1107 END FUNCTION control_moist_func 903 904 1108 905 1109 !! ================================================================================================================================
Note: See TracChangeset
for help on using the changeset viewer.