source: LMDZ6/trunk/libf/dyn3d_common/principal_cshift_m.f90 @ 5300

Last change on this file since 5300 was 5271, checked in by abarral, 12 months ago

Move dimensions.h into a module
Nb: doesn't compile yet

File size: 1.1 KB
Line 
1module principal_cshift_m
2
3  USE dimensions_mod, ONLY: iim, jjm, llm, ndm
4implicit none
5
6contains
7
8  subroutine principal_cshift(is2, xlon, xprimm)
9
10    ! Add or subtract 2 pi so that xlon is near [-pi, pi], then cshift
11    ! so that xlon is in ascending order. Make the same cshift on
12    ! xprimm.
13
14    use nrtype, only: twopi
15    use serre_mod, only: clon
16
17
18    ! for iim
19
20    integer, intent(in):: is2
21    real, intent(inout):: xlon(:), xprimm(:) ! (iim + 1)
22
23    !-----------------------------------------------------
24
25    if (is2 /= 0) then
26       IF (clon <= 0.) THEN
27          IF (is2 /= 1) THEN
28             xlon(:is2 - 1) = xlon(:is2 - 1) + twopi
29             xlon(:iim) = cshift(xlon(:iim), shift = is2 - 1)
30             xprimm(:iim) = cshift(xprimm(:iim), shift = is2 - 1)
31          END IF
32       else
33          xlon(is2 + 1:iim) = xlon(is2 + 1:iim) - twopi
34          xlon(:iim) = cshift(xlon(:iim), shift = is2)
35          xprimm(:iim) = cshift(xprimm(:iim), shift = is2)
36       end IF
37    end if
38
39    xlon(iim + 1) = xlon(1) + twopi
40    xprimm(iim + 1) = xprimm(1)
41
42  end subroutine principal_cshift
43
44end module principal_cshift_m
Note: See TracBrowser for help on using the repository browser.