- Timestamp:
- Jul 15, 2020, 10:14:35 PM (4 years ago)
- File:
-
- 1 edited
Legend:
- Unmodified
- Added
- Removed
-
LMDZ6/branches/Optimisation_LMDZ/libf/phylmd/cv3a_driver.f90
r3760 r3761 1 1 module cv3a_driver_mod 2 implicit none 2 3 contains 3 4 … … 164 165 USE print_control_mod, ONLY: prt_level, lunout 165 166 USE cv3a_compress_mod 166 USE cv3p_mixing_mod, ONLY : cv3p_mixing167 167 USE profiling_physic_mod 168 168 IMPLICIT NONE … … 262 262 ! Local (non compressed) arrays 263 263 INTEGER nk1(len) 264 INTEGER icb1(len)265 264 INTEGER icbs1(len) 266 265 … … 374 373 p1feed1, p2feed1, wght1, & 375 374 wghti1, tnk1, thnk1, qnk1, qsnk1, unk1, vnk1, & 376 cpnk1, hnk1, nk1, icb1, icbmax, iflag1, gznk1, plcl1)375 cpnk1, hnk1, nk1, kbas1, icbmax, iflag1, gznk1, plcl1) 377 376 378 377 ! -------------------------------------------------------------------- … … 386 385 tvp1(:, :) = 0. 387 386 clw1(:, :) = 0. 388 CALL cv3_undilute1(len, nd, t1, qs1, gz1, plcl1, p1, icb1, tnk1, qnk1, & ! nd->na387 CALL cv3_undilute1(len, nd, t1, qs1, gz1, plcl1, p1, kbas1, tnk1, qnk1, & ! nd->na 389 388 gznk1, tp1, tvp1, clw1, icbs1) 390 389 … … 394 393 395 394 call driver_log('cv3_trigger') 396 CALL cv3_trigger(len, nd, icb1, plcl1, p1, th1, tv1, tvp1, thnk1, & ! nd->na395 CALL cv3_trigger(len, nd, kbas1, plcl1, p1, th1, tv1, tvp1, thnk1, & ! nd->na 397 396 pbase1, buoybase1, iflag1, sig1, w01) 398 397 call exit_profile("cv3a_uncompressed") … … 505 504 call add_array_i1(cv3a_compress_list, iflag1, iflag) 506 505 call add_array_i1(cv3a_compress_list, nk1, nk) 507 call add_array_i1(cv3a_compress_list, icb1, icb)506 call add_array_i1(cv3a_compress_list, kbas1, icb) 508 507 call add_array_i1(cv3a_compress_list, icbs1, icbs) 509 508 call add_array_r1(cv3a_compress_list, plcl1, plcl) … … 555 554 call exit_profile("cv3a_compress") 556 555 557 if( timers_first ) then 558 call enter_profile("cv3p_mixing") 559 call exit_profile("cv3p_mixing") 560 call enter_profile("cv3_yield") 561 call exit_profile("cv3_yield") 562 call enter_profile("cv3_tracer") 563 call exit_profile("cv3_tracer") 564 565 timers_first = .false. 566 endif 567 568 call enter_profile("cv3a_compressed") 569 IF (ncum > 0) THEN 570 571 ! ------------------------------------------------------------------- 572 ! --- UNDILUTE (ADIABATIC) UPDRAFT / second part : 573 ! --- FIND THE REST OF THE LIFTED PARCEL TEMPERATURES 574 ! --- & 575 ! --- COMPUTE THE PRECIPITATION EFFICIENCIES AND THE 576 ! --- FRACTION OF PRECIPITATION FALLING OUTSIDE OF CLOUD 577 ! --- & 578 ! --- FIND THE LEVEL OF NEUTRAL BUOYANCY 579 ! ------------------------------------------------------------------- 580 581 call driver_log('cv3_undilute2') 582 CALL cv3_undilute2(nloc, ncum, nd, iflag, icb, icbs, nk, & 583 tnk, qnk, gznk, hnk, t, q, qs, gz, & 584 p, ph, h, tv, lv, lf, pbase, buoybase, plcl, & 585 inb, tp, tvp, clw, hp, ep, sigp, buoy, & 586 frac_a, frac_s, qpreca, qta) 587 588 ! epmax_cape 589 ! on recalcule ep et hp 590 call driver_log('cv3_epmax_cape') 591 call cv3_epmax_fn_cape(nloc, ncum, nd & 592 , ep, hp, icb, inb, clw, nk, t, h, hnk, lv, lf, frac_s & 593 , pbase, p, ph, tv, buoy, sig, w0, iflag & 594 , epmax_diag) 595 596 ! ------------------------------------------------------------------- 597 ! --- MIXING(1) (if iflag_mix .ge. 1) 598 ! ------------------------------------------------------------------- 599 call enter_profile("cv3p_mixing") 600 IF (iflag_mix >= 1) THEN 601 CALL zilch(supmax, nloc*nd) 602 call driver_log('cv3p_mixing') 603 CALL cv3p_mixing(nloc, ncum, nd, nd, ntra, icb, nk, inb, & 604 ph, t, q, qs, u, v, tra, h, lv, lf, frac_s, qta, & 605 unk, vnk, hp, tv, tvp, ep, clw, sig, & 606 ment, qent, hent, uent, vent, nent, & 607 sigij, elij, supmax, ments, qents, traent) 608 ELSE 609 CALL zilch(supmax, nloc*nd) 610 END IF 611 call exit_profile("cv3p_mixing") 612 613 ! ------------------------------------------------------------------- 614 ! --- CLOSURE 615 ! ------------------------------------------------------------------- 616 617 ptop2(:) = 0 618 coef_clos(:) = 1. 619 IF (iflag_clos == 0) THEN 620 call driver_log('cv3_closure') 621 CALL cv3_closure(nloc, ncum, nd, icb, inb, & 622 pbase, p, ph, tv, buoy, & 623 sig, w0, cape, m, iflag) 624 END IF ! iflag_clos==0 625 626 ok_inhib = iflag_mix == 2 627 628 IF (iflag_clos == 1) PRINT *, ' pas d appel cv3p_closure' 629 630 IF (iflag_clos == 2) THEN 631 call driver_log('cv3p1_closure') 632 CALL cv3p1_closure(nloc, ncum, nd, icb, inb, & 633 pbase, plcl, p, ph, tv, tvp, buoy, & 634 supmax, ok_inhib, Ale, Alp, omega, & 635 sig, w0, ptop2, cape, cin, m, iflag, coef_clos, & 636 Plim1, plim2, asupmax, supmax0, & 637 asupmaxmin, cbmf, plfc, wbeff) 638 if (prt_level >= 10) PRINT *, 'cv3p1_closure-> plfc,wbeff ', plfc(1), wbeff(1) 639 END IF ! iflag_clos==2 640 641 IF (iflag_clos == 3) THEN 642 call driver_log('cv3p2_closure') 643 CALL cv3p2_closure(nloc, ncum, nd, icb, inb, & 644 pbase, plcl, p, ph, tv, tvp, buoy, & 645 supmax, ok_inhib, Ale, Alp, omega, & 646 sig, w0, ptop2, cape, cin, m, iflag, coef_clos, & 647 Plim1, plim2, asupmax, supmax0, & 648 asupmaxmin, cbmf, plfc, wbeff) 649 if (prt_level >= 10) PRINT *, 'cv3p2_closure-> plfc,wbeff ', plfc(1), wbeff(1) 650 END IF ! iflag_clos==3 651 652 ! ------------------------------------------------------------------- 653 ! --- MIXING(2) 654 ! ------------------------------------------------------------------- 655 656 IF (iflag_mix == 0) THEN 657 call driver_log('cv3_mixing') 658 CALL cv3_mixing(nloc, ncum, nd, nd, ntra, icb, nk, inb, & ! na->nd 659 ph, t, q, qs, u, v, tra, h, lv, lf, frac_s, qnk, & 660 unk, vnk, hp, tv, tvp, ep, clw, m, sig, & 661 ment, qent, uent, vent, nent, sigij, elij, ments, qents, traent) 662 CALL zilch(hent, nloc*nd*nd) 663 ELSE 664 mm(:, :) = m(:, :) 665 CALL cv3_mixscale(nloc, ncum, nd, ment, mm) 666 IF (debut) PRINT *, ' cv3_mixscale-> ' 667 END IF 668 669 IF (debut) PRINT *, ' cv_mixing ->' 670 671 ! ------------------------------------------------------------------- 672 ! --- UNSATURATED (PRECIPITATING) DOWNDRAFTS 673 ! ------------------------------------------------------------------- 674 IF (debut) PRINT *, ' cva_driver -> cv3_unsat ' 675 676 call driver_log('cv3_unsat') 677 CALL cv3_unsat(nloc, ncum, nd, nd, ntra, icb, inb, iflag, & 678 t_wake, q_wake, qs_wake, gz, u, v, tra, p, ph, & 679 th_wake, tv_wake, lv_wake, lf_wake, cpn_wake, & 680 ep, sigp, clw, frac_s, qpreca, frac_a, qta, & 681 m, ment, elij, delt, plcl, coef_clos, & 682 mp, qp, up, vp, trap, wt, water, evap, fondue, ice, & 683 faci, b, sigd, & 684 wdtrainA, wdtrainS, wdtrainM) 685 IF (prt_level >= 10) THEN 686 Print *, 'cva_driver after cv3_unsat:mp , water, ice, evap, fondue ' 687 DO k = 1, nd 688 write (6, '(i4,5(1x,e13.6))'), & 689 k, mp(igout, k), water(igout, k), ice(igout, k), & 690 evap(igout, k), fondue(igout, k) 691 ENDDO 692 Print *, 'cva_driver after cv3_unsat: wdtrainA, wdtrainS, wdtrainM ' 693 DO k = 1, nd 694 write (6, '(i4,3(1x,e13.6))'), & 695 k, wdtrainA(igout, k), wdtrainS(igout, k), wdtrainM(igout, k) 696 ENDDO 697 ENDIF 698 699 IF (debut) PRINT *, 'cv_unsat-> ' 700 ! ------------------------------------------------------------------- 701 ! YIELD 702 ! (tendencies, precipitation, variables of interface with other processes, etc) 703 ! ------------------------------------------------------------------- 704 705 call driver_log('cv3_yield') 706 call enter_profile("cv3_yield") 707 CALL cv3_yield(nloc, ncum, nd, nd, ntra, ok_conserv_q, & 708 icb, inb, delt, & 709 t, q, t_wake, q_wake, s_wake, u, v, tra, & 710 gz, p, ph, h, hp, lv, lf, cpn, th, th_wake, & 711 ep, clw, qpreca, m, tp, mp, qp, up, vp, trap, & 712 wt, water, ice, evap, fondue, faci, b, sigd, & 713 ment, qent, hent, iflag_mix, uent, vent, & 714 nent, elij, traent, sig, & 715 tv, tvp, wghti, & 716 iflag, precip, Vprecip, Vprecipi, ft, fq, fu, fv, ftra, & 717 cbmf, upwd, dnwd, dnwd0, ma, mip, & 718 qcondc, wd, & 719 ftd, fqd, qta, qtc, sigt, tau_cld_cv, coefw_cld_cv) 720 call exit_profile("cv3_yield") 721 ! Test conseravtion de l'eau 722 IF (debut) PRINT *, ' cv3_yield -> fqd(1) = ', fqd(igout, 1) 723 IF (prt_level >= 10) THEN 724 Print *, 'cva_driver after cv3_yield:ft(1) , ftd(1) ', & 725 ft(igout, 1), ftd(igout, 1) 726 Print *, 'cva_driver after cv3_yield:fq(1) , fqd(1) ', & 727 fq(igout, 1), fqd(igout, 1) 728 ENDIF 729 730 !^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^ 731 !--- passive tracers 732 !^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^ 733 734 call driver_log('cv3_tracer') 735 call enter_profile("cv3_tracer") 736 CALL cv3_tracer(nloc, len, ncum, nd, nd, & 737 ment, sigij, da, phi, phi2, d1a, dam, & 738 ep, vprecip, elij, clw, epmlmMm, eplaMm, & 739 icb, inb) 740 call exit_profile("cv3_tracer") 741 END IF ! ncum>0 742 call exit_profile("cv3a_compressed") 556 call cv3a_driver_compressed(nloc, nd, ntra, & 557 debut, ok_conserv_q, iflag_mix, iflag_clos, prt_level, & 558 ! Input fields 559 delt, tau_cld_cv, coefw_cld_cv, nk, icbs, tnk, qnk, gznk, hnk, unk, vnk, pbase, buoybase, s_wake, Ale, Alp, wghti, th, t, q, qs, t_wake, q_wake, qs_wake, u, v, gz, h, th_wake, lv, lf, cpn, p, tv, tp, h_wake, lv_wake, lf_wake, cpn_wake, tv_wake, omega, ph, & 560 ! Input/output 561 iflag, icb, plcl, sig, w0, tvp, clw, & 562 ! Output fields 563 inb, precip, cbmf, plfc, wbeff, ptop2, sigd, wd, cape, cin, Plim1, plim2, supmax0, asupmaxmin, epmax_diag, ft, fq, fu, fv, ma, mip, upwd, dnwd, dnwd0, qcondc, ftd, fqd, asupmax, da, mp, d1a, dam, qta, evap, ep, eplaMm, wdtrainA, wdtrainS, wdtrainM, qtc, sigt, vprecip, vprecipi, phi, phi2, sigij, elij, epmlmMm) 743 564 744 565 ! ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^ … … 826 647 END SUBROUTINE 827 648 649 subroutine cv3a_driver_compressed(nloc, nd, ntra, & 650 debut, ok_conserv_q, iflag_mix, iflag_clos, prt_level, & 651 ! Input fields 652 delt, tau_cld_cv, coefw_cld_cv, nk, icbs, tnk, qnk, gznk, hnk, unk, vnk, pbase, buoybase, s_wake, Ale, Alp, wghti, th, t, q, qs, t_wake, q_wake, qs_wake, u, v, gz, h, th_wake, lv, lf, cpn, p, tv, tp, h_wake, lv_wake, lf_wake, cpn_wake, tv_wake, omega, ph, & 653 ! Input/output 654 iflag, icb, plcl, sig, w0, tvp, clw, & 655 ! Output fields 656 inb, precip, cbmf, plfc, wbeff, ptop2, sigd, wd, cape, cin, Plim1, plim2, supmax0, asupmaxmin, epmax_diag, ft, fq, fu, fv, ma, mip, upwd, dnwd, dnwd0, qcondc, ftd, fqd, asupmax, da, mp, d1a, dam, qta, evap, ep, eplaMm, wdtrainA, wdtrainS, wdtrainM, qtc, sigt, vprecip, vprecipi, phi, phi2, sigij, elij, epmlmMm) 657 use profiling_physic_mod 658 USE cv3p_mixing_mod, ONLY : cv3p_mixing 659 660 integer, intent(in) :: nloc, nd, ntra ! Arrays sizes 661 logical, intent(in) :: debut, ok_conserv_q 662 integer, intent(in) :: iflag_mix, iflag_clos, prt_level 663 real, intent(in) :: delt, tau_cld_cv, coefw_cld_cv 664 665 ! Input arrays 666 integer, dimension(nloc), intent(in) :: nk, icbs 667 real, dimension(nloc), intent(in) :: tnk, qnk, gznk, hnk, unk, vnk, pbase, buoybase, s_wake, Ale, Alp 668 real, dimension(nloc, nd), intent(in) :: wghti, th, t, q, qs, t_wake, q_wake, qs_wake, u, v, gz, h, th_wake, lv, lf, cpn, p, tv, tp, h_wake, lv_wake, lf_wake, cpn_wake, tv_wake, omega 669 real, dimension(nloc, nd + 1), intent(in) :: ph 670 671 ! Input/output arrays 672 integer, dimension(nloc), intent(inout) :: iflag, icb 673 real, dimension(nloc), intent(inout) :: plcl 674 real, dimension(nloc, nd), intent(inout) :: sig, w0, tvp, clw 675 676 ! Output arrays 677 integer, dimension(nloc), intent(out) :: inb 678 real, dimension(nloc), intent(out) :: precip, cbmf, plfc, wbeff, ptop2, sigd, wd, cape, cin, Plim1, plim2, supmax0, asupmaxmin, epmax_diag 679 real, dimension(nloc, nd), intent(out) :: ft, fq, fu, fv, ma, mip, upwd, dnwd, dnwd0, qcondc, ftd, fqd, asupmax, da, mp, d1a, dam, qta, evap, ep, eplaMm, wdtrainA, wdtrainS, wdtrainM, qtc, sigt 680 real, dimension(nloc, nd + 1), intent(out) :: vprecip, vprecipi 681 real, dimension(nloc, nd, nd), intent(out) :: phi, phi2, sigij, elij, epmlmMm 682 683 ! Local fields 684 INTEGER nent(nloc, nd) 685 REAL hp(nloc, nd), sigp(nloc, nd), qpreca(nloc, nd) 686 REAL buoy(nloc, nd) 687 REAL m(nloc, nd) 688 REAL mm(nloc, nd) 689 REAL ment(nloc, nd, nd) 690 REAL qent(nloc, nd, nd) 691 REAL hent(nloc, nd, nd) 692 REAL uent(nloc, nd, nd), vent(nloc, nd, nd) 693 REAL ments(nloc, nd, nd), qents(nloc, nd, nd) 694 REAL supmax(nloc, nd) 695 REAL coef_clos(nloc) 696 REAL, DIMENSION(nloc, nd) :: qp, up, vp 697 REAL, DIMENSION(nloc, nd) :: wt, water 698 REAL, DIMENSION(nloc, nd) :: ice, fondue, b 699 REAL, DIMENSION(nloc, nd) :: frac_a, frac_s, faci 700 REAL tra(nloc, nd, ntra), trap(nloc, nd, ntra) 701 REAL ftra(nloc, nd, ntra), traent(nloc, nd, nd, ntra) 702 703 LOGICAL ok_inhib ! True => possible inhibition of convection by dryness 704 integer :: k 705 706 integer :: ncum ! Number of convective cells 707 logical, save :: timers_first = .true. 708 !$omp threadprivate(timers_first) 709 INTEGER, PARAMETER :: igout = 1 710 711 if (timers_first) then 712 call enter_profile("cv3p_mixing") 713 call exit_profile("cv3p_mixing") 714 call enter_profile("cv3_yield") 715 call exit_profile("cv3_yield") 716 call enter_profile("cv3_tracer") 717 call exit_profile("cv3_tracer") 718 719 timers_first = .false. 720 endif 721 722 ncum = nloc 723 call enter_profile("cv3a_compressed") 724 IF (ncum > 0) THEN 725 726 ! ------------------------------------------------------------------- 727 ! --- UNDILUTE (ADIABATIC) UPDRAFT / second part : 728 ! --- FIND THE REST OF THE LIFTED PARCEL TEMPERATURES 729 ! --- & 730 ! --- COMPUTE THE PRECIPITATION EFFICIENCIES AND THE 731 ! --- FRACTION OF PRECIPITATION FALLING OUTSIDE OF CLOUD 732 ! --- & 733 ! --- FIND THE LEVEL OF NEUTRAL BUOYANCY 734 ! ------------------------------------------------------------------- 735 736 call driver_log('cv3_undilute2') 737 CALL cv3_undilute2(nloc, ncum, nd, iflag, icb, icbs, nk, & 738 tnk, qnk, gznk, hnk, t, q, qs, gz, & 739 p, ph, h, tv, lv, lf, pbase, buoybase, plcl, & 740 inb, tp, tvp, clw, hp, ep, sigp, buoy, & 741 frac_a, frac_s, qpreca, qta) 742 743 ! epmax_cape 744 ! on recalcule ep et hp 745 call driver_log('cv3_epmax_cape') 746 call cv3_epmax_fn_cape(nloc, ncum, nd & 747 , ep, hp, icb, inb, clw, nk, t, h, hnk, lv, lf, frac_s & 748 , pbase, p, ph, tv, buoy, sig, w0, iflag & 749 , epmax_diag) 750 751 ! ------------------------------------------------------------------- 752 ! --- MIXING(1) (if iflag_mix .ge. 1) 753 ! ------------------------------------------------------------------- 754 call enter_profile("cv3p_mixing") 755 IF (iflag_mix >= 1) THEN 756 CALL zilch(supmax, nloc*nd) 757 call driver_log('cv3p_mixing') 758 CALL cv3p_mixing(nloc, ncum, nd, nd, ntra, icb, nk, inb, & 759 ph, t, q, qs, u, v, tra, h, lv, lf, frac_s, qta, & 760 unk, vnk, hp, tv, tvp, ep, clw, sig, & 761 ment, qent, hent, uent, vent, nent, & 762 sigij, elij, supmax, ments, qents, traent) 763 ELSE 764 CALL zilch(supmax, nloc*nd) 765 END IF 766 call exit_profile("cv3p_mixing") 767 768 ! ------------------------------------------------------------------- 769 ! --- CLOSURE 770 ! ------------------------------------------------------------------- 771 772 ptop2(:) = 0 773 coef_clos(:) = 1. 774 IF (iflag_clos == 0) THEN 775 call driver_log('cv3_closure') 776 CALL cv3_closure(nloc, ncum, nd, icb, inb, & 777 pbase, p, ph, tv, buoy, & 778 sig, w0, cape, m, iflag) 779 END IF ! iflag_clos==0 780 781 ok_inhib = iflag_mix == 2 782 783 IF (iflag_clos == 1) PRINT *, ' pas d appel cv3p_closure' 784 785 IF (iflag_clos == 2) THEN 786 call driver_log('cv3p1_closure') 787 CALL cv3p1_closure(nloc, ncum, nd, icb, inb, & 788 pbase, plcl, p, ph, tv, tvp, buoy, & 789 supmax, ok_inhib, Ale, Alp, omega, & 790 sig, w0, ptop2, cape, cin, m, iflag, coef_clos, & 791 Plim1, plim2, asupmax, supmax0, & 792 asupmaxmin, cbmf, plfc, wbeff) 793 if (prt_level >= 10) PRINT *, 'cv3p1_closure-> plfc,wbeff ', plfc(1), wbeff(1) 794 END IF ! iflag_clos==2 795 796 IF (iflag_clos == 3) THEN 797 call driver_log('cv3p2_closure') 798 CALL cv3p2_closure(nloc, ncum, nd, icb, inb, & 799 pbase, plcl, p, ph, tv, tvp, buoy, & 800 supmax, ok_inhib, Ale, Alp, omega, & 801 sig, w0, ptop2, cape, cin, m, iflag, coef_clos, & 802 Plim1, plim2, asupmax, supmax0, & 803 asupmaxmin, cbmf, plfc, wbeff) 804 if (prt_level >= 10) PRINT *, 'cv3p2_closure-> plfc,wbeff ', plfc(1), wbeff(1) 805 END IF ! iflag_clos==3 806 807 ! ------------------------------------------------------------------- 808 ! --- MIXING(2) 809 ! ------------------------------------------------------------------- 810 811 IF (iflag_mix == 0) THEN 812 call driver_log('cv3_mixing') 813 CALL cv3_mixing(nloc, ncum, nd, nd, ntra, icb, nk, inb, & ! na->nd 814 ph, t, q, qs, u, v, tra, h, lv, lf, frac_s, qnk, & 815 unk, vnk, hp, tv, tvp, ep, clw, m, sig, & 816 ment, qent, uent, vent, nent, sigij, elij, ments, qents, traent) 817 CALL zilch(hent, nloc*nd*nd) 818 ELSE 819 mm(:, :) = m(:, :) 820 CALL cv3_mixscale(nloc, ncum, nd, ment, mm) 821 IF (debut) PRINT *, ' cv3_mixscale-> ' 822 END IF 823 824 IF (debut) PRINT *, ' cv_mixing ->' 825 826 ! ------------------------------------------------------------------- 827 ! --- UNSATURATED (PRECIPITATING) DOWNDRAFTS 828 ! ------------------------------------------------------------------- 829 IF (debut) PRINT *, ' cva_driver -> cv3_unsat ' 830 831 call driver_log('cv3_unsat') 832 CALL cv3_unsat(nloc, ncum, nd, nd, ntra, icb, inb, iflag, & 833 t_wake, q_wake, qs_wake, gz, u, v, tra, p, ph, & 834 th_wake, tv_wake, lv_wake, lf_wake, cpn_wake, & 835 ep, sigp, clw, frac_s, qpreca, frac_a, qta, & 836 m, ment, elij, delt, plcl, coef_clos, & 837 mp, qp, up, vp, trap, wt, water, evap, fondue, ice, & 838 faci, b, sigd, & 839 wdtrainA, wdtrainS, wdtrainM) 840 IF (prt_level >= 10) THEN 841 Print *, 'cva_driver after cv3_unsat:mp , water, ice, evap, fondue ' 842 DO k = 1, nd 843 write (6, '(i4,5(1x,e13.6))'), & 844 k, mp(igout, k), water(igout, k), ice(igout, k), & 845 evap(igout, k), fondue(igout, k) 846 ENDDO 847 Print *, 'cva_driver after cv3_unsat: wdtrainA, wdtrainS, wdtrainM ' 848 DO k = 1, nd 849 write (6, '(i4,3(1x,e13.6))'), & 850 k, wdtrainA(igout, k), wdtrainS(igout, k), wdtrainM(igout, k) 851 ENDDO 852 ENDIF 853 854 IF (debut) PRINT *, 'cv_unsat-> ' 855 ! ------------------------------------------------------------------- 856 ! YIELD 857 ! (tendencies, precipitation, variables of interface with other processes, etc) 858 ! ------------------------------------------------------------------- 859 860 call driver_log('cv3_yield') 861 call enter_profile("cv3_yield") 862 CALL cv3_yield(nloc, ncum, nd, nd, ntra, ok_conserv_q, & 863 icb, inb, delt, & 864 t, q, t_wake, q_wake, s_wake, u, v, tra, & 865 gz, p, ph, h, hp, lv, lf, cpn, th, th_wake, & 866 ep, clw, qpreca, m, tp, mp, qp, up, vp, trap, & 867 wt, water, ice, evap, fondue, faci, b, sigd, & 868 ment, qent, hent, iflag_mix, uent, vent, & 869 nent, elij, traent, sig, & 870 tv, tvp, wghti, & 871 iflag, precip, Vprecip, Vprecipi, ft, fq, fu, fv, ftra, & 872 cbmf, upwd, dnwd, dnwd0, ma, mip, & 873 qcondc, wd, & 874 ftd, fqd, qta, qtc, sigt, tau_cld_cv, coefw_cld_cv) 875 call exit_profile("cv3_yield") 876 ! Test conseravtion de l'eau 877 IF (debut) PRINT *, ' cv3_yield -> fqd(1) = ', fqd(igout, 1) 878 IF (prt_level >= 10) THEN 879 Print *, 'cva_driver after cv3_yield:ft(1) , ftd(1) ', & 880 ft(igout, 1), ftd(igout, 1) 881 Print *, 'cva_driver after cv3_yield:fq(1) , fqd(1) ', & 882 fq(igout, 1), fqd(igout, 1) 883 ENDIF 884 885 !^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^ 886 !--- passive tracers 887 !^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^ 888 889 call driver_log('cv3_tracer') 890 call enter_profile("cv3_tracer") 891 CALL cv3_tracer(nloc, -1, ncum, nd, nd, & 892 ment, sigij, da, phi, phi2, d1a, dam, & 893 ep, vprecip, elij, clw, epmlmMm, eplaMm, & 894 icb, inb) 895 call exit_profile("cv3_tracer") 896 END IF ! ncum>0 897 call exit_profile("cv3a_compressed") 898 end subroutine 899 828 900 subroutine driver_log(message) 829 901 use print_control_mod, only: prt_level
Note: See TracChangeset
for help on using the changeset viewer.