Changeset 8423 for branches/ORCHIDEE_2_2/ORCHIDEE/src_stomate
- Timestamp:
- 2024-02-13T13:45:31+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
r8418 r8423 644 644 rest_id_stom, hist_id_stom, hist_id_stom_IPCC, & 645 645 index, lalo, neighbours, resolution, & 646 contfrac, totfrac_nobio, clay, bulk,&647 temp_air, lai, veget, veget_max,&646 contfrac, totfrac_nobio, clay, temp_air, & 647 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)668 667 REAL(r_std),DIMENSION(kjpindex),INTENT(in) :: temp_air !! Air temperature at first atmospheric model layer (K) 669 668 REAL(r_std),DIMENSION(kjpindex,nvm),INTENT(in) :: lai !! Leaf area inex @tex $(m^2 m^{-2})$ @endtex … … 1189 1188 & (kjit, kjpij, kjpindex, & 1190 1189 & index, lalo, neighbours, resolution, contfrac, totfrac_nobio, clay, & 1191 & bulk,temp_air, temp_sol, stempdiag, &1192 & humrel, shumdiag, shumdiagSAT, litterhumdiag,litterhumdiagSAT, precip_rain, precip_snow, &1190 & temp_air, temp_sol, stempdiag, & 1191 & humrel, shumdiag, litterhumdiag, precip_rain, precip_snow, & 1193 1192 & gpp, deadleaf_cover, assim_param, & 1194 1193 & lai, frac_age, height, veget, veget_max, & … … 1226 1225 !! ice, cities, ... (unitless) 1227 1226 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)1229 1227 REAL(r_std),DIMENSION(kjpindex,nvm),INTENT(in) :: humrel !! Relative humidity ("moisture availability") 1230 1228 !! (0-1, unitless) … … 1233 1231 REAL(r_std),DIMENSION(kjpindex,nslm),INTENT(in) :: stempdiag !! Soil temperature (K) 1234 1232 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)1237 1233 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)1240 1234 REAL(r_std),DIMENSION(kjpindex),INTENT(in) :: precip_rain !! Rain precipitation 1241 1235 !! @tex $(mm dt_stomate^{-1})$ @endtex … … 1375 1369 1376 1370 !_ ================================================================================================================================ 1377 1378 1371 1379 1372 !! 1. Initialize variables 1380 1373 … … 1494 1487 CALL littercalc (kjpindex, & 1495 1488 turnover_littercalc, bm_to_littercalc, & 1496 veget_cov_max, temp_sol, stempdiag, shumdiag, litterhumdiag, shumdiagSAT,litterhumdiagSAT,&1489 veget_cov_max, temp_sol, stempdiag, shumdiag, litterhumdiag, & 1497 1490 litterpart, litter, dead_leaves, lignin_struc, & 1498 1491 deadleaf_cover, resp_hetero_litter, & 1499 1492 soilcarbon_input_inst, control_temp_inst, control_moist_inst, & 1500 matrixA, vectorB , bulk, clay, carbon)1493 matrixA, vectorB) 1501 1494 1502 1495 ! Heterothropic litter respiration during time step ::dt_sechiba @tex $(gC m^{-2})$ @endtex … … 1558 1551 & (kjpindex, dt_days, & 1559 1552 & veget_cov, veget_cov_max, & 1560 & humrel_daily, t2m_daily, tsoil_daily, & 1561 & soilhum_daily, lalo, & 1553 & humrel_daily, t2m_daily, tsoil_daily, soilhum_daily, lalo, & 1562 1554 & precip_daily, npp_daily, biomass, & 1563 1555 & turnover_daily, gpp_daily, when_growthinit, & … … 1570 1562 & maxfpc_lastyear, maxfpc_thisyear, & 1571 1563 & humrel_month, humrel_week, t2m_longterm, tau_longterm, & 1572 & t2m_month, t2m_week, tsoil_month, soilhum_month, &1564 & t2m_month, t2m_week, tsoil_month, soilhum_month, & 1573 1565 & npp_longterm, turnover_longterm, gpp_week, & 1574 1566 & gdd_m5_dormance, gdd_midwinter, ncd_dormance, ngd_minus5, & … … 1592 1584 & clay, herbivores, & 1593 1585 & tsurf_daily, tsoil_daily, t2m_daily, t2m_min_daily, & 1594 & litterhum_daily, soilhum_daily, 1586 & litterhum_daily, soilhum_daily, & 1595 1587 & maxhumrel_lastyear, minhumrel_lastyear, & 1596 1588 & gdd0_lastyear, precip_lastyear, & … … 2021 2013 !_ ================================================================================================================================ 2022 2014 2023 SUBROUTINE stomate_finalize (kjit, kjpindex, index, clay, bulk,assim_param)2015 SUBROUTINE stomate_finalize (kjit, kjpindex, index, clay, assim_param) 2024 2016 2025 2017 IMPLICIT NONE … … 2031 2023 INTEGER(i_std),DIMENSION(kjpindex),INTENT(in) :: index !! Indices of the terrestrial pixels only (unitless) 2032 2024 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)2034 2025 REAL(r_std),DIMENSION(kjpindex,nvm,npco2),INTENT(in) :: assim_param !! min+max+opt temperatures (K) & vmax for photosynthesis 2035 2026 … … 2118 2109 dt_days, days_since_beg, & 2119 2110 ind, adapted, regenerate, & 2120 humrel_daily, gdd_init_date, litterhum_daily, &2111 humrel_daily, gdd_init_date, litterhum_daily, & 2121 2112 t2m_daily, t2m_min_daily, tsurf_daily, tsoil_daily, & 2122 2113 soilhum_daily, precip_daily, & -
branches/ORCHIDEE_2_2/ORCHIDEE/src_stomate/stomate_io.f90
r8418 r8423 440 440 & .TRUE., litterhum_daily, 'gather', nbp_glo, index_g) 441 441 IF (ALL(litterhum_daily(:) == val_exp)) litterhum_daily(:) = zero 442 443 442 !- 444 443 t2m_daily(:) = val_exp … … 472 471 & .TRUE., soilhum_daily, 'gather', nbp_glo, index_g) 473 472 IF (ALL(soilhum_daily(:,:) == val_exp)) soilhum_daily(:,:) = zero 474 475 473 !- 476 474 precip_daily(:) = val_exp … … 606 604 & .TRUE., soilhum_month, 'gather', nbp_glo, index_g) 607 605 IF (ALL(soilhum_month(:,:) == val_exp)) soilhum_month(:,:) = zero 608 609 610 606 !- 611 607 ! 6 fire probability … … 997 993 CALL restget_p (rest_id_stomate, var_name, nbp_glo, nlitt , 1, itime, & 998 994 & .TRUE., litter(:,:,m,l,k), 'gather', nbp_glo, index_g) 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 995 IF (ALL(litter(:,:,m,l,k) == val_exp)) litter(:,:,m,l,k) = zero 1004 996 ENDDO 1005 997 ENDDO … … 1021 1013 CALL restget_p (rest_id_stomate, var_name, nbp_glo, ncarb , 1, itime, & 1022 1014 & .TRUE., carbon(:,:,m), 'gather', nbp_glo, index_g) 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 1015 IF (ALL(carbon(:,:,m) == val_exp)) carbon(:,:,m) = zero 1028 1016 ENDDO 1029 1017 !- … … 1701 1689 var_name = 't2m_daily' 1702 1690 CALL restput_p (rest_id_stomate, var_name, nbp_glo, 1, 1, itime, & 1703 1691 & t2m_daily, 'scatter', nbp_glo, index_g) 1704 1692 !- 1705 1693 var_name = 't2m_min_daily' 1706 1694 CALL restput_p (rest_id_stomate, var_name, nbp_glo, 1, 1, itime, & 1707 1695 & t2m_min_daily, 'scatter', nbp_glo, index_g) 1708 1696 !- 1709 1697 var_name = 'tsurf_daily' 1710 1698 CALL restput_p (rest_id_stomate, var_name, nbp_glo, 1, 1, itime, & 1711 1699 & tsurf_daily, 'scatter', nbp_glo, index_g) 1712 1700 !- 1713 1701 var_name = 'tsoil_daily' 1714 1702 CALL restput_p (rest_id_stomate, var_name, nbp_glo, nslm, 1, itime, & 1715 1703 & tsoil_daily, 'scatter', nbp_glo, index_g) 1716 1704 !- 1717 1705 var_name = 'soilhum_daily' -
branches/ORCHIDEE_2_2/ORCHIDEE/src_stomate/stomate_litter.f90
r8418 r8423 26 26 27 27 ! modules used: 28 USE xios_orchidee 28 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, &183 182 litterpart, litter, dead_leaves, lignin_struc, & 184 183 deadleaf_cover, resp_hetero_litter, & 185 184 soilcarbon_input, control_temp, control_moist, & 186 MatrixA, VectorB , bulk, clay, carbon)185 MatrixA, VectorB) 187 186 188 187 !! 0. Variable and parameter declaration … … 202 201 REAL(r_std), DIMENSION(npts,nslm), INTENT(in) :: soilhum !! Daily soil humidity of each soil layer 203 202 !! (unitless) 204 REAL(r_std), DIMENSION(npts,nslm), INTENT(in) :: soilhumSAT !! Daily soil humidity of each soil layer205 !! (unitless)206 203 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})$\f211 204 212 205 !! 0.2 Output variables … … 268 261 REAL(r_std), DIMENSION(npts) :: soilhum_decomp !! Humidity used for decompostition in soil 269 262 !! (unitless) 270 REAL(r_std), DIMENSION(npts) :: soilhumSAT_decomp !! Humidity used for decompostition in soil271 !! (unitless) for Moyano et al 2012272 263 REAL(r_std), DIMENSION(npts) :: fd !! Fraction of structural or metabolic litter 273 264 !! decomposed (unitless) … … 594 585 595 586 !! 4.1 above the ground: litter humidity 596 597 IF (ok_moyano_soilhumsat)THEN !!ok_moyano_soilhumsat is true 598 control_moist(:,iabove) = control_moist_func (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,clay,bulk,carbon, litter, litterhum, veget_cov_max) 601 ENDIF 602 603 CALL xios_orchidee_send_field("ControlMoistLitter",control_moist(:,iabove)) 604 CALL xios_orchidee_send_field("litterhumSAT",litterhumSAT(:)) 587 control_moist(:,iabove) = control_moist_func (npts, litterhum) 588 605 589 ! 606 590 !! 4.2 below: convolution of humidity and decomposer profiles … … 612 596 !! 4.2.2 integrate over the nslm levels 613 597 soilhum_decomp(:) = zero 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 (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,clay,bulk,carbon, litter, soilhum_decomp,veget_cov_max) 632 ENDIF 633 634 CALL xios_orchidee_send_field("ControlMoistSoil",control_moist(:,ibelow)) 635 CALL xios_orchidee_send_field("soilhumSAT",soilhumSAT_decomp(:)) 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) 636 608 637 609 !! 5. fluxes from litter to carbon pools and respiration … … 906 878 !_ ================================================================================================================================ 907 879 908 FUNCTION control_moist_func (npts, clay,bulk,carbon,litter,moist_in,veget_cov_max) RESULT (moistfunc_result)880 FUNCTION control_moist_func (npts, moist_in) RESULT (moistfunc_result) 909 881 910 882 !! 0. Variable and parameter declaration 911 883 912 884 !! 0.1 Input variables 913 INTEGER(i_std) :: k,m,n,i,l,e !!indices885 914 886 INTEGER(i_std), INTENT(in) :: npts !! Domain size - number of grid pixel (unitless) 915 887 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 888 924 889 !! 0.2 Output variables 925 890 … … 929 894 930 895 !! 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 IF (ok_moyano_soilhumsat)THEN !!ok_moyano_soilhumsat is true 949 950 !! In ok_moyano_soilhumsat total soil carbon per grid cells need to be computed and 951 !! converted from gC/m2soil to gC/gsoil 952 carbon_gCm2s(:)=zero 953 carbon_gCgs(:)=zero 954 DO n = 1, npts ! loop over grids 955 DO m = 1, nvm ! Loop over # PFTs 956 DO k = 1, ncarb ! Loop over carbon pools 957 carbon_gCm2s(n)=carbon_gCm2s(n)+carbon(n,k,m)*veget_cov_max(n,m) 958 ENDDO 959 ENDDO 960 ENDDO 961 962 IF (ok_orga) THEN 963 DO n = 1, npts ! loop over grids 964 carbon_gCgs(n)=carbon_gCm2s(n) / (bulk(n) * 1E3 * soilheight) 965 carbon_gCgs(n)= MAX(min_carbon_moyano,MIN(max_carbon_moyano,carbon_gCgs(n))) 966 clay_Moyano(n) = MAX(min_clay_moyano,MIN(max_clay_moyano,clay(n))) 967 ENDDO 968 969 !!1. compute Max(Prsr(M[0,0.01,1])); Prsr:Proportional Response of Soil 970 !!Respiration (PRSR) and Soil respiration(SR): SR(M)=SRo x Prsr(M)/Max(Prsr(M[0,0.01,1])) 971 !! M:soilhumSAT, SRo=1 (arbitrary) 972 DO n = 1,npts 973 Mint(:)= zero 974 SRmax = zero 975 DO i = 1,101 976 Mint(i)=0.01*(i-1) 977 IF (carbon_gCgs(n) .LT. limit_carbon_orga) THEN 978 PRSR(n,i) = beta1 * Mint(i) + beta2 * Mint(i)**2.0 + beta3 * Mint(i)**3.0 & 979 & + beta4 * clay_Moyano(n) + beta5 * clay_Moyano(n) * Mint(i) & 980 & + beta6 * carbon_gCgs(n) + intercept 981 ELSE 982 PRSR(n,i) = beta1_orga * Mint(i) + beta2_orga * Mint(i)**2.0 + & 983 & beta3_orga * Mint(i)**3.0 + intercept_orga 984 ENDIF 985 986 IF (i.LT.2) THEN 987 SR(n,i) = PRSR(n,i) 988 SRmax = MAX(SR(n,i),SRmax) 989 ELSE 990 SR(n,i) = PRSR(n,i) * SR(n,i-1) 991 SRmax = MAX(SR(n,i),SRmax) 992 ENDIF 993 ENDDO 994 SRnorm(n,:)= SRo * SR(n,:)/SRmax 995 ENDDO 996 ELSE 997 DO n = 1, npts ! loop over grids 998 carbon_gCgs(n)=carbon_gCm2s(n) / (bulk(n) * 1E3 * soilheight) 999 carbon_gCgs(n)= MAX(min_carbon_moyano,MIN(limit_carbon_orga,carbon_gCgs(n))) 1000 clay_Moyano(n) = MAX(min_clay_moyano,MIN(max_clay_moyano,clay(n))) 1001 ENDDO 1002 1003 !!1. compute Max(Prsr(M[0,0.01,1])); Prsr:Proportional Response of Soil 1004 !!Respiration (PRSR) and Soil respiration(SR): SR(M)=SRo x 1005 !Prsr(M)/Max(Prsr(M[0,0.01,1])) 1006 !! M:soilhumSAT, SRo=1 (arbitrary) 1007 DO n = 1,npts 1008 Mint(:)= zero 1009 SRmax = zero 1010 DO i = 1,101 1011 Mint(i)=0.01*(i-1) 1012 PRSR(n,i) = beta1 * Mint(i) + beta2 * Mint(i)**2.0 + beta3 * Mint(i)**3.0 & 1013 & + beta4 * clay_Moyano(n) + beta5 * clay_Moyano(n) * Mint(i) & 1014 & + beta6 * carbon_gCgs(n) + intercept 1015 1016 IF (i.LT.2) THEN 1017 SR(n,i) = PRSR(n,i) 1018 SRmax = MAX(SR(n,i),SRmax) 1019 ELSE 1020 SR(n,i) = PRSR(n,i) * SR(n,i-1) 1021 SRmax = MAX(SR(n,i),SRmax) 1022 ENDIF 1023 ENDDO 1024 SRnorm(n,:)= SRo * SR(n,:)/SRmax 1025 ENDDO 1026 ENDIF 1027 1028 !!2. Rescale SR values between 0 and 1 and defined SR for moist_in 1029 DO n = 1,npts 1030 ind = 1.0 1031 indmc = zero 1032 moist_round = zero 1033 SRscmax = zero 1034 SRsc(n,:) = zero 1035 SRmin = 1.0 1036 1037 ind = MAXLOC(SRnorm(n,:),1) 1038 DO i = 1,ind 1039 SRmin = MIN(SRnorm(n,i),SRmin) 1040 ENDDO 1041 DO i = 1,101 1042 SRsc(n,i) = SRnorm(n,i)- SRmin 1043 IF (i.LE.ind)THEN 1044 SRscmax = MAX(SRsc(n,i),SRscmax) 1045 ENDIF 1046 ENDDO 1047 SRsc(n,:)=SRsc(n,:)/SRscmax 1048 1049 moist_round=(NINT(moist_in(n)*100.))/100. 1050 indmc=INT(moist_round/0.01) + un 1051 1052 moistfunc_result(n) = SRsc(n,indmc) 1053 moistfunc_result(n) = MAX( moistcontSAT_min, MIN( un, moistfunc_result(n) )) 1054 ENDDO 1055 1056 ELSE !ok_moyano_soilhumsat is false by default 1057 moistfunc_result(:) = -moist_coeff(1) * moist_in(:) * moist_in(:) & 1058 & + moist_coeff(2)* moist_in(:) - moist_coeff(3) 1059 moistfunc_result(:) = MAX( moistcont_min, MIN( un, moistfunc_result(:) )) 1060 ENDIF 896 897 !_ ================================================================================================================================ 898 899 moistfunc_result(:) = -moist_coeff(1) * moist_in(:) * moist_in(:) + moist_coeff(2)* moist_in(:) - moist_coeff(3) 900 moistfunc_result(:) = MAX( moistcont_min, MIN( un, moistfunc_result(:) ) ) 1061 901 1062 902 END FUNCTION control_moist_func
Note: See TracChangeset
for help on using the changeset viewer.