/[lmdze]/trunk/libf/dyn3d/conf_dat2d.f90
ViewVC logotype

Contents of /trunk/libf/dyn3d/conf_dat2d.f90

Parent Directory Parent Directory | Revision Log Revision Log


Revision 39 - (show annotations)
Tue Jan 25 15:11:05 2011 UTC (13 years, 3 months ago) by guez
File size: 4157 byte(s)
"pi" comes from "nr_util". Removed subroutine "initialize" in module
"comconst".

Copied the content of "fxy_sin.h" into "fxysinus", instead of getting
it from an "include" line. Removed file "fxy_sin.h".

"ps" has rank 2 in "gcm" and "dynetat0".

Assumed-shape for argument "q" of "integrd".

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

  ViewVC Help
Powered by ViewVC 1.1.21