source: LMDZ6/trunk/libf/dyn3d_common/gr_v_scal.f90

Last change on this file was 5246, checked in by abarral, 23 hours ago

Convert fixed-form to free-form sources .F -> .{f,F}90
(WIP: some .F remain, will be handled in subsequent commits)

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