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

Last change on this file since 5209 was 5159, checked in by abarral, 3 months 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
  • Property svn:eol-style set to native
  • Property svn:keywords set to Author Date Id Revision
File size: 1.4 KB
RevLine 
[5099]1
[524]2! $Header$
[5099]3
[5106]4SUBROUTINE bernoui(ngrid,nlay,pphi,pecin,pbern)
5  USE lmdz_filtreg, ONLY: filtreg
[5159]6  USE lmdz_dimensions, ONLY: iim, jjm, llm, ndm
7  USE lmdz_paramet
[5105]8  IMPLICIT NONE
[524]9
[5105]10  !=======================================================================
[5159]11
[5105]12  !   Auteur:   P. Le Van
13  !   -------
[5159]14
[5105]15  !   Objet:
16  !   ------
17  ! calcul de la fonction de Bernouilli aux niveaux s  .....
18  ! phi  et  ecin  sont des arguments d'entree pour le s-pg .......
19  !      bern       est un  argument de sortie pour le s-pg  ......
[5159]20
[5105]21  !    fonction de Bernouilli = bern = filtre de( geopotentiel +
22  !                          energ.cinet.)
[5159]23
[5105]24  !=======================================================================
[5159]25
[5105]26  !-----------------------------------------------------------------------
27  !   Decalrations:
28  !   -------------
29  !
[5159]30
31
32
[5105]33  !   Arguments:
34  !   ----------
[5159]35
[5105]36  INTEGER :: nlay,ngrid
37  REAL :: pphi(ngrid*nlay),pecin(ngrid*nlay),pbern(ngrid*nlay)
[5159]38
[5105]39  !   Local:
40  !   ------
[5159]41
[5105]42  INTEGER :: ijl
[5159]43
[5105]44  !-----------------------------------------------------------------------
45  !   calcul de Bernouilli:
46  !   ---------------------
[5159]47
[5105]48  DO ijl = 1,ngrid*nlay
49     pbern( ijl ) =  pphi( ijl ) + pecin( ijl )
50  END DO
[5159]51
[5105]52  !-----------------------------------------------------------------------
53  !   filtre:
54  !   -------
[5159]55
[5105]56  CALL filtreg( pbern, jjp1, llm, 2,1, .TRUE., 1 )
[5159]57
[5105]58  !-----------------------------------------------------------------------
59  RETURN
60END SUBROUTINE bernoui
Note: See TracBrowser for help on using the repository browser.