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

Contents of /trunk/dyn3d/conf_dat3d.f

Parent Directory Parent Directory | Revision Log Revision Log


Revision 3 - (show annotations)
Wed Feb 27 13:16:39 2008 UTC (16 years, 2 months ago) by guez
Original Path: trunk/libf/dyn3d/conf_dat3d.f90
File size: 3277 byte(s)
Initial import
1 module conf_dat3d_m
2
3 IMPLICIT NONE
4
5 contains
6
7 SUBROUTINE conf_dat3d(xd, yd, zd, xf, yf, zf, champd)
8
9 ! From dyn3d/conf_dat3d.F, version 1.1.1.1 2004/05/19 12:53:05
10
11 ! Author : P. Le Van
12
13 ! Ce sous-programme configure le champ de données 3D 'champd' pour
14 ! que la longitude varie de - pi à pi, la latitude de pi/2 à
15 ! - pi/2 et pour que la coordonnée pression soit décroissante.
16
17 use comconst, only: pi
18 use nrutil, only: assert_eq
19
20 REAL, intent(in):: xd(:), yd(:) ! longitudes et latitudes initiales
21 REAL, intent(in):: zd(:) ! pressure levels, in Pa or hPa
22
23 REAL, intent(out):: xf(:) ! longitude, in rad, - pi to pi
24 REAL, intent(out):: yf(:) ! latitude, in rad, pi/2 to -pi/2
25 REAL, intent(out):: zf(:) ! pressure levels, in decreasing order, in Pa
26 REAL, intent(inout):: champd(:, :, :)
27
28 ! Variables locales :
29
30 INTEGER lons, lats, levs
31 LOGICAL radianlon, invlon , radianlat
32 REAL rlatmin, rlatmax, oldxd1
33 INTEGER i
34
35 !--------------------------------------
36
37 lons = assert_eq(size(xd), size(xf), size(champd, 1), "conf_dat3d lons")
38 lats = assert_eq(size(yd), size(yf), size(champd, 2), "conf_dat3d lats")
39 levs = assert_eq(size(zd), size(zf), size(champd, 3), "conf_dat3d levs")
40
41 IF (xd(1) >= - pi - 0.5 .AND. xd(lons) <= pi + 0.5) THEN
42 radianlon = .TRUE.
43 invlon = .FALSE.
44 ELSE IF (xd(1) >= -0.5 .AND. xd(lons) <= 2 * pi+0.5) THEN
45 radianlon = .TRUE.
46 invlon = .TRUE.
47 ELSE IF (xd(1) >= -180.5 .AND. xd(lons) <= 180.5) THEN
48 radianlon = .FALSE.
49 invlon = .FALSE.
50 ELSE IF (xd(1) >= -0.5 .AND. xd(lons) <= 360.5) THEN
51 radianlon = .FALSE.
52 invlon = .TRUE.
53 ELSE
54 print *, 'Problème sur les longitudes des données'
55 stop 1
56 ENDIF
57
58 rlatmin = MIN(yd(1), yd(lats))
59 rlatmax = MAX(yd(1), yd(lats))
60
61 IF (rlatmin >= -pi / 2 - 0.5 .AND. rlatmax <= pi / 2 + 0.5) THEN
62 radianlat = .TRUE.
63 ELSE IF (rlatmin >= - 90. - 0.5 .AND. rlatmax <= 90. + 0.5) THEN
64 radianlat = .FALSE.
65 ELSE
66 print *, ' Problème sur les latitudes des données'
67 stop 1
68 ENDIF
69
70 IF (radianlon) THEN
71 xf(:) = xd(:)
72 else
73 xf(:) = xd(:) * pi / 180.
74 ENDIF
75
76 IF (radianlat) THEN
77 yf(:) = yd(:)
78 else
79 yf(:) = yd(:) * pi / 180.
80 ENDIF
81
82 IF (invlon) THEN
83 ! On tourne les longitudes pour avoir - pi à pi
84 DO i=1, lons
85 IF (xf(i) > pi) exit
86 ENDDO
87
88 where (xf > pi) xf = xf - 2 * pi
89 xf = cshift(xf, i - 1)
90 ! On tourne les longitudes pour "champd":
91 champd = cshift(champd, i - 1)
92 ENDIF
93
94 IF (yd(1) < yd(lats)) THEN
95 yf = yf(lats:1:-1)
96 champd = champd(:, lats:1:-1, :)
97 ENDIF
98
99 oldxd1 = xf(1)
100 forall (i = 1: lons-1) xf(i) = 0.5 * (xf(i) + xf(i+1))
101 xf(lons) = 0.5 * (xf(lons) + oldxd1 + 2 * pi)
102 forall (i = 1: lats-1) yf(i) = 0.5 * (yf(i) + yf(i+1))
103
104 IF (MAX(zd(1), zd(levs)) < 1200.) THEN
105 zf(:) = zd(:) * 100. ! convert from hPa to Pa
106 else
107 zf(:) = zd(:)
108 ENDIF
109
110 IF (zd(1) < zd(levs)) THEN
111 zf(:) = zf(levs:1:-1)
112 champd(:, :, :) = champd(:, :, levs:1:-1)
113 ENDIF
114
115 END SUBROUTINE conf_dat3d
116
117 end module conf_dat3d_m

  ViewVC Help
Powered by ViewVC 1.1.21