Changeset 4383


Ignore:
Timestamp:
Jan 13, 2023, 12:58:50 PM (16 months ago)
Author:
evignon
Message:

on renomme la variable theta de thermcell_updown_dq en trac et
on commente un peu l'entete du fichier

File:
1 edited

Legend:

Unmodified
Added
Removed
  • LMDZ6/trunk/libf/phylmd/thermcell_down.F90

    r4381 r4383  
    1    SUBROUTINE thermcell_updown_dq(ngrid,nlay,ptimestep,lmax,eup,dup,edn,ddn,masse,theta)
    2 
    3 !--------------------------------------------------------------
    4 ! thermcell_updown_dq: calcul du transport d'un traceur en pr??sence
    5 ! d'up/down drafts
    6 !
    7 !--------------------------------------------------------------
    8 
    9    ! Suite du travail :
    10    ! Calculer les tendances d'un traceur (ici theta) en tenant compte
    11    ! des up et down drafts et de la subsidence compensatoire.
     1   SUBROUTINE thermcell_updown_dq(ngrid,nlay,ptimestep,lmax,eup,dup,edn,ddn,masse,trac)
     2
     3!-----------------------------------------------------------------
     4! thermcell_updown_dq: computes the tendency of tracers associated
     5! with the presence of convective up/down drafts
     6! This routine that has been collectively written during the
     7! "ateliers downdrafts" in 2022/2023
     8! Maelle, Frédéric, Catherine, Fleur, Florent, Etienne
     9!------------------------------------------------------------------
    1210
    1311
    1412   IMPLICIT NONE
    1513
    16 ! arguments
    17 
    18    integer,intent(in) :: ngrid,nlay
    19    real,intent(in) :: ptimestep
    20    real,intent(in), dimension(ngrid,nlay) :: eup,dup,edn,ddn,masse
    21    real,intent(inout), dimension(ngrid,nlay) :: theta
    22    integer, intent(in), dimension(ngrid) :: lmax
     14! declarations
     15!==============================================================
     16
     17! input/output
     18
     19   integer,intent(in)  :: ngrid ! number of horizontal grid points
     20   integer, intent(in) :: nlay  ! number of vertical layers
     21   real,intent(in) :: ptimestep ! time step of the physics [s]
     22   real,intent(in), dimension(ngrid,nlay) :: eup ! entrainment to updrafts * dz [same unit as flux]
     23   real,intent(in), dimension(ngrid,nlay) :: dup ! detrainment from updrafts * dz [same unit as flux]
     24   real,intent(in), dimension(ngrid,nlay) :: edn ! entrainment to downdrafts * dz [same unit as flux]
     25   real,intent(in), dimension(ngrid,nlay) :: ddn ! detrainment from downdrafts * dz [same unit as flux]
     26   real,intent(in), dimension(ngrid,nlay) :: masse ! mass of layers = rho dz
     27   real,intent(inout), dimension(ngrid,nlay) :: trac ! tracer
     28   integer, intent(in), dimension(ngrid) :: lmax ! max level index at which downdraft are present
    2329
    2430   
     
    2632
    2733   real, dimension(ngrid,nlay+1) :: fup,fdn,fthu,fthd,fthe,fthtot
    28    real, dimension(ngrid,nlay) :: thetau,thetad,dtheta
     34   real, dimension(ngrid,nlay) :: tracu,tracd,dtrac
    2935   real :: www
    30 
    3136   integer ig,ilay
    3237
     
    3742   fthe(:,:)=0.
    3843   fthtot(:,:)=0.
    39    thetad(:,:)=0.
    40    thetau(:,:)=0.
     44   tracd(:,:)=0.
     45   tracu(:,:)=0.
    4146
    4247   ! lmax : indice tel que fu(kmax+1)=0
    4348   
    44    ! Dans ce cas, pas besoin d'initialiser thetad(lmax) ( =theta(lmax) )
     49   ! Dans ce cas, pas besoin d'initialiser tracd(lmax) ( =trac(lmax) )
    4550
    4651   print*,'ON PASSE BIEN PAR LA CCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCC'
     
    5156            fdn(ig,ilay)=fdn(ig,ilay+1)+edn(ig,ilay)-ddn(ig,ilay)
    5257            if ( 1 == 0 ) then
    53                thetad(ig,ilay)=( fdn(ig,ilay+1)*thetad(ig,ilay+1) + edn(ig,ilay)*theta(ig,ilay) ) / (fdn(ig,ilay)+ddn(ig,ilay))
     58               tracd(ig,ilay)=( fdn(ig,ilay+1)*tracd(ig,ilay+1) + edn(ig,ilay)*trac(ig,ilay) ) / (fdn(ig,ilay)+ddn(ig,ilay))
    5459            else
    5560               www=fdn(ig,ilay+1)/ (fdn(ig,ilay)+ddn(ig,ilay))
    56                thetad(ig,ilay)=www*thetad(ig,ilay+1) + (1.-www)*theta(ig,ilay)
     61               tracd(ig,ilay)=www*tracd(ig,ilay+1) + (1.-www)*trac(ig,ilay)
    5762            endif
    5863         endif
     
    6671            fup(ig,ilay+1)=fup(ig,ilay)+eup(ig,ilay)-dup(ig,ilay)
    6772            if (ilay == 1 ) then
    68                thetau(ig,ilay)=theta(ig,ilay)
     73               tracu(ig,ilay)=trac(ig,ilay)
    6974            else
    70                !thetau(ig,ilay)=( fup(ig,ilay)*thetau(ig,ilay-1) + eup(ig,ilay)*theta(ig,ilay) ) / (fup(ig,ilay+1)+dup(ig,ilay))
     75               !tracu(ig,ilay)=( fup(ig,ilay)*tracu(ig,ilay-1) + eup(ig,ilay)*trac(ig,ilay) ) / (fup(ig,ilay+1)+dup(ig,ilay))
    7176               !eup(ig,ilay)=fup(ig,ilay+1)-fup(ig,ilay)+dup(ig,ilay)
    72                !thetau(ig,ilay)=( fup(ig,ilay)*thetau(ig,ilay-1) + (fup(ig,ilay+1)-fup(ig,ilay)+dup(ig,ilay))*theta(ig,ilay) ) / (fup(ig,ilay+1)+dup(ig,ilay))
     77               !tracu(ig,ilay)=( fup(ig,ilay)*tracu(ig,ilay-1) + (fup(ig,ilay+1)-fup(ig,ilay)+dup(ig,ilay))*trac(ig,ilay) ) / (fup(ig,ilay+1)+dup(ig,ilay))
    7378               www=fup(ig,ilay)/(fup(ig,ilay+1)+dup(ig,ilay))
    7479               !1-www=(fup(ig,ilay+1)+dup(ig,ilay)-fup(ig,ilay))/(fup(ig,ilay+1)+dup(ig,ilay))
    75                thetau(ig,ilay)=www*thetau(ig,ilay-1)+(1.-www)*theta(ig,ilay)
     80               tracu(ig,ilay)=www*tracu(ig,ilay-1)+(1.-www)*trac(ig,ilay)
    7681            endif
    7782         endif
     
    8186   do ilay=2,nlay,1
    8287     do ig=1,ngrid
    83        fthu(ig,ilay)=fup(ig,ilay)*thetau(ig,ilay-1)
    84        fthd(ig,ilay)=-fdn(ig,ilay)*thetad(ig,ilay)
    85        !!!!ATTENTION HYPOTHESE de FLUX COMPENSATOIRE DESCENDANT ET DONC comme schema amont on va chercher theta au dessus!!!!!
     88       fthu(ig,ilay)=fup(ig,ilay)*tracu(ig,ilay-1)
     89       fthd(ig,ilay)=-fdn(ig,ilay)*tracd(ig,ilay)
     90       !!!!ATTENTION HYPOTHESE de FLUX COMPENSATOIRE DESCENDANT ET DONC comme schema amont on va chercher trac au dessus!!!!!
    8691       !!!! si ce n'est pas le cas on stoppe le code !!!!
    8792       if (fup(ig,ilay)-fdn(ig,ilay) .lt. 0.) then
     
    8994          stop         
    9095       endif
    91        fthe(ig,ilay)=-(fup(ig,ilay)-fdn(ig,ilay))*theta(ig,ilay)
     96       fthe(ig,ilay)=-(fup(ig,ilay)-fdn(ig,ilay))*trac(ig,ilay)
    9297       fthtot(ig,ilay)=fthu(ig,ilay)+fthd(ig,ilay)+fthe(ig,ilay)
    9398     enddo
    9499   enddo
    95    !Boucle pour calculer theta
     100   !Boucle pour calculer trac
    96101   do ilay=1,nlay,1
    97102     do ig=1,ngrid
    98        dtheta(ig,ilay)=(fthtot(ig,ilay)-fthtot(ig,ilay+1))*(ptimestep/masse(ig,ilay))
    99 !       theta(ig,ilay)=theta(ig,ilay) + (fthtot(ig,ilay)-fthtot(ig,ilay+1))*(ptimestep/masse(ig,ilay))
     103       dtrac(ig,ilay)=(fthtot(ig,ilay)-fthtot(ig,ilay+1))*(ptimestep/masse(ig,ilay))
     104!       trac(ig,ilay)=trac(ig,ilay) + (fthtot(ig,ilay)-fthtot(ig,ilay+1))*(ptimestep/masse(ig,ilay))
    100105     enddo
    101106   enddo
     
    103108    do ilay=1,nlay,1
    104109     do ig=1,ngrid
    105        theta(ig,ilay)=theta(ig,ilay) + (fup(ig,ilay)*thetau(ig,ilay-1)-fup(ig,ilay+1)*thetau(ig,ilay) + &
    106        & (fup(ig,ilay+1)+fdn(ig,ilay+1))*theta(ig,ilay+1) - (fup(ig,ilay)+fdn(ig,ilay))*theta(ig,ilay) + &
    107        & fdn(ig,ilay+1)*thetad(ig,ilay+1)-fdn(ig,ilay)*thetad(ig,ilay))*(ptimestep/masse(ig,ilay))
     110       trac(ig,ilay)=trac(ig,ilay) + (fup(ig,ilay)*tracu(ig,ilay-1)-fup(ig,ilay+1)*tracu(ig,ilay) + &
     111       & (fup(ig,ilay+1)+fdn(ig,ilay+1))*trac(ig,ilay+1) - (fup(ig,ilay)+fdn(ig,ilay))*trac(ig,ilay) + &
     112       & fdn(ig,ilay+1)*tracd(ig,ilay+1)-fdn(ig,ilay)*tracd(ig,ilay))*(ptimestep/masse(ig,ilay))
    108113     enddo
    109114    enddo
    110115   endif
    111116! Il reste a coder :
    112 ! d(rho theta)/dt = - d/dz(rho w'theta')
    113 ! d(theta)/dt = -1/rho * d/dz(rho w'theta')
     117! d(rho trac)/dt = - d/dz(rho w'trac')
     118! d(trac)/dt = -1/rho * d/dz(rho w'trac')
    114119! hydrostatique : dp - rho g dz
    115120! dz = - dp /  (rho g)
    116121! 1 / dz = - (rho g ) / dp
    117122
    118 ! d(theta)/dt = -1/rho * d/dp(rho w'theta') * (- rho g )
    119 ! d(theta)/dt =  d/dp(rho w'theta') * g
    120 
    121 
    122 ! ----> calculer d/dz(w'theta')
    123 ! w'theta' = alpha_up*(w_up-w_bar)*(theta_up-theta_bar)
    124 !          + alpha_down*(w_down-w_bar)*(theta_down-theta_bar)
    125 !          + (1-alpha_up-alpha_down)*(w_env-w_bar)*(theta_env-theta_bar)
     123! d(trac)/dt = -1/rho * d/dp(rho w'trac') * (- rho g )
     124! d(trac)/dt =  d/dp(rho w'trac') * g
     125
     126
     127! ----> calculer d/dz(w'trac')
     128! w'trac' = alpha_up*(w_up-w_bar)*(trac_up-trac_bar)
     129!          + alpha_down*(w_down-w_bar)*(trac_down-trac_bar)
     130!          + (1-alpha_up-alpha_down)*(w_env-w_bar)*(trac_env-trac_bar)
    126131! avec w_bar=0=alpha_up*w_up+alpha_down*w_dn+(1-alpha_up-alpha_down)w_env
    127132! -> w_env= - (alpha_up*w_up+alpha_down*w_dn)/(1-alpha_up-alpha_down)
    128 !  et on a : theta_bar=alpha_up*theta_up + alpha_down*theta_dn + (1-alpha_up-alpha_down)theta_env
     133!  et on a : trac_bar=alpha_up*trac_up + alpha_down*trac_dn + (1-alpha_up-alpha_down)trac_env
    129134!
    130 ! w'theta' = alpha_up*w_up*(theta_up-theta_bar)
    131 !          + alpha_down*w_down*(theta_down-theta_bar)
    132 !          + (1-alpha_up-alpha_down)*w_env*(theta_env-theta_bar)
    133 
    134 ! rho*w'theta' = rho*alpha_up*w_up*(theta_up-theta_bar)
    135 !              + rho*alpha_down*w_down*(theta_down-theta_bar)
    136 !              + rho*(1-alpha_up-alpha_down)*w_env*(theta_env-theta_bar)
     135! w'trac' = alpha_up*w_up*(trac_up-trac_bar)
     136!          + alpha_down*w_down*(trac_down-trac_bar)
     137!          + (1-alpha_up-alpha_down)*w_env*(trac_env-trac_bar)
     138
     139! rho*w'trac' = rho*alpha_up*w_up*(trac_up-trac_bar)
     140!              + rho*alpha_down*w_down*(trac_down-trac_bar)
     141!              + rho*(1-alpha_up-alpha_down)*w_env*(trac_env-trac_bar)
    137142!
    138143
    139 ! rho*w'theta' = fup*(theta_up-theta_bar)
    140 !              + fdn*(theta_down-theta_bar)
    141 !              - rho*(alpha_up*w_up+alpha_down*w_dn)*(theta_env-theta_bar)
    142 
    143 !              - rho*(alpha_up*w_up+alpha_down*w_dn)*((theta_bar-alpha_up*theta_up-alpha_down*theta_down) /(1-alpha_up-alpha_down)- theta_bar)
    144 !              - rho*(alpha_up*w_up+alpha_down*w_dn)*(theta_bar*(1/(1-alpha_up-alpha_down)-1) - (alpha_up*theta_up+alpha_down*theta_down) /(1-alpha_up-alpha_down))
    145 
    146 ! rho*w'theta' = fup*(theta_up-theta_bar)
    147 !              + fdn*(theta_down-theta_bar)
    148 !              - (fup+fdn)*(theta_env-theta_bar)
    149 
    150 
    151 ! rho*w'theta' = fup*(theta_up-theta_bar)
    152 !              + fdn*(theta_down-theta_bar)
    153 !              - (fup+fdn)*( (theta_bar-alpha_up*theta_up-alpha_down*theta_down) /(1-alpha_up-alpha_down) - theta_bar)
     144! rho*w'trac' = fup*(trac_up-trac_bar)
     145!              + fdn*(trac_down-trac_bar)
     146!              - rho*(alpha_up*w_up+alpha_down*w_dn)*(trac_env-trac_bar)
     147
     148!              - rho*(alpha_up*w_up+alpha_down*w_dn)*((trac_bar-alpha_up*trac_up-alpha_down*trac_down) /(1-alpha_up-alpha_down)- trac_bar)
     149!              - rho*(alpha_up*w_up+alpha_down*w_dn)*(trac_bar*(1/(1-alpha_up-alpha_down)-1) - (alpha_up*trac_up+alpha_down*trac_down) /(1-alpha_up-alpha_down))
     150
     151! rho*w'trac' = fup*(trac_up-trac_bar)
     152!              + fdn*(trac_down-trac_bar)
     153!              - (fup+fdn)*(trac_env-trac_bar)
     154
     155
     156! rho*w'trac' = fup*(trac_up-trac_bar)
     157!              + fdn*(trac_down-trac_bar)
     158!              - (fup+fdn)*( (trac_bar-alpha_up*trac_up-alpha_down*trac_down) /(1-alpha_up-alpha_down) - trac_bar)
    154159
    155160!!! hypoth??se : alpha_up+alpha_down << 1 -> 1/(1-alpha_up-alpha_down) ~ 1
    156161
    157 ! rho*w'theta' = fup*(theta_up-theta_bar)
    158 
    159 !              + fdn*(theta_down-theta_bar)
    160 !              + (fup+fdn)*(alpha_up*theta_up+alpha_down*theta_down)
    161 
    162 ! d(theta)/dt= -1/rho d/dz(rho*w'theta')
     162! rho*w'trac' = fup*(trac_up-trac_bar)
     163
     164!              + fdn*(trac_down-trac_bar)
     165!              + (fup+fdn)*(alpha_up*trac_up+alpha_down*trac_down)
     166
     167! d(trac)/dt= -1/rho d/dz(rho*w'trac')
    163168! choix de schema temporel (euler explicite)
    164 ! (theta(t,k)-theta(t-1,k))/dt = f(t-1,k)
    165 ! (theta(t,k)-theta(t-1,k))/dt = f(t,k) ---> euler implicite
     169! (trac(t,k)-trac(t-1,k))/dt = f(t-1,k)
     170! (trac(t,k)-trac(t-1,k))/dt = f(t,k) ---> euler implicite
    166171! -----> on choisit explicite en temps
    167172
    168173!dans le cas d'une ascendance sans downdraft :
    169 ! d/dz(rho*w'theta') = fup(k)*qa(k-1) -fup(k+1)*qa(k)
    170 
    171 !(rho*w'theta'(k+1)-rho*w'theta'(k))/dz = fup(k)thetau(k-1)-fup(k+1)thetaup(k) + (fup+fdn)(k+1)*theta_env(k+1) - (fup+fdn)(k)*theta_env(k) + fdn(k+1) thetadn(k+1)
    172 !                   - fdn(k) thetadn(k)
    173 
    174 ! en continue on a  : d(theta)/dt = -1/rho * d/dz(rho w'theta')
     174! d/dz(rho*w'trac') = fup(k)*qa(k-1) -fup(k+1)*qa(k)
     175
     176!(rho*w'trac'(k+1)-rho*w'trac'(k))/dz = fup(k)tracu(k-1)-fup(k+1)tracup(k) + (fup+fdn)(k+1)*trac_env(k+1) - (fup+fdn)(k)*trac_env(k) + fdn(k+1) tracdn(k+1)
     177!                   - fdn(k) tracdn(k)
     178
     179! en continue on a  : d(trac)/dt = -1/rho * d/dz(rho w'trac')
    175180! en discretis?? on a :
    176 ! (theta(t,k)-theta(t-1,k))/dt = -1/rho * rho*w'theta'(k+1)-rho*w'theta'(k))/dz
    177 ! theta(t,k) = theta(t-1,k) - dt/rho * (rho*w'theta'(k+1)-rho*w'theta'(k))/dz
    178 ! theta(t,k) = theta(t-1,k) - dt/rho * [fup(k)thetau(k-1)-fup(k+1)thetaup(k) + (fup+fdn)(k+1)*theta_env(k+1) -
    179 ! (fup+fdn)(k)*theta_env(k) + fdn(k+1) thetadn(k+1) - fdn(k) thetadn(k)]
    180 
    181 
    182 
    183 ! d(theta)/dt =  d/dp(rho w'theta') * g
    184 ! -1/rho * d/dz(rho w'theta') = g*d/dp(rho w'theta') = g * [fup(k)thetau(k-1)-fup(k+1)thetaup(k) + (fup+fdn)(k+1)*theta_env(k+1) -
    185 ! (fup+fdn)(k)*theta_env(k) + fdn(k+1) thetadn(k+1) - fdn(k) thetadn(k)]
     181! (trac(t,k)-trac(t-1,k))/dt = -1/rho * rho*w'trac'(k+1)-rho*w'trac'(k))/dz
     182! trac(t,k) = trac(t-1,k) - dt/rho * (rho*w'trac'(k+1)-rho*w'trac'(k))/dz
     183! trac(t,k) = trac(t-1,k) - dt/rho * [fup(k)tracu(k-1)-fup(k+1)tracup(k) + (fup+fdn)(k+1)*trac_env(k+1) -
     184! (fup+fdn)(k)*trac_env(k) + fdn(k+1) tracdn(k+1) - fdn(k) tracdn(k)]
     185
     186
     187
     188! d(trac)/dt =  d/dp(rho w'trac') * g
     189! -1/rho * d/dz(rho w'trac') = g*d/dp(rho w'trac') = g * [fup(k)tracu(k-1)-fup(k+1)tracup(k) + (fup+fdn)(k+1)*trac_env(k+1) -
     190! (fup+fdn)(k)*trac_env(k) + fdn(k+1) tracdn(k+1) - fdn(k) tracdn(k)]
    186191
    187192
    188193
    189194! choix de sch??ma spatial
    190 ! d/dz(rho*w'theta') = (rho*w'theta'(k+1)-rho*w'theta'(k))*dz
    191 ! d/dz(rho*w'theta') = (rho*w'theta'(k)-rho*w'theta'(k-1))*dz
    192 
    193 
    194 
    195 ! d/dz(rho*w'theta') = rho w'theta'(k+1)-rho w'theta'(k)
     195! d/dz(rho*w'trac') = (rho*w'trac'(k+1)-rho*w'trac'(k))*dz
     196! d/dz(rho*w'trac') = (rho*w'trac'(k)-rho*w'trac'(k-1))*dz
     197
     198
     199
     200! d/dz(rho*w'trac') = rho w'trac'(k+1)-rho w'trac'(k)
    196201
    197202!^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^
Note: See TracChangeset for help on using the changeset viewer.