source: LMDZ6/trunk/libf/dyn3dmem/covcont_loc.f90 @ 5308

Last change on this file since 5308 was 5285, checked in by abarral, 4 days ago

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