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

Last change on this file since 5133 was 5116, checked in by abarral, 5 months ago

rename modules properly lmdz_*
move ismin, ismax, minmax into new lmdz_libmath.f90
(lint) uppercase fortran keywords

  • 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: 767 bytes
RevLine 
[5099]1
[524]2! $Header$
[5099]3
[5105]4  SUBROUTINE interpost(q,qppm)
[524]5
[5113]6   IMPLICIT NONE
[524]7
8
[5105]9  include "dimensions.h"
10  include "paramet.h"
11  include "comgeom2.h"
[524]12
[5105]13  ! Arguments
[5116]14  REAL :: q(iip1,jjp1,llm)
15  REAL :: qppm(iim,jjp1,llm)
[5105]16  ! Local
[5116]17  INTEGER :: l,i,j
[524]18
[5105]19  ! RE-INVERSION DES NIVEAUX
20  ! le programme ppm3d travaille avec une 3ème coordonnée inversée par rapport
21  ! de celle du LMDZ: z=1<=>niveau max, z=llm+1<=>surface
22  ! On passe donc des niveaux de Lin à ceux du LMDZ
23
24    do l=1,llm
25      do j=1,jjp1
26         do i=1,iim
27             q(i,j,l)=qppm(i,j,llm-l+1)
[524]28         enddo
[5105]29      enddo
30     enddo
[524]31
[5105]32  ! BOUCLAGE EN LONGITUDE PAS EFFECTUE DANS PPM3D
33
34     do l=1,llm
35       do j=1,jjp1
36        q(iip1,j,l)=q(1,j,l)
37       enddo
38     enddo
39
40
41   return
42
[5116]43END SUBROUTINE interpost
Note: See TracBrowser for help on using the repository browser.