source: LMDZ6/trunk/libf/dyn3d_common/gr_u_scal.f90 @ 5271

Last change on this file since 5271 was 5271, checked in by abarral, 24 hours ago

Move dimensions.h into a module
Nb: doesn't compile yet

  • 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.1 KB
Line 
1!
2! $Header$
3!
4SUBROUTINE gr_u_scal(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 dimensions_mod, ONLY: iim, jjm, llm, ndm
28IMPLICIT NONE
29  !-----------------------------------------------------------------------
30  !   Declararations:
31  !   ---------------
32
33
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.