source: trunk/LMDZ.COMMON/libf/dyn3d/cpdet_mod.F90 @ 1066

Last change on this file since 1066 was 1017, checked in by emillour, 12 years ago

Common dynamics: (and collateral adaptations in Venus physics)
Improved cpdet routines in and additional sponge mode:

  • Additionnal sponge mode (trigered with "callsponge" flag), in line with the one used in the Generic and Martian GCM. This sponge is called whenever there is a dissipation step.
  • Improvement of the cpdet routines : created routines tpot2t_glo_p and t2tpot_glo_p which handle fields on the whole dynamics (scaler) grid, which are more efficient than calling tpot2t_p or t2tpot_p with slabs of data (generated use of intermediate copies of these chunks of data at every call)
  • Turned cpdet.F into a module cpdet_mod.F90 (and correspondingly adapted all routines in the Venus physics).

EM

File size: 4.0 KB
Line 
1      module cpdet_mod
2
3      implicit none
4
5! ADAPTATION OF GCM TO CP(T)
6!======================================================================
7! S. Lebonnois, 10/2010
8!
9! Cp must be computed using cpdet(t) to be valid
10!
11! The Exner function is still pk = RCPD*(play/pref)**RKAPPA
12! (RCPD=cpp, RKAPPA=kappa)
13!
14! One goes from T to teta (potential temperature) using t2tpot(t,teta,pk)
15! One goes from teta to T using tpot2t(teta,t,pk)
16!
17!======================================================================
18
19      contains
20
21      SUBROUTINE ini_cpdet
22     
23      USE control_mod, ONLY: planet_type
24      IMPLICIT none
25!======================================================================
26! Initialization of nu_venus and t0_venus
27!======================================================================
28
29! for cpp, nu_venus and t0_venus:
30#include "comconst.h"
31
32      if (planet_type.eq."venus") then
33          nu_venus=0.35
34          t0_venus=460.
35      else
36          nu_venus=0.
37          t0_venus=0.
38      endif
39
40      return
41      end subroutine ini_cpdet
42
43!======================================================================
44!======================================================================
45
46      FUNCTION cpdet(t)
47
48      USE control_mod, ONLY: planet_type
49      IMPLICIT none
50
51! for cpp, nu_venus and t0_venus:
52#include "comconst.h"
53
54      real,intent(in) :: t
55      real cpdet
56
57      if (planet_type.eq."venus") then
58          cpdet = cpp*(t/t0_venus)**nu_venus
59      else
60          cpdet = cpp
61      endif
62
63      return
64      end function cpdet
65     
66!======================================================================
67!======================================================================
68
69      SUBROUTINE t2tpot(npoints, yt, yteta, ypk)
70!======================================================================
71! Arguments:
72!
73! yt   --------input-R- Temperature
74! yteta-------output-R- Temperature potentielle
75! ypk  --------input-R- Fonction d'Exner: RCPD*(pplay/pref)**RKAPPA
76!
77!======================================================================
78
79      USE control_mod, ONLY: planet_type
80      IMPLICIT NONE
81     
82! for cpp, nu_venus and t0_venus:
83#include "comconst.h"
84
85      integer,intent(in) :: npoints
86      REAL,intent(in) :: yt(npoints), ypk(npoints)
87      REAL,intent(out) :: yteta(npoints)
88     
89      if (planet_type.eq."venus") then
90          yteta = yt**nu_venus                                          &
91     &            - nu_venus * t0_venus**nu_venus * log(ypk/cpp)
92          yteta = yteta**(1./nu_venus)
93      else
94          yteta = yt * cpp/ypk
95      endif
96
97      return
98      end subroutine t2tpot
99
100!======================================================================
101!======================================================================
102
103      SUBROUTINE tpot2t(npoints,yteta, yt, ypk)
104!======================================================================
105! Arguments:
106!
107! yteta--------input-R- Temperature potentielle
108! yt   -------output-R- Temperature
109! ypk  --------input-R- Fonction d'Exner: RCPD*(pplay/pref)**RKAPPA
110!
111!======================================================================
112
113      USE control_mod, ONLY: planet_type
114      IMPLICIT NONE
115
116! for cpp, nu_venus and t0_venus:
117#include "comconst.h"
118
119      integer,intent(in) :: npoints
120      REAL,intent(in) :: yteta(npoints), ypk(npoints)
121      REAL,intent(out) :: yt(npoints)
122     
123      if (planet_type.eq."venus") then
124         yt = yteta**nu_venus                                           &
125     &       + nu_venus * t0_venus**nu_venus * log(ypk/cpp)
126         yt = yt**(1./nu_venus)
127      else
128          yt = yteta * ypk/cpp
129      endif
130 
131      return
132      end subroutine tpot2t
133
134!======================================================================
135!======================================================================
136!
137! ATTENTION
138!
139! Si un jour on a besoin, il faudra coder les routines
140!    dt2dtpot / dtpto2dt
141!
142!======================================================================
143!======================================================================
144      end module cpdet_mod
Note: See TracBrowser for help on using the repository browser.