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

Contents of /trunk/dyn3d/conf_dat2d.f

Parent Directory Parent Directory | Revision Log Revision Log


Revision 82 - (show annotations)
Wed Mar 5 14:57:53 2014 UTC (10 years, 2 months ago) by guez
File size: 4158 byte(s)
Changed all ".f90" suffixes to ".f".
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 LOGICAL, intent(in), optional:: interbar
40 REAL, intent(out):: xf(:), yf(:) ! longitudes and latitudes, in rad
41 REAL, intent(inout):: champd(:, :)
42
43 ! Variables locales:
44
45 INTEGER lons, lats
46 LOGICAL radianlon ! "xd" is in degrees
47 logical invlon ! "xd" contains longitudes between 0 and 2 pi
48 logical radianlat ! "yd" is in rad
49 REAL rlatmin, rlatmax, old_xf_1
50 INTEGER i, j
51 logical mid_values
52
53 !------------------------------
54
55 lons = assert_eq(size(xd), size(xf), size(champd, 1), "conf_dat2d lons")
56 lats = assert_eq(size(yd), size(yf), size(champd, 2), "conf_dat2d lats")
57
58 IF (xd(1) >= - pi -0.5 .AND. xd(lons) <= pi + 0.5) THEN
59 radianlon = .TRUE.
60 invlon = .FALSE.
61 ELSE IF (xd(1) >= -0.5 .AND. xd(lons) <= 2 * pi+0.5) THEN
62 radianlon = .TRUE.
63 invlon = .TRUE.
64 ELSE IF (xd(1) >= -180.5 .AND. xd(lons) <= 180.5) THEN
65 radianlon = .FALSE.
66 invlon = .FALSE.
67 ELSE IF (xd(1) >= -0.5 .AND. xd(lons) <= 360.5) THEN
68 radianlon = .FALSE.
69 invlon = .TRUE.
70 ELSE
71 stop '"conf_dat2d": problem with longitudes'
72 ENDIF
73
74 rlatmin = MIN(yd(1), yd(lats))
75 rlatmax = MAX(yd(1), yd(lats))
76
77 IF (rlatmin >= -pi / 2 - 0.5 .AND. rlatmax <= pi / 2 + 0.5)THEN
78 radianlat = .TRUE.
79 ELSE IF (rlatmin >= -90. - 0.5 .AND. rlatmax <= 90. + 0.5) THEN
80 radianlat = .FALSE.
81 ELSE
82 stop '"conf_dat2d": problem with latitudes'
83 ENDIF
84
85 IF (radianlon) THEN
86 xf(:) = xd(:)
87 else
88 xf(:) = xd(:) * pi / 180. ! convert to rad
89 ENDIF
90
91 IF (radianlat) THEN
92 yf(:) = yd(:)
93 else
94 yf(:) = yd(:) * pi / 180. ! convert to rad
95 ENDIF
96
97 IF (invlon) THEN
98 ! On tourne les longitudes pour avoir - pi à + pi :
99
100 ! Get the index of the first longitude > pi:
101 i = 1
102 do while (xf(i) <= pi)
103 i = i + 1
104 end do
105
106 xf(i:) = xf(i:) - 2 * pi
107 xf(:) = cshift(xf, shift=i - 1)
108 champd(:, :) = cshift(champd, shift=i - 1)
109 ENDIF
110
111 IF (yd(1) < yd(lats)) THEN
112 ! "yd" contains latitudes from south pole to north pole,
113 ! reverse their order in "yf":
114 yf(lats:1:-1) = yf(:)
115 champd(:, lats:1:-1) = champd(:, :)
116 ENDIF
117
118 if (present(interbar)) then
119 mid_values = interbar
120 else
121 mid_values = .true. ! default
122 end if
123 if (mid_values) then
124 ! Replace longitudes and latitudes by their mid-values:
125 old_xf_1 = xf(1)
126 forall (i = 1: lons - 1) xf(i) = 0.5 * (xf(i) + xf(i+1))
127 xf(lons) = 0.5 * (xf(lons) + old_xf_1 + 2 * pi)
128
129 forall (j = 1: lats - 1) yf(j) = 0.5 * (yf(j) + yf(j+1))
130 end if
131
132 END SUBROUTINE conf_dat2d
133
134 end module conf_dat2d_m

  ViewVC Help
Powered by ViewVC 1.1.21