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

Contents of /trunk/dyn3d/conf_dat2d.f

Parent Directory Parent Directory | Revision Log Revision Log


Revision 36 - (show annotations)
Thu Dec 2 17:11:04 2010 UTC (13 years, 5 months ago) by guez
Original Path: trunk/libf/dyn3d/conf_dat2d.f90
File size: 4180 byte(s)
Now using the library "NR_util".

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

  ViewVC Help
Powered by ViewVC 1.1.21