source: LMDZ6/branches/Amaury_dev/libf/dyn3dmem/bernoui_loc.f90 @ 5153

Last change on this file since 5153 was 5134, checked in by abarral, 8 weeks 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
File size: 1.7 KB
Line 
1SUBROUTINE bernoui_loc(ngrid,nlay,pphi,pecin,pbern)
2  USE parallel_lmdz
3  USE lmdz_filtreg_p
4  IMPLICIT NONE
5
6  !=======================================================================
7  !
8  !   Auteur:   P. Le Van
9  !   -------
10  !
11  !   Objet:
12  !   ------
13  ! calcul de la fonction de Bernouilli aux niveaux s  .....
14  ! phi  et  ecin  sont des arguments d'entree pour le s-pg .......
15  !      bern       est un  argument de sortie pour le s-pg  ......
16  !
17  !    fonction de Bernouilli = bern = filtre de( geopotentiel +
18  !                          energ.cinet.)
19  !
20  !=======================================================================
21  !
22  !-----------------------------------------------------------------------
23  !   Decalrations:
24  !   -------------
25  !
26  INCLUDE "dimensions.h"
27  INCLUDE "paramet.h"
28  !
29  !   Arguments:
30  !   ----------
31  !
32  INTEGER :: nlay,ngrid
33  REAL :: pphi(ijb_u:ije_u,nlay),pecin(ijb_u:ije_u,nlay)
34  REAL :: pbern(ijb_u:ije_u,nlay)
35  !
36  !   Local:
37  !   ------
38  !
39  INTEGER :: ij,l,ijb,ije,jjb,jje
40  !
41  !-----------------------------------------------------------------------
42  !   calcul de Bernouilli:
43  !   ---------------------
44  !
45  ijb=ij_begin
46  ije=ij_end+iip1
47  IF (pole_sud) ije=ij_end
48
49  jjb=jj_begin
50  jje=jj_end+1
51  IF (pole_sud) jje=jj_end
52
53!$OMP DO SCHEDULE(STATIC,OMP_CHUNK)
54  DO l=1,llm
55
56    DO ij = ijb,ije
57      pbern( ij,l ) =  pphi( ij,l ) + pecin( ij,l )
58  END DO
59
60   ENDDO
61!$OMP END DO NOWAIT
62  !
63  !-----------------------------------------------------------------------
64  !   filtre:
65  !   -------
66  !
67
68
69    CALL filtreg_p( pbern,jjb_u,jje_u,jjb,jje, jjp1, llm, &
70          2,1, .TRUE., 1 )
71  !
72  !-----------------------------------------------------------------------
73
74
75
76END SUBROUTINE bernoui_loc
Note: See TracBrowser for help on using the repository browser.