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

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