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

Last change on this file since 5279 was 5272, checked in by abarral, 33 hours ago

Turn paramet.h into a module

  • 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.9 KB
Line 
1SUBROUTINE bernoui_loc (ngrid,nlay,pphi,pecin,pbern)
2  USE parallel_lmdz
3  USE mod_filtreg_p
4  USE dimensions_mod, ONLY: iim, jjm, llm, ndm
5USE paramet_mod_h, ONLY: iip1, iip2, iip3, jjp1, llmp1, llmp2, llmm1, kftd, ip1jm, ip1jmp1, &
6          ip1jmi1, ijp1llm, ijmllm, mvar, jcfil, jcfllm
7IMPLICIT NONE
8
9  !=======================================================================
10  !
11  !   Auteur:   P. Le Van
12  !   -------
13  !
14  !   Objet:
15  !   ------
16  ! calcul de la fonction de Bernouilli aux niveaux s  .....
17  ! phi  et  ecin  sont des arguments d'entree pour le s-pg .......
18  !      bern       est un  argument de sortie pour le s-pg  ......
19  !
20  !    fonction de Bernouilli = bern = filtre de( geopotentiel +
21  !                          energ.cinet.)
22  !
23  !=======================================================================
24  !
25  !-----------------------------------------------------------------------
26  !   Decalrations:
27  !   -------------
28  !
29
30
31  !
32  !   Arguments:
33  !   ----------
34  !
35  INTEGER :: nlay,ngrid
36  REAL :: pphi(ijb_u:ije_u,nlay),pecin(ijb_u:ije_u,nlay)
37  REAL :: pbern(ijb_u:ije_u,nlay)
38  !
39  !   Local:
40  !   ------
41  !
42  INTEGER :: ij,l,ijb,ije,jjb,jje
43  !
44  !-----------------------------------------------------------------------
45  !   calcul de Bernouilli:
46  !   ---------------------
47  !
48  ijb=ij_begin
49  ije=ij_end+iip1
50  if (pole_sud) ije=ij_end
51
52  jjb=jj_begin
53  jje=jj_end+1
54  if (pole_sud) jje=jj_end
55
56!$OMP DO SCHEDULE(STATIC,OMP_CHUNK)
57  DO l=1,llm
58
59    DO ij = ijb,ije
60      pbern( ij,l ) =  pphi( ij,l ) + pecin( ij,l )
61    END DO
62
63   ENDDO
64!$OMP END DO NOWAIT
65  !
66  !-----------------------------------------------------------------------
67  !   filtre:
68  !   -------
69  !
70
71
72    CALL filtreg_p( pbern,jjb_u,jje_u,jjb,jje, jjp1, llm, &
73          2,1, .true., 1 )
74  !
75  !-----------------------------------------------------------------------
76
77
78  RETURN
79END SUBROUTINE bernoui_loc
Note: See TracBrowser for help on using the repository browser.