Changeset 5453
- Timestamp:
- Dec 23, 2024, 8:19:39 PM (24 hours ago)
- Location:
- LMDZ6/branches/contrails/libf/phylmd
- Files:
-
- 8 edited
Legend:
- Unmodified
- Added
- Removed
-
LMDZ6/branches/contrails/libf/phylmd/lmdz_aviation.f90
r5452 r5453 7 7 CONTAINS 8 8 9 SUBROUTINE aviation_water_emissions( & 10 klon, klev, dtime, paprs, pplay, temp, qtot, cell_area, & 11 flight_h2o, d_q_avi & 12 ) 13 14 USE lmdz_lscp_ini, ONLY: RD, RG 15 16 IMPLICIT NONE 17 18 INTEGER, INTENT(IN) :: klon, klev ! number of horizontal grid points and vertical levels 19 REAL, INTENT(IN) :: dtime ! time step [s] 20 REAL, DIMENSION(klon,klev+1), INTENT(IN) :: paprs ! inter-layer pressure [Pa] 21 REAL, DIMENSION(klon,klev), INTENT(IN) :: pplay ! mid-layer pressure [Pa] 22 REAL, DIMENSION(klon,klev), INTENT(IN) :: temp ! temperature (K) 23 REAL, DIMENSION(klon,klev), INTENT(IN) :: qtot ! total specific humidity (in vapor phase) [kg/kg] 24 REAL, DIMENSION(klon), INTENT(IN) :: cell_area ! area of each cell [m2] 25 REAL, DIMENSION(klon,klev), INTENT(IN) :: flight_h2o ! aviation H2O emitted within the mesh [kgH2O/s/mesh] 26 REAL, DIMENSION(klon,klev), INTENT(OUT) :: d_q_avi ! water vapor tendency from aviation [kg/kg] 27 ! Local 28 INTEGER :: i, k 29 REAL :: rho, rhodz, dz, M_cell 30 31 DO i=1, klon 32 DO k=1, klev 33 !--Dry density [kg/m3] 34 rho = pplay(i,k) / temp(i,k) / RD 35 !--Dry air mass [kg/m2] 36 rhodz = ( paprs(i,k) - paprs(i,k+1) ) / RG 37 !--Cell thickness [m] 38 dz = rhodz / rho 39 !--Cell dry air mass [kg] 40 M_cell = rhodz * cell_area(i) 41 42 !--q is the specific humidity (kg/kg humid air) hence the complicated equation to update q 43 ! qnew = ( m_humid_air * qold + dm_H2O ) / ( m_humid_air + dm_H2O ) 44 ! = ( m_dry_air * qold + dm_h2O * (1-qold) ) / (m_dry_air + dm_H2O * (1-qold) ) 45 !--The equation is derived by writing m_humid_air = m_dry_air + m_H2O = m_dry_air / (1-q) 46 !--flight_h2O is in kg H2O / s / mesh 47 48 !d_q_avi(i,k) = ( M_cell * qtot(i,k) + flight_h2o(i,k) * dtime * ( 1. - qtot(i,k) ) ) & 49 ! / ( M_cell + flight_h2o(i,k) * dtime * ( 1. - qtot(i,k) ) ) & 50 ! - qtot(i,k) 51 !--Same formula, more computationally effective but less readable 52 d_q_avi(i,k) = flight_h2o(i,k) * ( 1. - qtot(i,k) ) & 53 / ( M_cell / dtime / ( 1. - qtot(i,k) ) + flight_h2o(i,k) ) 54 ENDDO 55 ENDDO 56 57 END SUBROUTINE aviation_water_emissions 58 9 59 10 60 !********************************************************************************** 11 61 SUBROUTINE contrails_formation_evolution( & 12 62 dtime, pplay, temp, qsat, qsatl, gamma_cond, rcont_seri, flight_dist, & 13 cldfra, qvc, V_cell, M_cell, pdf_loc, pdf_scale, pdf_alpha, &63 cldfra, qvc, dz, V_cell, pdf_loc, pdf_scale, pdf_alpha, & 14 64 Tcritcont, qcritcont, potcontfraP, potcontfraNP, contfra, & 15 65 dcf_avi, dqvc_avi, dqi_avi & … … 35 85 REAL, INTENT(IN) :: gamma_cond ! condensation threshold w.r.t. qsat [-] 36 86 REAL, INTENT(IN) :: rcont_seri ! ratio of contrails fraction to total cloud fraction [-] 37 REAL, INTENT(IN) :: flight_dist ! 87 REAL, INTENT(IN) :: flight_dist ! aviation distance flown within the mesh [m/s/mesh] 38 88 REAL, INTENT(IN) :: cldfra ! cloud fraction [-] 39 89 REAL, INTENT(IN) :: qvc ! gridbox-mean vapor in the cloud [kg/kg] 90 REAL, INTENT(IN) :: dz ! cell width [m] 40 91 REAL, INTENT(IN) :: V_cell ! cell volume [m3] 41 REAL, INTENT(IN) :: M_cell ! cell mass [kg]42 92 REAL, INTENT(IN) :: pdf_loc ! location parameter of the clear sky PDF [%] 43 93 REAL, INTENT(IN) :: pdf_scale ! scale parameter of the clear sky PDF [%] … … 46 96 ! Output 47 97 ! 48 REAL, INTENT(OUT) :: Tcritcont ! 49 REAL, INTENT(OUT) :: qcritcont ! 50 REAL, INTENT(OUT) :: potcontfraP ! 51 REAL, INTENT(OUT) :: potcontfraNP ! 52 REAL, INTENT(OUT) :: contfra ! 53 REAL, INTENT(OUT) :: dcf_avi ! 54 REAL, INTENT(OUT) :: dqvc_avi ! 55 REAL, INTENT(OUT) :: dqi_avi ! 98 REAL, INTENT(OUT) :: Tcritcont ! critical temperature for contrail formation [K] 99 REAL, INTENT(OUT) :: qcritcont ! critical specific humidity for contrail formation [kg/kg] 100 REAL, INTENT(OUT) :: potcontfraP ! potential persistent contrail fraction [-] 101 REAL, INTENT(OUT) :: potcontfraNP ! potential non-persistent contrail fraction [-] 102 REAL, INTENT(OUT) :: contfra ! contrail fraction [-] 103 REAL, INTENT(OUT) :: dcf_avi ! cloud fraction tendency because of aviation [s-1] 104 REAL, INTENT(OUT) :: dqvc_avi ! specific ice content tendency because of aviation [kg/kg/s] 105 REAL, INTENT(OUT) :: dqi_avi ! specific cloud water vapor tendency because of aviation [kg/kg/s] 56 106 ! 57 107 ! Local … … 65 115 REAL :: qpotcontP 66 116 ! 67 ! 117 ! for new contrail formation 68 118 REAL :: contrail_cross_section, contfra_new 69 119 70 120 qzero(:) = 0. 71 72 !--more local variables for diagnostics73 !--values from Schumann, Meteorol Zeitschrift, 199674 !--EiH2O = 1.25 / 2.24 / 8.94 kg H2O / kg fuel for kerosene / methane / dihydrogen75 !--Qheat = 43. / 50. / 120. MJ / kg fuel for kerosene / methane / dihydrogen76 !REAL, PARAMETER :: EiH2O=1.25 !--emission index of water vapour for kerosene (kg kg-1)77 !REAL, PARAMETER :: Qheat=43.E6 !--specific combustion heat for kerosene (J kg-1)78 !REAL, PARAMETER :: eta=0.3 !--average propulsion efficiency of the aircraft79 !--Gcontr is the slope of the mean phase trajectory in the turbulent exhaust field on an absolute80 !--temperature versus water vapor partial pressure diagram. G has the unit of Pa K−1. Rap et al JGR 2010.81 !--Tcontr = critical temperature for contrail formation (T_LM in Schumann 1996, Eq 31 in appendix 2)82 121 83 122 !--------------------------------- … … 86 125 !--Revised by Schumann (1996) and Rap et al. (2010) 87 126 127 !--Gcont is the slope of the mean phase trajectory in the turbulent exhaust field on an absolute 128 !--in Pa / K. See Rap et al. (2010) in JGR. 88 129 !--kg H2O/kg fuel * J kg air-1 K-1 * Pa / (kg H2O / kg air * J kg fuel-1) 89 !--in Pa / K90 130 Gcont = EI_H2O_aviation * RCPD * pplay & 91 131 / ( EPS_W * qheat_fuel_aviation * ( 1. - prop_efficiency_aviation ) ) 92 !--critical T_LM below which no liquid contrail can form in exhaust 132 !--critical temperature below which no liquid contrail can form in exhaust 133 !--noted T_LM in Schumann (1996), their Eq. 31 in Appendix 2 93 134 !--in Kelvins 94 135 Tcritcont = 226.69 + 9.43 * LOG( MAX(Gcont, 0.1) - 0.053 ) & … … 105 146 106 147 107 IF ( temp .LT. Tcritcont ) THEN !--contrail formation is possible148 IF ( ( ( 1. - cldfra ) .GT. eps ) .AND. ( temp .LT. Tcritcont ) ) THEN 108 149 109 150 pdf_x = qcritcont / qsatl * 100. … … 132 173 133 174 potcontfraNP = MAX(0., pdf_fra_above_qcritcont - pdf_fra_above_qsat) 134 potcontfraP = M IN(pdf_fra_above_qsat - pdf_fra_above_qnuc, &135 pdf_fra_above_qcritcont - pdf_fra_above_qnuc) 136 qpotcontP = M IN(pdf_q_above_qsat - pdf_q_above_qnuc, &137 pdf_q_above_qcritcont - pdf_q_above_qnuc) 175 potcontfraP = MAX(0., MIN(pdf_fra_above_qsat - pdf_fra_above_qnuc, & 176 pdf_fra_above_qcritcont - pdf_fra_above_qnuc)) 177 qpotcontP = MAX(0., MIN(pdf_q_above_qsat - pdf_q_above_qnuc, & 178 pdf_q_above_qcritcont - pdf_q_above_qnuc)) 138 179 139 180 ELSE … … 143 184 144 185 ENDIF ! temp .LT. Tcritcont 145 146 147 ! Ajout des émissions de H2O dues à l'aviation148 ! q is the specific humidity (kg/kg humid air) hence the complicated equation to update q149 ! qnew = ( m_humid_air * qold + dm_H2O ) / ( m_humid_air + dm_H2O )150 ! = ( m_dry_air * qold + dm_h2O * (1-qold) ) / (m_dry_air + dm_H2O * (1-qold) )151 ! The equation is derived by writing m_humid_air = m_dry_air + m_H2O = m_dry_air / (1-q)152 ! flight_h2O is in kg H2O / s / cell153 !154 !IF (ok_plane_h2o) THEN155 ! q = ( M_cell*q + flight_h2o(i,k)*dtime*(1.-q) ) / (M_cell + flight_h2o(i,k)*dtime*(1.-q) )156 !ENDIF157 186 158 187 !--Convert existing contrail fraction into "natural" cirrus cloud fraction … … 165 194 dqvc_avi = 0. 166 195 IF ( potcontfraP .GT. eps ) THEN 167 contrail_cross_section = CONTRAIL_CROSS_SECTION_ONERA( )196 contrail_cross_section = CONTRAIL_CROSS_SECTION_ONERA(dz) 168 197 contfra_new = MIN(1., flight_dist * dtime * contrail_cross_section / V_cell) 169 198 dcf_avi = potcontfraP * contfra_new … … 565 594 566 595 !********************************************************************************** 567 FUNCTION contrail_cross_section_onera() 596 FUNCTION contrail_cross_section_onera(dz) 597 598 USE lmdz_lscp_init, ONLY: initial_width_contrails 568 599 569 600 IMPLICIT NONE 570 601 571 ! input 572 ! output 602 ! 603 ! Input 604 ! 605 REAL :: dz ! cell width [m] 606 ! 607 ! Output 608 ! 573 609 REAL :: contrail_cross_section_onera ! [m2] 574 ! local 575 576 contrail_cross_section_onera = 200. * 200. 610 ! 611 ! Local 612 ! 613 614 contrail_cross_section_onera = initial_width_contrails * dz 577 615 578 616 END FUNCTION contrail_cross_section_onera 617 618 619 SUBROUTINE read_aviation_emissions( & 620 klon, klev, latitude_deg, longitude_deg, pplay, & 621 flight_dist, flight_h2o & 622 ) 623 624 IMPLICIT NONE 625 ! 626 ! Input 627 ! 628 INTEGER, INTENT(IN) :: klon, klev ! number of horizontal grid points and vertical levels 629 REAL, INTENT(IN), DIMENSION(klon) :: latitude_deg ! latitude of the grid points [deg] 630 REAL, INTENT(IN), DIMENSION(klon) :: longitude_deg ! longitude of the grid points [deg] 631 REAL, INTENT(IN), DIMENSION(klon,klev) :: pplay ! layer pressure [Pa] 632 ! 633 ! Output 634 ! 635 REAL, INTENT(OUT), DIMENSION(klon,klev) :: flight_dist ! aviation distance flown within the mesh [m/s/mesh] 636 REAL, INTENT(OUT), DIMENSION(klon,klev) :: flight_h2o ! aviation H2O emitted within the mesh [kgH2O/s/mesh] 637 ! 638 ! Local 639 ! 640 INTEGER :: i, k 641 642 !--Initialisation 643 flight_dist(:,:) = 0. 644 flight_h2o(:,:) = 0. 645 646 !DO i=1, klon 647 ! IF ( ( latitude_deg(i) .GE. 42. ) .AND. ( latitude_deg(i) .LE. 48. ) ) THEN 648 ! flight_dist(i,14) = 50000. !--5000 m of flight/second in grid cell x 10 scaling 649 ! flight_h2o(i,14) = 100. !--10 kgH2O/second in grid cell x 10 scaling 650 ! ENDIF 651 !ENDDO 652 653 END SUBROUTINE read_aviation_emissions 579 654 580 655 END MODULE lmdz_aviation … … 754 829 !! 755 830 !END SUBROUTINE airplane 756 !757 !!********************************************************************758 !! simple routine to initialise flight_m and test a flight corridor759 !!--Olivier Boucher - 2021760 !!761 !SUBROUTINE flight_init()762 ! USE dimphy763 ! USE geometry_mod, ONLY: cell_area, latitude_deg, longitude_deg764 ! IMPLICIT NONE765 ! INTEGER :: i766 !767 ! ALLOCATE(flight_m(klon,klev))768 ! ALLOCATE(flight_h2o(klon,klev))769 ! !770 ! flight_m(:,:) = 0.0 !--initialisation771 ! flight_h2o(:,:) = 0.0 !--initialisation772 ! !773 ! DO i=1, klon774 ! IF (latitude_deg(i).GE.42.0.AND.latitude_deg(i).LE.48.0) THEN775 ! flight_m(i,38) = 50000.0 !--5000 m of flight/second in grid cell x 10 scaling776 ! ENDIF777 ! ENDDO778 !779 ! RETURN780 !END SUBROUTINE flight_init781 !782 ! !--add a source of cirrus from aviation contrails783 ! IF (ok_plane_contrail) THEN784 ! drneb_avi(i,k) = rnebss*flight_m(i,k)*contrail_cross_section/V_cell !--tendency rneb due to aviation [s-1]785 ! drneb_avi(i,k) = MIN(drneb_avi(i,k), rnebss/dtime) !--majoration786 ! dqss_avi = qss*drneb_avi(i,k)/MAX(eps,rnebss) !--tendency q aviation [kg kg-1 s-1]787 ! rneb = rneb + drneb_avi(i,k)*dtime !--add tendency to rneb788 ! qcld = qcld + dqss_avi*dtime !--add tendency to qcld789 ! rnebss = rnebss - drneb_avi(i,k)*dtime !--add tendency to rnebss790 ! qss = qss - dqss_avi*dtime !--add tendency to qss791 ! ELSE792 ! drneb_avi(i,k)=0.0793 ! ENDIF794 !795 ! RETURN796 !END SUBROUTINE ice_sursat -
LMDZ6/branches/contrails/libf/phylmd/lmdz_lscp.f90
r5452 r5453 175 175 !-------------------------------------------------- 176 176 REAL, DIMENSION(klon,klev), INTENT(INOUT):: rcont_seri ! ratio of contrails fraction to total cloud fraction [-] 177 REAL, DIMENSION(klon,klev), INTENT(IN) :: flight_dist ! Aviation distance flown within the mesh [m/s/mesh]178 REAL, DIMENSION(klon,klev), INTENT(IN) :: flight_h2o ! Aviation H2O emitted within the mesh [kgH2O/s/mesh]177 REAL, DIMENSION(klon,klev), INTENT(IN) :: flight_dist ! aviation distance flown within the mesh [m/s/mesh] 178 REAL, DIMENSION(klon,klev), INTENT(IN) :: flight_h2o ! aviation H2O emitted within the mesh [kgH2O/s/mesh] 179 179 180 180 ! OUTPUT variables … … 1066 1066 rvc_seri(i,k) = qvc(i) / zq(i) 1067 1067 ELSE 1068 rvc_seri(i,k) = min_ratio1068 rvc_seri(i,k) = 0. 1069 1069 ENDIF 1070 1070 !--The MIN barrier is NEEDED because of: … … 1077 1077 rcont_seri(i,k) = contfra(i) / rneb(i,k) 1078 1078 ELSE 1079 rcont_seri(i,k) = min_ratio1079 rcont_seri(i,k) = 0. 1080 1080 ENDIF 1081 1081 !--This barrier should never be activated -
LMDZ6/branches/contrails/libf/phylmd/lmdz_lscp_condensation.f90
r5452 r5453 157 157 ! 158 158 REAL, INTENT(INOUT), DIMENSION(klon) :: rcont_seri ! ratio of contrails fraction to total cloud fraction [-] 159 REAL, INTENT(IN), DIMENSION(klon) :: flight_dist ! 160 REAL, INTENT(IN), DIMENSION(klon) :: flight_h2o ! 159 REAL, INTENT(IN), DIMENSION(klon) :: flight_dist ! aviation distance flown within the mesh [m/s/mesh] 160 REAL, INTENT(IN), DIMENSION(klon) :: flight_h2o ! aviation H2O emitted within the mesh [kgH2O/s/mesh] 161 161 ! 162 162 ! Output … … 238 238 ! 239 239 ! for cell properties 240 REAL :: rho, rhodz, dz 241 REAL :: V_cell, M_cell 240 REAL :: rho, rhodz, dz, V_cell 242 241 243 242 qzero(:) = 0. … … 336 335 !--Cell volume [m3] 337 336 V_cell = dz * cell_area(i) 338 !--Cell dry air mass [kg]339 M_cell = rhodz * cell_area(i)340 337 341 338 … … 504 501 ENDIF 505 502 pdf_e3 = k0_pdf_lscp + kappa_pdf_lscp * MAX( temp_nowater - temp(i), 0. ) 506 pdf_alpha = EXP( rhl_clr / 100. ) * pdf_e3 507 pdf_alpha = MIN(10., pdf_alpha) 503 pdf_alpha = EXP( MIN(1000., rhl_clr) / 100. ) * pdf_e3 508 504 509 505 IF ( ok_warm_cloud ) THEN … … 790 786 dtime, pplay(i), temp(i), qsat(i), qsatl(i), gamma_cond(i), & 791 787 rcont_seri(i), flight_dist(i), cldfra(i), qvc(i), & 792 V_cell, M_cell, pdf_loc, pdf_scale, pdf_alpha, &788 dz, V_cell, pdf_loc, pdf_scale, pdf_alpha, & 793 789 Tcritcont(i), qcritcont(i), potcontfraP(i), potcontfraNP(i), contfra(i), & 794 790 dcf_avi(i), dqvc_avi(i), dqi_avi(i) & -
LMDZ6/branches/contrails/libf/phylmd/lmdz_lscp_ini.f90
r5452 r5453 236 236 REAL, SAVE, PROTECTED :: linear_contrails_lifetime=10800. ! [s] timescale of the lifetime of linear contrails 237 237 !$OMP THREADPRIVATE(linear_contrails_lifetime) 238 239 REAL, SAVE, PROTECTED :: initial_width_contrails=200. ! [m] initial width of the linear contrails formed 240 !$OMP THREADPRIVATE(initial_width_contrails) 238 241 !--End of the parameters for aviation 239 242 … … 475 478 CALL getin_p('prop_efficiency_aviation',prop_efficiency_aviation) 476 479 CALL getin_p('linear_contrails_lifetime',linear_contrails_lifetime) 480 CALL getin_p('initial_width_contrails',initial_width_contrails) 477 481 478 482 … … 566 570 WRITE(lunout,*) 'lscp_ini, prop_efficiency_aviation:', prop_efficiency_aviation 567 571 WRITE(lunout,*) 'lscp_ini, linear_contrails_lifetime:', linear_contrails_lifetime 572 WRITE(lunout,*) 'lscp_ini, initial_width_contrails:', initial_width_contrails 568 573 569 574 -
LMDZ6/branches/contrails/libf/phylmd/phys_local_var_mod.F90
r5452 r5453 665 665 666 666 !-- LSCP - aviation and contrails variables 667 REAL, SAVE, ALLOCATABLE :: d_q_avi(:,:) 668 !$OMP THREADPRIVATE(d_q_avi) 667 669 REAL, SAVE, ALLOCATABLE :: rcont_seri(:,:), d_rcont_dyn(:,:) 668 670 !$OMP THREADPRIVATE(rcont_seri, d_rcont_dyn) … … 1215 1217 1216 1218 !-- LSCP - aviation and contrails variables 1219 ALLOCATE(d_q_avi(klon,klev)) 1217 1220 ALLOCATE(rcont_seri(klon,klev), d_rcont_dyn(klon,klev)) 1218 1221 ALLOCATE(flight_dist(klon,klev), flight_h2o(klon,klev)) … … 1621 1624 1622 1625 !-- LSCP - aviation and contrails variables 1623 DEALLOCATE( rcont_seri, d_rcont_dyn, flight_dist, flight_h2o)1626 DEALLOCATE(d_q_avi, rcont_seri, d_rcont_dyn, flight_dist, flight_h2o) 1624 1627 DEALLOCATE(Tcritcont, qcritcont, potcontfraP, potcontfraNP) 1625 1628 DEALLOCATE(dcf_avi, dqi_avi, dqvc_avi) -
LMDZ6/branches/contrails/libf/phylmd/phys_output_ctrlout_mod.F90
r5452 r5453 2168 2168 2169 2169 !-- LSCP - aviation variables 2170 TYPE(ctrl_out), SAVE :: o_dqavi = ctrl_out((/ 11, 11, 11, 11, 11, 11, 11, 11, 11, 11/),& 2171 'dqavi', 'Water vapor emissions from aviation tendency', 'kg/kg/s', (/ ('',i=1,10) /)) 2172 TYPE(ctrl_out), SAVE :: o_rcontseri = ctrl_out((/ 11, 11, 11, 11, 11, 11, 11, 11, 11, 11/),& 2173 'rcontseri', 'Contrails fraction to total cloud fraction ratio', '-', (/ ('',i=1,10) /)) 2174 TYPE(ctrl_out), SAVE :: o_drcontdyn = ctrl_out((/ 11, 11, 11, 11, 11, 11, 11, 11, 11, 11/),& 2175 'drcontdyn', 'Dynamics contrails fraction to total cloud fraction ratio tendency', 's-1', (/ ('',i=1,10) /)) 2170 2176 TYPE(ctrl_out), SAVE :: o_Tcritcont = ctrl_out((/ 11, 11, 11, 11, 11, 11, 11, 11, 11, 11/),& 2171 2177 'Tcritcont', 'Temperature threshold for contrail formation', 'K', (/ ('',i=1,10) /)) -
LMDZ6/branches/contrails/libf/phylmd/phys_output_write_mod.F90
r5452 r5453 226 226 o_dqvcadj, o_dqvcsub, o_dqvccon, o_dqvcmix, o_qsatl, o_qsati, & 227 227 !-- LSCP - aviation variables 228 o_rcontseri, o_drcontdyn, o_dqavi, & 228 229 o_Tcritcont, o_qcritcont, o_potcontfraP, o_potcontfraNP, & 229 230 o_dcfavi, o_dqiavi, o_dqvcavi, o_flight_dist, o_flight_h2o, & … … 349 350 dqvc_adj, dqvc_sub, dqvc_con, dqvc_mix, & 350 351 qsatliq, qsatice, & 352 rcont_seri, d_rcont_dyn, d_q_avi, & 351 353 Tcritcont, qcritcont, potcontfraP, potcontfraNP, & 352 354 dcf_avi, dqi_avi, dqvc_avi, flight_dist, flight_h2o, & … … 2123 2125 !-- LSCP - aviation variables 2124 2126 IF (ok_plane_contrail) THEN 2127 CALL histwrite_phy(o_rcontseri, rcont_seri) 2128 CALL histwrite_phy(o_drcontdyn, d_rcont_dyn) 2125 2129 CALL histwrite_phy(o_flight_dist, flight_dist) 2126 2130 CALL histwrite_phy(o_Tcritcont, Tcritcont) … … 2134 2138 IF (ok_plane_h2o) THEN 2135 2139 CALL histwrite_phy(o_flight_h2o, flight_h2o) 2140 CALL histwrite_phy(o_dqavi, d_q_avi) 2136 2141 ENDIF 2137 2142 -
LMDZ6/branches/contrails/libf/phylmd/physiq_mod.F90
r5452 r5453 75 75 USE write_field_phy 76 76 use wxios_mod, ONLY: g_ctx, wxios_set_context 77 USE lmdz_aviation, ONLY : read_aviation_emissions, aviation_water_emissions 77 78 USE lmdz_lscp, ONLY : lscp 78 79 USE lmdz_call_cloud_optics_prop, ONLY : call_cloud_optics_prop … … 327 328 dqvc_adj, dqvc_sub, dqvc_con, dqvc_mix, qsatliq, qsatice, & 328 329 !-- LSCP - aviation and contrails variables 329 rcont_seri, d_rcont_dyn, flight_dist, flight_h2o, &330 d_q_avi, rcont_seri, d_rcont_dyn, flight_dist, flight_h2o, & 330 331 Tcritcont, qcritcont, potcontfraP, potcontfraNP, & 331 332 dcf_avi, dqi_avi, dqvc_avi, & … … 3863 3864 ratqs,ratqsc,ratqs_inter_,sigma_qtherm) 3864 3865 3866 !--Read the aviation emissions 3867 IF ( ok_plane_h2o .OR. ok_plane_contrail ) THEN 3868 CALL read_aviation_emissions(klon, klev, latitude_deg, longitude_deg, pplay, & 3869 flight_dist, flight_h2o) 3870 ENDIF 3871 3872 !--Add the water emissions from aviation 3873 IF ( ok_plane_h2o ) THEN 3874 CALL aviation_water_emissions(klon, klev, phys_tstep, paprs, pplay, & 3875 t_seri, q_seri, cell_area, flight_h2o, d_q_avi) 3876 CALL add_phys_tend(du0, dv0, dt0, d_q_avi, dql0, dqi0, dqbs0, paprs, & 3877 'avi', abortphy, flag_inhib_tend, itap, 0) 3878 d_q_avi = d_q_avi / phys_tstep 3879 ENDIF 3880 3865 3881 ! 3866 3882 ! Appeler le processus de condensation a grande echelle … … 3875 3891 3876 3892 IF (ok_new_lscp) THEN 3877 3878 3893 3879 3894 DO k = 1, klev … … 3883 3898 ENDDO 3884 3899 ENDDO 3885 3886 3887 !--mise à jour de flight_m et flight_h2o dans leur module3888 !IF (ok_plane_h2o .OR. ok_plane_contrail) THEN3889 ! CALL airplane(debut,pphis,pplay,paprs,t_seri)3890 !ENDIF3891 3900 3892 3901 CALL lscp(klon,klev,phys_tstep,missing_val,paprs,pplay,omega, &
Note: See TracChangeset
for help on using the changeset viewer.