source: LMDZ6/trunk/libf/dyn3d_common/convflu.f90 @ 5272

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

Turn paramet.h into a module

  • 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.7 KB
Line 
1!
2! $Header$
3!
4SUBROUTINE convflu( xflu,yflu,nbniv,convfl )
5  !
6  !  P. Le Van
7  !
8  !
9  !    *******************************************************************
10  !  ... calcule la (convergence horiz. * aire locale)du flux ayant pour
11  !  composantes xflu et yflu ,variables extensives .  ......
12  !    *******************************************************************
13  !  xflu , yflu et nbniv sont des arguments d'entree pour le s-pg ..
14  !  convfl                est  un argument de sortie pour le s-pg .
15  !
16  ! njxflu  est le nombre de lignes de latitude de xflu,
17  ! ( = jjm ou jjp1 )
18  ! nbniv   est le nombre de niveaux vert. de  xflu et de yflu .
19  !
20  USE dimensions_mod, ONLY: iim, jjm, llm, ndm
21USE paramet_mod_h, ONLY: iip1, iip2, iip3, jjp1, llmp1, llmp2, llmm1, kftd, ip1jm, ip1jmp1, &
22          ip1jmi1, ijp1llm, ijmllm, mvar, jcfil, jcfllm
23IMPLICIT NONE
24  !
25
26
27  REAL :: xflu,yflu,convfl,convpn,convps
28  INTEGER :: l,ij,nbniv
29  DIMENSION  xflu( ip1jmp1,nbniv ),yflu( ip1jm,nbniv ) , &
30        convfl( ip1jmp1,nbniv )
31  !
32  REAL :: SSUM
33  !
34  !
35  INCLUDE "comgeom.h"
36  !
37  DO l = 1,nbniv
38  !
39  DO  ij = iip2, ip1jm - 1
40  convfl( ij + 1,l ) =  xflu(   ij,l ) - xflu( ij +  1,l )   + &
41        yflu(ij +1,l ) - yflu( ij -iim,l )
42  END DO
43  !
44  !
45
46  ! ....  correction pour  convfl( 1,j,l)  ......
47  ! ....   convfl(1,j,l)= convfl(iip1,j,l) ...
48  !
49  !DIR$ IVDEP
50  DO ij = iip2,ip1jm,iip1
51  convfl( ij,l ) = convfl( ij + iim,l )
52  END DO
53  !
54  ! ......  calcul aux poles  .......
55  !
56  convpn =   SSUM( iim, yflu(     1    ,l ),  1 )
57  convps = - SSUM( iim, yflu( ip1jm-iim,l ),  1 )
58  DO ij = 1,iip1
59  convfl(     ij   ,l ) = convpn * aire(   ij     ) / apoln
60  convfl( ij+ ip1jm,l ) = convps * aire( ij+ ip1jm) / apols
61  END DO
62  !
63  END DO
64  RETURN
65END SUBROUTINE convflu
Note: See TracBrowser for help on using the repository browser.