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

Last change on this file since 5272 was 5272, checked in by abarral, 23 hours ago

Turn paramet.h into a module

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