source: LMDZ6/branches/Amaury_dev/libf/dyn3d_common/limx.f90 @ 5158

Last change on this file since 5158 was 5158, checked in by abarral, 7 weeks ago

Add missing klon on strataer_emiss_mod.F90
Correct various missing explicit declarations
Replace tabs by spaces (tabs are not part of the fortran charset)
Continue cleaning modules
Removed unused arguments and variables

  • 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: 2.1 KB
Line 
1
2! $Header$
3
4SUBROUTINE limx(s0,sx,sm,pente_max)
5  !
6  ! Auteurs:   P.Le Van, F.Hourdin, F.Forget
7  !
8  !    ********************************************************************
9  ! Shema  d'advection " pseudo amont " .
10  !    ********************************************************************
11  ! nq,iq,q,pbaru,pbarv,w sont des arguments d'entree  pour le s-pg ....
12  !
13  !
14  !   --------------------------------------------------------------------
15  USE lmdz_comgeom
16
17  IMPLICIT NONE
18  !
19  INCLUDE "dimensions.h"
20  INCLUDE "paramet.h"
21  !
22  !
23  !   Arguments:
24  !   ----------
25  REAL :: pente_max
26  REAL :: s0(ip1jmp1,llm),sm(ip1jmp1,llm)
27  REAL :: sx(ip1jmp1,llm)
28  !
29  !  Local
30  !   ---------
31  !
32  INTEGER :: ij,l,j,i,iju,ijq,indu(ip1jmp1),niju
33  INTEGER :: n0,iadvplus(ip1jmp1,llm),nl(llm)
34  !
35  REAL :: q(ip1jmp1,llm)
36  REAL :: dxq(ip1jmp1,llm)
37
38
39  REAL :: new_m,zm
40  REAL :: dxqu(ip1jmp1)
41  REAL :: adxqu(ip1jmp1),dxqmax(ip1jmp1)
42
43  Logical :: extremum,first
44  save first
45  data first/.TRUE./
46
47
48   DO  l = 1,llm
49     DO  ij=1,ip1jmp1
50           q(ij,l) = s0(ij,l) / sm ( ij,l )
51           dxq(ij,l) = sx(ij,l) /sm(ij,l)
52     ENDDO
53   ENDDO
54
55  !   calcul de la pente a droite et a gauche de la maille
56
57  DO l = 1, llm
58     DO ij=iip2,ip1jm-1
59        dxqu(ij)=q(ij+1,l)-q(ij,l)
60     enddo
61     DO ij=iip1+iip1,ip1jm,iip1
62        dxqu(ij)=dxqu(ij-iim)
63     enddo
64
65     DO ij=iip2,ip1jm
66        adxqu(ij)=abs(dxqu(ij))
67     enddo
68
69  !   calcul de la pente maximum dans la maille en valeur absolue
70
71     DO ij=iip2+1,ip1jm
72        dxqmax(ij)=pente_max*min(adxqu(ij-1),adxqu(ij))
73     enddo
74
75     DO ij=iip1+iip1,ip1jm,iip1
76        dxqmax(ij-iim)=dxqmax(ij)
77     enddo
78
79  !   calcul de la pente avec limitation
80
81     DO ij=iip2+1,ip1jm
82        IF(     dxqu(ij-1)*dxqu(ij)>0. &
83              .AND. dxq(ij,l)*dxqu(ij)>0.) THEN
84          dxq(ij,l)= &
85                sign(min(abs(dxq(ij,l)),dxqmax(ij)),dxq(ij,l))
86        else
87  !   extremum local
88           dxq(ij,l)=0.
89        endif
90     enddo
91     DO ij=iip1+iip1,ip1jm,iip1
92        dxq(ij-iim,l)=dxq(ij,l)
93     enddo
94
95     DO  ij=1,ip1jmp1
96           sx(ij,l) = dxq(ij,l)*sm(ij,l)
97     ENDDO
98
99   ENDDO
100
101  RETURN
102END SUBROUTINE limx
Note: See TracBrowser for help on using the repository browser.