source: trunk/libf/phyvenus/flott_gwd_ran.F @ 4

Last change on this file since 4 was 3, checked in by slebonnois, 15 years ago

Creation de repertoires:

  • chantiers : pour communiquer sur nos projets de modifs
  • documentation : pour stocker les docs

Ajout de:

  • libf/phytitan : physique de Titan
  • libf/chimtitan: chimie de Titan
  • libf/phyvenus : physique de Venus
File size: 13.1 KB
Line 
1      SUBROUTINE FLOTT_GWD_RAN(NLON,NLEV,DTIME, pp, pn2,
2     I      tt,uu,vv,
3     O      zustr,zvstr,
4     O      d_t, d_u, d_v)
5
6C ########################################################################
7C Parametrization of the momentum flux deposition due to a discrete
8C numbe of gravity waves.
9C    F. Lott (2008)
10C                 LMDz model stand alone version
11C ########################################################################
12C
13C
14      implicit none
15
16#include "dimensions.h"
17#include "paramet.h"
18#include "dimphy.h"
19
20#include "YOEGWD.h"
21#include "YOMCST.h"
22
23c VENUS ATTENTION: CP VARIABLE
24      real cp(NLON,NLEV)
25
26C  DECLARATIONS:
27C  INPUTS
28      INTEGER NLON,NLEV
29      REAL DTIME
30      REAL pp(NLON,NLEV)    ! Pressure at full levels
31c VENUS ATTENTION: CP VARIABLE PN2 CALCULE EN AMONT DES PARAMETRISATIONS
32      REAL pn2(NLON,NLEV)   ! N2 (BV^2) at 1/2 levels
33      REAL TT(NLON,NLEV)                 ! Temp at full levels
34      REAL UU(NLON,NLEV),VV(NLON,NLEV) ! Temp, and winds at full levels
35
36C  OUTPUTS
37      REAL zustr(NLON),zvstr(NLON)          ! Surface Stresses
38      REAL d_t(NLON,NLEV)                   ! Tendency on Temp.
39      REAL d_u(NLON,NLEV), d_v(NLON,NLEV)   ! Tendencies on winds
40
41c ON CONSERVE LA MEMOIRE un certain temps AVEC UN SAVE ET UN COEF
42      real coef,d_u_sav(KLON,KLEV),d_v_sav(KLON,KLEV)
43      parameter (coef = 0.986)
44      save d_u_sav,d_v_sav
45
46C  GRAVITY-WAVES SPECIFICATIONS
47
48      INTEGER JK,NK,JP,NP,JO,NO,JW,NW,II,LL
49      PARAMETER(NK=4,NP=4,NO=4,NW=NK*NP*NO) ! nombres d'ondes envoyées
50      REAL KMIN,KMAX   !  Min and Max horizontal wavenumbers
51      REAL OMIN,OMAX   ! Max frequency and security for divisions!
52      PARAMETER (KMIN=2.E-5,KMAX=2.E-4,OMIN=2.E-5,OMAX=2.E-3)
53      REAL RUWMAX,SAT  ! MAX EP FLUX AT LAUNCH LEVEL, SATURATION PARAMETER
54      PARAMETER (RUWMAX=1.E-3,SAT=0.1)
55      REAL ZK(NW,KLON),ZP(NW),ZO(NW,KLON)  ! Waves absolute specifications!
56      REAL ZOM(NW,KLON),ZOP(NW,KLON)  ! Intrisic frequency at 1/2 levels
57      REAL PHM(NW,KLON),PHP(NW,KLON)  ! Phi at 1/2 levels
58      REAL RUW0(NW,KLON)              ! Fluxes at lauch level
59      REAL RUWP(NW,KLON),RVWP(NW,KLON)! Fluxes X and Y for each wave
60      INTEGER LAUNCH
61      REAL ALEAS
62      EXTERNAL ALEAS
63
64C  OUTPUT FOR RAW PROFILES:
65
66      INTEGER IU
67
68C  PARAMETERS OF WAVES DISSPATIONS
69      REAL RDISS,ZOISEC  !  COEFF DE DISSIPATION, SECURITY FOR INTRINSIC FREQ
70      PARAMETER (RDISS=10.,ZOISEC=1.E-5)
71
72C  INTERNAL ARRAYS
73      real PR,RH(KLON,KLEV+1) ! Ref Press. intervient dans amplitude ?
74      PARAMETER (PR=9.2e6)    ! VENUS!!
75
76
77      REAL UH(KLON,KLEV+1),VH(KLON,KLEV+1) ! Winds at 1/2 levels
78      REAL PH(KLON,KLEV+1)                 ! Pressure at 1/2 levels
79      REAL PHM1(KLON,KLEV+1)               ! 1/Press  at 1/2 levels
80      REAL BV(KLON,KLEV+1),BVSEC           ! BVF at 1/2 levels
81      REAL PSEC                            ! SECURITY TO AVOID DIVISION
82      PARAMETER (PSEC=1.E-6)               ! BY O PRESSURE VALUE
83      REAL RUW(KLON,KLEV+1)                ! Flux x at semi levels
84      REAL RVW(KLON,KLEV+1)                ! Flux y at semi levels
85
86C  INITIALISATION
87
88      BVSEC=1.E-6
89
90c      PRINT *,ALEAS(0.)
91
92C  WAVES CHARACTERISTTICS
93
94      JW=0
95      DO 11 JP=1,NP
96      DO 11 JK=1,NK
97      DO 11 JO=1,NO
98        JW=JW+1
99      ZP(JW)=2.*RPI*FLOAT(JP-1)/FLOAT(NP) ! Angle
100      DO 11 II=1,NLON
101        ZK(JW,II)=KMIN+(KMAX-KMIN)*ALEAS(0.)  ! Hor. Wavenbr
102        ZO(JW,II)=OMIN+(OMAX-OMIN)*ALEAS(0.)  ! Absolute frequency
103        RUW0(JW,II)=RUWMAX/FLOAT(NW)*ALEAS(0.) ! Momentum flux at launch lev     
10411    CONTINUE
105     
106c      print*,"cos(ZP)=",cos(ZP)
107
108c        PRINT *,'Catch 22'
109
110C  2. SETUP
111
112c  VENUS: CP(T) at ph levels
113      do II=1,NLON
114        do LL=2,KLEV
115          cp(II,LL)=cpdet(0.5*(TT(II,LL)+TT(II,LL-1)))
116        enddo
117      enddo
118C  PRESSURE AT HALPH LEVELS
119
120        II=KLON/2
121
122        DO 20 LL=2,KLEV
123        PH(:,LL)=EXP((ALOG(PP(:,LL))+ALOG(PP(:,LL-1)))/2.)
124        PHM1(:,LL)=1./PH(:,LL)
12520      CONTINUE
126
127        PH(:,KLEV+1)=0. 
128        PHM1(:,KLEV+1)=1./PSEC
129
130        PH(:,1)=2.*PP(:,1)-PH(:,2)
131
132C  LOG-PRESSURE ALTITUDE AND DENSITY
133
134
135        DO 22 LL=1,KLEV+1 
136          RH(:,LL)=PH(:,LL)/PR           !  Reference density
13722      CONTINUE
138
139C   LAUNCHING ALTITUDE
140
141      DO LL=1,NLEV
142      IF(PH(NLON/2,LL)/PH(NLON/2,1).GT.0.8)LAUNCH=LL
143      ENDDO
144c      PRINT *,'LAUNCH:',LAUNCH
145
146C  WINDS AND BV FREQUENCY AT 1/2 LEVELS
147
148        DO 23 LL=2,KLEV
149        UH(:,LL)=0.5*(UU(:,LL)+UU(:,LL-1))
150        VH(:,LL)=0.5*(VV(:,LL)+VV(:,LL-1))
151
152c VENUS ATTENTION: CP VARIABLE PSTAB CALCULE EN AMONT DES PARAMETRISATIONS
153        BV(:,LL)=SQRT(AMAX1(BVSEC,pn2(:,LL)))
154
15523      CONTINUE
156       
157c       print *,'catch 23'
158
159        BV(:,1)=BV(:,2)
160        UH(:,1)=0.
161        VH(:,1)=0.
162        BV(:,KLEV+1)=BV(:,KLEV)
163        UH(:,KLEV+1)=UU(:,KLEV)
164        VH(:,KLEV+1)=VV(:,KLEV)
165
166C  3. COMPUTE THE FLUXES!!
167
168        DO  3 JW=1,NW
169
170        ZOP(JW,:)=ZO(JW,:)-ZK(JW,:)*COS(ZP(JW))*UH(:,LAUNCH) ! Intrinsic
171     C                    -ZK(JW,:)*SIN(ZP(JW))*VH(:,LAUNCH) ! Frequency
172        PHP(JW,:)=
173C       AMIN1(                          ! Phi at launch level
174C  ENSURES THE IMPOSED MOM FLUX:
175     C SQRT(ABS(ZOP(JW,:))*BV(:,LAUNCH)
176     C      *RUW0(JW,:)/RH(:,LAUNCH))/ZK(JW,:)
177        RUWP(JW,:)=COS(ZP(JW))*SIGN(1.,ZOP(JW,:))*RUW0(JW,:)
178        RVWP(JW,:)=SIN(ZP(JW))*SIGN(1.,ZOP(JW,:))*RUW0(JW,:)
179
1803       CONTINUE
181
182        do LL=1,LAUNCH
183         RUW(:,LL)=0
184         RVW(:,LL)=0
185         do JW=1,NW
186          RUW(:,LL)=RUW(:,LL)+RUWP(JW,:)
187          RVW(:,LL)=RVW(:,LL)+RVWP(JW,:)
188         enddo
189        enddo
190
191        DO 33 LL=LAUNCH,KLEV-1
192
193        DO  34 JW=1,NW
194          ZOM(JW,:)=ZOP(JW,:)
195          PHM(JW,:)=PHP(JW,:)
196
197        ZOP(JW,:)=ZO(JW,:)-ZK(JW,:)*COS(ZP(JW))*UH(:,LL+1) ! Intrinsic
198     C                  -ZK(JW,:)*SIN(ZP(JW))*VH(:,LL+1) ! Frequency
199C
200        PHP(JW,:)=           
201     C             AMIN1(                             
202C  NO BREAKING
203     C               SQRT(PH(:,LL)*PHM1(:,LL+1))*PHM(JW,:)
204     C              *SQRT(BV(:,LL+1)/BV(:,LL)
205     C              *ABS(ZOP(JW,:))/AMAX1(ABS(ZOM(JW,:)),ZOISEC))
206C  CRITICAL LEVELS
207     C           ,
208     C              AMAX1(0.,SIGN(1.,ZOP(JW,:)*ZOM(JW,:)))
209C  SATURATION
210     C              *ZOP(JW,:)**2/ZK(JW,:)**2/SQRT(FLOAT(NK*NO))*SAT
211     C           )
212
21334      CONTINUE
214
215        DO 35 JW=1,NW
216        RUWP(JW,:)=ZOP(JW,:)*COS(ZP(JW))*ZK(JW,:)**2
217     C      *PH(:,LL+1)/PR*PHP(JW,:)**2/BV(:,LL+1)
218     C      /AMAX1(ABS(ZOP(JW,:)),ZOISEC)**2
219        RVWP(JW,:)=ZOP(JW,:)*SIN(ZP(JW))*ZK(JW,:)**2
220     C      *PH(:,LL+1)/PR*PHP(JW,:)**2/BV(:,LL+1)
221     C      /AMAX1(ABS(ZOP(JW,:)),ZOISEC)**2
222 35     CONTINUE
223
224        RUW(:,LL+1)=0.
225        RVW(:,LL+1)=0.
226
227
228        DO 36 JW=1,NW
229        RUW(:,LL+1)=RUW(:,LL+1)+RUWP(JW,:)           
230        RVW(:,LL+1)=RVW(:,LL+1)+RVWP(JW,:)           
231 36     CONTINUE
232
233
23433      CONTINUE
235
236C  4 CALCUL DES TENDANCES:
237
238C  RECTIFICATION AU SOMMET ET DANS LES BASSES COUCHES:
239
240        RUW(:,1)=RUW(:,LAUNCH)
241        RVW(:,1)=RVW(:,LAUNCH)
242        DO 4 LL=2,LAUNCH
243        RUW(:,LL)=RUW(:,LL-1)+(RUW(:,LAUNCH+1)-RUW(:,1))*
244     C            (PH(:,LL)-PH(:,LL-1))/(PH(:,LAUNCH+1)-PH(:,1))
245        RVW(:,LL)=RVW(:,LL-1)+(RVW(:,LAUNCH+1)-RVW(:,1))*
246     C            (PH(:,LL)-PH(:,LL-1))/(PH(:,LAUNCH+1)-PH(:,1))
247 4      CONTINUE
248       
249        DO 41 LL=1,KLEV
250        D_U(:,LL)=RG*(RUW(:,LL+1)-RUW(:,LL))
251     C              /(PH(:,LL+1)-PH(:,LL))*DTIME
252        D_V(:,LL)=RG*(RVW(:,LL+1)-RVW(:,LL))
253     C              /(PH(:,LL+1)-PH(:,LL))*DTIME
254 41     CONTINUE
255 
256c ON CONSERVE LA MEMOIRE un certain temps AVEC UN SAVE ET UN COEF
257        d_u = d_u + coef * d_u_sav
258        d_v = d_v + coef * d_v_sav
259        d_u_sav = d_u
260        d_v_sav = d_v
261
262c        PRINT *,'OUT LOTT, LONG?'
263c        DO JW=1,NW
264c        PRINT *,'ONDE ',COS(ZP(JW))*JW,' KM:',2*RPI/ZK(JW)/1000.
265c     C         ,' HR:',2*RPI/ZO(JW)/3600.,' C:',ZO(JW)/ZK(JW)
266c        ENDDO
267
268        RETURN
269        END
270
271
272c===================================================================
273c===================================================================
274c===================================================================
275c===================================================================
276
277      FUNCTION ALEAS (R)
278C***BEGIN PROLOGUE  ALEAS
279C***PURPOSE  Generate a uniformly distributed random number.
280C***LIBRARY   SLATEC (FNLIB)
281C***CATEGORY  L6A21
282C***TYPE      SINGLE PRECISION (ALEAS-S)
283C***KEYWORDS  FNLIB, ALEAS NUMBER, SPECIAL FUNCTIONS, UNIFORM
284C***AUTHOR  Fullerton, W., (LANL)
285C***DESCRIPTION
286C
287C      This pseudo-random number generator is portable among a wide
288C variety of computers.  RAND(R) undoubtedly is not as good as many
289C readily available installation dependent versions, and so this
290C routine is not recommended for widespread usage.  Its redeeming
291C feature is that the exact same random numbers (to within final round-
292C off error) can be generated from machine to machine.  Thus, programs
293C that make use of random numbers can be easily transported to and
294C checked in a new environment.
295C
296C      The random numbers are generated by the linear congruential
297C method described, e.g., by Knuth in Seminumerical Methods (p.9),
298C Addison-Wesley, 1969.  Given the I-th number of a pseudo-random
299C sequence, the I+1 -st number is generated from
300C             X(I+1) = (A*X(I) + C) MOD M,
301C where here M = 2**22 = 4194304, C = 1731 and several suitable values
302C of the multiplier A are discussed below.  Both the multiplier A and
303C random number X are represented in double precision as two 11-bit
304C words.  The constants are chosen so that the period is the maximum
305C possible, 4194304.
306C
307C      In order that the same numbers be generated from machine to
308C machine, it is necessary that 23-bit integers be reducible modulo
309C 2**11 exactly, that 23-bit integers be added exactly, and that 11-bit
310C integers be multiplied exactly.  Furthermore, if the restart option
311C is used (where R is between 0 and 1), then the product R*2**22 =
312C R*4194304 must be correct to the nearest integer.
313C
314C      The first four random numbers should be .0004127026,
315C .6750836372, .1614754200, and .9086198807.  The tenth random number
316C is .5527787209, and the hundredth is .3600893021 .  The thousandth
317C number should be .2176990509 .
318C
319C      In order to generate several effectively independent sequences
320C with the same generator, it is necessary to know the random number
321C for several widely spaced calls.  The I-th random number times 2**22,
322C where I=K*P/8 and P is the period of the sequence (P = 2**22), is
323C still of the form L*P/8.  In particular we find the I-th random
324C number multiplied by 2**22 is given by
325C I   =  0  1*P/8  2*P/8  3*P/8  4*P/8  5*P/8  6*P/8  7*P/8  8*P/8
326C RAND=  0  5*P/8  2*P/8  7*P/8  4*P/8  1*P/8  6*P/8  3*P/8  0
327C Thus the 4*P/8 = 2097152 random number is 2097152/2**22.
328C
329C      Several multipliers have been subjected to the spectral test
330C (see Knuth, p. 82).  Four suitable multipliers roughly in order of
331C goodness according to the spectral test are
332C    3146757 = 1536*2048 + 1029 = 2**21 + 2**20 + 2**10 + 5
333C    2098181 = 1024*2048 + 1029 = 2**21 + 2**10 + 5
334C    3146245 = 1536*2048 +  517 = 2**21 + 2**20 + 2**9 + 5
335C    2776669 = 1355*2048 + 1629 = 5**9 + 7**7 + 1
336C
337C      In the table below LOG10(NU(I)) gives roughly the number of
338C random decimal digits in the random numbers considered I at a time.
339C C is the primary measure of goodness.  In both cases bigger is better.
340C
341C                   LOG10 NU(I)              C(I)
342C       A       I=2  I=3  I=4  I=5    I=2  I=3  I=4  I=5
343C
344C    3146757    3.3  2.0  1.6  1.3    3.1  1.3  4.6  2.6
345C    2098181    3.3  2.0  1.6  1.2    3.2  1.3  4.6  1.7
346C    3146245    3.3  2.2  1.5  1.1    3.2  4.2  1.1  0.4
347C    2776669    3.3  2.1  1.6  1.3    2.5  2.0  1.9  2.6
348C   Best
349C    Possible   3.3  2.3  1.7  1.4    3.6  5.9  9.7  14.9
350C
351C             Input Argument --
352C R      If R=0., the next random number of the sequence is generated.
353C        If R .LT. 0., the last generated number will be returned for
354C          possible use in a restart procedure.
355C        If R .GT. 0., the sequence of random numbers will start with
356C          the seed R mod 1.  This seed is also returned as the value of
357C          RAND provided the arithmetic is done exactly.
358C
359C             Output Value --
360C RAND   a pseudo-random number between 0. and 1.
361C
362C***REFERENCES  (NONE)
363C***ROUTINES CALLED  (NONE)
364C***REVISION HISTORY  (YYMMDD)
365C   770401  DATE WRITTEN
366C   890531  Changed all specific intrinsics to generic.  (WRB)
367C   890531  REVISION DATE from Version 3.2
368C   891214  Prologue converted to Version 4.0 format.  (BAB)
369C***END PROLOGUE  RAND
370      SAVE IA1, IA0, IA1MA0, IC, IX1, IX0
371      DATA IA1, IA0, IA1MA0 /1536, 1029, 507/
372      DATA IC /1731/
373      DATA IX1, IX0 /0, 0/
374C***FIRST EXECUTABLE STATEMENT  RAND
375      IF (R.LT.0.) GO TO 10
376      IF (R.GT.0.) GO TO 20
377C
378C           A*X = 2**22*IA1*IX1 + 2**11*(IA1*IX1 + (IA1-IA0)*(IX0-IX1)
379C                   + IA0*IX0) + IA0*IX0
380C
381      IY0 = IA0*IX0
382      IY1 = IA1*IX1 + IA1MA0*(IX0-IX1) + IY0
383      IY0 = IY0 + IC
384      IX0 = MOD (IY0, 2048)
385      IY1 = IY1 + (IY0-IX0)/2048
386      IX1 = MOD (IY1, 2048)
387C
388 10   ALEAS = IX1*2048 + IX0
389      ALEAS = ALEAS / 4194304.
390      RETURN
391C
392 20   IX1 = MOD(R,1.)*4194304. + 0.5
393      IX0 = MOD (IX1, 2048)
394      IX1 = (IX1-IX0)/2048
395      GO TO 10
396C
397      END
398
399
Note: See TracBrowser for help on using the repository browser.