/[lmdze]/trunk/dyn3d/Inter_barxy/ord_coord.f
ViewVC logotype

Contents of /trunk/dyn3d/Inter_barxy/ord_coord.f

Parent Directory Parent Directory | Revision Log Revision Log


Revision 98 - (show annotations)
Tue May 13 17:23:16 2014 UTC (10 years ago) by guez
File size: 1910 byte(s)
Split inter_barxy.f : one procedure per module, one module per
file. Grouped the files into a directory.

Split orbite.f.

Value of raz_date read from the namelist is taken into account
(resetting the step counter) even if annee_ref == anneeref and day_ref
== dayref. raz_date is no longer modified by gcm main unit. (Following
LMDZ.)

Removed argument klon of interfsur_lim. Renamed arguments lmt_alb,
lmt_rug to alb_new, z0_new (same name as corresponding actual
arguments in interfsurf_hq).

Removed argument klon of interfsurf_hq.

Removed arguments qs and d_qs of diagetpq. Were always
zero. Downgraded arguments d_qw, d_ql of diagetpq to local variables,
they were not used in physiq. Removed all computations for solid water
in diagetpq, was just zero.


Downgraded arguments fs_bound, fq_bound of diagphy to local variables,
they were not used in physiq. Encapsulated in a test on iprt all
computations in diagphy.

Removed parameter nbtr of module dimphy. Replaced it everywhere in the
program by nqmx - 2.

Removed parameter rnpb of procedure physiq. Kept the true case in
physiq and phytrac. Could not work with false case anyway.

Removed arguments klon, llm, airephy of qcheck. Removed argument ftsol
of initrrnpb, was not used.

1 module ord_coord_m
2
3 implicit none
4
5 contains
6
7
8 !******************************
9
10 SUBROUTINE ord_coord(xi, xo, decrois)
11
12 ! From dyn3d/ord_coord.F, version 1.1.1.1 2004/05/19 12:53:06
13 ! Author : P. Le Van
14
15 ! This procedure receives an array of latitudes.
16 ! It converts them to degrees if they are in radians.
17 ! If the input latitudes are in decreasing order, the procedure
18 ! reverses their order.
19 ! Finally, the procedure adds 90° as the last value of the array.
20
21 use nr_util, only: assert_eq, pi
22
23
24 REAL, intent(in):: xi(:)
25 ! (latitude, in degrees or radians, in increasing or decreasing order)
26 ! ("xi" should contain latitudes from pole to pole.
27 ! "xi" should contain the latitudes of the boundaries of grid
28 ! cells, not the centers of grid cells.
29 ! So the extreme values should not be 90° and -90°.)
30
31 REAL, intent(out):: xo(:) ! angles in degrees
32 LOGICAL, intent(out):: decrois
33
34 ! Variables local to the procedure:
35 INTEGER nmax, i
36
37 !--------------------
38
39 nmax = assert_eq(size(xi), size(xo) - 1, "ord_coord")
40
41 ! Check monotonicity:
42 decrois = xi(2) < xi(1)
43 DO i = 3, nmax
44 IF (decrois .neqv. xi(i) < xi(i-1)) then
45 print *, '"ord_coord": latitudes are not monotonic'
46 stop 1
47 end IF
48 ENDDO
49
50 IF (abs(xi(1)) < pi) then
51 ! "xi" contains latitudes in radians
52 xo(:nmax) = xi(:) * 180. / pi
53 else
54 ! "xi" contains latitudes in degrees
55 xo(:nmax) = xi(:)
56 end IF
57
58 IF (ABS(abs(xo(1)) - 90) < 0.001 .or. ABS(abs(xo(nmax)) - 90) < 0.001) THEN
59 print *, "ord_coord"
60 PRINT *, '"xi" should contain the latitudes of the boundaries of ' &
61 // 'grid cells, not the centers of grid cells.'
62 STOP 1
63 ENDIF
64
65 IF (decrois) xo(:nmax) = xo(nmax:1:- 1)
66 xo(nmax + 1) = 90.
67
68 END SUBROUTINE ord_coord
69
70 end module ord_coord_m

  ViewVC Help
Powered by ViewVC 1.1.21