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

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