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

Annotation of /trunk/dyn3d/fxysinus.f

Parent Directory Parent Directory | Revision Log Revision Log


Revision 97 - (hide annotations)
Fri Apr 25 14:58:31 2014 UTC (10 years, 1 month ago) by guez
File size: 2595 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 97 module fxysinus_m
2 guez 3
3 guez 81 IMPLICIT NONE
4 guez 3
5 guez 97 private
6     public fxysinus
7 guez 3
8 guez 97 contains
9 guez 3
10 guez 97 SUBROUTINE fxysinus(rlatu, yprimu, rlatv, yprimv, rlatu1, yprimu1, rlatu2, &
11     yprimu2, rlonu, xprimu, rlonv, xprimv, rlonm025, xprimm025, rlonp025, &
12     xprimp025)
13 guez 3
14 guez 97 ! From LMDZ4/libf/dyn3d/fxysinus.F, version 1.1.1.1, 2004/05/19 12:53:06
15     ! and LMDZ4/libf/grid/fxy_sin.h, v 1.1.1.1, 2004/05/19 12:53:05
16 guez 3
17 guez 97 ! Author: P. Le Van
18 guez 3
19 guez 97 ! Calcul des longitudes et des latitudes pour une fonction f(x, y)
20     ! avec y = Arcsin(j).
21 guez 3
22 guez 97 USE dimens_m, only: iim, jjm
23     USE nr_util, ONLY: pi
24 guez 3
25 guez 97 INTEGER i, j
26 guez 3
27 guez 97 REAL, intent(out):: rlatu(:), yprimu(:) ! (jjp1)
28     REAL, intent(out):: rlatv(:), yprimv(:) ! (jjm)
29     REAL, intent(out):: rlatu1(:) ! (jjm)
30     real, intent(out):: yprimu1(:), rlatu2(:), yprimu2(:) ! (jjm)
31     REAL, intent(out):: rlonu(:), xprimu(:), rlonv(:), xprimv(:) ! (iip1)
32     REAL, intent(out):: rlonm025(:) ! (iip1)
33     real, intent(out):: xprimm025(:), rlonp025(:), xprimp025(:) ! (iip1)
34 guez 3
35 guez 97 ! Local:
36     real fxprim
37 guez 3
38 guez 97 !-----------------------------------------------------------------------
39 guez 3
40 guez 97 fxprim = 2. * pi / iim
41 guez 81
42 guez 97 ! Calcul des latitudes et de y'
43 guez 81
44 guez 97 forall(j = 1: jjm + 1)
45     rlatu(j) = fy(real(j))
46     yprimu(j) = fyprim(real(j))
47     END forall
48 guez 81
49 guez 97 forall(j = 1: jjm)
50     rlatv(j) = fy(real(j) + 0.5)
51     rlatu1(j) = fy(real(j) + 0.25)
52     rlatu2(j) = fy(real(j) + 0.75)
53 guez 81
54 guez 97 yprimv(j) = fyprim(real(j) + 0.5)
55     yprimu1(j) = fyprim(real(j) + 0.25)
56     yprimu2(j) = fyprim(real(j) + 0.75)
57     END forall
58 guez 81
59 guez 97 ! Calcul des longitudes et de x'
60     forall(i = 1: iim + 1)
61     rlonv(i) = fx(real(i))
62     rlonu(i) = fx(real(i) + 0.5)
63     rlonm025(i) = fx(real(i) - 0.25)
64     rlonp025(i) = fx(real(i) + 0.25)
65 guez 81
66 guez 97 xprimv(i) = fxprim
67     xprimu(i) = fxprim
68     xprimm025(i) = fxprim
69     xprimp025(i) = fxprim
70     END forall
71 guez 81
72 guez 97 END SUBROUTINE fxysinus
73 guez 81
74 guez 97 ! Fonctions à changer éventuellement, selon x(x) et y(y) choisis.
75     ! Ici, on a l'application particulière suivante :
76 guez 81
77 guez 97 ! x = 2 * pi / iim * X
78     ! y = pi / jjm * Y
79 guez 81
80 guez 97 pure REAL function fy(rj)
81     USE dimens_m, only: jjm
82     REAL, intent(in):: rj
83     fy = asin(1. + 2. * ((1. - rj) / jjm))
84     end function fy
85 guez 81
86 guez 97 pure real function fx(ri)
87     USE dimens_m, only: iim
88     USE nr_util, ONLY: pi
89     REAL, intent(in):: ri
90     fx = 2.*pi/real(iim)*(ri-0.5*real(iim)-1.)
91     end function fx
92 guez 81
93 guez 97 pure real function fyprim(rj)
94     USE dimens_m, only: jjm
95     REAL, intent(in):: rj
96     fyprim = 1./sqrt((rj-1.)*(jjm + 1.-rj))
97     end function fyprim
98 guez 81
99 guez 97 end module fxysinus_m

  ViewVC Help
Powered by ViewVC 1.1.21