source: LMDZ6/trunk/libf/dyn3d/dteta1.f90 @ 5285

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