Changeset 2727 for trunk/LMDZ.GENERIC
- Timestamp:
- Jun 21, 2022, 11:05:47 AM (3 years ago)
- File:
-
- 1 edited
Legend:
- Unmodified
- Added
- Removed
-
trunk/LMDZ.GENERIC/libf/phystd/callcorrk.F90
r2631 r2727 33 33 use callkeys_mod, only: varactive,diurnal,tracer,water,varfixed,satval,diagdtau, & 34 34 kastprof,strictboundcorrk,specOLR,CLFvarying, & 35 tplanckmin,tplanckmax,global1d 35 tplanckmin,tplanckmax,global1d,generic_condensation 36 36 use optcv_mod, only: optcv 37 37 use optci_mod, only: optci 38 38 use recombin_corrk_mod, only: corrk_recombin, call_recombin 39 use generic_cloud_common_h, only: Psat_generic, epsi_generic 40 use generic_tracer_index_mod, only: generic_tracer_index 39 41 implicit none 40 42 … … 154 156 REAL*8 albv(L_NSPECTV) ! Spectral Visible Albedo. 155 157 156 INTEGER ig,l,k,nw,iaer 158 INTEGER ig,l,k,nw,iaer,iq 157 159 158 160 real*8,allocatable,save :: taugsurf(:,:) 159 161 real*8,allocatable,save :: taugsurfi(:,:) 160 162 !$OMP THREADPRIVATE(taugsurf,taugsurfi) 161 real*8 qvar(L_LEVELS) ! Mixing ratio of variable component (mol/mol). 163 real*8 qvar(L_LEVELS) ! Mixing ratio of variable component (mol/mol). index 1 is the top of the atmosphere, index L_LEVELS is the bottom 162 164 163 165 ! Local aerosol optical properties for each column on RADIATIVE grid. … … 201 203 ! local variable 202 204 integer ok ! status (returned by NetCDF functions) 205 206 integer igcm_generic_vap, igcm_generic_ice! index of the vap and ice of generic_tracer 207 logical call_ice_vap_generic ! to call only one time the ice/vap pair of a tracer 208 real, save :: metallicity ! metallicity of planet --- is not used here, but necessary to call function Psat_generic 209 !$OMP THREADPRIVATE(metallicity) 210 REAL, SAVE :: qvap_deep ! deep mixing ratio of water vapor when simulating bottom less planets 211 !$OMP THREADPRIVATE(qvap_deep) 203 212 204 213 !=============================================================== … … 394 403 endif 395 404 396 if((igcm_h2o_vap.eq.0) .and. varactive )then405 if((igcm_h2o_vap.eq.0) .and. varactive .and. water)then 397 406 message='varactive in callcorrk but no h2o_vap tracer.' 398 407 call abort_physic(subname,message,1) 408 endif 409 410 if(varfixed .and. generic_condensation .and. .not. water)then 411 write(*,*) "Deep water vapor mixing ratio ? (no effect if negative) " 412 qvap_deep=-1. ! default value 413 call getin_p("qvap_deep",qvap_deep) 414 write(*,*) " qvap_deep = ",qvap_deep 415 416 metallicity=0.0 ! default value --- is not used here but necessary to call function Psat_generic 417 call getin_p("metallicity",metallicity) ! --- is not used here but necessary to call function Psat_generic 399 418 endif 400 419 … … 648 667 649 668 650 !----------------------------------------------------------------------- 651 ! Water vapour (to be generalised for other gases eventually ...) 652 !----------------------------------------------------------------------- 669 !----------------------------------------------------------------------- 670 ! Water vapour (to be generalised for other gases eventually ...) 671 !----------------------------------------------------------------------- 672 673 if (water) then 674 if(varactive)then 675 676 i_var=igcm_h2o_vap 677 do l=1,nlayer 678 qvar(2*l) = pq(ig,nlayer+1-l,i_var) 679 qvar(2*l+1) = pq(ig,nlayer+1-l,i_var) 680 !JL13index qvar(2*l+1) = (pq(ig,nlayer+1-l,i_var)+pq(ig,max(nlayer-l,1),i_var))/2 681 !JL13index Average approximation as for temperature... 682 end do 683 qvar(1)=qvar(2) 684 685 elseif(varfixed)then 686 687 do l=1,nlayer ! Here we will assign fixed water vapour profiles globally. 688 RH = satval * ((pplay(ig,l)/pplev(ig,1) - 0.02) / 0.98) 689 if(RH.lt.0.0) RH=0.0 690 691 call Psat_water(pt(ig,l),pplay(ig,l),psat,qsat) 692 693 !pq_temp(l) = qsat ! fully saturated everywhere 694 pq_temp(l) = RH * qsat ! ~realistic profile (e.g. 80% saturation at ground) 695 end do 696 697 do l=1,nlayer 698 qvar(2*l) = pq_temp(nlayer+1-l) 699 qvar(2*l+1) = (pq_temp(nlayer+1-l)+pq_temp(max(nlayer-l,1)))/2 700 end do 701 702 qvar(1)=qvar(2) 703 704 ! Lowest layer of atmosphere 705 RH = satval * (1 - 0.02) / 0.98 706 if(RH.lt.0.0) RH=0.0 707 708 qvar(2*nlayer+1)= RH * qsat ! ~realistic profile (e.g. 80% saturation at ground) 709 710 else 711 do k=1,L_LEVELS 712 qvar(k) = 1.0D-7 713 end do 714 end if ! varactive/varfixed 653 715 654 if(varactive)then 655 656 i_var=igcm_h2o_vap 657 do l=1,nlayer 658 qvar(2*l) = pq(ig,nlayer+1-l,i_var) 659 qvar(2*l+1) = pq(ig,nlayer+1-l,i_var) 660 !JL13index qvar(2*l+1) = (pq(ig,nlayer+1-l,i_var)+pq(ig,max(nlayer-l,1),i_var))/2 661 !JL13index ! Average approximation as for temperature... 662 end do 663 qvar(1)=qvar(2) 664 665 elseif(varfixed)then 666 667 do l=1,nlayer ! Here we will assign fixed water vapour profiles globally. 668 RH = satval * ((pplay(ig,l)/pplev(ig,1) - 0.02) / 0.98) 669 if(RH.lt.0.0) RH=0.0 716 endif ! if (water) 717 718 !----------------------------------------------------------------------- 719 ! GCS (Generic Condensable Specie) Vapor 720 ! If you have GCS tracers and they are : variable & radiatively active 721 ! 722 ! NC22 723 !----------------------------------------------------------------------- 724 725 if (generic_condensation .and. .not. water ) then 726 727 ! For now, only one GCS tracer can be both variable and radiatively active 728 ! If you set two GCS tracers, that are variable and radiatively active, 729 ! the last one in tracer.def will be chosen as the one that will be vadiatively active 730 731 do iq=1,nq 732 733 call generic_tracer_index(nq,iq,igcm_generic_vap,igcm_generic_ice,call_ice_vap_generic) 670 734 671 call Psat_water(pt(ig,l),pplay(ig,l),psat,qsat) 672 673 !pq_temp(l) = qsat ! fully saturated everywhere 674 pq_temp(l) = RH * qsat ! ~realistic profile (e.g. 80% saturation at ground) 675 end do 735 if (call_ice_vap_generic) then ! to call only one time the ice/vap pair of a tracer 736 737 if(varactive)then 738 739 i_var=igcm_generic_vap 740 do l=1,nlayer 741 qvar(2*l) = pq(ig,nlayer+1-l,i_var) 742 qvar(2*l+1) = pq(ig,nlayer+1-l,i_var) 743 !JL13index qvar(2*l+1) = (pq(ig,nlayer+1-l,i_var)+pq(ig,max(nlayer-l,1),i_var))/2 744 !JL13index ! Average approximation as for temperature... 745 end do 746 qvar(1)=qvar(2) 747 748 elseif(varfixed .and. (qvap_deep .ge. 0))then 749 750 do l=1,nlayer ! Here we will assign fixed water vapour profiles globally. 751 752 call Psat_generic(pt(ig,l),pplay(ig,l),metallicity,psat,qsat) 753 754 if (qsat .lt. qvap_deep) then 755 pq_temp(l) = qsat ! fully saturated everywhere 756 else 757 pq_temp(l) = qvap_deep 758 end if 759 760 end do 761 762 do l=1,nlayer 763 qvar(2*l) = pq_temp(nlayer+1-l) 764 qvar(2*l+1) = (pq_temp(nlayer+1-l)+pq_temp(max(nlayer-l,1)))/2 765 end do 766 767 qvar(1)=qvar(2) 676 768 677 do l=1,nlayer 678 qvar(2*l) = pq_temp(nlayer+1-l) 679 qvar(2*l+1) = (pq_temp(nlayer+1-l)+pq_temp(max(nlayer-l,1)))/2 680 end do 681 682 qvar(1)=qvar(2) 683 684 ! Lowest layer of atmosphere 685 RH = satval * (1 - 0.02) / 0.98 686 if(RH.lt.0.0) RH=0.0 687 688 qvar(2*nlayer+1)= RH * qsat ! ~realistic profile (e.g. 80% saturation at ground) 689 690 else 769 else 770 do k=1,L_LEVELS 771 qvar(k) = 1.0D-7 772 end do 773 end if ! varactive/varfixed 774 775 endif 776 777 end do ! do iq=1,nq loop on tracers 778 779 end if ! if (generic_condensation .and. .not. water ) 780 781 !----------------------------------------------------------------------- 782 ! No Water vapor and No GCS (Generic Condensable Specie) vapor 783 !----------------------------------------------------------------------- 784 785 if (.not. generic_condensation .and. .not. water ) then 691 786 do k=1,L_LEVELS 692 787 qvar(k) = 1.0D-7 693 788 end do 694 end if ! varactive/varfixed 789 end if ! if (.not. generic_condensation .and. .not. water ) 790 695 791 696 792 if(.not.kastprof)then 697 793 ! IMPORTANT: Now convert from kg/kg to mol/mol. 698 794 do k=1,L_LEVELS 699 qvar(k) = qvar(k)/(epsi+qvar(k)*(1.-epsi)) 795 if (water) then 796 qvar(k) = qvar(k)/(epsi+qvar(k)*(1.-epsi)) 797 endif 798 if (generic_condensation .and. .not. water) then 799 qvar(k) = qvar(k)/(epsi_generic+qvar(k)*(1.-epsi_generic)) 800 endif 700 801 end do 701 802 end if
Note: See TracChangeset
for help on using the changeset viewer.