source: LMDZ6/branches/Amaury_dev/libf/dyn3d/lmdz_dudv1.f90 @ 5214

Last change on this file since 5214 was 5186, checked in by abarral, 12 days ago

Encapsulate files in 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
  • Property svn:eol-style set to native
  • Property svn:keywords set to Author Date Id Revision
File size: 1.5 KB
RevLine 
[5186]1MODULE lmdz_dudv1
2  IMPLICIT NONE; PRIVATE
3  PUBLIC dudv1
[5099]4
[5186]5CONTAINS
[5159]6
7
[5186]8  SUBROUTINE dudv1(vorpot, pbaru, pbarv, du, dv)
9    USE lmdz_dimensions, ONLY: iim, jjm, llm, ndm
10    USE lmdz_paramet
11    IMPLICIT NONE
[5159]12
[5186]13    !-----------------------------------------------------------------------
[5159]14
[5186]15    !   Auteur:   P. Le Van
16    !   -------
[524]17
[5186]18    !   Objet:
19    !   ------
20    !   calcul du terme de  rotation
21    !   ce terme est ajoute a  d(ucov)/dt et a d(vcov)/dt  ..
22    !   vorpot, pbaru et pbarv sont des arguments d'entree  pour le s-pg ..
23    !   du  et dv              sont des arguments de sortie pour le s-pg ..
[524]24
[5186]25    !-----------------------------------------------------------------------
[5159]26
[5186]27    REAL :: vorpot(ip1jm, llm), pbaru(ip1jmp1, llm), &
28            pbarv(ip1jm, llm), du(ip1jmp1, llm), dv(ip1jm, llm)
29    INTEGER :: l, ij
[5159]30
[5186]31    DO l = 1, llm
[5159]32
[5186]33      DO ij = iip2, ip1jm - 1
34        du(ij, l) = 0.125 * (vorpot(ij - iip1, l) + vorpot(ij, l)) * &
35                (pbarv(ij - iip1, l) + pbarv(ij - iim, l) + &
36                        pbarv(ij, l) + pbarv(ij + 1, l))
37      END DO
[5159]38
[5186]39      DO ij = 1, ip1jm - 1
40        dv(ij + 1, l) = - 0.125 * (vorpot(ij, l) + vorpot(ij + 1, l)) * &
41                (pbaru(ij, l) + pbaru(ij + 1, l) + &
42                        pbaru(ij + iip1, l) + pbaru(ij + iip2, l))
43      END DO
[5159]44
[5186]45      !    .... correction  pour  dv( 1,j,l )  .....
46      !    ....   dv(1,j,l)= dv(iip1,j,l) ....
[5159]47
[5186]48      !DIR$ IVDEP
49      DO ij = 1, ip1jm, iip1
50        dv(ij, l) = dv(ij + iim, l)
51      END DO
52
[5103]53    END DO
[5159]54
[5186]55  END SUBROUTINE dudv1
[5159]56
57
[5186]58END MODULE lmdz_dudv1
Note: See TracBrowser for help on using the repository browser.