source: LMDZ6/branches/Amaury_dev/libf/dyn3dmem/covcont_loc.f90 @ 5153

Last change on this file since 5153 was 5136, checked in by abarral, 8 weeks ago

Put comgeom.h, comgeom2.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.3 KB
Line 
1SUBROUTINE covcont_loc(klevel,ucov, vcov, ucont, vcont )
2  USE parallel_lmdz
3  USE lmdz_comgeom
4
5  IMPLICIT NONE
6
7  !=======================================================================
8  !
9  !   Auteur:  P. Le Van
10  !   -------
11  !
12  !   Objet:
13  !   ------
14  !
15  !  *********************************************************************
16  !    calcul des compos. contravariantes a partir des comp.covariantes
17  !  ********************************************************************
18  !
19  !=======================================================================
20
21  INCLUDE "dimensions.h"
22  INCLUDE "paramet.h"
23
24  INTEGER :: klevel
25  REAL :: ucov( ijb_u:ije_u,klevel ),  vcov( ijb_v:ije_v,klevel )
26  REAL :: ucont( ijb_u:ije_u,klevel ), vcont( ijb_v:ije_v,klevel )
27  INTEGER :: l,ij
28  INTEGER :: ijbu,ijbv,ijeu,ijev
29
30
31  ijbu=ij_begin-iip1
32  ijbv=ij_begin-iip1
33  ijeu=ij_end+iip1
34  ijev=ij_end+iip1
35
36  IF (pole_nord) THEN
37    ijbu=ij_begin+iip1
38    ijbv=ij_begin
39  ENDIF
40
41  IF (pole_sud) THEN
42    ijeu=ij_end-iip1
43    ijev=ij_end-iip1
44  ENDIF
45
46!$OMP DO SCHEDULE(STATIC,OMP_CHUNK)
47  DO l = 1,klevel
48
49  DO ij = ijb_u,ije_u
50  ucont( ij,l ) = ucov( ij,l ) * unscu2( ij )
51  END DO
52
53  DO ij = ijb_v,ije_v
54  vcont( ij,l ) = vcov( ij,l ) * unscv2( ij )
55  END DO
56
57  END DO
58!$OMP END DO NOWAIT
59
60END SUBROUTINE covcont_loc
Note: See TracBrowser for help on using the repository browser.