source: LMDZ6/branches/Amaury_dev/libf/dyn3dmem/geopot_loc.f90 @ 5159

Last change on this file since 5159 was 5159, checked in by abarral, 7 weeks ago

Put dimensions.h and paramet.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
File size: 1.6 KB
Line 
1SUBROUTINE geopot_loc( ngrid, teta, pk, pks, phis, phi )
2  USE parallel_lmdz
3  USE lmdz_dimensions, ONLY: iim, jjm, llm, ndm
4  USE lmdz_paramet
5  IMPLICIT NONE
6
7
8  !=======================================================================
9
10  !   Auteur:  P. Le Van
11  !   -------
12
13  !   Objet:
14  !   ------
15
16  !    *******************************************************************
17  !    ....   calcul du geopotentiel aux milieux des couches    .....
18  !    *******************************************************************
19
20  ! ....   l'integration se fait de bas en haut  ....
21
22  ! .. ngrid,teta,pk,pks,phis sont des argum. d'entree pour le s-pg ..
23  !          phi               est un  argum. de sortie pour le s-pg .
24
25  !=======================================================================
26  !-----------------------------------------------------------------------
27  !   Declarations:
28  !   -------------
29
30
31
32
33  !   Arguments:
34  !   ----------
35  INTEGER :: ngrid
36  REAL :: teta(ijb_u:ije_u,llm),pks(ijb_u:ije_u),phis(ijb_u:ije_u), &
37        pk(ijb_u:ije_u,llm) , phi(ijb_u:ije_u,llm)
38
39
40  !   Local:
41  !   ------
42
43  INTEGER :: l, ij,ijb,ije
44
45
46  !-----------------------------------------------------------------------
47  ! calcul de phi au niveau 1 pres du sol  .....
48  ijb=ij_begin
49  ije=ij_end+iip1
50
51  IF (pole_sud)  ije=ij_end
52
53  DO  ij  = ijb, ije
54  phi( ij,1 ) = phis( ij ) + teta(ij,1) * ( pks(ij) - pk(ij,1) )
55  ENDDO
56
57  ! calcul de phi aux niveaux superieurs  .......
58
59  DO  l = 2,llm
60    DO  ij    = ijb,ije
61    phi(ij,l) = phi(ij,l-1) + 0.5 * ( teta(ij,l)  + teta(ij,l-1) ) &
62          *   (  pk(ij,l-1) -  pk(ij,l)    )
63    ENDDO
64  ENDDO
65
66
67END SUBROUTINE geopot_loc
Note: See TracBrowser for help on using the repository browser.