source: LMDZ6/branches/Amaury_dev/libf/dyn3d_common/bernoui.f90 @ 5139

Last change on this file since 5139 was 5134, checked in by abarral, 4 months ago

Replace academic.h, alpale.h, comdissip.h, comdissipn.h, comdissnew.h by modules
Remove unused clesph0.h

  • 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.5 KB
Line 
1
2! $Header$
3
4SUBROUTINE bernoui(ngrid,nlay,pphi,pecin,pbern)
5  USE lmdz_filtreg, ONLY: filtreg
6  IMPLICIT NONE
7
8  !=======================================================================
9  !
10  !   Auteur:   P. Le Van
11  !   -------
12  !
13  !   Objet:
14  !   ------
15  ! calcul de la fonction de Bernouilli aux niveaux s  .....
16  ! phi  et  ecin  sont des arguments d'entree pour le s-pg .......
17  !      bern       est un  argument de sortie pour le s-pg  ......
18  !
19  !    fonction de Bernouilli = bern = filtre de( geopotentiel +
20  !                          energ.cinet.)
21  !
22  !=======================================================================
23  !
24  !-----------------------------------------------------------------------
25  !   Decalrations:
26  !   -------------
27  !
28  INCLUDE "dimensions.h"
29  INCLUDE "paramet.h"
30  !
31  !   Arguments:
32  !   ----------
33  !
34  INTEGER :: nlay,ngrid
35  REAL :: pphi(ngrid*nlay),pecin(ngrid*nlay),pbern(ngrid*nlay)
36  !
37  !   Local:
38  !   ------
39  !
40  INTEGER :: ijl
41  !
42  !-----------------------------------------------------------------------
43  !   calcul de Bernouilli:
44  !   ---------------------
45  !
46  DO ijl = 1,ngrid*nlay
47     pbern( ijl ) =  pphi( ijl ) + pecin( ijl )
48  END DO
49  !
50  !-----------------------------------------------------------------------
51  !   filtre:
52  !   -------
53  !
54  CALL filtreg( pbern, jjp1, llm, 2,1, .TRUE., 1 )
55  !
56  !-----------------------------------------------------------------------
57  RETURN
58END SUBROUTINE bernoui
Note: See TracBrowser for help on using the repository browser.