source: LMDZ6/branches/Amaury_dev/libf/dyn3d_common/gr_v_scal.f90 @ 5136

Last change on this file since 5136 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
  • 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_v_scal(nx, x_v, 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_comgeom
27  IMPLICIT NONE
28  !-----------------------------------------------------------------------
29  !   Declararations:
30  !   ---------------
31
32  INCLUDE "dimensions.h"
33  INCLUDE "paramet.h"
34
35  !   Arguments:
36  !   ----------
37
38  INTEGER :: nx
39  REAL :: x_v(ip1jm, nx), x_scal(ip1jmp1, nx)
40
41  !   Local:
42  !   ------
43
44  INTEGER :: l, ij
45
46  !-----------------------------------------------------------------------
47
48  DO l = 1, nx
49    DO ij = iip2, ip1jm
50      x_scal(ij, l) = &
51              (airev(ij - iip1) * x_v(ij - iip1, l) + airev(ij) * x_v(ij, l)) &
52                      / (airev(ij - iip1) + airev(ij))
53    ENDDO
54    DO ij = 1, iip1
55      x_scal(ij, l) = 0.
56    ENDDO
57    DO ij = ip1jm + 1, ip1jmp1
58      x_scal(ij, l) = 0.
59    ENDDO
60  ENDDO
61
62  RETURN
63END SUBROUTINE gr_v_scal
Note: See TracBrowser for help on using the repository browser.