source: trunk/LMDZ.COMMON/libf/dyn3dpar/cpdet.F @ 953

Last change on this file since 953 was 953, checked in by slebonnois, 12 years ago

SL: optimisation pour le parallèle suite à tests Venus / petite correction appels routines secondaires dans Venus et Titan

File size: 5.7 KB
Line 
1! ADAPTATION GCM POUR CP(T)
2c======================================================================
3c S. Lebonnois, 10/2010
4c
5c Cp doit être calculé par cpdet(t) pour être valable partout
6c
7c La fonction d'Exner reste pk = RCPD*(play/pref)**RKAPPA
8c (RCPD=cpp, RKAPPA=kappa)
9c
10c On passe de T a teta (temperature potentielle) par t2tpot(t,teta,pk)
11c On passe de teta a T par tpot2t(teta,t,pk)
12c
13c======================================================================
14
15      SUBROUTINE ini_cpdet
16     
17      USE control_mod, ONLY: planet_type
18      IMPLICIT none
19c======================================================================
20c Initialisation de nu_venus et t0_venus
21c======================================================================
22
23! for cpp, nu_venus and t0_venus:
24#include "comconst.h"
25
26      if (planet_type.eq."venus") then
27          nu_venus=0.35
28          t0_venus=460.
29      else
30          nu_venus=0.
31          t0_venus=0.
32      endif
33
34      return
35      end
36
37c======================================================================
38c======================================================================
39
40      FUNCTION cpdet(t)
41
42      USE control_mod, ONLY: planet_type
43      IMPLICIT none
44
45! for cpp, nu_venus and t0_venus:
46#include "comconst.h"
47
48      real cpdet,t
49
50      if (planet_type.eq."venus") then
51          cpdet = cpp*(t/t0_venus)**nu_venus
52      else
53          cpdet = cpp
54      endif
55
56      return
57      end
58     
59c======================================================================
60c======================================================================
61
62      SUBROUTINE t2tpot(npoints, yt, yteta, ypk)
63c======================================================================
64c Arguments:
65c
66c yt   --------input-R- Temperature
67c yteta-------output-R- Temperature potentielle
68c ypk  --------input-R- Fonction d'Exner: RCPD*(pplay/pref)**RKAPPA
69c
70c======================================================================
71
72      USE control_mod, ONLY: planet_type
73      IMPLICIT NONE
74     
75! for cpp, nu_venus and t0_venus:
76#include "comconst.h"
77
78      integer npoints
79      REAL    yt(npoints), yteta(npoints), ypk(npoints)
80     
81      if (planet_type.eq."venus") then
82          yteta = yt**nu_venus                                          &
83     &            - nu_venus * t0_venus**nu_venus * log(ypk/cpp)
84          yteta = yteta**(1./nu_venus)
85      else
86          yteta = yt * cpp/ypk
87      endif
88
89      return
90      end
91
92c======================================================================
93c======================================================================
94
95      SUBROUTINE t2tpot_p(nlon,nlev, yt, yteta, ypk)
96! Parallel version of t2tpot
97      USE parallel
98      USE control_mod, only : planet_type
99      IMPLICIT none
100
101! for cpp, nu_venus and t0_venus:
102#include "comconst.h"
103
104      integer,intent(in) :: nlon,nlev
105      real,intent(in) :: yt(nlon,nlev)
106      real,intent(out) :: yteta(nlon,nlev)
107      real,intent(in) :: ypk(nlon,nlev)
108! local variable:
109      integer :: l
110     
111      if (planet_type.eq."venus") then
112        do l=1,nlev
113          yteta(:,l)=yt(:,l)**nu_venus                                  &
114     &                     -nu_venus*t0_venus**nu_venus*                &
115     &                          log(ypk(:,l)/cpp)
116          yteta(:,l)=yteta(:,l)**(1./nu_venus)
117        enddo
118      else
119        do l=1,nlev
120          yteta(:,l)=yt(:,l)*cpp/ypk(:,l)
121        enddo
122      endif ! of if (planet_type.eq."venus")
123
124      END
125
126c======================================================================
127
128      SUBROUTINE tpot2t(npoints,yteta, yt, ypk)
129c======================================================================
130c Arguments:
131c
132c yteta--------input-R- Temperature potentielle
133c yt   -------output-R- Temperature
134c ypk  --------input-R- Fonction d'Exner: RCPD*(pplay/pref)**RKAPPA
135c
136c======================================================================
137
138      USE control_mod, ONLY: planet_type
139      IMPLICIT NONE
140
141! for cpp, nu_venus and t0_venus:
142#include "comconst.h"
143
144      integer npoints
145      REAL    yt(npoints), yteta(npoints), ypk(npoints)
146     
147      if (planet_type.eq."venus") then
148         yt = yteta**nu_venus                                           &
149     &       + nu_venus * t0_venus**nu_venus * log(ypk/cpp)
150         yt = yt**(1./nu_venus)
151      else
152          yt = yteta * ypk/cpp
153      endif
154 
155      return
156      end
157
158c======================================================================
159c======================================================================
160      SUBROUTINE tpot2t_p(nlon,nlev,yteta,yt,ypk)
161! Parallel version of tpot2t
162      USE parallel
163      USE control_mod, only : planet_type
164      IMPLICIT none
165! for cpp, nu_venus and t0_venus:
166#include "comconst.h"
167
168      integer,intent(in) :: nlon,nlev
169      real,intent(out) :: yt(nlon,nlev)
170      real,intent(in) :: yteta(nlon,nlev)
171      real,intent(in) :: ypk(nlon,nlev)
172
173! local variable:
174      integer :: l
175
176      if (planet_type.eq."venus") then
177        do l=1,nlev
178          yt(:,l)=yteta(:,l)**nu_venus                                  &
179     &                  +nu_venus*t0_venus**nu_venus*                   &
180     &                       log(ypk(:,l)/cpp)
181          yt(:,l)=yt(:,l)**(1./nu_venus)
182        enddo
183      else
184        do l=1,nlev
185          yt(:,l)=yteta(:,l)*ypk(:,l)/cpp
186        enddo
187      endif ! of if (planet_type.eq."venus")
188      END
189
190c======================================================================
191c======================================================================
192c
193c ATTENTION
194c
195c Si un jour on a besoin, il faudra coder les routines
196c    dt2dtpot / dtpto2dt
197c
198c======================================================================
199c======================================================================
Note: See TracBrowser for help on using the repository browser.