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

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

Parent Directory Parent Directory | Revision Log Revision Log


Revision 254 - (hide annotations)
Mon Feb 5 10:39:38 2018 UTC (6 years, 4 months ago) by guez
File size: 1910 byte(s)
Move Sources/* to root directory.
1 guez 98 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