source: LMDZ6/branches/Amaury_dev/libf/dyn3dmem/gr_u_scal_loc.f90 @ 5153

Last change on this file since 5153 was 5136, checked in by abarral, 8 weeks ago

Put 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.4 KB
Line 
1
2! $Header$
3
4SUBROUTINE gr_u_scal_loc(nx,x_u,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  USE lmdz_comgeom
29
30  IMPLICIT NONE
31  !-----------------------------------------------------------------------
32  !   Declararations:
33  !   ---------------
34
35  INCLUDE "dimensions.h"
36  INCLUDE "paramet.h"
37
38  !   Arguments:
39  !   ----------
40
41  INTEGER :: nx
42  REAL :: x_u(ijb_u:ije_u,nx),x_scal(ijb_u:ije_u,nx)
43
44  !   Local:
45  !   ------
46
47  INTEGER :: l,ij
48  INTEGER :: ijb,ije
49
50  !-----------------------------------------------------------------------
51  ijb=ij_begin
52  ije=ij_end
53
54!$OMP DO SCHEDULE(STATIC,OMP_CHUNK)
55  DO l=1,nx
56     DO ij=ijb+1,ije
57        x_scal(ij,l)= &
58              (aireu(ij)*x_u(ij,l)+aireu(ij-1)*x_u(ij-1,l)) &
59              /(aireu(ij)+aireu(ij-1))
60     ENDDO
61  ENDDO
62!$OMP ENDDO NOWAIT
63
64  ijb=ij_begin
65  ije=ij_end
66
67!$OMP DO SCHEDULE(STATIC,OMP_CHUNK)
68  DO l=1,nx
69     DO ij=ijb,ije-iip1+1,iip1
70       x_scal(ij,l)=x_scal(ij+iip1-1,l)
71     ENDDO
72  ENDDO
73!$OMP ENDDO NOWAIT
74
75
76END SUBROUTINE gr_u_scal_loc
Note: See TracBrowser for help on using the repository browser.