source: LMDZ6/branches/Amaury_dev/libf/dyn3d/lmdz_dteta1.f90 @ 5186

Last change on this file since 5186 was 5186, checked in by abarral, 9 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.9 KB
RevLine 
[5186]1MODULE lmdz_dteta1
2  IMPLICIT NONE; PRIVATE
3  PUBLIC dteta1
[5099]4
[5186]5CONTAINS
[524]6
[5159]7
[5186]8  SUBROUTINE dteta1(teta, pbaru, pbarv, dteta)
9    USE lmdz_filtreg, ONLY: filtreg
10    USE lmdz_dimensions, ONLY: iim, jjm, llm, ndm
11    USE lmdz_paramet
12    IMPLICIT NONE
[5159]13
[5186]14    !=======================================================================
[5159]15
[5186]16    !   Auteur:  P. Le Van
17    !   -------
18    ! Modif F.Forget 03/94 (on retire q et dq  pour construire dteta1)
[524]19
[5186]20    !   ********************************************************************
21    !   ... calcul du terme de convergence horizontale du flux d'enthalpie
22    !    potentielle   ......
23    !   ********************************************************************
24    !  .. teta,pbaru et pbarv sont des arguments d'entree  pour le s-pg ....
25    ! dteta               sont des arguments de sortie pour le s-pg ....
[524]26
[5186]27    !=======================================================================
[5159]28
[5186]29    REAL :: teta(ip1jmp1, llm), pbaru(ip1jmp1, llm), pbarv(ip1jm, llm)
30    REAL :: dteta(ip1jmp1, llm)
31    INTEGER :: l, ij
[5159]32
[5186]33    REAL :: hbyv(ip1jm, llm), hbxu(ip1jmp1, llm)
[524]34
[5186]35    !
[524]36
[5186]37    DO l = 1, llm
[524]38
[5186]39      DO ij = iip2, ip1jm - 1
40        hbxu(ij, l) = pbaru(ij, l) * 0.5 * (teta(ij, l) + teta(ij + 1, l))
41      END DO
[524]42
[5186]43      !    .... correction pour  hbxu(iip1,j,l)  .....
44      !    ....   hbxu(iip1,j,l)= hbxu(1,j,l) ....
[524]45
[5186]46      !DIR$ IVDEP
47      DO ij = iip1 + iip1, ip1jm, iip1
48        hbxu(ij, l) = hbxu(ij - iim, l)
49      END DO
[524]50
[5186]51      DO ij = 1, ip1jm
52        hbyv(ij, l) = pbarv(ij, l) * 0.5 * (teta(ij, l) + teta(ij + iip1, l))
53      END DO
[524]54
[5103]55    END DO
[524]56
[5186]57    CALL  convflu (hbxu, hbyv, llm, dteta)
[524]58
59
[5186]60    !    stockage dans  dh de la convergence horizont. filtree' du  flux
61    ! ....                           ...........
62    ! d'enthalpie potentielle .
[524]63
[5186]64    CALL filtreg(dteta, jjp1, llm, 2, 2, .TRUE., 1)
[524]65
[5186]66    !
[524]67
[5186]68  END SUBROUTINE dteta1
[5105]69
[5186]70
71END MODULE lmdz_dteta1
Note: See TracBrowser for help on using the repository browser.