source: LMDZ6/trunk/libf/dyn3d_common/bernoui.f90 @ 5248

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

Convert fixed-form to free-form sources .F -> .{f,F}90
(WIP: some .F remain, will be handled in subsequent commits)

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