Changeset 7255 for branches/ORCHIDEE_2_2/ORCHIDEE
- Timestamp:
- 2021-07-21T20:43:52+02:00 (3 years ago)
- Location:
- branches/ORCHIDEE_2_2/ORCHIDEE
- Files:
-
- 5 edited
Legend:
- Unmodified
- Added
- Removed
-
branches/ORCHIDEE_2_2/ORCHIDEE/src_parallel/xios_orchidee.f90
r6151 r7255 418 418 IF (.NOT. ok_freeze_cwrr) THEN 419 419 CALL xios_set_field_attr("profil_froz_hydro",enabled=.FALSE.) 420 CALL xios_set_field_attr("temp_hydro",enabled=.FALSE.)421 420 END IF 422 421 -
branches/ORCHIDEE_2_2/ORCHIDEE/src_sechiba/hydrol.f90
r7239 r7255 415 415 REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:,:,:) :: profil_froz_hydro_ns !! As profil_froz_hydro per soiltile 416 416 !$OMP THREADPRIVATE(profil_froz_hydro_ns) 417 REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:,:) :: temp_hydro !! Temp profile on hydrological levels418 !$OMP THREADPRIVATE(temp_hydro)419 417 420 418 … … 971 969 IF (ok_freeze_cwrr) THEN 972 970 CALL xios_orchidee_send_field("profil_froz_hydro",profil_froz_hydro) 973 CALL xios_orchidee_send_field("temp_hydro",temp_hydro)974 971 END IF 975 972 CALL xios_orchidee_send_field("profil_froz_hydro_ns", profil_froz_hydro_ns) … … 1156 1153 IF (ok_freeze_cwrr) THEN 1157 1154 CALL histwrite_p(hist_id, 'profil_froz_hydro', kjit,profil_froz_hydro , kjpindex*nslm, indexlayer) 1158 1159 CALL histwrite_p(hist_id, 'temp_hydro', kjit,temp_hydro , kjpindex*nslm, indexlayer)1160 1155 ENDIF 1161 1156 CALL histwrite_p(hist_id, 'kk_moy', kjit, kk_moy,kjpindex*nslm, indexlayer) ! averaged over soiltiles … … 1761 1756 IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable profil_froz_hydrol','','') 1762 1757 profil_froz_hydro(:,:) = zero 1763 1764 ALLOCATE (temp_hydro(kjpindex, nslm),stat=ier)1765 IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable temp_hydro','','')1766 temp_hydro(:,:) = 280.1767 1758 ENDIF 1768 1759 … … 3829 3820 ! 0.1 Calculate the temperature and fozen fraction at the hydrological levels 3830 3821 3831 ! AD16*** This subroutine could probably be simplified massively given 3832 ! that hydro and T share the same vertical discretization 3833 ! Here stempdiag is in from thermosoil and temp_hydro is out 3834 CALL hydrol_calculate_temp_hydro(kjpindex, stempdiag, snow,snowdz) 3835 3836 ! Calculates profil_froz_hydro_ns as a function of temp_hydro, and mc if ok_thermodynamical_freezing 3822 ! Calculates profil_froz_hydro_ns as a function of stempdiag and mc if ok_thermodynamical_freezing 3837 3823 ! These values will be kept till the end of the prognostic loop 3838 3824 DO jst=1,nstm 3839 CALL hydrol_soil_froz(nvan, avan, mcr, mcs, kjpindex,jst,njsc )3825 CALL hydrol_soil_froz(nvan, avan, mcr, mcs, kjpindex,jst,njsc,stempdiag) 3840 3826 ENDDO 3841 3827 … … 3970 3956 !! The conductivity comes from hydrol_soil_coef and relates to the liquid phase only 3971 3957 ! This seems consistent with ok_freeze 3972 CALL hydrol_soil_infilt(ks, nvan, avan, mcr, mcs, mcfc, mcw, kjpindex, jst, njsc, flux_infilt, qinfilt_ns, ru_infilt_ns, &3973 3958 CALL hydrol_soil_infilt(ks, nvan, avan, mcr, mcs, mcfc, mcw, kjpindex, jst, njsc, flux_infilt, stempdiag, & 3959 qinfilt_ns, ru_infilt_ns, check_infilt_ns) 3974 3960 ru_ns(:,jst) = ru_infilt_ns(:,jst) 3975 3961 … … 4646 4632 4647 4633 !! 8.2 Since we estimate bare soile evap for the next time step, we update profil_froz_hydro and mcl 4648 ! (effect of mc only, the change in temp_hydrois neglected)4649 IF ( ok_freeze_cwrr ) CALL hydrol_soil_froz(nvan, avan, mcr, mcs,kjpindex,jst,njsc )4650 4634 ! (effect of mc only, the change in stempdiag is neglected) 4635 IF ( ok_freeze_cwrr ) CALL hydrol_soil_froz(nvan, avan, mcr, mcs,kjpindex,jst,njsc,stempdiag) 4636 DO jsl = 1, nslm 4651 4637 DO ji =1, kjpindex 4652 4638 mcl(ji,jsl,jst)= MIN( mc(ji,jsl,jst), mcr(ji) + & … … 4936 4922 !_ hydrol_soil_infilt 4937 4923 4938 SUBROUTINE hydrol_soil_infilt(ks, nvan, avan, mcr, mcs, mcfc, mcw, kjpindex, ins, njsc, flux_infilt, qinfilt_ns, ru_infilt, check) 4924 SUBROUTINE hydrol_soil_infilt(ks, nvan, avan, mcr, mcs, mcfc, mcw, kjpindex, ins, njsc, flux_infilt, stempdiag, & 4925 qinfilt_ns, ru_infilt, check) 4939 4926 4940 4927 !! 0. Variable and parameter declaration … … 4956 4943 REAL(r_std), DIMENSION (kjpindex), INTENT (in) :: flux_infilt !! Water to infiltrate 4957 4944 !! @tex $(kg m^{-2})$ @endtex 4945 REAL(r_std),DIMENSION (kjpindex,nslm), INTENT (in):: stempdiag !! Diagnostic temp profile from thermosoil 4958 4946 !! 0.2 Output variables 4959 4947 REAL(r_std), DIMENSION(kjpindex,nstm), INTENT(out) :: check !! delta SM - flux (mm/dt_sechiba) … … 5022 5010 5023 5011 IF (ok_freeze_cwrr) THEN 5024 IF ( temp_hydro(ji, jsl) .LT. ZeroCelsius) THEN5012 IF (stempdiag(ji, jsl) .LT. ZeroCelsius) THEN 5025 5013 k_m = k(ji,jsl) 5026 5014 ENDIF … … 5782 5770 !_ hydrol_soil_froz 5783 5771 5784 SUBROUTINE hydrol_soil_froz(nvan, avan, mcr, mcs, kjpindex,ins,njsc )5772 SUBROUTINE hydrol_soil_froz(nvan, avan, mcr, mcs, kjpindex,ins,njsc,stempdiag) 5785 5773 5786 5774 IMPLICIT NONE … … 5798 5786 REAL(r_std),DIMENSION (kjpindex), INTENT (in) :: mcr !! Residual volumetric water content (m^{3} m^{-3}) 5799 5787 REAL(r_std),DIMENSION (kjpindex), INTENT (in) :: mcs !! Saturated volumetric water content (m^{3} m^{-3}) 5788 REAL(r_std),DIMENSION (kjpindex,nslm), INTENT (in):: stempdiag !! Diagnostic temp profile from thermosoil 5800 5789 5801 5790 !! 0.2 Output variables … … 5829 5818 IF ((.NOT. ok_thermodynamical_freezing).OR.(mc(ji,jsl, ins).LT.(mcr(ji)+min_sechiba))) THEN 5830 5819 ! Linear soil freezing or soil moisture below residual 5831 IF ( temp_hydro(ji, jsl).GE.(ZeroCelsius+fr_dT/2.)) THEN5820 IF (stempdiag(ji, jsl).GE.(ZeroCelsius+fr_dT/2.)) THEN 5832 5821 x=1._r_std 5833 ELSE IF ( ( temp_hydro(ji,jsl) .GE. (ZeroCelsius-fr_dT/2.)) .AND. &5834 ( temp_hydro(ji,jsl) .LT. (ZeroCelsius+fr_dT/2.)) ) THEN5835 x=( temp_hydro(ji, jsl)-(ZeroCelsius-fr_dT/2.))/fr_dT5822 ELSE IF ( (stempdiag(ji,jsl) .GE. (ZeroCelsius-fr_dT/2.)) .AND. & 5823 (stempdiag(ji,jsl) .LT. (ZeroCelsius+fr_dT/2.)) ) THEN 5824 x=(stempdiag(ji, jsl)-(ZeroCelsius-fr_dT/2.))/fr_dT 5836 5825 ELSE 5837 5826 x=0._r_std … … 5839 5828 ELSE IF (ok_thermodynamical_freezing) THEN 5840 5829 ! Thermodynamical soil freezing 5841 IF ( temp_hydro(ji, jsl).GE.(ZeroCelsius+fr_dT/2.)) THEN5830 IF (stempdiag(ji, jsl).GE.(ZeroCelsius+fr_dT/2.)) THEN 5842 5831 x=1._r_std 5843 ELSE IF ( ( temp_hydro(ji,jsl) .GE. (ZeroCelsius-fr_dT/2.)) .AND. &5844 ( temp_hydro(ji,jsl) .LT. (ZeroCelsius+fr_dT/2.)) ) THEN5832 ELSE IF ( (stempdiag(ji,jsl) .GE. (ZeroCelsius-fr_dT/2.)) .AND. & 5833 (stempdiag(ji,jsl) .LT. (ZeroCelsius+fr_dT/2.)) ) THEN 5845 5834 ! Factor 2.2 from the PhD of Isabelle Gouttevin 5846 5835 x=MIN(((mcs(ji)-mcr(ji)) & 5847 *((2.2*1000.*avan(ji)*(ZeroCelsius+fr_dT/2.- temp_hydro(ji, jsl)) &5836 *((2.2*1000.*avan(ji)*(ZeroCelsius+fr_dT/2.-stempdiag(ji, jsl)) & 5848 5837 *lhf/ZeroCelsius/10.)**nvan(ji)+1.)**(-m)) / & 5849 5838 (mc(ji,jsl, ins)-mcr(ji)),1._r_std) … … 6645 6634 END SUBROUTINE hydrol_alma 6646 6635 ! 6647 6648 6649 !! ================================================================================================================================6650 !! SUBROUTINE : hydrol_calculate_temp_hydro6651 !!6652 !>\BRIEF Calculate the temperature at hydrological levels6653 !!6654 !! DESCRIPTION : None6655 !!6656 !! RECENT CHANGE(S) : None6657 !!6658 !! MAIN OUTPUT VARIABLE(S) :6659 !!6660 !! REFERENCE(S) :6661 !!6662 !! FLOWCHART : None6663 !! \n6664 !_ ================================================================================================================================6665 6666 6667 SUBROUTINE hydrol_calculate_temp_hydro(kjpindex, stempdiag, snow,snowdz)6668 6669 !! 0.1 Input variables6670 6671 INTEGER(i_std), INTENT(in) :: kjpindex6672 REAL(r_std),DIMENSION (kjpindex,nslm), INTENT (in) :: stempdiag6673 REAL(r_std),DIMENSION (kjpindex), INTENT (in) :: snow6674 REAL(r_std),DIMENSION (kjpindex,nsnow), INTENT (in) :: snowdz6675 6676 6677 !! 0.2 Local variables6678 6679 INTEGER jh, jsl, ji6680 REAL(r_std) :: snow_h6681 REAL(r_std) :: lev_diag, prev_diag, lev_prog, prev_prog6682 REAL(r_std), DIMENSION(nslm,nslm) :: intfactt6683 6684 6685 DO ji=1,kjpindex6686 !The snow pack is above the surface soil in the new snow model.6687 snow_h=06688 6689 intfactt(:,:)=0.6690 prev_diag = snow_h6691 DO jh = 1, nslm6692 IF (jh.EQ.1) THEN6693 lev_diag = zz(2)/1000./2.+snow_h6694 ELSEIF (jh.EQ.nslm) THEN6695 lev_diag = zz(nslm)/1000.+snow_h6696 6697 ELSE6698 lev_diag = zz(jh)/1000. &6699 & +(zz(jh+1)-zz(jh))/1000./2.+snow_h6700 6701 ENDIF6702 prev_prog = 0.06703 DO jsl = 1, nslm6704 lev_prog = diaglev(jsl)6705 IF ((lev_diag.GT.diaglev(nslm).AND. &6706 & prev_diag.LT.diaglev(nslm)-min_sechiba)) THEN6707 lev_diag=diaglev(nslm)6708 ENDIF6709 intfactt(jh,jsl) = MAX(MIN(lev_diag,lev_prog)-MAX(prev_diag, prev_prog),&6710 & 0.0)/(lev_diag-prev_diag)6711 prev_prog = lev_prog6712 ENDDO6713 IF (lev_diag.GT.diaglev(nslm).AND. &6714 & prev_diag.GE.diaglev(nslm)-min_sechiba) intfactt(jh,nslm)=1.6715 prev_diag = lev_diag6716 ENDDO6717 ENDDO6718 6719 temp_hydro(:,:)=0.6720 DO jsl= 1, nslm6721 DO jh= 1, nslm6722 DO ji = 1, kjpindex6723 temp_hydro(ji,jh) = temp_hydro(ji,jh) + stempdiag(ji,jsl)*intfactt(jh,jsl)6724 ENDDO6725 ENDDO6726 ENDDO6727 6728 END SUBROUTINE hydrol_calculate_temp_hydro6729 6730 6636 6731 6637 !! ================================================================================================================================ -
branches/ORCHIDEE_2_2/ORCHIDEE/src_sechiba/ioipslctrl.f90
r6319 r7255 508 508 CALL histdef(hist_id, 'profil_froz_hydro', 'Frozen fraction for each hydrological soil layer', '-', & 509 509 & iim,jjm, hori_id, nslm, 1, nslm, solayax_id, 32, avescatter(1), dt,dw) 510 CALL histdef(hist_id, 'temp_hydro', 'Soil temperature interpolated on hydrological layers', 'K', &511 & iim,jjm, hori_id, nslm, 1, nslm, solayax_id, 32, avescatter(1), dt,dw)512 510 END IF 513 511 … … 1019 1017 ENDDO 1020 1018 1021 CALL histdef(hist_id, 'temp_hydro', 'Soil temperature interpolated on hydrological layers', 'K', &1022 & iim,jjm, hori_id, nslm, 1, nslm, solayax_id, 32, avescatter(1), dt,dw)1023 1019 CALL histdef(hist_id, 'kk_moy', 'Mean hydrological conductivity', 'mm/d', & 1024 1020 & iim,jjm,hori_id, nslm,1,nslm, solayax_id, 32, avescatter(1), dt,dw) -
branches/ORCHIDEE_2_2/ORCHIDEE/src_xml/field_def_orchidee.xml
r6369 r7255 325 325 <field id="ACond" name="ACond" long_name="Aerodynamic conductance" unit="m/s"/> 326 326 <field id="albedo_snow" name="SAlbedo" long_name="Snow albedo" unit="1"/> 327 <field id="temp_hydro" name="temp_hydro" long_name="Temperature profile on hydrological levels" unit="K" grid_ref="grid_nslm"/>328 327 <field id="kk_moy" name="kk_moy" long_name="Mean hydraulic conductivity over soiltiles" unit="10^(-6) m/s" grid_ref="grid_nslm" > this*1000/86400 </field> 329 328 <field id="psi_moy" name="psi_moy" long_name="Mean soil pressure head over soiltiles" unit="m" grid_ref="grid_nslm"/> -
branches/ORCHIDEE_2_2/ORCHIDEE/src_xml/file_def_orchidee.xml
r6369 r7255 168 168 <field field_ref="lwnet" level="5"/> 169 169 <field field_ref="diffevap" level="5"/> 170 <field field_ref="temp_hydro" grid_ref="grid_nslm_out" level="5"/>171 170 <field field_ref="snowmelt" level="5"/> 172 171 <field field_ref="tot_melt" level="5"/> … … 438 437 <field field_ref="maxvegetfrac" grid_ref="grid_nvm_out" level="5"/> 439 438 <field field_ref="nobiofrac" grid_ref="grid_nnobio_out" level="5"/> 440 <field field_ref="temp_hydro" grid_ref="grid_nslm_out" level="5"/>441 439 <!-- level 6 --> 442 440 <field field_ref="humtot" level="6"/>
Note: See TracChangeset
for help on using the changeset viewer.