source: LMDZ6/branches/Amaury_dev/libf/dyn3dmem/convflu_loc.f90

Last change on this file was 5159, checked in by abarral, 7 weeks ago

Put dimensions.h and paramet.h into modules

  • 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: 1.9 KB
RevLine 
[5105]1SUBROUTINE convflu_loc( xflu,yflu,nbniv,convfl )
[5159]2
[5105]3  !  P. Le Van
[5159]4
5
[5105]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 .
[5159]12
[5105]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 .
[5159]16
[5105]17  USE parallel_lmdz
[5123]18  USE lmdz_ssum_scopy, ONLY: ssum
[5136]19  USE lmdz_comgeom
[5123]20
[5159]21USE lmdz_dimensions, ONLY: iim, jjm, llm, ndm
22  USE lmdz_paramet
[5105]23  IMPLICIT NONE
24  !
[5159]25
26
[5105]27  REAL :: xflu,yflu,convfl,convpn,convps
28  INTEGER :: l,ij,nbniv
29  DIMENSION  xflu( ijb_u:ije_u,nbniv ),yflu( ijb_v:ije_v,nbniv ) , &
30        convfl( ijb_u:ije_u,nbniv )
[5159]31
[5105]32  INTEGER :: ijb,ije
[1632]33
[5105]34!$OMP DO SCHEDULE(STATIC,OMP_CHUNK)
35  DO l = 1,nbniv
[5159]36
[5105]37    ijb=ij_begin
38    ije=ij_end+iip1
39
40    IF (pole_nord) ijb=ij_begin+iip1
41    IF (pole_sud)  ije=ij_end-iip1
42
43    DO ij = ijb , ije - 1
44      convfl(ij+1,l) = xflu(ij,l) - xflu(ij+ 1,l)   + &
45            yflu(ij +1,l ) - yflu( ij -iim,l )
46  END DO
[5159]47
[5105]48  !
49
50  ! ....  correction pour  convfl( 1,j,l)  ......
51  ! ....   convfl(1,j,l)= convfl(iip1,j,l) ...
[5159]52
[5105]53  !DIR$ IVDEP
54    DO ij = ijb,ije,iip1
55      convfl( ij,l ) = convfl( ij + iim,l )
56  END DO
[5159]57
[5105]58  ! ......  calcul aux poles  .......
[5159]59
[5105]60    IF (pole_nord) THEN
61
62      convpn =   SSUM( iim, yflu(     1    ,l ),  1 )
63
64      DO ij = 1,iip1
65        convfl(ij,l) = convpn * aire(ij) / apoln
66      ENDDO
67
68    ENDIF
69
70    IF (pole_sud) THEN
71
72      convps = - SSUM( iim, yflu( ip1jm-iim,l ),  1 )
73
74      DO ij = 1,iip1
75        convfl(ij+ip1jm,l) = convps * aire(ij+ ip1jm) / apols
76      ENDDO
77
78    ENDIF
79
80  END DO
81!$OMP END DO NOWAIT
82
83END SUBROUTINE convflu_loc
Note: See TracBrowser for help on using the repository browser.