source: LMDZ6/trunk/libf/dyn3dmem/tourpot_loc.F90 @ 3803

Last change on this file since 3803 was 2603, checked in by Ehouarn Millour, 8 years ago

Cleanup in the dynamics: turn logic.h into module logic_mod.F90
EM

  • 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.0 KB
Line 
1SUBROUTINE tourpot_loc ( vcov, ucov, massebxy, vorpot )
2!
3!-------------------------------------------------------------------------------
4! Authors: P. Le Van.
5!-------------------------------------------------------------------------------
6! Purpose: Compute potential vorticity.
7  USE parallel_lmdz
8  USE mod_filtreg_p
9  IMPLICIT NONE
10  include "dimensions.h"
11  include "paramet.h"
12  include "comgeom.h"
13!===============================================================================
14! Arguments:
15  REAL, INTENT(IN)  :: vcov    (ijb_v:ije_v,llm)
16  REAL, INTENT(IN)  :: ucov    (ijb_u:ije_u,llm)
17  REAL, INTENT(IN)  :: massebxy(ijb_v:ije_v,llm)
18  REAL, INTENT(OUT) :: vorpot  (ijb_v:ije_v,llm)
19!===============================================================================
20! Method used:
21!   vorpot = ( Filtre( d(vcov)/dx - d(ucov)/dy ) + fext ) /psbarxy
22!===============================================================================
23! Local variables:
24  INTEGER :: l, ij, ije, ijb, jje, jjb
25  REAL    :: rot(ijb_v:ije_v,llm)
26!===============================================================================
27
28  ijb=ij_begin-iip1
29  ije=ij_end
30  IF(pole_nord) ijb=ij_begin
31
32!--- Wind vorticity ; correction: rot(iip1,j,l) = rot(1,j,l)
33!$OMP DO SCHEDULE(STATIC,OMP_CHUNK)
34  DO l=1,llm
35    IF(pole_sud) ije=ij_end-iip1-1
36    DO ij=ijb,ije
37      rot(ij,l)=vcov(ij+1,l)-vcov(ij,l)+ucov(ij+iip1,l)-ucov(ij,l)
38    END DO
39    IF(pole_sud) ije=ij_end-iip1
40    DO ij=ijb+iip1-1,ije,iip1; rot(ij,l)=rot(ij-iim,l); END DO
41  END DO
42!$OMP END DO NOWAIT
43
44!--- Filter
45  jjb=jj_begin-1
46  jje=jj_end
47  IF(pole_nord) jjb=jjb+1
48  IF(pole_sud)  jje=jje-1
49  CALL filtreg_p(rot,jjb_v,jje_v,jjb,jje,jjm,llm,2,1,.FALSE.,1)
50
51!--- Potential vorticity ; correction: rot(iip1,j,l) = rot(1,j,l)
52!$OMP DO SCHEDULE(STATIC,OMP_CHUNK)
53  DO l=1,llm
54    IF(pole_sud) ije=ij_end-iip1-1
55    DO ij=ijb,ije
56      vorpot(ij,l)=(rot(ij,l)+fext(ij))/massebxy(ij,l)
57    END DO
58    IF(pole_sud) ije=ij_end-iip1
59    DO ij=ijb+iip1-1,ije,iip1; vorpot(ij,l)=vorpot(ij-iim,l); END DO
60  END DO
61!$OMP END DO NOWAIT
62
63END SUBROUTINE tourpot_loc
64
Note: See TracBrowser for help on using the repository browser.