source: trunk/libf/dyn3dpar/cpdet.F @ 16

Last change on this file since 16 was 8, checked in by emillour, 15 years ago

Debut de mise a jour de la dynamique parallele par rapport aux modifs dans la partie sequentielle.

Mais NON TESTE , car pas (encore) possibilite de compiler et faire tourner cas simple (type newtonien sans physique).

Voir commit_v8.log pour les details.

Ehouarn

File size: 6.1 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      IMPLICIT none
17c======================================================================
18c Initialisation de nu_venus et t0_venus
19c======================================================================
20
21! for planet_type:
22      USE control_mod
23
24! for cpp, nu_venus and t0_venus:
25#include "comconst.h"
26
27      if (planet_type.eq."venus") then
28          nu_venus=0.35
29          t0_venus=460.
30      else
31          nu_venus=0.
32          t0_venus=0.
33      endif
34
35      return
36      end
37
38c======================================================================
39c======================================================================
40
41      FUNCTION cpdet(t)
42      IMPLICIT none
43
44! for planet_type:
45      USE control_mod
46
47! for cpp, nu_venus and t0_venus:
48#include "comconst.h"
49
50      real cpdet,t
51
52      if (planet_type.eq."venus") then
53          cpdet = cpp*(t/t0_venus)**nu_venus
54      else
55          cpdet = cpp
56      endif
57
58      return
59      end
60     
61c======================================================================
62c======================================================================
63
64      SUBROUTINE t2tpot(npoints, yt, yteta, ypk)
65      IMPLICIT none
66c======================================================================
67c Arguments:
68c
69c yt   --------input-R- Temperature
70c yteta-------output-R- Temperature potentielle
71c ypk  --------input-R- Fonction d'Exner: RCPD*(pplay/pref)**RKAPPA
72c
73c======================================================================
74
75! for planet_type:
76      USE control_mod
77
78! for cpp, nu_venus and t0_venus:
79#include "comconst.h"
80
81      integer npoints
82      REAL    yt(npoints), yteta(npoints), ypk(npoints)
83     
84      if (planet_type.eq."venus") then
85          yteta = yt**nu_venus                                          &
86     &            - nu_venus * t0_venus**nu_venus * log(ypk/cpp)
87          yteta = yteta**(1./nu_venus)
88      else
89          yteta = yt * cpp/ypk
90      endif
91
92      return
93      end
94
95c======================================================================
96c======================================================================
97
98      SUBROUTINE t2tpot_p(ip1jmp1,llm, yt, yteta, ypk)
99! Parallel version of t2tpot
100      USE parallel
101      USE control_mod, only : planet_type
102      IMPLICIT none
103
104! for cpp, nu_venus and t0_venus:
105#include "comconst.h"
106
107      integer,intent(in) :: ip1jmp1,llm
108      real,intent(in) :: yt(ip1jmp1,llm)
109      real,intent(out) :: yteta(ip1jmp1,llm)
110      real,intent(in) :: ypk(ip1jmp1,llm)
111! local variable:
112      integer :: ij,l,ijb,ije
113     
114      ijb=ij_begin
115      ije=ij_end 
116     
117      if (planet_type.eq."venus") then
118!$OMP DO SCHEDULE(STATIC,OMP_CHUNK)
119        do l=1,llm
120          yteta(ijb:ije,l)=yt(ijb:ije,l)**nu_venus                      &
121     &                     -nu_venus*t0_venus**nu_venus*                &
122     &                          log(ypk(ijb:ije,l)/cpp)
123          yteta(ijb:ije,l)=yteta(ijb:ije,l)**(1./nu_venus)
124        enddo
125!$OMP END DO
126      else
127!$OMP DO SCHEDULE(STATIC,OMP_CHUNK)
128        do l=1,llm
129          yteta(ijb:ije,l)=yt(ijb:ije,l)*cpp/ypk(ijb:ije,l)
130        enddo
131!$OMP END DO
132      endif ! of if (planet_type.eq."venus")
133
134      END
135
136c======================================================================
137
138      SUBROUTINE tpot2t(npoints,yteta, yt, ypk)
139      IMPLICIT none
140c======================================================================
141c Arguments:
142c
143c yteta--------input-R- Temperature potentielle
144c yt   -------output-R- Temperature
145c ypk  --------input-R- Fonction d'Exner: RCPD*(pplay/pref)**RKAPPA
146c
147c======================================================================
148
149! for planet_type:
150      USE control_mod
151
152! for cpp, nu_venus and t0_venus:
153#include "comconst.h"
154
155      integer npoints
156      REAL    yt(npoints), yteta(npoints), ypk(npoints)
157     
158      if (planet_type.eq."venus") then
159         yt = yteta**nu_venus                                           &
160     &       + nu_venus * t0_venus**nu_venus * log(ypk/cpp)
161         yt = yt**(1./nu_venus)
162      else
163          yt = yteta * ypk/cpp
164      endif
165 
166      return
167      end
168
169c======================================================================
170c======================================================================
171      SUBROUTINE tpot2t_p(ip1jmp1,llm,yteta, yt, ypk)
172! Parallel version of tpot2t
173      USE parallel
174      USE control_mod, only : planet_type
175      IMPLICIT none
176! for cpp, nu_venus and t0_venus:
177#include "comconst.h"
178
179      integer,intent(in) :: ip1jmp1,llm
180      real,intent(out) :: yt(ip1jmp1,llm)
181      real,intent(in) :: yteta(ip1jmp1,llm)
182      real,intent(in) :: ypk(ip1jmp1,llm)
183! local variable:
184      integer :: ij,l,ijb,ije
185     
186      ijb=ij_begin
187      ije=ij_end 
188
189      if (planet_type.eq."venus") then
190!$OMP DO SCHEDULE(STATIC,OMP_CHUNK)
191        do l=1,llm
192          yt(ijb:ije,l)=yteta(ijb:ije,l)**nu_venus                      &
193     &                  +nu_venus*t0_venus**nu_venus*                   &
194     &                       log(ypk(ijb:ije,l)/cpp)
195          yt(ijb:ije,l)=yt(ijb:ije,l)**(1./nu_venus)
196        enddo
197!$OMP END DO
198      else
199!$OMP DO SCHEDULE(STATIC,OMP_CHUNK)
200        do l=1,llm
201          yt(ijb:ije,l)=yteta(ijb:ije,l)*ypk(ijb:ije,l)/cpp
202        enddo
203!$OMP END DO
204      endif ! of if (planet_type.eq."venus")
205      END
206
207c======================================================================
208c======================================================================
209c
210c ATTENTION
211c
212c Si un jour on a besoin, il faudra coder les routines
213c    dt2dtpot / dtpto2dt
214c
215c======================================================================
216c======================================================================
Note: See TracBrowser for help on using the repository browser.