Ignore:
Timestamp:
May 3, 2019, 1:10:27 PM (6 years ago)
Author:
slebonnois
Message:

SL, Venus: new keys for flexibility cp0/cp(T) and Held-Suarez type physics

File:
1 edited

Legend:

Unmodified
Added
Removed
  • trunk/LMDZ.COMMON/libf/dyn3d_common/cpdet_mod.F90

    r1659 r2135  
    2121      SUBROUTINE ini_cpdet
    2222     
    23       USE control_mod, ONLY: planet_type
     23      USE control_mod, ONLY: cpofT
    2424      USE comconst_mod, ONLY: nu_venus,t0_venus
    2525      IMPLICIT none
     
    2828!======================================================================
    2929
    30       if (planet_type.eq."venus") then
     30      if (cpofT) then
    3131          nu_venus=0.35
    3232          t0_venus=460.
     
    4444      FUNCTION cpdet(t)
    4545
    46       USE control_mod, ONLY: planet_type
     46      USE control_mod, ONLY: cpofT
    4747      USE comconst_mod, ONLY: cpp,t0_venus,nu_venus
    4848      IMPLICIT none
     
    5353      real cpdet
    5454
    55       if (planet_type.eq."venus") then
     55      if (cpofT) then
    5656          cpdet = cpp*(t/t0_venus)**nu_venus
    5757      else
     
    7575!======================================================================
    7676
    77       USE control_mod, ONLY: planet_type
     77      USE control_mod, ONLY: cpofT
    7878      USE comconst_mod, ONLY: cpp,t0_venus,nu_venus
    7979
     
    107107!----------------------
    108108
    109       if (planet_type.eq."venus") then
     109      if (cpofT) then
    110110          yteta = yt**nu_venus                                          &
    111111     &            - nu_venus * t0_venus**nu_venus * log(ypk/cpp)
     
    136136!======================================================================
    137137
    138       USE control_mod, ONLY: planet_type
     138      USE control_mod, ONLY: cpofT
    139139      USE comconst_mod, ONLY: cpp,nu_venus,t0_venus
    140140
     
    168168!----------------------
    169169
    170       if (planet_type.eq."venus") then
     170      if (cpofT) then
    171171
    172172!----------------------
     
    193193      SUBROUTINE t2tpot_p(nlon,nlev, yt, yteta, ypk)
    194194! Parallel version of t2tpot, for an arbitrary number of columns
    195       USE control_mod, only : planet_type
     195      USE control_mod, only : cpofT
    196196      USE parallel_lmdz, only : OMP_CHUNK
    197197      USE comconst_mod, ONLY: cpp,nu_venus,t0_venus
     
    231231!----------------------
    232232
    233       if (planet_type.eq."venus") then
     233      if (cpofT) then
    234234!$OMP DO SCHEDULE(STATIC,OMP_CHUNK)
    235235        do l=1,nlev
     
    250250        enddo
    251251!$OMP END DO
    252       endif ! of if (planet_type.eq."venus")
     252      endif ! of if (cpofT)
    253253
    254254      end subroutine t2tpot_p
     
    261261! (more efficient than multiple calls to t2tpot_p() with slices of data)
    262262      USE parallel_lmdz, only : jj_begin,jj_end,OMP_CHUNK
    263       USE control_mod, only : planet_type
     263      USE control_mod, only : cpofT
    264264      USE comconst_mod, ONLY: cpp,nu_venus,t0_venus
    265265
     
    306306      jje=jj_end
    307307
    308       if (planet_type.eq."venus") then
     308      if (cpofT) then
    309309!$OMP DO SCHEDULE(STATIC,OMP_CHUNK)
    310310        do l=1,llm
     
    325325        enddo
    326326!$OMP END DO
    327       endif ! of if (planet_type.eq."venus")
     327      endif ! of if (cpofT)
    328328
    329329      end subroutine t2tpot_glo_p
     
    334334      SUBROUTINE tpot2t_p(nlon,nlev,yteta,yt,ypk)
    335335! Parallel version of tpot2t, for an arbitrary number of columns
    336       USE control_mod, only : planet_type
     336      USE control_mod, only : cpofT
    337337      USE parallel_lmdz, only : OMP_CHUNK
    338338      USE comconst_mod, ONLY: cpp,nu_venus,t0_venus
     
    373373!----------------------
    374374
    375       if (planet_type.eq."venus") then
     375      if (cpofT) then
    376376!$OMP DO SCHEDULE(STATIC,OMP_CHUNK)
    377377        do l=1,nlev
     
    391391        enddo
    392392!$OMP END DO
    393       endif ! of if (planet_type.eq."venus")
     393      endif ! of if (cpofT)
    394394      end subroutine tpot2t_p
    395395
     
    401401! (more efficient than multiple calls to tpot2t_p() with slices of data)
    402402      USE parallel_lmdz, only : jj_begin,jj_end,OMP_CHUNK
    403       USE control_mod, only : planet_type
     403      USE control_mod, only : cpofT
    404404      USE comconst_mod, ONLY: cpp,nu_venus,t0_venus
    405405
     
    446446      jje=jj_end
    447447
    448       if (planet_type.eq."venus") then
     448      if (cpofT) then
    449449!$OMP DO SCHEDULE(STATIC,OMP_CHUNK)
    450450        do l=1,llm
     
    465465        enddo
    466466!$OMP END DO
    467       endif ! of if (planet_type.eq."venus")
     467      endif ! of if (cpofT)
    468468      end subroutine tpot2t_glo_p
    469469
Note: See TracChangeset for help on using the changeset viewer.