Changeset 1914 for trunk/LMDZ.TITAN/libf/phytitan
- Timestamp:
- Apr 4, 2018, 4:18:35 PM (7 years ago)
- File:
-
- 1 edited
Legend:
- Unmodified
- Added
- Removed
-
trunk/LMDZ.TITAN/libf/phytitan/physiq_mod.F90
r1904 r1914 36 36 use comcstfi_mod, only: pi, g, rcp, r, rad, mugaz, cpp 37 37 use time_phylmdz_mod, only: daysec 38 use logic_mod, only: moyzon_ch , moyzon_mu38 use logic_mod, only: moyzon_ch 39 39 use moyzon_mod, only: tmoy, playmoy, zphibar, zphisbar, zplevbar, & 40 40 zplaybar, zzlevbar, zzlaybar, ztfibar, zqfibar … … 367 367 ! ---------------------------------------------------- 368 368 369 real ctimestep ! Chemistry timestep (s) 369 real,save :: ctimestep ! Chemistry timestep (s) 370 !$OMP THREADPRIVATE(ctimestep) 370 371 371 372 ! Chemical tracers in molar fraction 372 real, dimension(:,:,:), allocatable, save :: ychim ! (mol/mol) 373 !$OMP THREADPRIVATE(ychim) 373 real, dimension(ngrid,nlayer,nkim) :: ychim ! (mol/mol) 374 374 375 375 ! Molar fraction tendencies ( chemistry and condensation ) for tracers (mol/mol/s) … … 381 381 real, dimension(:,:), allocatable, save :: qysat ! (mol/mol) 382 382 !$OMP THREADPRIVATE(qysat) 383 real temp_eq(nlayer), press_eq(nlayer) ! Planetary averages for the init. of saturation profiles .383 real temp_eq(nlayer), press_eq(nlayer) ! Planetary averages for the init. of saturation profiles (K,mbar) 384 384 385 385 ! Surface methane tank … … 403 403 ! Or one can put calmufi in MMP_GCM module (in muphytitan). 404 404 INTERFACE 405 SUBROUTINE calmufi(dt, plev, zlev, play, zlay, temp, pq, zdq )405 SUBROUTINE calmufi(dt, plev, zlev, play, zlay, temp, pq, zdqfi, zdq) 406 406 REAL(kind=8), INTENT(IN) :: dt !! Physics timestep (s). 407 407 REAL(kind=8), DIMENSION(:,:), INTENT(IN) :: plev !! Pressure levels (Pa). … … 410 410 REAL(kind=8), DIMENSION(:,:), INTENT(IN) :: zlay !! Altitude at the center of each layer (m). 411 411 REAL(kind=8), DIMENSION(:,:), INTENT(IN) :: temp !! Temperature at the center of each layer (K). 412 REAL(kind=8), DIMENSION(:,:,:), INTENT(IN) :: pq !! Tracers (\(kg.kg^{-1}}\)). 413 REAL(kind=8), DIMENSION(:,:,:), INTENT(OUT) :: zdq !! Tendency for tracers (\(kg.kg^{-1}}\)). 412 REAL(kind=8), DIMENSION(:,:,:), INTENT(IN) :: pq !! Tracers (\(kg.kg^{-1}}\)). 413 REAL(kind=8), DIMENSION(:,:,:), INTENT(IN) :: zdqfi !! Tendency from former processes for tracers (\(kg.kg^{-1}}\)). 414 REAL(kind=8), DIMENSION(:,:,:), INTENT(OUT) :: zdq !! Microphysical tendency for tracers (\(kg.kg^{-1}}\)). 414 415 END SUBROUTINE calmufi 415 416 END INTERFACE … … 505 506 if ( callchim ) then 506 507 507 allocate(ychim(ngrid,nlayer,nkim)) 508 if ( moyzon_ch .and. ngrid.eq.1 ) then 509 print *, "moyzon_ch=",moyzon_ch," and ngrid=1" 510 print *, "Please desactivate zonal mean for 1D !" 511 stop 512 endif 513 508 514 allocate(dycchi(ngrid,nlayer,nkim)) ! only for chemical tracers 509 515 allocate(qysat(nlayer,nkim)) … … 513 519 514 520 ! qysat is taken at the equator ( small variations of t,p ) 515 temp_eq(:) = tmoy(:) 516 press_eq(:) = playmoy(:)/100. ! in mbar 521 if (ngrid.ne.1) then ! TODO : a patcher (lecture d'un profil?) si jamais on a plus acces a moyzon_mod ! 522 temp_eq(:) = tmoy(:) 523 press_eq(:) = playmoy(:)/100. ! in mbar 524 else 525 temp_eq(:) = pt(1,:) 526 press_eq(:) = pplay(1,:)/100. 527 endif 517 528 518 529 call inicondens(press_eq,temp_eq,qysat) … … 553 564 if (is_master) write(*,*) "Physiq: initializing tsoil(:) to pt(:,1) !!" 554 565 do isoil=1,nsoilmx 555 tsoil( 1:ngrid,isoil)=tsurf(1:ngrid)566 tsoil(:,isoil)=tsurf(:) 556 567 enddo 557 568 if (is_master) write(*,*) "Physiq: initializing day_ini to pdat !" … … 648 659 ! ~~~~~~~~~~~~~~~~~~~~~~~~~~~~ 649 660 650 pdt( 1:ngrid,1:nlayer)= 0.0651 zdtsurf( 1:ngrid)= 0.0652 pdq( 1:ngrid,1:nlayer,1:nq)= 0.0653 dqsurf( 1:ngrid,1:nq)= 0.0654 pdu( 1:ngrid,1:nlayer)= 0.0655 pdv( 1:ngrid,1:nlayer)= 0.0656 pdpsrf( 1:ngrid)= 0.0657 zflubid( 1:ngrid)= 0.0658 taux( 1:ngrid)= 0.0659 tauy( 1:ngrid)= 0.0661 pdt(:,:) = 0.0 662 zdtsurf(:) = 0.0 663 pdq(:,:,:) = 0.0 664 dqsurf(:,:) = 0.0 665 pdu(:,:) = 0.0 666 pdv(:,:) = 0.0 667 pdpsrf(:) = 0.0 668 zflubid(:) = 0.0 669 taux(:) = 0.0 670 tauy(:) = 0.0 660 671 661 672 zday=pday+ptime ! Compute time, in sols (and fraction thereof). … … 696 707 ! Compute geopotential between layers. 697 708 ! ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ 698 zzlay( 1:ngrid,1:nlayer)=pphi(1:ngrid,1:nlayer)709 zzlay(:,:)=pphi(:,:) 699 710 do l=1,nlayer 700 zzlay( 1:ngrid,l)= zzlay(1:ngrid,l)/glat(1:ngrid)711 zzlay(:,l)= zzlay(:,l)/glat(:) 701 712 enddo 702 713 703 zzlev( 1:ngrid,1)=0.704 zzlev( 1:ngrid,nlayer+1)=1.e7 ! Dummy top of last layer above 10000 km...714 zzlev(:,1)=0. 715 zzlev(:,nlayer+1)=1.e7 ! Dummy top of last layer above 10000 km... 705 716 706 717 do l=2,nlayer … … 712 723 enddo 713 724 714 ! Zonal averages needed for chemistry and microphysics 715 ! ~~~~~~~~~~~~~ Taken from old Titan ~~~~~~~~~~~~~~~~~ 716 if (moyzon_ch .or. moyzon_mu) then 717 718 print *, "------------------------------ </CRITICAL ALERT> -------------------------------" 719 print *, "WARNING : YOU ARE USING ZONAL MEANS THAT SEEM TO LEAD TO CRASHES (-infinity) ..." 720 print *, "------------------------------ <CRITICAL ALERT/> -------------------------------" 721 725 ! Zonal averages needed for chemistry 726 ! ~~~~~~~ Taken from old Titan ~~~~~~ 727 if (moyzon_ch) then 728 722 729 zzlaybar(1,:)=(zphibar(1,:)+zphisbar(1))/g 723 730 ! SI ON TIENT COMPTE DE LA VARIATION DE G AVEC L'ALTITUDE: … … 770 777 ! But first linearly interpolate mass flux to mid-layers 771 778 do l=1,nlayer-1 772 pw( 1:ngrid,l)=0.5*(flxw(1:ngrid,l)+flxw(1:ngrid,l+1))779 pw(:,l)=0.5*(flxw(:,l)+flxw(:,l+1)) 773 780 enddo 774 pw( 1:ngrid,nlayer)=0.5*flxw(1:ngrid,nlayer) ! since flxw(nlayer+1)=0781 pw(:,nlayer)=0.5*flxw(:,nlayer) ! since flxw(nlayer+1)=0 775 782 do l=1,nlayer 776 pw(1:ngrid,l)=(pw(1:ngrid,l)*r*pt(1:ngrid,l)) / & 777 (pplay(1:ngrid,l)*cell_area(1:ngrid)) 783 pw(:,l)=(pw(:,l)*r*pt(:,l)) / (pplay(:,l)*cell_area(:)) 778 784 enddo 779 785 … … 828 834 ! computations... waste of time... 829 835 DO i = 1, ngrid 830 i2e( :) = ( pplev(i,1:nlayer)-pplev(i,2:nlayer+1) ) / g836 i2e(1:nlayer) = ( pplev(i,1:nlayer)-pplev(i,2:nlayer+1) ) / g 831 837 pqo(i,:,:) = 0.0 832 838 DO j=1,nmicro-nice … … 847 853 ! Radiative flux from the sky absorbed by the surface (W.m-2). 848 854 GSR=0.0 849 fluxrad_sky( 1:ngrid)=emis(1:ngrid)*fluxsurf_lw(1:ngrid)+fluxsurfabs_sw(1:ngrid)855 fluxrad_sky(:)=emis(:)*fluxsurf_lw(:)+fluxsurfabs_sw(:) 850 856 851 857 !if(noradsurf)then ! no lower surface; SW flux just disappears 852 ! GSR = SUM(fluxsurf_sw( 1:ngrid)*cell_area(1:ngrid))/totarea853 ! fluxrad_sky( 1:ngrid)=emis(1:ngrid)*fluxsurf_lw(1:ngrid)858 ! GSR = SUM(fluxsurf_sw(:)*cell_area(:))/totarea 859 ! fluxrad_sky(:)=emis(:)*fluxsurf_lw(:) 854 860 ! print*,'SW lost in deep atmosphere = ',GSR,' W m^-2' 855 861 !endif 856 862 857 863 ! Net atmospheric radiative heating rate (K.s-1) 858 dtrad( 1:ngrid,1:nlayer)=zdtsw(1:ngrid,1:nlayer)+zdtlw(1:ngrid,1:nlayer)864 dtrad(:,:)=zdtsw(:,:)+zdtlw(:,:) 859 865 860 866 elseif(newtonian)then … … 865 871 call newtrelax(ngrid,nlayer,mu0,sinlat,zpopsk,pt,pplay,pplev,dtrad,firstcall) 866 872 867 zdtsurf( 1:ngrid) = +(pt(1:ngrid,1)-tsurf(1:ngrid))/ptimestep873 zdtsurf(:) = +(pt(:,1)-tsurf(:))/ptimestep 868 874 ! e.g. surface becomes proxy for 1st atmospheric layer ? 869 875 … … 873 879 ! II.c Atmosphere has no radiative effect 874 880 ! ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ 875 fluxtop_dn( 1:ngrid) = fract(1:ngrid)*mu0(1:ngrid)*Fat1AU/dist_star**2881 fluxtop_dn(:) = fract(:)*mu0(:)*Fat1AU/dist_star**2 876 882 if(ngrid.eq.1)then ! / by 4 globally in 1D case... 877 883 fluxtop_dn(1) = fract(1)*Fat1AU/dist_star**2/2.0 878 884 endif 879 fluxsurf_sw( 1:ngrid) = fluxtop_dn(1:ngrid)885 fluxsurf_sw(:) = fluxtop_dn(:) 880 886 print*,'------------WARNING---WARNING------------' ! by MT2015. 881 887 print*,'You are in corrk=false mode, ' 882 888 print*,'and the surface albedo is taken equal to the first visible spectral value' 883 889 884 fluxsurfabs_sw( 1:ngrid) = fluxtop_dn(1:ngrid)*(1.-albedo(1:ngrid,1))885 fluxrad_sky( 1:ngrid) = fluxsurfabs_sw(1:ngrid)886 fluxtop_lw( 1:ngrid) = emis(1:ngrid)*sigma*tsurf(1:ngrid)**4887 888 dtrad( 1:ngrid,1:nlayer)=0.0 ! no atmospheric radiative heating890 fluxsurfabs_sw(:) = fluxtop_dn(:)*(1.-albedo(:,1)) 891 fluxrad_sky(:) = fluxsurfabs_sw(:) 892 fluxtop_lw(:) = emis(:)*sigma*tsurf(:)**4 893 894 dtrad(:,:)=0.0 ! no atmospheric radiative heating 889 895 890 896 endif ! end of corrk … … 895 901 ! Transformation of the radiative tendencies 896 902 ! ------------------------------------------ 897 zplanck( 1:ngrid)=tsurf(1:ngrid)*tsurf(1:ngrid)898 zplanck( 1:ngrid)=emis(1:ngrid)*sigma*zplanck(1:ngrid)*zplanck(1:ngrid)899 fluxrad( 1:ngrid)=fluxrad_sky(1:ngrid)-zplanck(1:ngrid)900 pdt( 1:ngrid,1:nlayer)=pdt(1:ngrid,1:nlayer)+dtrad(1:ngrid,1:nlayer)903 zplanck(:)=tsurf(:)*tsurf(:) 904 zplanck(:)=emis(:)*sigma*zplanck(:)*zplanck(:) 905 fluxrad(:)=fluxrad_sky(:)-zplanck(:) 906 pdt(:,:)=pdt(:,:)+dtrad(:,:) 901 907 902 908 ! Test of energy conservation … … 931 937 if (calldifv) then 932 938 933 zflubid( 1:ngrid)=fluxrad(1:ngrid)+fluxgrd(1:ngrid)939 zflubid(:)=fluxrad(:)+fluxgrd(:) 934 940 935 941 ! JL12 the following if test is temporarily there to allow us to compare the old vdifc with turbdiff. … … 947 953 else 948 954 949 zdh( 1:ngrid,1:nlayer)=pdt(1:ngrid,1:nlayer)/zpopsk(1:ngrid,1:nlayer)955 zdh(:,:)=pdt(:,:)/zpopsk(:,:) 950 956 951 957 call vdifc(ngrid,nlayer,nq,zpopsk, & … … 958 964 taux,tauy,lastcall) 959 965 960 zdtdif( 1:ngrid,1:nlayer)=zdhdif(1:ngrid,1:nlayer)*zpopsk(1:ngrid,1:nlayer) ! for diagnostic only961 zdqevap( 1:ngrid,1:nlayer)=0.966 zdtdif(:,:)=zdhdif(:,:)*zpopsk(:,:) ! for diagnostic only 967 zdqevap(:,:)=0. 962 968 963 969 end if !end of 'UseTurbDiff' 964 970 965 971 966 pdv( 1:ngrid,1:nlayer)=pdv(1:ngrid,1:nlayer)+zdvdif(1:ngrid,1:nlayer)967 pdu( 1:ngrid,1:nlayer)=pdu(1:ngrid,1:nlayer)+zdudif(1:ngrid,1:nlayer)968 pdt( 1:ngrid,1:nlayer)=pdt(1:ngrid,1:nlayer)+zdtdif(1:ngrid,1:nlayer)969 zdtsurf( 1:ngrid)=zdtsurf(1:ngrid)+zdtsdif(1:ngrid)972 pdv(:,:)=pdv(:,:)+zdvdif(:,:) 973 pdu(:,:)=pdu(:,:)+zdudif(:,:) 974 pdt(:,:)=pdt(:,:)+zdtdif(:,:) 975 zdtsurf(:)=zdtsurf(:)+zdtsdif(:) 970 976 971 977 if (tracer) then 972 pdq( 1:ngrid,1:nlayer,1:nq)=pdq(1:ngrid,1:nlayer,1:nq)+ zdqdif(1:ngrid,1:nlayer,1:nq)973 dqsurf( 1:ngrid,1:nq)=dqsurf(1:ngrid,1:nq) + zdqsdif(1:ngrid,1:nq)978 pdq(:,:,:)=pdq(:,:,:)+ zdqdif(:,:,:) 979 dqsurf(:,:)=dqsurf(:,:) + zdqsdif(:,:) 974 980 end if ! of if (tracer) 975 981 … … 1010 1016 if(.not.newtonian)then 1011 1017 1012 zdtsurf( 1:ngrid) = zdtsurf(1:ngrid) + (fluxrad(1:ngrid) + fluxgrd(1:ngrid))/capcal(1:ngrid)1018 zdtsurf(:) = zdtsurf(:) + (fluxrad(:) + fluxgrd(:))/capcal(:) 1013 1019 1014 1020 endif … … 1023 1029 if(calladj) then 1024 1030 1025 zdh( 1:ngrid,1:nlayer) = pdt(1:ngrid,1:nlayer)/zpopsk(1:ngrid,1:nlayer)1026 zduadj( 1:ngrid,1:nlayer)=0.01027 zdvadj( 1:ngrid,1:nlayer)=0.01028 zdhadj( 1:ngrid,1:nlayer)=0.01031 zdh(:,:) = pdt(:,:)/zpopsk(:,:) 1032 zduadj(:,:)=0.0 1033 zdvadj(:,:)=0.0 1034 zdhadj(:,:)=0.0 1029 1035 1030 1036 … … 1036 1042 zdqadj) 1037 1043 1038 pdu( 1:ngrid,1:nlayer) = pdu(1:ngrid,1:nlayer) + zduadj(1:ngrid,1:nlayer)1039 pdv( 1:ngrid,1:nlayer) = pdv(1:ngrid,1:nlayer) + zdvadj(1:ngrid,1:nlayer)1040 pdt( 1:ngrid,1:nlayer) = pdt(1:ngrid,1:nlayer) + zdhadj(1:ngrid,1:nlayer)*zpopsk(1:ngrid,1:nlayer)1041 zdtadj( 1:ngrid,1:nlayer) = zdhadj(1:ngrid,1:nlayer)*zpopsk(1:ngrid,1:nlayer) ! for diagnostic only1044 pdu(:,:) = pdu(:,:) + zduadj(:,:) 1045 pdv(:,:) = pdv(:,:) + zdvadj(:,:) 1046 pdt(:,:) = pdt(:,:) + zdhadj(:,:)*zpopsk(:,:) 1047 zdtadj(:,:) = zdhadj(:,:)*zpopsk(:,:) ! for diagnostic only 1042 1048 1043 1049 if(tracer) then 1044 pdq( 1:ngrid,1:nlayer,1:nq) = pdq(1:ngrid,1:nlayer,1:nq) + zdqadj(1:ngrid,1:nlayer,1:nq)1050 pdq(:,:,:) = pdq(:,:,:) + zdqadj(:,:,:) 1045 1051 end if 1046 1052 … … 1060 1066 1061 1067 if (tracer) then 1062 1068 1063 1069 ! ------------------------- 1064 1070 ! V.1. Chemistry … … 1067 1073 if (callchim) then 1068 1074 1069 ! Convert to molar fraction 1070 if (moyzon_ch) then 1071 do iq = 1,nkim 1072 ychim(:,:,iq) = zqfibar(:,:,iq+nmicro) / rat_mmol(iq+nmicro) 1073 enddo 1074 else 1075 do iq = 1,nkim 1076 ychim(:,:,iq) = pq(:,:,iq+nmicro) / rat_mmol(iq+nmicro) 1077 enddo 1078 endif 1079 1080 ! Condensation tendency after the transport 1075 ! o. Convert updated tracers to molar fraction 1076 ! ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ 1077 do iq = 1,nkim 1078 ychim(:,:,iq) = ( pq(:,:,iq+nmicro) + pdq(:,:,iq+nmicro) ) / rat_mmol(iq+nmicro) 1079 enddo 1080 1081 ! i. Condensation after the transport 1082 ! ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ 1081 1083 do iq=1,nkim 1082 1084 do l=1,nlayer 1083 1085 do ig=1,ngrid 1084 1086 if ( ychim(ig,l,iq).gt.qysat(l,iq) ) then 1085 dyccond(ig,l,iq+nmicro)= ( -ychim(ig,l,iq)+qysat(l,iq) ) / ptimestep 1087 dyccond(ig,l,iq+nmicro) = ( -ychim(ig,l,iq)+qysat(l,iq) ) / ptimestep 1088 else 1089 dyccond(ig,l,iq+nmicro) = 0.0 ! since array not saved 1086 1090 endif 1087 1091 enddo … … 1089 1093 enddo 1090 1094 1091 if ( callclouds ) dyccond(:,:,ices_indx) = 0.0 ! Condensation will be calculated in the cloud microphysics 1092 1095 if ( callclouds ) dyccond(:,:,ices_indx) = 0.0 ! Condensation will be calculated in the cloud microphysics 1096 1097 do iq=1,nkim 1098 ychim(:,:,iq) = ychim(:,:,iq) + dyccond(:,:,iq+nmicro) ! update molar ychim for following calchim 1099 zdqcond(:,:,iq+nmicro) = dyccond(:,:,iq+nmicro)*rat_mmol(iq+nmicro) ! convert tendencies to mass mixing ratio 1100 enddo 1101 1102 pdq(:,:,:) = pdq(:,:,:) + zdqcond(:,:,:) 1103 1104 ! ii. Photochemistry 1105 ! ~~~~~~~~~~~~~~~~~~ 1093 1106 if( mod(icount-1,ichim).eq.0. ) then 1094 1107 1095 1108 print *, "We enter in the chemistry ..." 1096 1109 1097 if (moyzon_ch.and.(ngrid.ne.1)) then ! 2D zonally averaged chemistry !! SEEMS TO CRASH DON'T USE IT !! 1098 call calchim(ngrid,ychim,declin,zls,ctimestep,ztfibar,zphibar, & 1110 if (moyzon_ch) then ! 2D zonally averaged chemistry 1111 1112 do iq = 1,nkim ! In this case we send zonal average from dynamics to chem. module 1113 ychim(:,:,iq) = zqfibar(:,:,iq+nmicro) / rat_mmol(iq+nmicro) 1114 enddo 1115 1116 call calchim(ngrid,ychim,declin,ctimestep,ztfibar,zphibar, & 1099 1117 zplaybar,zplevbar,zzlaybar,zzlevbar,dycchi) 1118 1100 1119 else ! 3D chemistry (or 1D run) 1101 call calchim(ngrid,ychim,declin, zls,ctimestep,pt,pphi, &1120 call calchim(ngrid,ychim,declin,ctimestep,pt,pphi, & 1102 1121 pplay,pplev,zzlay,zzlev,dycchi) 1103 endif 1104 1122 endif ! if moyzon 1105 1123 endif 1106 1124 1107 ! TEMPORARY COMMENT1108 ! These conversions as well as 2D/1D should be put in phytrac1109 ! ( GCM-friendly tracers and tendencies -> format for photochem and microphys )1110 1111 ! We convert tendencies to mass mixing ratio1112 1125 do iq=1,nkim 1113 zdqchi(:,:,iq+nmicro) = dycchi(:,:,iq) * rat_mmol(iq+nmicro)1114 zdqcond(:,:,iq+nmicro) = dyccond(:,:,iq+nmicro) * rat_mmol(iq+nmicro)1115 enddo1116 1117 pdq(1:ngrid,1:nlayer,1:nq) = pdq(1:ngrid,1:nlayer,1:nq) + &1118 zdqchi(1:ngrid,1:nlayer,1:nq) + zdqcond(1:ngrid,1:nlayer,1:nq) 1119 1126 zdqchi(:,:,iq+nmicro) = dycchi(:,:,iq)*rat_mmol(iq+nmicro) ! convert tendencies to mass mixing ratio 1127 1128 where( (pq(:,:,iq+nmicro)+zdqchi(:,:,iq+nmicro) ).LT.1e-40) & ! When using zonal means we set the same tendency 1129 zdqchi(:,:,iq+nmicro) = 1e-40 - ( pq(:,:,iq+nmicro) ) ! everywhere in longitude -> can lead to negs ! 1130 enddo 1131 1132 pdq(:,:,:) = pdq(:,:,:) + zdqchi(:,:,:) 1120 1133 1121 1134 endif ! end of 'callchim' … … 1127 1140 if (callmufi) then 1128 1141 #ifdef USE_QTEST 1129 call calmufi(ptimestep,pplev,zzlev,pplay,zzlay,pt,tpq,zdqmufi) 1130 tpq(:,:,:) = tpq(:,:,:) + zdqmufi(:,:,:)*ptimestep ! only manipulation of tpq->*ptimesep here 1142 dtpq(:,:,:) = 0.0 ! we want tpq to go only through mufi 1143 call calmufi(ptimestep,pplev,zzlev,pplay,zzlay,pt,tpq,dtpq,zdqmufi) 1144 tpq(:,:,:) = tpq(:,:,:) + zdqmufi(:,:,:)*ptimestep ! only manipulation of tpq->*ptimestep here 1131 1145 #else 1132 ! Inside this routine we will split 2D->1D, intensive->extensive and separate different types of tracers 1133 ! Should be put in phytrac 1134 1135 if (moyzon_mu.and.(ngrid.ne.1)) then ! 2D zonally averaged microphysics !! SEEMS TO CRASH DON'T USE IT !! 1136 call calmufi(ptimestep,zplevbar,zzlevbar,zplaybar,zzlaybar,ztfibar,zqfibar,zdqmufi) 1137 else ! 3D microphysics (or 1D run) 1138 call calmufi(ptimestep,pplev,zzlev,pplay,zzlay,pt,pq,zdqmufi) 1139 endif 1140 1141 pdq(1:ngrid,1:nlayer,1:nq) = pdq(1:ngrid,1:nlayer,1:nq) + zdqmufi(1:ngrid,1:nlayer,1:nq) 1146 call calmufi(ptimestep,pplev,zzlev,pplay,zzlay,pt,pq,pdq,zdqmufi) 1147 pdq(:,:,:) = pdq(:,:,:) + zdqmufi(:,:,:) 1142 1148 #endif 1143 endif ! end of 'callmufi'1149 endif 1144 1150 1145 1151 ! --------------- … … 1150 1156 if(mass_redistrib) then 1151 1157 1152 zdmassmr( 1:ngrid,1:nlayer) = mass(1:ngrid,1:nlayer) * zdqevap(1:ngrid,1:nlayer)1158 zdmassmr(:,:) = mass(:,:) * zdqevap(:,:) 1153 1159 1154 1160 do ig = 1, ngrid 1155 zdmassmr_col(ig)=SUM(zdmassmr(ig, 1:nlayer))1161 zdmassmr_col(ig)=SUM(zdmassmr(ig,:)) 1156 1162 enddo 1157 1163 … … 1165 1171 zdtmr,zdtsurfmr,zdpsrfmr,zdumr,zdvmr,zdqmr,zdqsurfmr) 1166 1172 1167 pdq( 1:ngrid,1:nlayer,1:nq) = pdq(1:ngrid,1:nlayer,1:nq) + zdqmr(1:ngrid,1:nlayer,1:nq)1168 dqsurf( 1:ngrid,1:nq) = dqsurf(1:ngrid,1:nq) + zdqsurfmr(1:ngrid,1:nq)1169 pdt( 1:ngrid,1:nlayer) = pdt(1:ngrid,1:nlayer) + zdtmr(1:ngrid,1:nlayer)1170 pdu( 1:ngrid,1:nlayer) = pdu(1:ngrid,1:nlayer) + zdumr(1:ngrid,1:nlayer)1171 pdv( 1:ngrid,1:nlayer) = pdv(1:ngrid,1:nlayer) + zdvmr(1:ngrid,1:nlayer)1172 pdpsrf( 1:ngrid) = pdpsrf(1:ngrid) + zdpsrfmr(1:ngrid)1173 zdtsurf( 1:ngrid) = zdtsurf(1:ngrid) + zdtsurfmr(1:ngrid)1173 pdq(:,:,:) = pdq(:,:,:) + zdqmr(:,:,:) 1174 dqsurf(:,:) = dqsurf(:,:) + zdqsurfmr(:,:) 1175 pdt(:,:) = pdt(:,:) + zdtmr(:,:) 1176 pdu(:,:) = pdu(:,:) + zdumr(:,:) 1177 pdv(:,:) = pdv(:,:) + zdvmr(:,:) 1178 pdpsrf(:) = pdpsrf(:) + zdpsrfmr(:) 1179 zdtsurf(:) = zdtsurf(:) + zdtsurfmr(:) 1174 1180 1175 1181 endif … … 1179 1185 ! ----------------------------- 1180 1186 1181 qsurf( 1:ngrid,1:nq) = qsurf(1:ngrid,1:nq) + ptimestep*dqsurf(1:ngrid,1:nq)1187 qsurf(:,:) = qsurf(:,:) + ptimestep*dqsurf(:,:) 1182 1188 1183 1189 ! Add qsurf to qsurf_hist, which is what we save in diagfi.nc. At the same time, we set the water … … 1195 1201 ! Increment surface temperature 1196 1202 1197 tsurf( 1:ngrid)=tsurf(1:ngrid)+ptimestep*zdtsurf(1:ngrid)1203 tsurf(:)=tsurf(:)+ptimestep*zdtsurf(:) 1198 1204 1199 1205 ! Compute soil temperatures and subsurface heat flux. … … 1220 1226 1221 1227 ! Temperature, zonal and meridional winds. 1222 zt( 1:ngrid,1:nlayer) = pt(1:ngrid,1:nlayer) + pdt(1:ngrid,1:nlayer)*ptimestep1223 zu( 1:ngrid,1:nlayer) = pu(1:ngrid,1:nlayer) + pdu(1:ngrid,1:nlayer)*ptimestep1224 zv( 1:ngrid,1:nlayer) = pv(1:ngrid,1:nlayer) + pdv(1:ngrid,1:nlayer)*ptimestep1228 zt(:,:) = pt(:,:) + pdt(:,:)*ptimestep 1229 zu(:,:) = pu(:,:) + pdu(:,:)*ptimestep 1230 zv(:,:) = pv(:,:) + pdv(:,:)*ptimestep 1225 1231 1226 1232 ! Diagnostic. 1227 zdtdyn( 1:ngrid,1:nlayer) = (pt(1:ngrid,1:nlayer)-ztprevious(1:ngrid,1:nlayer)) / ptimestep1228 ztprevious( 1:ngrid,1:nlayer) = zt(1:ngrid,1:nlayer)1229 1230 zdudyn( 1:ngrid,1:nlayer) = (pu(1:ngrid,1:nlayer)-zuprevious(1:ngrid,1:nlayer)) / ptimestep1231 zuprevious( 1:ngrid,1:nlayer) = zu(1:ngrid,1:nlayer)1233 zdtdyn(:,:) = (pt(:,:)-ztprevious(:,:)) / ptimestep 1234 ztprevious(:,:) = zt(:,:) 1235 1236 zdudyn(:,:) = (pu(:,:)-zuprevious(:,:)) / ptimestep 1237 zuprevious(:,:) = zu(:,:) 1232 1238 1233 1239 if(firstcall)then 1234 zdtdyn( 1:ngrid,1:nlayer)=0.01235 zdudyn( 1:ngrid,1:nlayer)=0.01240 zdtdyn(:,:)=0.0 1241 zdudyn(:,:)=0.0 1236 1242 endif 1237 1243 … … 1242 1248 1243 1249 ! Tracers. 1244 zq( 1:ngrid,1:nlayer,1:nq) = pq(1:ngrid,1:nlayer,1:nq) + pdq(1:ngrid,1:nlayer,1:nq)*ptimestep1250 zq(:,:,:) = pq(:,:,:) + pdq(:,:,:)*ptimestep 1245 1251 1246 1252 ! Surface pressure. 1247 ps( 1:ngrid) = pplev(1:ngrid,1) + pdpsrf(1:ngrid)*ptimestep1253 ps(:) = pplev(:,1) + pdpsrf(:)*ptimestep 1248 1254 1249 1255
Note: See TracChangeset
for help on using the changeset viewer.