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

Last change on this file was 5159, checked in by abarral, 3 months ago

Put dimensions.h and paramet.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
RevLine 
[524]1! $Header$
[5099]2
[5119]3SUBROUTINE gr_u_scal(nx, x_u, x_scal)
[5105]4  !%W%    %G%
5  !=======================================================================
[5159]6
[5105]7  !   Author:    Frederic Hourdin      original: 11/11/92
8  !   -------
[5159]9
[5105]10  !   Subject:
11  !   ------
[5159]12
[5105]13  !   Method:
14  !   --------
[5159]15
[5105]16  !   Interface:
17  !   ----------
[5159]18
[5105]19  !  Input:
20  !  ------
[5159]21
[5105]22  !  Output:
23  !  -------
[5159]24
[5105]25  !=======================================================================
[5119]26  USE lmdz_ssum_scopy, ONLY: scopy
[5136]27  USE lmdz_comgeom
[5119]28
[5159]29  USE lmdz_dimensions, ONLY: iim, jjm, llm, ndm
30  USE lmdz_paramet
[5105]31  IMPLICIT NONE
32  !-----------------------------------------------------------------------
33  !   Declararations:
34  !   ---------------
[524]35
36
[5159]37
38
[5105]39  !   Arguments:
40  !   ----------
[524]41
[5105]42  INTEGER :: nx
[5119]43  REAL :: x_u(ip1jmp1, nx), x_scal(ip1jmp1, nx)
[524]44
[5105]45  !   Local:
46  !   ------
[524]47
[5119]48  INTEGER :: l, ij
[524]49
[5105]50  !-----------------------------------------------------------------------
[524]51
[5119]52  DO l = 1, nx
53    DO ij = ip1jmp1, 2, -1
54      x_scal(ij, l) = &
55              (aireu(ij) * x_u(ij, l) + aireu(ij - 1) * x_u(ij - 1, l)) &
56                      / (aireu(ij) + aireu(ij - 1))
57    ENDDO
[5105]58  ENDDO
[524]59
[5119]60  CALL SCOPY(nx * jjp1, x_scal(iip1, 1), iip1, x_scal(1, 1), iip1)
[524]61
[5105]62  RETURN
63END SUBROUTINE gr_u_scal
Note: See TracBrowser for help on using the repository browser.