source: trunk/LMDZ.COMMON/libf/dyn3d_common/cpdet_mod.F90 @ 1422

Last change on this file since 1422 was 1422, checked in by milmd, 10 years ago

In GENERIC, MARS and COMMON models replace some include files by modules (usefull for decoupling physics with dynamics).

File size: 9.6 KB
Line 
1module cpdet_mod
2
3implicit 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
19contains
20
21      SUBROUTINE ini_cpdet
22     
23      USE control_mod, ONLY: planet_type
24      USE comconst_mod, ONLY: nu_venus,t0_venus
25      IMPLICIT none
26!======================================================================
27! Initialization of nu_venus and t0_venus
28!======================================================================
29
30      if (planet_type.eq."venus") then
31          nu_venus=0.35
32          t0_venus=460.
33      else
34          nu_venus=0.
35          t0_venus=0.
36      endif
37
38      return
39      end subroutine ini_cpdet
40
41!======================================================================
42!======================================================================
43
44      FUNCTION cpdet(t)
45
46      USE control_mod, ONLY: planet_type
47      USE comconst_mod, ONLY: cpp,t0_venus,nu_venus
48      IMPLICIT none
49
50! for cpp, nu_venus and t0_venus:
51
52      real,intent(in) :: t
53      real cpdet
54
55      if (planet_type.eq."venus") then
56          cpdet = cpp*(t/t0_venus)**nu_venus
57      else
58          cpdet = cpp
59      endif
60
61      return
62      end function cpdet
63     
64!======================================================================
65!======================================================================
66
67      SUBROUTINE t2tpot(npoints, yt, yteta, ypk)
68!======================================================================
69! Arguments:
70!
71! yt   --------input-R- Temperature
72! yteta-------output-R- Temperature potentielle
73! ypk  --------input-R- Fonction d'Exner: RCPD*(pplay/pref)**RKAPPA
74!
75!======================================================================
76
77      USE control_mod, ONLY: planet_type
78      USE comconst_mod, ONLY: cpp,t0_venus,nu_venus
79
80      IMPLICIT NONE
81
82      integer,intent(in) :: npoints
83      REAL,intent(in) :: yt(npoints), ypk(npoints)
84      REAL,intent(out) :: yteta(npoints)
85     
86      if (planet_type.eq."venus") then
87          yteta = yt**nu_venus                                          &
88     &            - nu_venus * t0_venus**nu_venus * log(ypk/cpp)
89          yteta = yteta**(1./nu_venus)
90      else
91          yteta = yt * cpp/ypk
92      endif
93
94      return
95      end subroutine t2tpot
96
97!======================================================================
98!======================================================================
99
100      SUBROUTINE tpot2t(npoints,yteta, yt, ypk)
101!======================================================================
102! Arguments:
103!
104! yteta--------input-R- Temperature potentielle
105! yt   -------output-R- Temperature
106! ypk  --------input-R- Fonction d'Exner: RCPD*(pplay/pref)**RKAPPA
107!
108!======================================================================
109
110      USE control_mod, ONLY: planet_type
111      USE comconst_mod, ONLY: cpp,nu_venus,t0_venus
112
113      IMPLICIT NONE
114
115      integer,intent(in) :: npoints
116      REAL,intent(in) :: yteta(npoints), ypk(npoints)
117      REAL,intent(out) :: yt(npoints)
118     
119      if (planet_type.eq."venus") then
120         yt = yteta**nu_venus                                           &
121     &       + nu_venus * t0_venus**nu_venus * log(ypk/cpp)
122         yt = yt**(1./nu_venus)
123      else
124          yt = yteta * ypk/cpp
125      endif
126 
127      return
128      end subroutine tpot2t
129
130!======================================================================
131!======================================================================
132! Routines pour les calculs paralleles
133!======================================================================
134#ifdef CPP_PARA
135!======================================================================
136
137      SUBROUTINE t2tpot_p(nlon,nlev, yt, yteta, ypk)
138! Parallel version of t2tpot, for an arbitrary number of columns
139      USE control_mod, only : planet_type
140      USE parallel_lmdz, only : OMP_CHUNK
141      USE comconst_mod, ONLY: cpp,nu_venus,t0_venus
142
143      IMPLICIT none
144
145      integer,intent(in) :: nlon,nlev
146      real,intent(in) :: yt(nlon,nlev)
147      real,intent(out) :: yteta(nlon,nlev)
148      real,intent(in) :: ypk(nlon,nlev)
149! local variable:
150      integer :: l
151     
152      if (planet_type.eq."venus") then
153!$OMP DO SCHEDULE(STATIC,OMP_CHUNK)
154        do l=1,nlev
155          yteta(:,l)=yt(:,l)**nu_venus                                  &
156     &                     -nu_venus*t0_venus**nu_venus*                &
157     &                          log(ypk(:,l)/cpp)
158          yteta(:,l)=yteta(:,l)**(1./nu_venus)
159        enddo
160!$OMP END DO
161      else
162!$OMP DO SCHEDULE(STATIC,OMP_CHUNK)
163        do l=1,nlev
164          yteta(:,l)=yt(:,l)*cpp/ypk(:,l)
165        enddo
166!$OMP END DO
167      endif ! of if (planet_type.eq."venus")
168
169      end subroutine t2tpot_p
170
171!======================================================================
172!======================================================================
173
174      SUBROUTINE t2tpot_glo_p(yt, yteta, ypk)
175! Parallel version of t2tpot, over the full dynamics (scalar) grid
176! (more efficient than multiple calls to t2tpot_p() with slices of data)
177      USE parallel_lmdz, only : jj_begin,jj_end,OMP_CHUNK
178      USE control_mod, only : planet_type
179      USE comconst_mod, ONLY: cpp,nu_venus,t0_venus
180
181      IMPLICIT none
182! for iip1, jjp1 and llm
183#include "dimensions.h"
184#include "paramet.h"
185
186      real,intent(in) :: yt(iip1,jjp1,llm)
187      real,intent(out) :: yteta(iip1,jjp1,llm)
188      real,intent(in) :: ypk(iip1,jjp1,llm)
189! local variable:
190      integer :: j,l
191      integer :: jjb,jje
192     
193      jjb=jj_begin
194      jje=jj_end
195
196      if (planet_type.eq."venus") then
197!$OMP DO SCHEDULE(STATIC,OMP_CHUNK)
198        do l=1,llm
199          yteta(:,jjb:jje,l)=yt(:,jjb:jje,l)**nu_venus                  &
200     &                     -nu_venus*t0_venus**nu_venus*                &
201     &                          log(ypk(:,jjb:jje,l)/cpp)
202          yteta(:,jjb:jje,l)=yteta(:,jjb:jje,l)**(1./nu_venus)
203        enddo
204!$OMP END DO
205      else
206!$OMP DO SCHEDULE(STATIC,OMP_CHUNK)
207        do l=1,llm
208          yteta(:,jjb:jje,l)=yt(:,jjb:jje,l)*cpp/ypk(:,jjb:jje,l)
209        enddo
210!$OMP END DO
211      endif ! of if (planet_type.eq."venus")
212
213      end subroutine t2tpot_glo_p
214
215!======================================================================
216!======================================================================
217
218      SUBROUTINE tpot2t_p(nlon,nlev,yteta,yt,ypk)
219! Parallel version of tpot2t, for an arbitrary number of columns
220      USE control_mod, only : planet_type
221      USE parallel_lmdz, only : OMP_CHUNK
222      USE comconst_mod, ONLY: cpp,nu_venus,t0_venus
223
224      IMPLICIT none
225
226      integer,intent(in) :: nlon,nlev
227      real,intent(out) :: yt(nlon,nlev)
228      real,intent(in) :: yteta(nlon,nlev)
229      real,intent(in) :: ypk(nlon,nlev)
230
231! local variable:
232      integer :: l
233
234      if (planet_type.eq."venus") then
235!$OMP DO SCHEDULE(STATIC,OMP_CHUNK)
236        do l=1,nlev
237          yt(:,l)=yteta(:,l)**nu_venus                                  &
238     &                  +nu_venus*t0_venus**nu_venus*                   &
239     &                       log(ypk(:,l)/cpp)
240          yt(:,l)=yt(:,l)**(1./nu_venus)
241        enddo
242!$OMP END DO
243      else
244!$OMP DO SCHEDULE(STATIC,OMP_CHUNK)
245        do l=1,nlev
246          yt(:,l)=yteta(:,l)*ypk(:,l)/cpp
247        enddo
248!$OMP END DO
249      endif ! of if (planet_type.eq."venus")
250      end subroutine tpot2t_p
251
252!======================================================================
253!======================================================================
254
255      SUBROUTINE tpot2t_glo_p(yteta,yt,ypk)
256! Parallel version of tpot2t, over the full dynamics (scalar) grid
257! (more efficient than multiple calls to tpot2t_p() with slices of data)
258      USE parallel_lmdz, only : jj_begin,jj_end,OMP_CHUNK
259      USE control_mod, only : planet_type
260      USE comconst_mod, ONLY: cpp,nu_venus,t0_venus
261
262      IMPLICIT none
263! for iip1, jjp1 and llm
264#include "dimensions.h"
265#include "paramet.h"
266
267      real,intent(out) :: yt(iip1,jjp1,llm)
268      real,intent(in) :: yteta(iip1,jjp1,llm)
269      real,intent(in) :: ypk(iip1,jjp1,llm)
270! local variable:
271      integer :: j,l
272      integer :: jjb,jje
273     
274      jjb=jj_begin
275      jje=jj_end
276
277      if (planet_type.eq."venus") then
278!$OMP DO SCHEDULE(STATIC,OMP_CHUNK)
279        do l=1,llm
280          yt(:,jjb:jje,l)=yteta(:,jjb:jje,l)**nu_venus                  &
281     &                  +nu_venus*t0_venus**nu_venus*                   &
282     &                       log(ypk(:,jjb:jje,l)/cpp)
283          yt(:,jjb:jje,l)=yt(:,jjb:jje,l)**(1./nu_venus)
284        enddo
285!$OMP END DO
286      else
287!$OMP DO SCHEDULE(STATIC,OMP_CHUNK)
288        do l=1,llm
289          yt(:,jjb:jje,l)=yteta(:,jjb:jje,l)*ypk(:,jjb:jje,l)/cpp
290        enddo
291!$OMP END DO
292      endif ! of if (planet_type.eq."venus")
293      end subroutine tpot2t_glo_p
294
295!======================================================================
296#endif
297!======================================================================
298! Fin routines specifiques parallele
299!======================================================================
300!======================================================================
301!
302! ATTENTION
303!
304! Si un jour on a besoin, il faudra coder les routines
305!    dt2dtpot / dtpto2dt
306!
307!======================================================================
308!======================================================================
309end module cpdet_mod
Note: See TracBrowser for help on using the repository browser.