source: LMDZ6/trunk/libf/dyn3dmem/convflu_loc.f90 @ 5278

Last change on this file since 5278 was 5272, checked in by abarral, 2 days 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
File size: 2.1 KB
Line 
1SUBROUTINE convflu_loc( xflu,yflu,nbniv,convfl )
2  !
3  !  P. Le Van
4  !
5  !
6  !    *******************************************************************
7  !  ... calcule la (convergence horiz. * aire locale)du flux ayant pour
8  !  composantes xflu et yflu ,variables extensives .  ......
9  !    *******************************************************************
10  !  xflu , yflu et nbniv sont des arguments d'entree pour le s-pg ..
11  !  convfl                est  un argument de sortie pour le s-pg .
12  !
13  ! njxflu  est le nombre de lignes de latitude de xflu,
14  ! ( = jjm ou jjp1 )
15  ! nbniv   est le nombre de niveaux vert. de  xflu et de yflu .
16  !
17  USE parallel_lmdz
18  USE dimensions_mod, ONLY: iim, jjm, llm, ndm
19USE paramet_mod_h, ONLY: iip1, iip2, iip3, jjp1, llmp1, llmp2, llmm1, kftd, ip1jm, ip1jmp1, &
20          ip1jmi1, ijp1llm, ijmllm, mvar, jcfil, jcfllm
21IMPLICIT NONE
22  !
23
24
25  REAL :: xflu,yflu,convfl,convpn,convps
26  INTEGER :: l,ij,nbniv
27  DIMENSION  xflu( ijb_u:ije_u,nbniv ),yflu( ijb_v:ije_v,nbniv ) , &
28        convfl( ijb_u:ije_u,nbniv )
29  !
30  INTEGER :: ijb,ije
31  EXTERNAL   SSUM
32  REAL :: SSUM
33  !
34  !
35  INCLUDE "comgeom.h"
36  !
37
38!$OMP DO SCHEDULE(STATIC,OMP_CHUNK)
39  DO l = 1,nbniv
40  !
41    ijb=ij_begin
42    ije=ij_end+iip1
43
44    IF (pole_nord) ijb=ij_begin+iip1
45    IF (pole_sud)  ije=ij_end-iip1
46
47    DO  ij = ijb , ije - 1
48      convfl(ij+1,l) = xflu(ij,l) - xflu(ij+ 1,l)   + &
49            yflu(ij +1,l ) - yflu( ij -iim,l )
50    END DO
51  !
52  !
53
54  ! ....  correction pour  convfl( 1,j,l)  ......
55  ! ....   convfl(1,j,l)= convfl(iip1,j,l) ...
56  !
57  !DIR$ IVDEP
58    DO ij = ijb,ije,iip1
59      convfl( ij,l ) = convfl( ij + iim,l )
60    END DO
61  !
62  ! ......  calcul aux poles  .......
63  !
64    IF (pole_nord) THEN
65
66      convpn =   SSUM( iim, yflu(     1    ,l ),  1 )
67
68      DO ij = 1,iip1
69        convfl(ij,l) = convpn * aire(ij) / apoln
70      ENDDO
71
72    ENDIF
73
74    IF (pole_sud) THEN
75
76      convps = - SSUM( iim, yflu( ip1jm-iim,l ),  1 )
77
78      DO ij = 1,iip1
79        convfl(ij+ip1jm,l) = convps * aire(ij+ ip1jm) / apols
80      ENDDO
81
82    ENDIF
83
84  END DO
85!$OMP END DO NOWAIT
86  RETURN
87END SUBROUTINE convflu_loc
Note: See TracBrowser for help on using the repository browser.