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

Last change on this file since 5116 was 5116, checked in by abarral, 2 months ago

rename modules properly lmdz_*
move ismin, ismax, minmax into new lmdz_libmath.f90
(lint) uppercase fortran keywords

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