source: LMDZ6/trunk/libf/dyn3dmem/gr_v_scal_loc.f90 @ 5282

Last change on this file since 5282 was 5281, checked in by abarral, 7 weeks ago

Turn comgeom.h comgeom2.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.8 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 comgeom_mod_h
28  USE parallel_lmdz
29  USE dimensions_mod, ONLY: iim, jjm, llm, ndm
30USE paramet_mod_h, ONLY: iip1, iip2, iip3, jjp1, llmp1, llmp2, llmm1, kftd, ip1jm, ip1jmp1, &
31          ip1jmi1, ijp1llm, ijmllm, mvar, jcfil, jcfllm
32IMPLICIT NONE
33  !-----------------------------------------------------------------------
34  !   Declararations:
35  !   ---------------
36
37
38
39
40  !   Arguments:
41  !   ----------
42
43  INTEGER :: nx
44  REAL :: x_v(ijb_v:ije_v,nx),x_scal(ijb_v:ije_v,nx)
45
46  !   Local:
47  !   ------
48
49  INTEGER :: l,ij
50  INTEGER :: ijb,ije
51  !-----------------------------------------------------------------------
52  ijb=ij_begin
53  ije=ij_end
54  if (pole_nord) ijb=ij_begin+iip1
55  if (pole_sud)  ije=ij_end-iip1
56
57!$OMP DO SCHEDULE(STATIC,OMP_CHUNK)
58  DO l=1,nx
59     DO ij=ijb,ije
60        x_scal(ij,l)= &
61              (airev(ij-iip1)*x_v(ij-iip1,l)+airev(ij)*x_v(ij,l)) &
62              /(airev(ij-iip1)+airev(ij))
63     ENDDO
64  ENDDO
65!$OMP ENDDO NOWAIT
66
67  if (pole_nord) then
68!$OMP DO SCHEDULE(STATIC,OMP_CHUNK)
69    DO l=1,nx
70       DO ij=1,iip1
71          x_scal(ij,l)=0.
72       ENDDO
73    ENDDO
74!$OMP ENDDO NOWAIT
75  endif
76
77  if (pole_sud) then
78!$OMP DO SCHEDULE(STATIC,OMP_CHUNK)
79    DO l=1,nx
80       DO ij=ip1jm+1,ip1jmp1
81          x_scal(ij,l)=0.
82       ENDDO
83    ENDDO
84!$OMP ENDDO NOWAIT
85  endif
86
87  RETURN
88END SUBROUTINE gr_v_scal_loc
Note: See TracBrowser for help on using the repository browser.