/[lmdze]/trunk/dyn3d/principal_cshift.f90
ViewVC logotype

Contents of /trunk/dyn3d/principal_cshift.f90

Parent Directory Parent Directory | Revision Log Revision Log


Revision 328 - (show annotations)
Thu Jun 13 14:40:06 2019 UTC (4 years, 11 months ago) by guez
File size: 1140 byte(s)
Change all `.f` suffixes to `.f90`. (The opposite was done in revision
82.)  Because of change of philosopy in GNUmakefile: we already had a
rewritten rule for `.f`, so it does not make the makefile longer to
replace it by a rule for `.f90`. And it spares us options of
makedepf90 and of the compiler. Also we prepare the way for a simpler
`CMakeLists.txt`.

1 module principal_cshift_m
2
3 IMPLICIT NONE
4
5 contains
6
7 subroutine principal_cshift(is2, xlon, xprimm)
8
9 ! Add or subtract 2 pi so that xlon is near [-pi, pi], then cshift
10 ! so that xlon is in ascending order. Make the same cshift on
11 ! xprimm.
12
13 ! Libraries:
14 use nr_util, only: twopi
15
16 use dynetat0_chosen_m, only: clon
17 USE dimensions, ONLY: iim
18
19 integer, intent(in):: is2
20 real, intent(inout):: xlon(:), xprimm(:) ! (iim + 1)
21
22 !-----------------------------------------------------
23
24 if (is2 /= 0) then
25 IF (clon <= 0.) THEN
26 IF (is2 /= 1) THEN
27 xlon(:is2 - 1) = xlon(:is2 - 1) + twopi
28 xlon(:iim) = cshift(xlon(:iim), shift = is2 - 1)
29 xprimm(:iim) = cshift(xprimm(:iim), shift = is2 - 1)
30 END IF
31 else
32 xlon(is2 + 1:iim) = xlon(is2 + 1:iim) - twopi
33 xlon(:iim) = cshift(xlon(:iim), shift = is2)
34 xprimm(:iim) = cshift(xprimm(:iim), shift = is2)
35 end IF
36 end if
37
38 xlon(iim + 1) = xlon(1) + twopi
39 xprimm(iim + 1) = xprimm(1)
40
41 end subroutine principal_cshift
42
43 end module principal_cshift_m

  ViewVC Help
Powered by ViewVC 1.1.21