source: LMDZ6/branches/Amaury_dev/libf/dyn3d_common/interpost.f90 @ 5157

Last change on this file since 5157 was 5136, checked in by abarral, 3 months ago

Put comgeom.h, comgeom2.h into modules

  • Property copyright set to
    Name of program: LMDZ
    Creation date: 1984
    Version: LMDZ5
    License: CeCILL version 2
    Holder: Laboratoire de m\'et\'eorologie dynamique, CNRS, UMR 8539
    See the license file in the root directory
  • Property svn:eol-style set to native
  • Property svn:keywords set to Author Date Id Revision
File size: 761 bytes
Line 
1! $Header$
2
3SUBROUTINE interpost(q, qppm)
4  USE lmdz_comgeom2
5
6  IMPLICIT NONE
7
8  INCLUDE "dimensions.h"
9  INCLUDE "paramet.h"
10
11  ! Arguments
12  REAL :: q(iip1, jjp1, llm)
13  REAL :: qppm(iim, jjp1, llm)
14  ! Local
15  INTEGER :: l, i, j
16
17  ! RE-INVERSION DES NIVEAUX
18  ! le programme ppm3d travaille avec une 3ème coordonnée inversée par rapport
19  ! de celle du LMDZ: z=1<=>niveau max, z=llm+1<=>surface
20  ! On passe donc des niveaux de Lin à ceux du LMDZ
21
22  do l = 1, llm
23    do j = 1, jjp1
24      do i = 1, iim
25        q(i, j, l) = qppm(i, j, llm - l + 1)
26      enddo
27    enddo
28  enddo
29
30  ! BOUCLAGE EN LONGITUDE PAS EFFECTUE DANS PPM3D
31
32  do l = 1, llm
33    do j = 1, jjp1
34      q(iip1, j, l) = q(1, j, l)
35    enddo
36  enddo
37
38  return
39
40END SUBROUTINE interpost
Note: See TracBrowser for help on using the repository browser.