Changeset 2330 for trunk/ICOSA_LMDZ


Ignore:
Timestamp:
May 25, 2020, 4:21:38 PM (4 years ago)
Author:
slebonnois
Message:

SL: modifications to be able to turn the physics with Cp(T)

File:
1 edited

Legend:

Unmodified
Added
Removed
  • trunk/ICOSA_LMDZ/src/phyvenus/interface_icosa_lmdz.f90

    r2319 r2330  
    326326    ! value in physics daysec=10087066.76s, important for solar radiation,
    327327    ! for the rest ptime/timeofday is what matters. To well estimate them,
    328     ! day_length must be multiple of dt*itau_physics. Error order:1e-4.
     328    ! day_length must be multiple of dt*itau_physics. Error order:1e-5.
    329329    day_length=10087000   
    330330    CALL getin('day_length',day_length)
     
    368368          ! we reset date to midnight at lon=0 in the physics
    369369          ptime=0.0
     370          day_ini=0
    370371        else
    371372          write(*,*)"Error: physics time step in startphy.nc is different"
     
    407408
    408409    ! Initialize some physical constants
    409     CALL suphec
     410    CALL suphec(cpp)
    410411
    411412    ! Initialize cpdet_phy module
    412     nu_venus=0.35
    413     t0_venus=460.
     413! FLAG CP CONSTANT OR NOT... (in LMDZ.COMMON: cpofT in gcm.def)
     414! here, it allows to run the physics with a variable Cp together with dynamics
     415! with constant Cp.
     416! Conversion Theta/T takes this into account (see below)
     417! IF CP(T)
     418!    nu_venus=0.35
     419!    t0_venus=460.
     420! IF CP CONSTANT
     421    nu_venus=0.
     422    t0_venus=0.
    414423    CALL init_cpdet_phy(cpp,nu_venus,t0_venus)
    415424 
     
    733742    USE wind_mod
    734743    USE omp_para
     744    USE cpdet_phy_mod, only: tpot2t
    735745    IMPLICIT NONE
    736746   
    737747    REAL(rstd) :: uc(3)
    738748    INTEGER :: i,j,ij,l
     749    REAL    :: tmpT(1),tmptheta(1),tmppk(1)
    739750   
    740751
     
    776787
    777788!   compute theta, temperature and pression at layer
     789! Conversion Theta/T takes Cp(T) into account
    778790    DO    l    = ll_begin, ll_end
    779791      DO j=jj_begin,jj_end
     
    781793          ij=(j-1)*iim+i
    782794          theta(ij,l) = theta_rhodz(ij,l,1) / ((p(ij,l)-p(ij,l+1))/g)
    783           Temp(ij,l) = theta(ij,l) * pk(ij,l) / cpp
     795          tmptheta(1) = theta(ij,l)
     796          tmppk(1)    = pk(ij,l)
     797          call tpot2t(1,tmptheta,tmpT,tmppk)
     798          Temp(ij,l)  = tmpT(1)
    784799          p_layer(ij,l)=preff*(pk(ij,l)/cpp)**(1./kappa)
    785800        ENDDO
     
    789804
    790805!!! Compute geopotential
     806!!  This computation (with teta = cp T / pk !) is identical to
     807!!     delta phi = R/RMD T/p delta p         (r=R/RMD=cpp*kappa)
    791808       
    792809  ! for first layer
     
    795812      DO i=ii_begin,ii_end
    796813        ij=(j-1)*iim+i
    797         phi( ij,1 ) = phis( ij ) + theta(ij,1) * ( pks(ij) - pk(ij,1) )
     814        phi( ij,1 ) = phis( ij ) + ( cpp*Temp(ij,1)/pk(ij,1) ) &
     815                                 * ( pks(ij) - pk(ij,1) )
    798816      ENDDO
    799817    ENDDO
     
    806824      DO i=ii_begin,ii_end
    807825        ij=(j-1)*iim+i
    808         phi(ij,l) =  0.5 * ( theta(ij,l)  + theta(ij,l-1) ) &
    809                          * (  pk(ij,l-1) -  pk(ij,l)    )
     826        phi(ij,l) =  0.5 *cpp*( Temp(ij,l)/pk(ij,l)+Temp(ij,l-1)/pk(ij,l-1) ) &
     827                         * ( pk(ij,l-1) - pk(ij,l) )
    810828      ENDDO
    811829    ENDDO
     
    855873    USE theta2theta_rhodz_mod
    856874    USE omp_para
     875    USE cpdet_phy_mod, only: t2tpot
    857876    IMPLICIT NONE
    858877      INTEGER :: i,j,ij,l,iq
     878      REAL    :: tmptheta(1),tmpT(1),tmppk(1)
    859879         
    860880      DO l=ll_begin,ll_end
     
    948968
    949969!   compute theta, temperature and pression at layer
     970! Conversion Theta/T takes Cp(T) into account
    950971    DO    l    = ll_begin, ll_end
    951972      DO j=jj_begin,jj_end
    952973        DO i=ii_begin,ii_end
    953974          ij=(j-1)*iim+i
    954           theta_rhodz(ij,l,1) = temp(ij,l) * ((p(ij,l)-p(ij,l+1))/g) / (pk(ij,l) / cpp )
     975          tmpT(1)  = Temp(ij,l)
     976          tmppk(1) = pk(ij,l)
     977          call t2tpot(1,tmpT,tmptheta,tmppk)
     978          theta_rhodz(ij,l,1) = tmptheta(1) * ((p(ij,l)-p(ij,l+1))/g)
    955979        ENDDO
    956980      ENDDO
Note: See TracChangeset for help on using the changeset viewer.