source: LMDZ6/trunk/libf/phylmd/cv3_mixscale.f90 @ 5773

Last change on this file since 5773 was 5692, checked in by yann meurdesoif, 6 weeks ago

Convection GPU porting : set convection subroutines into module

Files will be renamed later to *_mod.f90

YM

  • 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: 990 bytes
Line 
1MODULE cv3_mixscale_mod
2  PRIVATE
3
4  PUBLIC cv3_mixscale
5
6CONTAINS
7
8SUBROUTINE cv3_mixscale(nloc, ncum, na, ment, m)
9  ! **************************************************************
10  ! *
11  ! CV3_MIXSCALE                                                *
12  ! *
13  ! *
14  ! written by   : Jean-Yves Grandpeix, 30/05/2003, 16.34.37    *
15  ! modified by :                                               *
16  ! **************************************************************
17
18   USE lmdz_cv_ini, ONLY : nl
19    IMPLICIT NONE
20
21
22!inputs:
23  INTEGER, INTENT (IN)                               :: ncum, na, nloc
24  REAL, DIMENSION (nloc, na), INTENT (IN)            :: m
25!input/outputs:
26  REAL, DIMENSION (nloc, na, na), INTENT (INOUT)     :: ment
27
28!local variables:
29  INTEGER i, j, il
30
31    DO j = 1, nl
32      DO i = 1, nl
33        DO il = 1, ncum
34          ment(il, i, j) = m(il, i)*ment(il, i, j)
35        END DO
36      END DO
37    END DO
38
39
40  RETURN
41END SUBROUTINE cv3_mixscale
42
43END MODULE cv3_mixscale_mod
Note: See TracBrowser for help on using the repository browser.