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

Contents of /trunk/dyn3d/conf_dat2d.f

Parent Directory Parent Directory | Revision Log Revision Log


Revision 122 - (show annotations)
Tue Feb 3 19:30:48 2015 UTC (9 years, 3 months ago) by guez
File size: 4149 byte(s)
In procedure fxhyp_loop_ik, when testing whether xvrai is between -pi
and pi, changed back the boundaries from -pi - 1d-5 to - pi_d - 0.1
and from pi + 1d-5 to pi_d + 0.1. Fixed the logic: for ik = 1, we
rearrange longitudes between -pi and pi, if necessary. For other
values of ik, we apply the same rearrangement.

In module serre, change the default values of dzoomx and dzoomy to
0.2, because dzoomx must be > 0 when grossismx > 1.

With this revision, we recover the results of revision 120 and we
remove the bug that appeared with clon = 20.

1 module conf_dat2d_m
2
3 IMPLICIT NONE
4
5 contains
6
7 SUBROUTINE conf_dat2d(xd, yd, xf, yf, champd, interbar)
8
9 ! From conf_dat2d.F, version 1.2 2006/01/27 15:14:22
10 ! Author : P. Le Van
11
12 ! Ce sous-programme configure le champ de données 2D 'champd' et
13 ! les longitudes et latitudes de telle façon qu'on ait - pi à pi
14 ! en longitude et pi/2 à - pi/2 en latitude.
15
16 ! This procedure receives a 2D field, with the corresponding
17 ! coordinate variables: longitude and latitude.
18 ! The procedure converts longitude and latitude to radians, if the
19 ! input values are in degrees.
20 ! If the input longitudes are between 0 and 2 pi, the procedure
21 ! computes the congruent longitudes between -pi and pi, and permutes
22 ! them so they stay in increasing order.
23 ! If the input latitudes are from south pole to north pole, the
24 ! procedure permutes them so they become from north to south.
25 ! Any change on longitudes or latitudes induces a change on the 2D field.
26 ! If required, the longitudes and latitudes are finally replaced
27 ! by their mid-values.
28
29 use nr_util, only: assert_eq, pi
30
31 REAL, intent(in):: xd(:)
32 ! (longitudes, in degrees or radians, in increasing order, from 0°
33 ! to 360° or -180° to 180°)
34
35 REAL, intent(in):: yd(:)
36 ! (latitudes, in degrees or radians, in increasing or decreasing
37 ! order, from pole to pole)
38
39 REAL, intent(out):: xf(:), yf(:) ! longitudes and latitudes, in rad
40 REAL, intent(inout):: champd(:, :)
41 LOGICAL, intent(in), optional:: interbar
42
43 ! Local:
44 INTEGER lons, lats
45 LOGICAL radianlon ! "xd" is in degrees
46 logical invlon ! "xd" contains longitudes between 0 and 2 pi
47 logical radianlat ! "yd" is in rad
48 REAL rlatmin, rlatmax, old_xf_1
49 INTEGER i, j
50 logical mid_values
51
52 !------------------------------
53
54 lons = assert_eq(size(xd), size(xf), size(champd, 1), "conf_dat2d lons")
55 lats = assert_eq(size(yd), size(yf), size(champd, 2), "conf_dat2d lats")
56
57 IF (xd(1) >= - pi -0.5 .AND. xd(lons) <= pi + 0.5) THEN
58 radianlon = .TRUE.
59 invlon = .FALSE.
60 ELSE IF (xd(1) >= -0.5 .AND. xd(lons) <= 2 * pi+0.5) THEN
61 radianlon = .TRUE.
62 invlon = .TRUE.
63 ELSE IF (xd(1) >= -180.5 .AND. xd(lons) <= 180.5) THEN
64 radianlon = .FALSE.
65 invlon = .FALSE.
66 ELSE IF (xd(1) >= -0.5 .AND. xd(lons) <= 360.5) THEN
67 radianlon = .FALSE.
68 invlon = .TRUE.
69 ELSE
70 stop '"conf_dat2d": problem with longitudes'
71 ENDIF
72
73 rlatmin = MIN(yd(1), yd(lats))
74 rlatmax = MAX(yd(1), yd(lats))
75
76 IF (rlatmin >= -pi / 2 - 0.5 .AND. rlatmax <= pi / 2 + 0.5)THEN
77 radianlat = .TRUE.
78 ELSE IF (rlatmin >= -90. - 0.5 .AND. rlatmax <= 90. + 0.5) THEN
79 radianlat = .FALSE.
80 ELSE
81 stop '"conf_dat2d": problem with latitudes'
82 ENDIF
83
84 IF (radianlon) THEN
85 xf(:) = xd(:)
86 else
87 xf(:) = xd(:) * pi / 180. ! convert to rad
88 ENDIF
89
90 IF (radianlat) THEN
91 yf(:) = yd(:)
92 else
93 yf(:) = yd(:) * pi / 180. ! convert to rad
94 ENDIF
95
96 IF (invlon) THEN
97 ! On tourne les longitudes pour avoir - pi à + pi :
98
99 ! Get the index of the first longitude > pi:
100 i = 1
101 do while (xf(i) <= pi)
102 i = i + 1
103 end do
104
105 xf(i:) = xf(i:) - 2 * pi
106 xf(:) = cshift(xf, shift = i - 1)
107 champd(:, :) = cshift(champd, shift = i - 1)
108 ENDIF
109
110 IF (yd(1) < yd(lats)) THEN
111 ! "yd" contains latitudes from south pole to north pole,
112 ! reverse their order in "yf":
113 yf(lats:1:-1) = yf(:)
114 champd(:, lats:1:-1) = champd(:, :)
115 ENDIF
116
117 if (present(interbar)) then
118 mid_values = interbar
119 else
120 mid_values = .true. ! default
121 end if
122 if (mid_values) then
123 ! Replace longitudes and latitudes by their mid-values:
124 old_xf_1 = xf(1)
125 forall (i = 1: lons - 1) xf(i) = 0.5 * (xf(i) + xf(i+1))
126 xf(lons) = 0.5 * (xf(lons) + old_xf_1 + 2 * pi)
127
128 forall (j = 1: lats - 1) yf(j) = 0.5 * (yf(j) + yf(j+1))
129 end if
130
131 END SUBROUTINE conf_dat2d
132
133 end module conf_dat2d_m

  ViewVC Help
Powered by ViewVC 1.1.21