source: LMDZ6/branches/Amaury_dev/libf/dyn3dmem/gr_v_scal_loc.f90 @ 5116

Last change on this file since 5116 was 5116, checked in by abarral, 2 months ago

rename modules properly lmdz_*
move ismin, ismax, minmax into new lmdz_libmath.f90
(lint) uppercase fortran keywords

  • 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.6 KB
Line 
1
2! $Header$
3
4SUBROUTINE gr_v_scal_loc(nx,x_v,x_scal)
5  !%W%    %G%
6  !=======================================================================
7  !
8  !   Author:    Frederic Hourdin      original: 11/11/92
9  !   -------
10  !
11  !   Subject:
12  !   ------
13  !
14  !   Method:
15  !   --------
16  !
17  !   Interface:
18  !   ----------
19  !
20  !  Input:
21  !  ------
22  !
23  !  Output:
24  !  -------
25  !
26  !=======================================================================
27  USE parallel_lmdz
28  IMPLICIT NONE
29  !-----------------------------------------------------------------------
30  !   Declararations:
31  !   ---------------
32
33  INCLUDE "dimensions.h"
34  INCLUDE "paramet.h"
35  INCLUDE "comgeom.h"
36
37  !   Arguments:
38  !   ----------
39
40  INTEGER :: nx
41  REAL :: x_v(ijb_v:ije_v,nx),x_scal(ijb_v:ije_v,nx)
42
43  !   Local:
44  !   ------
45
46  INTEGER :: l,ij
47  INTEGER :: ijb,ije
48  !-----------------------------------------------------------------------
49  ijb=ij_begin
50  ije=ij_end
51  if (pole_nord) ijb=ij_begin+iip1
52  if (pole_sud)  ije=ij_end-iip1
53
54!$OMP DO SCHEDULE(STATIC,OMP_CHUNK)
55  DO l=1,nx
56     DO ij=ijb,ije
57        x_scal(ij,l)= &
58              (airev(ij-iip1)*x_v(ij-iip1,l)+airev(ij)*x_v(ij,l)) &
59              /(airev(ij-iip1)+airev(ij))
60     ENDDO
61  ENDDO
62!$OMP ENDDO NOWAIT
63
64  if (pole_nord) THEN
65!$OMP DO SCHEDULE(STATIC,OMP_CHUNK)
66    DO l=1,nx
67       DO ij=1,iip1
68          x_scal(ij,l)=0.
69       ENDDO
70    ENDDO
71!$OMP ENDDO NOWAIT
72  endif
73
74  if (pole_sud) THEN
75!$OMP DO SCHEDULE(STATIC,OMP_CHUNK)
76    DO l=1,nx
77       DO ij=ip1jm+1,ip1jmp1
78          x_scal(ij,l)=0.
79       ENDDO
80    ENDDO
81!$OMP ENDDO NOWAIT
82  endif
83
84
85END SUBROUTINE gr_v_scal_loc
Note: See TracBrowser for help on using the repository browser.