/[lmdze]/trunk/dyn3d/fxyhyper.f
ViewVC logotype

Annotation of /trunk/dyn3d/fxyhyper.f

Parent Directory Parent Directory | Revision Log Revision Log


Revision 97 - (hide annotations)
Fri Apr 25 14:58:31 2014 UTC (10 years ago) by guez
File size: 3871 byte(s)
Module pressure_var is now only used in gcm. Created local variables
pls and p3d in etat0, added argument p3d to regr_pr_o3.

In leapfrog, moved computation of p3d and exner function immediately
after integrd, for clarity (does not change the execution).

Removed unused arguments: ntra, tra1 and tra of cv3_compress; ntra,
tra and traent of cv3_mixing; ntra, ftra, ftra1 of cv3_uncompress;
ntra, tra, trap of cv3_unsat; ntra, tra, trap, traent, ftra of
cv3_yield; tra, tvp, pbase, bbase, dtvpdt1, dtvpdq1, dplcldt,
dplcldr, ntra of concvl; ndp1, ntra, tra1 of cv_driver

Removed argument d_tra and computation of d_tra in concvl. Removed
argument ftra1 and computation of ftra1 in cv_driver. ftra1 was just
set to 0 in cv_driver, associated to d_tra in concvl, and set again to
zero in concvl.

