source: LMDZ6/trunk/libf/dyn3dmem/bernoui_loc.f90 @ 5300

Last change on this file since 5300 was 5285, checked in by abarral, 4 days ago

As discussed internally, remove generic ONLY: ... for new _mod_h 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.8 KB
RevLine 
[5246]1SUBROUTINE bernoui_loc (ngrid,nlay,pphi,pecin,pbern)
2  USE parallel_lmdz
3  USE mod_filtreg_p
[5271]4  USE dimensions_mod, ONLY: iim, jjm, llm, ndm
[5285]5USE paramet_mod_h
[5271]6IMPLICIT NONE
[1632]7
[5246]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  !
[5271]28
[5272]29
[5246]30  !
31  !   Arguments:
32  !   ----------
33  !
34  INTEGER :: nlay,ngrid
35  REAL :: pphi(ijb_u:ije_u,nlay),pecin(ijb_u:ije_u,nlay)
36  REAL :: pbern(ijb_u:ije_u,nlay)
37  !
38  !   Local:
39  !   ------
40  !
41  INTEGER :: ij,l,ijb,ije,jjb,jje
42  !
43  !-----------------------------------------------------------------------
44  !   calcul de Bernouilli:
45  !   ---------------------
46  !
47  ijb=ij_begin
48  ije=ij_end+iip1
49  if (pole_sud) ije=ij_end
[1632]50
[5246]51  jjb=jj_begin
52  jje=jj_end+1
53  if (pole_sud) jje=jj_end
[1632]54
[5246]55!$OMP DO SCHEDULE(STATIC,OMP_CHUNK)
56  DO l=1,llm
[1632]57
[5246]58    DO ij = ijb,ije
59      pbern( ij,l ) =  pphi( ij,l ) + pecin( ij,l )
60    END DO
61
62   ENDDO
63!$OMP END DO NOWAIT
64  !
65  !-----------------------------------------------------------------------
66  !   filtre:
67  !   -------
68  !
69
70
71    CALL filtreg_p( pbern,jjb_u,jje_u,jjb,jje, jjp1, llm, &
72          2,1, .true., 1 )
73  !
74  !-----------------------------------------------------------------------
75
76
77  RETURN
78END SUBROUTINE bernoui_loc
Note: See TracBrowser for help on using the repository browser.