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

Last change on this file was 5159, checked in by abarral, 7 weeks 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
File size: 1.7 KB
RevLine 
[5106]1SUBROUTINE bernoui_loc(ngrid,nlay,pphi,pecin,pbern)
[5105]2  USE parallel_lmdz
[5106]3  USE lmdz_filtreg_p
[5159]4  USE lmdz_dimensions, ONLY: iim, jjm, llm, ndm
5  USE lmdz_paramet
[5105]6  IMPLICIT NONE
[1632]7
[5105]8  !=======================================================================
[5159]9
[5105]10  !   Auteur:   P. Le Van
11  !   -------
[5159]12
[5105]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  ......
[5159]18
[5105]19  !    fonction de Bernouilli = bern = filtre de( geopotentiel +
20  !                          energ.cinet.)
[5159]21
[5105]22  !=======================================================================
[5159]23
[5105]24  !-----------------------------------------------------------------------
25  !   Decalrations:
26  !   -------------
27  !
[5159]28
29
30
[5105]31  !   Arguments:
32  !   ----------
[5159]33
[5105]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)
[5159]37
[5105]38  !   Local:
39  !   ------
[5159]40
[5105]41  INTEGER :: ij,l,ijb,ije,jjb,jje
[5159]42
[5105]43  !-----------------------------------------------------------------------
44  !   calcul de Bernouilli:
45  !   ---------------------
[5159]46
[5105]47  ijb=ij_begin
48  ije=ij_end+iip1
[5117]49  IF (pole_sud) ije=ij_end
[1632]50
[5105]51  jjb=jj_begin
52  jje=jj_end+1
[5117]53  IF (pole_sud) jje=jj_end
[1632]54
[5105]55!$OMP DO SCHEDULE(STATIC,OMP_CHUNK)
56  DO l=1,llm
[1632]57
[5105]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
[5159]64
[5105]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 )
[5159]73
[5105]74  !-----------------------------------------------------------------------
75
76
77
78END SUBROUTINE bernoui_loc
Note: See TracBrowser for help on using the repository browser.