1 guez 70 module fxyhyper_m
2 guez 3
3 guez 70 IMPLICIT NONE
4 guez 3
5 guez 70 contains
6 guez 38
7 guez 70 SUBROUTINE fxyhyper(yzoom, grossy, dzoomy, tauy, xzoom, grossx, dzoomx, &
8     taux, rlatu, yprimu, rlatv, yprimv, rlatu1, yprimu1, rlatu2, yprimu2, &
9     rlonu, xprimu, rlonv, xprimv, rlonm025, xprimm025, rlonp025, xprimp025)
10 guez 3
11 guez 97 ! From dyn3d/fxyhyper.F, version 1.1.1.1, 2004/05/19 12:53:06
12 guez 3
13 guez 70 USE dimens_m, ONLY: jjm
14 guez 78 use fxhyp_m, only: fxhyp
15 guez 97 use fyhyp_m, only: fyhyp
16     USE paramet_m, ONLY: iip1
17 guez 3
18 guez 97 ! Auteur : P. Le Van d'après les formulations de R. Sadourny
19 guez 3
20 guez 70 ! Cette procédure calcule les latitudes (routine fyhyp) et
21     ! longitudes (fxhyp) par des fonctions à tangente hyperbolique.
22 guez 3
23 guez 78 ! Il y a trois paramètres, en plus des coordonnées du centre du
24     ! zoom (xzoom et yzoom) :
25 guez 3
26 guez 70 ! a) le grossissement du zoom : grossy (en y) et grossx (en x)
27     ! b) l' extension du zoom : dzoomy (en y) et dzoomx (en x)
28     ! c) la raideur de la transition du zoom : taux et tauy
29 guez 3
30 guez 78 ! Nota bene : il vaut mieux avoir : grossx * dzoomx < pi (radians)
31     ! et grossy * dzoomy < pi/2 (radians)
32 guez 38
33 guez 78 REAL yzoom, grossy, dzoomy, tauy, xzoom, grossx, dzoomx, taux
34 guez 97 REAL rlatu(:), yprimu(:) ! (jjm + 1)
35     real rlatv(:), yprimv(:) ! (jjm)
36     real rlatu1(:), yprimu1(:), rlatu2(:), yprimu2(:) ! (jjm)
37     REAL rlonu(:), xprimu(:), rlonv(:), xprimv(:) ! (iim + 1)
38     REAL rlonm025(:), xprimm025(:), rlonp025(:), xprimp025(:) ! (iim + 1)
39 guez 38
40 guez 97 ! Local:
41 guez 38
42 guez 78 double precision dxmin, dxmax, dymin, dymax
43 guez 70 INTEGER i, j
44 guez 38
45 guez 70 !----------------------------------------------------------
46 guez 38
47 guez 70 CALL fyhyp(yzoom, grossy, dzoomy, tauy, rlatu, yprimu, rlatv, yprimv, &
48     rlatu2, yprimu2, rlatu1, yprimu1, dymin, dymax)
49     CALL fxhyp(xzoom, grossx, dzoomx, taux, rlonm025, xprimm025, rlonv, &
50     xprimv, rlonu, xprimu, rlonp025, xprimp025, dxmin, dxmax)
51 guez 3
52 guez 70 DO i = 1, iip1
53     IF(rlonp025(i).LT.rlonv(i)) THEN
54     print *, ' Attention ! rlonp025 < rlonv', i
55     STOP 1
56     ENDIF
57 guez 3
58 guez 70 IF(rlonv(i).LT.rlonm025(i)) THEN
59     print *, ' Attention ! rlonm025 > rlonv', i
60     STOP 1
61     ENDIF
62 guez 3
63 guez 70 IF(rlonp025(i).GT.rlonu(i)) THEN
64     print *, ' Attention ! rlonp025 > rlonu', i
65     STOP 1
66     ENDIF
67     ENDDO
68 guez 3
69 guez 70 print *, 'Test de coherence ok pour fx'
70 guez 38
71 guez 70 DO j = 1, jjm
72     IF(rlatu1(j).LE.rlatu2(j)) THEN
73     print *, 'Attention ! rlatu1 < rlatu2 ', rlatu1(j), rlatu2(j), j
74     STOP 13
75     ENDIF
76 guez 38
77 guez 70 IF(rlatu2(j).LE.rlatu(j+1)) THEN
78     print *, 'Attention ! rlatu2 < rlatup1 ', rlatu2(j), rlatu(j+1), j
79     STOP 14
80     ENDIF
81 guez 38
82 guez 70 IF(rlatu(j).LE.rlatu1(j)) THEN
83     print *, ' Attention ! rlatu < rlatu1 ', rlatu(j), rlatu1(j), j
84     STOP 15
85     ENDIF
86 guez 38
87 guez 70 IF(rlatv(j).LE.rlatu2(j)) THEN
88     print *, ' Attention ! rlatv < rlatu2 ', rlatv(j), rlatu2(j), j
89     STOP 16
90     ENDIF
91 guez 38
92 guez 70 IF(rlatv(j).ge.rlatu1(j)) THEN
93     print *, ' Attention ! rlatv > rlatu1 ', rlatv(j), rlatu1(j), j
94     STOP 17
95     ENDIF
96 guez 38
97 guez 70 IF(rlatv(j).ge.rlatu(j)) THEN
98     print *, ' Attention ! rlatv > rlatu ', rlatv(j), rlatu(j), j
99     STOP 18
100     ENDIF
101     ENDDO
102 guez 38
103 guez 70 print *, 'Test de coherence ok pour fy'
104 guez 3
105 guez 70 print *, 'Latitudes'
106     print 3, dymin, dymax
107     print *, 'Si cette derniere est trop lache, modifiez les parametres'
108     print *, 'grossism, tau, dzoom pour Y et repasser ! '
109 guez 38
110 guez 70 print *, ' Longitudes '
111     print 3, dxmin, dxmax
112     print *, 'Si cette derniere est trop lache, modifiez les parametres'
113     print *, 'grossism, tau, dzoom pour Y et repasser ! '
114 guez 3
115 guez 70 3 Format(1x, ' Au centre du zoom, la longueur de la maille est', &
116     ' d environ ', f0.2, ' degres ', /, &
117     ' alors que la maille en dehors de la zone du zoom est ', &
118     "d'environ", f0.2, ' degres ')
119    
120     END SUBROUTINE fxyhyper
121    
122     end module fxyhyper_m

  ViewVC Help
Powered by ViewVC 1.1.21