source: LMDZ6/trunk/libf/dyn3dmem/gr_v_scal_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.6 KB
RevLine 
[1632]1!
2! $Header$
3!
[5246]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  !=======================================================================
[5281]27  USE comgeom_mod_h
[5246]28  USE parallel_lmdz
[5271]29  USE dimensions_mod, ONLY: iim, jjm, llm, ndm
[5285]30USE paramet_mod_h
[5271]31IMPLICIT NONE
[5246]32  !-----------------------------------------------------------------------
33  !   Declararations:
34  !   ---------------
[1632]35
[5271]36
[5272]37
[1632]38
[5246]39  !   Arguments:
40  !   ----------
[1632]41
[5246]42  INTEGER :: nx
43  REAL :: x_v(ijb_v:ije_v,nx),x_scal(ijb_v:ije_v,nx)
[1632]44
[5246]45  !   Local:
46  !   ------
[1632]47
[5246]48  INTEGER :: l,ij
49  INTEGER :: ijb,ije
50  !-----------------------------------------------------------------------
51  ijb=ij_begin
52  ije=ij_end
53  if (pole_nord) ijb=ij_begin+iip1
54  if (pole_sud)  ije=ij_end-iip1
55
56!$OMP DO SCHEDULE(STATIC,OMP_CHUNK)
57  DO l=1,nx
58     DO ij=ijb,ije
59        x_scal(ij,l)= &
60              (airev(ij-iip1)*x_v(ij-iip1,l)+airev(ij)*x_v(ij,l)) &
61              /(airev(ij-iip1)+airev(ij))
62     ENDDO
63  ENDDO
[1632]64!$OMP ENDDO NOWAIT
[5246]65
66  if (pole_nord) then
67!$OMP DO SCHEDULE(STATIC,OMP_CHUNK)
68    DO l=1,nx
69       DO ij=1,iip1
70          x_scal(ij,l)=0.
71       ENDDO
72    ENDDO
[1632]73!$OMP ENDDO NOWAIT
[5246]74  endif
75
76  if (pole_sud) then
77!$OMP DO SCHEDULE(STATIC,OMP_CHUNK)
78    DO l=1,nx
79       DO ij=ip1jm+1,ip1jmp1
80          x_scal(ij,l)=0.
81       ENDDO
82    ENDDO
[1632]83!$OMP ENDDO NOWAIT
[5246]84  endif
[1632]85
[5246]86  RETURN
87END SUBROUTINE gr_v_scal_loc
Note: See TracBrowser for help on using the repository browser.