source: LMDZ6/branches/Amaury_dev/libf/dyn3d_common/gr_u_scal.f90 @ 5119

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

enforce PRIVATE by default in several modules, expose PUBLIC as needed
move eigen.f90 to obsolete/
(lint) aslong the way

  • 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
  • Property svn:eol-style set to native
  • Property svn:keywords set to Author Date Id Revision
File size: 1.2 KB
Line 
1! $Header$
2
3SUBROUTINE gr_u_scal(nx, x_u, x_scal)
4  !%W%    %G%
5  !=======================================================================
6  !
7  !   Author:    Frederic Hourdin      original: 11/11/92
8  !   -------
9  !
10  !   Subject:
11  !   ------
12  !
13  !   Method:
14  !   --------
15  !
16  !   Interface:
17  !   ----------
18  !
19  !  Input:
20  !  ------
21  !
22  !  Output:
23  !  -------
24  !
25  !=======================================================================
26  USE lmdz_ssum_scopy, ONLY: scopy
27
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_u(ip1jmp1, nx), x_scal(ip1jmp1, nx)
42
43  !   Local:
44  !   ------
45
46  INTEGER :: l, ij
47
48  !-----------------------------------------------------------------------
49
50  DO l = 1, nx
51    DO ij = ip1jmp1, 2, -1
52      x_scal(ij, l) = &
53              (aireu(ij) * x_u(ij, l) + aireu(ij - 1) * x_u(ij - 1, l)) &
54                      / (aireu(ij) + aireu(ij - 1))
55    ENDDO
56  ENDDO
57
58  CALL SCOPY(nx * jjp1, x_scal(iip1, 1), iip1, x_scal(1, 1), iip1)
59
60  RETURN
61END SUBROUTINE gr_u_scal
Note: See TracBrowser for help on using the repository browser.