/[lmdze]/trunk/Sources/dyn3d/Guide/init_tau2alpha.f
ViewVC logotype

Contents of /trunk/Sources/dyn3d/Guide/init_tau2alpha.f

Parent Directory Parent Directory | Revision Log Revision Log


Revision 173 - (show annotations)
Tue Oct 6 15:57:02 2015 UTC (8 years, 7 months ago) by guez
File size: 2561 byte(s)
correctbid did nothing. (Not used either in LMDZ since revision 1170.)

Avoid aliasing in arguments of nat2gcm: use a single set of arguments
with intent inout. Argument q of nat2gcm was not used.

pres2lev now accepts po in any monotonic order. So the input files for
nudging can now have the pressure coordinate in any order. Also, we
read the latitude coordinate from the input files for nudging and we
invert order if necessary so the input files for nudging can now have
the latitude coordinate in any order.

In pre2lev, no need for lmomx: use automatic arrays.

Removed variable ncep of module conf_guide_m. Instead, we find out
what the pressure coordinate is with find_coord.


1 module init_tau2alpha_m
2
3 IMPLICIT NONE
4
5 REAL dxdy_min, dxdy_max, gamma
6
7 contains
8
9 SUBROUTINE init_tau2alpha(dxdys, dxdyu, dxdyv)
10
11 USE comgeom, ONLY: cu_2d, cv_2d
12 use conf_guide_m, only: guide_u, guide_v
13 use coordij_m, only: coordij
14 USE dimens_m, ONLY: iim, jjm
15 USE dynetat0_m, ONLY: clat, clon, grossismx, grossismy, rlatu
16 USE paramet_m, ONLY: iip1, jjp1
17 use writefield_m, only: writefield
18
19 REAL, intent(out):: dxdys(iip1, jjp1), dxdyu(iip1, jjp1), dxdyv(iip1, jjm)
20
21 ! Local:
22 INTEGER i, j, ilon, ilat
23 REAL dx(iip1, jjp1), dy(iip1, jjp1)
24
25 !------------------------------------------------------------
26
27 PRINT *, 'Call sequence information: init_tau2alpha'
28
29 DO j = 2, jjm
30 DO i = 2, iip1
31 dx(i, j) = 0.5 * (cu_2d(i - 1, j) + cu_2d(i, j)) / cos(rlatu(j))
32 END DO
33 dx(1, j) = dx(iip1, j)
34 END DO
35 DO j = 2, jjm
36 DO i = 1, iip1
37 dy(i, j) = 0.5 * (cv_2d(i, j - 1) + cv_2d(i, j))
38 END DO
39 END DO
40 DO i = 1, iip1
41 dx(i, 1) = dx(i, 2)
42 dx(i, jjp1) = dx(i, jjm)
43 dy(i, 1) = dy(i, 2)
44 dy(i, jjp1) = dy(i, jjm)
45 END DO
46
47 DO j = 1, jjp1
48 DO i = 1, iip1
49 dxdys(i, j) = sqrt(dx(i, j)**2 + dy(i, j)**2)
50 END DO
51 END DO
52 CALL writefield("dxdys", dxdys)
53
54 if (guide_u) then
55 DO j = 1, jjp1
56 DO i = 1, iim
57 dxdyu(i, j) = 0.5 * (dxdys(i, j) + dxdys(i + 1, j))
58 END DO
59 dxdyu(iip1, j) = dxdyu(1, j)
60 END DO
61 end if
62
63 if (guide_v) then
64 DO j = 1, jjm
65 DO i = 1, iip1
66 dxdyv(i, j) = 0.5 * (dxdys(i, j) + dxdys(i, j + 1))
67 END DO
68 END DO
69 end if
70
71 ! coordonnees du centre du zoom
72 CALL coordij(clon, clat, ilon, ilat)
73 ! aire de la maille au centre du zoom
74 dxdy_min = dxdys(ilon, ilat)
75 print *, "dxdy_min = ", dxdy_min
76
77 ! dxdy maximal de la maille :
78 dxdy_max = maxval(dxdys)
79 print *, "dxdy_max = ", dxdy_max
80
81 IF (abs(grossismx - 1.) < 0.1 .OR. abs(grossismy - 1.) < 0.1) THEN
82 PRINT *, 'Attention : modèle peu zoomé.'
83 PRINT *, 'On prend une constante de guidage constante.'
84 ELSE
85 gamma = (dxdy_max - 2. * dxdy_min) / (dxdy_max - dxdy_min)
86 IF (gamma < 1E-5) THEN
87 PRINT *, '(dxdy_max - 2. * dxdy_min) / (dxdy_max - dxdy_min) ' &
88 // '< 1e-5'
89 STOP 1
90 END IF
91 gamma = log(0.5) / log(gamma)
92 PRINT *, 'gamma=', gamma
93 END IF
94
95 END SUBROUTINE init_tau2alpha
96
97 end module init_tau2alpha_m

  ViewVC Help
Powered by ViewVC 1.1.21