source: LMDZ6/branches/Amaury_dev/libf/dyn3d_common/divgrad.f90 @ 5209

Last change on this file since 5209 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
  • Property svn:eol-style set to native
  • Property svn:keywords set to Author Date Id Revision
File size: 1.3 KB
RevLine 
[524]1! $Header$
[5099]2
[5119]3SUBROUTINE divgrad(klevel, h, lh, divgra)
[5106]4  USE lmdz_filtreg, ONLY: filtreg
[5119]5  USE lmdz_ssum_scopy, ONLY: scopy
[5134]6  USE lmdz_comdissipn, ONLY: tetaudiv, tetaurot, tetah, cdivu, crot, cdivh
[5136]7  USE lmdz_comgeom
[5134]8
[5159]9  USE lmdz_dimensions, ONLY: iim, jjm, llm, ndm
10  USE lmdz_paramet
[5105]11  IMPLICIT NONE
[5159]12
[5105]13  !=======================================================================
[5159]14
[5105]15  !  Auteur :   P. Le Van
16  !  ----------
[5159]17
[5105]18  !                          lh
19  !  calcul de  (div( grad ))   de h  .....
20  !  h  et lh  sont des arguments  d'entree pour le s-prog
21  !  divgra     est  un argument  de sortie pour le s-prog
[5159]22
[5105]23  !=======================================================================
[5159]24
[5105]25  !   declarations:
26  !   -------------
27  !
[5159]28
29
30
[5105]31  INTEGER :: klevel
[5119]32  REAL :: h(ip1jmp1, klevel), divgra(ip1jmp1, klevel)
[5159]33
[5119]34  REAL :: ghy(ip1jm, llm), ghx(ip1jmp1, llm)
[524]35
[5119]36  INTEGER :: l, ij, iter, lh
[5159]37
38
39
[5119]40  CALL SCOPY (ip1jmp1 * klevel, h, 1, divgra, 1)
[5159]41
[5119]42  DO iter = 1, lh
[524]43
[5119]44    CALL filtreg (divgra, jjp1, klevel, 2, 1, .TRUE., 1)
[524]45
[5119]46    CALL    grad (klevel, divgra, ghx, ghy)
47    CALL  diverg (klevel, ghx, ghy, divgra)
[524]48
[5119]49    CALL filtreg (divgra, jjp1, klevel, 2, 1, .TRUE., 1)
[524]50
[5119]51    DO l = 1, klevel
52      DO ij = 1, ip1jmp1
53        divgra(ij, l) = - cdivh * divgra(ij, l)
54      END DO
55    END DO
[5159]56
[5105]57  END DO
58  RETURN
59END SUBROUTINE divgrad
Note: See TracBrowser for help on using the repository browser.