source: LMDZ6/trunk/libf/dyn3d_common/limy.f90 @ 5271

Last change on this file since 5271 was 5271, checked in by abarral, 24 hours ago

Move dimensions.h into a module
Nb: doesn't compile yet

  • 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: 4.6 KB
Line 
1!
2! $Id: limy.f90 5271 2024-10-24 14:25:39Z abarral $
3!
4SUBROUTINE limy(s0,sy,sm,pente_max)
5  !
6  ! Auteurs:   P.Le Van, F.Hourdin, F.Forget
7  !
8  !    ********************************************************************
9  ! Shema  d'advection " pseudo amont " .
10  !    ********************************************************************
11  ! q,w sont des arguments d'entree  pour le s-pg ....
12  ! dq         sont des arguments de sortie pour le s-pg ....
13  !
14  !
15  !   --------------------------------------------------------------------
16  USE comconst_mod, ONLY: pi
17  USE dimensions_mod, ONLY: iim, jjm, llm, ndm
18IMPLICIT NONE
19  !
20
21  include "paramet.h"
22  include "comgeom.h"
23  !
24  !
25  !   Arguments:
26  !   ----------
27  real :: pente_max
28  real :: s0(ip1jmp1,llm),sy(ip1jmp1,llm),sm(ip1jmp1,llm)
29  !
30  !  Local
31  !   ---------
32  !
33  INTEGER :: i,ij,l
34  !
35  REAL :: q(ip1jmp1,llm)
36  REAL :: airej2,airejjm,airescb(iim),airesch(iim)
37  real :: sigv,dyq(ip1jmp1),dyqv(ip1jm)
38  real :: adyqv(ip1jm),dyqmax(ip1jmp1)
39  REAL :: qbyv(ip1jm,llm)
40
41  REAL :: qpns,qpsn,appn,apps,dyn1,dys1,dyn2,dys2
42  Logical :: extremum,first
43  save first
44
45  real :: convpn,convps,convmpn,convmps
46  real :: sinlon(iip1),sinlondlon(iip1)
47  real :: coslon(iip1),coslondlon(iip1)
48  save sinlon,coslon,sinlondlon,coslondlon
49  !
50  !
51  REAL :: SSUM
52  integer :: ismax,ismin
53  EXTERNAL  SSUM, convflu,ismin,ismax
54  EXTERNAL filtreg
55
56  data first/.true./
57
58  if(first) then
59     print*,'SCHEMA AMONT NOUVEAU'
60     first=.false.
61     do i=2,iip1
62        coslon(i)=cos(rlonv(i))
63        sinlon(i)=sin(rlonv(i))
64        coslondlon(i)=coslon(i)*(rlonu(i)-rlonu(i-1))/pi
65        sinlondlon(i)=sinlon(i)*(rlonu(i)-rlonu(i-1))/pi
66     enddo
67     coslon(1)=coslon(iip1)
68     coslondlon(1)=coslondlon(iip1)
69     sinlon(1)=sinlon(iip1)
70     sinlondlon(1)=sinlondlon(iip1)
71  endif
72
73  !
74
75  do l = 1, llm
76  !
77     DO ij=1,ip1jmp1
78           q(ij,l) = s0(ij,l) / sm ( ij,l )
79           dyq(ij) = sy(ij,l) / sm ( ij,l )
80     ENDDO
81  !
82  !   --------------------------------
83  !  CALCUL EN LATITUDE
84  !   --------------------------------
85
86  !   On commence par calculer la valeur du traceur moyenne sur le premier cercle
87  !   de latitude autour du pole (qpns pour le pole nord et qpsn pour
88  !    le pole nord) qui sera utilisee pour evaluer les pentes au pole.
89
90  airej2 = SSUM( iim, aire(iip2), 1 )
91  airejjm= SSUM( iim, aire(ip1jm -iim), 1 )
92  DO i = 1, iim
93  airescb(i) = aire(i+ iip1) * q(i+ iip1,l)
94  airesch(i) = aire(i+ ip1jm- iip1) * q(i+ ip1jm- iip1,l)
95  ENDDO
96  qpns   = SSUM( iim,  airescb ,1 ) / airej2
97  qpsn   = SSUM( iim,  airesch ,1 ) / airejjm
98
99  !   calcul des pentes aux points v
100
101  do ij=1,ip1jm
102     dyqv(ij)=q(ij,l)-q(ij+iip1,l)
103     adyqv(ij)=abs(dyqv(ij))
104  ENDDO
105
106  !   calcul des pentes aux points scalaires
107
108  do ij=iip2,ip1jm
109     dyqmax(ij)=min(adyqv(ij-iip1),adyqv(ij))
110     dyqmax(ij)=pente_max*dyqmax(ij)
111  enddo
112
113  !   calcul des pentes aux poles
114
115  !   calcul des pentes limites aux poles
116
117  ! print*,dyqv(iip1+1)
118  ! appn=abs(dyq(1)/dyqv(iip1+1))
119  ! print*,dyq(ip1jm+1)
120  ! print*,dyqv(ip1jm-iip1+1)
121  ! apps=abs(dyq(ip1jm+1)/dyqv(ip1jm-iip1+1))
122  ! do ij=2,iim
123  !    appn=amax1(abs(dyq(ij)/dyqv(ij)),appn)
124  !    apps=amax1(abs(dyq(ip1jm+ij)/dyqv(ip1jm-iip1+ij)),apps)
125  ! enddo
126  ! appn=min(pente_max/appn,1.)
127  ! apps=min(pente_max/apps,1.)
128
129
130  !   cas ou on a un extremum au pole
131
132  ! if(dyqv(ismin(iim,dyqv,1))*dyqv(ismax(iim,dyqv,1)).le.0.)
133  !    &   appn=0.
134  ! if(dyqv(ismax(iim,dyqv(ip1jm-iip1+1),1)+ip1jm-iip1+1)*
135  !    &   dyqv(ismin(iim,dyqv(ip1jm-iip1+1),1)+ip1jm-iip1+1).le.0.)
136  !    &   apps=0.
137
138  !   limitation des pentes aux poles
139  ! do ij=1,iip1
140  !    dyq(ij)=appn*dyq(ij)
141  !    dyq(ip1jm+ij)=apps*dyq(ip1jm+ij)
142  ! enddo
143
144  !   test
145  !  do ij=1,iip1
146  !     dyq(iip1+ij)=0.
147  !     dyq(ip1jm+ij-iip1)=0.
148  !  enddo
149  !  do ij=1,ip1jmp1
150  !     dyq(ij)=dyq(ij)*cos(rlatu((ij-1)/iip1+1))
151  !  enddo
152
153  if(dyqv(ismin(iim,dyqv,1))*dyqv(ismax(iim,dyqv,1)).le.0.) &
154        then
155     do ij=1,iip1
156        dyqmax(ij)=0.
157     enddo
158  else
159     do ij=1,iip1
160        dyqmax(ij)=pente_max*abs(dyqv(ij))
161     enddo
162  endif
163
164  if(dyqv(ismax(iim,dyqv(ip1jm-iip1+1),1)+ip1jm-iip1+1)* &
165        dyqv(ismin(iim,dyqv(ip1jm-iip1+1),1)+ip1jm-iip1+1).le.0.) &
166        then
167     do ij=ip1jm+1,ip1jmp1
168        dyqmax(ij)=0.
169     enddo
170  else
171     do ij=ip1jm+1,ip1jmp1
172        dyqmax(ij)=pente_max*abs(dyqv(ij-iip1))
173     enddo
174  endif
175
176  !   calcul des pentes limitees
177
178  do ij=1,ip1jmp1
179     if(dyqv(ij)*dyqv(ij-iip1).gt.0.) then
180        dyq(ij)=sign(min(abs(dyq(ij)),dyqmax(ij)),dyq(ij))
181     else
182        dyq(ij)=0.
183     endif
184  enddo
185
186     DO ij=1,ip1jmp1
187           sy(ij,l) = dyq(ij) * sm ( ij,l )
188    ENDDO
189
190  enddo ! fin de la boucle sur les couches verticales
191
192  RETURN
193END SUBROUTINE limy
Note: See TracBrowser for help on using the repository browser.