source: LMDZ6/trunk/libf/dyn3d_common/geopot.f90 @ 5272

Last change on this file since 5272 was 5272, checked in by abarral, 23 hours ago

Turn paramet.h into a module

  • 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: 1.7 KB
Line 
1!
2! $Header$
3!
4SUBROUTINE geopot (ngrid, teta, pk, pks, phis, phi )
5  USE dimensions_mod, ONLY: iim, jjm, llm, ndm
6  USE paramet_mod_h, ONLY: iip1, iip2, iip3, jjp1, llmp1, llmp2, llmm1, kftd, ip1jm, ip1jmp1, &
7          ip1jmi1, ijp1llm, ijmllm, mvar, jcfil, jcfllm
8
9IMPLICIT NONE
10
11  !=======================================================================
12  !
13  !   Auteur:  P. Le Van
14  !   -------
15  !
16  !   Objet:
17  !   ------
18  !
19  !    *******************************************************************
20  !    ....   calcul du geopotentiel aux milieux des couches    .....
21  !    *******************************************************************
22  !
23  ! ....   l'integration se fait de bas en haut  ....
24  !
25  ! .. ngrid,teta,pk,pks,phis sont des argum. d'entree pour le s-pg ..
26  !          phi               est un  argum. de sortie pour le s-pg .
27  !
28  !=======================================================================
29  !-----------------------------------------------------------------------
30  !   Declarations:
31  !   -------------
32
33  !   Arguments:
34  !   ----------
35
36  INTEGER :: ngrid
37  REAL :: teta(ngrid,llm),pks(ngrid),phis(ngrid),pk(ngrid,llm) , &
38        phi(ngrid,llm)
39
40
41  !   Local:
42  !   ------
43
44  INTEGER :: l, ij
45
46
47  !-----------------------------------------------------------------------
48  ! calcul de phi au niveau 1 pres du sol  .....
49
50  DO  ij  = 1, ngrid
51  phi( ij,1 ) = phis( ij ) + teta(ij,1) * ( pks(ij) - pk(ij,1) )
52  END DO
53
54  ! calcul de phi aux niveaux superieurs  .......
55
56  DO  l = 2,llm
57    DO  ij    = 1,ngrid
58    phi(ij,l) = phi(ij,l-1) + 0.5 * ( teta(ij,l)  + teta(ij,l-1) ) &
59          *   (  pk(ij,l-1) -  pk(ij,l)    )
60    ENDDO
61  ENDDO
62
63  RETURN
64END SUBROUTINE geopot
Note: See TracBrowser for help on using the repository browser.