source: trunk/LMDZ.VENUS/libf/phyvenus/flott_gwd_ran.F90 @ 1453

Last change on this file since 1453 was 826, checked in by slebonnois, 12 years ago

SL: amelioration angmom.F90 (Venus, Titan Tools) + correction bug GW non-oro (Venus)

File size: 18.7 KB
RevLine 
[778]1      SUBROUTINE FLOTT_GWD_RAN(NLON,NLEV,DTIME, pp, pn2,  &
2                  tt,uu,vv,zustr,zvstr,d_t, d_u, d_v)
3
4    !----------------------------------------------------------------------
5    ! Parametrization of the momentum flux deposition due to a discrete
6    ! number of gravity waves.
7    ! F. Lott (version 9: 16 February, 2012), reproduce v3 but with only
8    !         two waves present at each time step
9    ! LMDz model online version     
10    ! ADAPTED FOR VENUS
11    !---------------------------------------------------------------------
12
13      use dimphy
14      implicit none
15
16#include "dimensions.h"
17#include "paramet.h"
18
19#include "YOEGWD.h"
20#include "YOMCST.h"
21
22    ! 0. DECLARATIONS:
23
24    ! 0.1 INPUTS
25    INTEGER, intent(in):: NLON, NLEV
26    REAL, intent(in):: DTIME ! Time step of the Physics
27    REAL, intent(in):: pp(NLON, NLEV)   ! Pressure at full levels
28! VENUS ATTENTION: CP VARIABLE PN2 CALCULE EN AMONT DES PARAMETRISATIONS
29    REAL, intent(in):: pn2(NLON,NLEV)   ! N2 (BV^2) at 1/2 levels
30    REAL, intent(in):: TT(NLON, NLEV)   ! Temp at full levels
31
32    REAL, intent(in):: UU(NLON, NLEV) , VV(NLON, NLEV)
33    ! Hor winds at full levels
34
35    ! 0.2 OUTPUTS
36    REAL, intent(out):: zustr(NLON), zvstr(NLON) ! Surface Stresses
37    REAL, intent(inout):: d_t(NLON, NLEV)        ! Tendency on Temp.
38
39    REAL, intent(inout):: d_u(NLON, NLEV), d_v(NLON, NLEV)
40    ! Tendencies on winds
41
42    ! O.3 INTERNAL ARRAYS
43
44    INTEGER II, LL, IEQ
45
46    ! 0.3.0 TIME SCALE OF THE LIFE CYCLE OF THE WAVES PARAMETERIZED
47
48    REAL DELTAT
49
50    ! 0.3.1 GRAVITY-WAVES SPECIFICATIONS
51
[808]52!VENUS
53    INTEGER, PARAMETER:: NK = 2, NP = 2, NO = 2, NW = NK * NP * NO
[778]54    !Online output: change NO
[808]55!    INTEGER, PARAMETER:: NK = 1, NP = 2, NO = 11, NW = NK * NP * NO
[778]56    INTEGER JK, JP, JO, JW
57    REAL KMIN, KMAX ! Min and Max horizontal wavenumbers
58    REAL CMIN, CMAX ! Min and Max absolute ph. vel.
59    REAL CPHA ! absolute PHASE VELOCITY frequency
60    REAL ZK(NW, KLON) ! Horizontal wavenumber amplitude
61    REAL ZP(NW)       ! Horizontal wavenumber angle       
62    REAL ZO(NW, KLON) ! Absolute frequency      !
63
64    ! Waves Intr. freq. at the 1/2 lev surrounding the full level
65    REAL ZOM(NW, KLON), ZOP(NW, KLON)
66
67    ! Wave vertical velocities at the 2 1/2 lev surrounding the full level
68    REAL WWM(NW, KLON), WWP(NW, KLON)
69
70    REAL RUW0(NW, KLON) ! Fluxes at launching level
71
72    REAL RUWP(NW, KLON), RVWP(NW, KLON)
73    ! Fluxes X and Y for each waves at 1/2 Levels
74
75    INTEGER LAUNCH   ! Launching altitude
76
77    REAL RUWMAX,SAT  ! saturation parameter
78    REAL XLAUNCH     ! Controle the launching altitude
79    REAL RUW(KLON, KLEV + 1) ! Flux x at semi levels
80    REAL RVW(KLON, KLEV + 1) ! Flux y at semi levels
81
82    ! 0.3.2 PARAMETERS OF WAVES DISSIPATIONS
83
84    REAL RDISS, ZOISEC ! COEFF DE DISSIPATION, SECURITY FOR INTRINSIC FREQ
85
86    ! 0.3.3 BACKGROUND FLOW AT 1/2 LEVELS AND VERTICAL COORDINATE
87
[808]88    REAL H0bis(KLON, KLEV) ! Characteristic Height of the atmosphere
89    REAL H0 ! Characteristic Height of the atmosphere
90    REAL PR, TR ! Reference Pressure and Temperature
[778]91
[808]92    REAL ZH(KLON, KLEV + 1) ! Log-pressure altitude (constant H0)
93    REAL ZHbis(KLON, KLEV + 1) ! Log-pressure altitude (varying H)
[778]94
95    REAL UH(KLON, KLEV + 1), VH(KLON, KLEV + 1) ! Winds at 1/2 levels
96    REAL PH(KLON, KLEV + 1) ! Pressure at 1/2 levels
97    REAL PSEC ! Security to avoid division by 0 pressure
98    REAL BV(KLON, KLEV + 1) ! Brunt Vaisala freq. (BVF) at 1/2 levels
99    REAL BVSEC ! Security to avoid negative BVF
100
101! COSMETICS TO DIAGNOSE EACH WAVES CONTRIBUTION.
102    logical output
103    data output/.false./
104  ! CAUTION ! IF output is .true. THEN change NO to 10 at least !
105    character*14 outform
106    character*2  str2
107
108! ON CONSERVE LA MEMOIRE un certain temps AVEC UN SAVE
109    real,save,allocatable :: d_u_sav(:,:),d_v_sav(:,:)
110    LOGICAL firstcall
111    SAVE firstcall
112    DATA firstcall/.true./
113
[808]114      REAL ALEAS
115      EXTERNAL ALEAS
116
[778]117    !-----------------------------------------------------------------
118    !  1. INITIALISATIONS
119
120      IF (firstcall) THEN
121        allocate(d_u_sav(NLON,NLEV),d_v_sav(NLON,NLEV))
[826]122        d_u_sav = 0.
123        d_v_sav = 0.
[778]124        firstcall=.false.
125      ENDIF
126   
127    !    1.1 Basic parameter
128
129    !  PARAMETERS CORRESPONDING TO V3:
130    RUWMAX = 0.005      ! Max EP-Flux at Launch altitude
131    SAT    = 0.85       ! Saturation parameter: Sc in (12)
132    RDISS  = 10.        ! Diffusion parameter
133
134    DELTAT=24.*3600.    ! Time scale of the waves (first introduced in 9b)
135
136    KMIN = 1.E-6        ! Min horizontal wavenumber
137    KMAX = 2.E-5        ! Max horizontal wavenumber
138    !Online output: one value only
139    if (output) then
[808]140      KMIN = 6.3E-6
141      KMAX = 6.3E-6
[778]142    endif
143    CMIN = 1.           ! Min phase velocity
[808]144    CMAX = 61.          ! Max phase speed velocity
[778]145    XLAUNCH=0.6         ! Parameter that control launching altitude
146
147    PR = 9.2e6          ! Reference pressure    ! VENUS!!
[808]148    TR = 240.           ! Reference Temperature ! VENUS: cloud layer
149    H0 = RD * TR / RG   ! Characteristic vertical scale height
[778]150
151    BVSEC  = 1.E-5      ! Security to avoid negative BVF 
[808]152    PSEC   = 1.E-8      ! Security to avoid division by 0 pressure
153    ZOISEC = 1.E-8      ! Security FOR 0 INTRINSIC FREQ
[778]154
155    IF(DELTAT.LT.DTIME)THEN
156       PRINT *,'GWD RANDO: DELTAT LT DTIME!'
157       STOP
158    ENDIF
159
160
161    IF (NLEV < NW) THEN
162       PRINT *, 'YOU WILL HAVE PROBLEM WITH RANDOM NUMBERS'
163       PRINT *, 'FLOTT GWD STOP'
164       STOP 1
165    ENDIF
166
167    ! 1.2 WAVES CHARACTERISTICS CHOSEN RANDOMLY
168    !-------------------------------------------
169
170    ! The mod function of here a weird arguments
171    ! are used to produce the waves characteristics
172    ! in a stochastic way
173
174    JW = 0
175    DO JP = 1, NP
176       DO JK = 1, NK
177          DO JO = 1, NO
178             JW = JW + 1
179             !  Angle
180             ZP(JW) = 2. * RPI * REAL(JP - 1) / REAL(NP)
181             DO II = 1, KLON
182                ! Horizontal wavenumber amplitude
[808]183!                ZK(JW, II) = KMIN + (KMAX - KMIN) * MOD(TT(II, JW) * 100., 1.)
184                ZK(JW, II) = KMIN + (KMAX - KMIN) * ALEAS(0.)
[778]185                ! Horizontal phase speed
[808]186!                CPHA = CMIN + (CMAX - CMIN) * MOD(TT(II, JW)**2, 1.)
187                CPHA = CMIN + (CMAX - CMIN) * ALEAS(0.)
[778]188       !Online output: linear
[808]189                if (output) CPHA = CMIN + (CMAX - CMIN) * (JO-1)/(NO-1)
[778]190                ! Intrinsic frequency
191                ZO(JW, II) = CPHA * ZK(JW, II)
192                ! Momentum flux at launch lev
193                ! RUW0(JW, II) = RUWMAX / REAL(NW) &
194                RUW0(JW, II) = RUWMAX &
[808]195!                     * MOD(100. * (UU(II, JW)**2 + VV(II, JW)**2), 1.)
196                     * ALEAS(0.)
197       !Online output: fixed to max
198                if (output) RUW0(JW, II) = RUWMAX
[778]199             ENDDO
200          end DO
201       end DO
202    end DO
203
204    !  2. EVALUATION OF THE BACKGROUND FLOW AT SEMI-LEVELS
205    !-------------------------------------------------------------
206
207    IEQ = KLON / 2
208    !Online output
209    if (output) OPEN(11,file="impact-gwno.dat")
210
211    ! Pressure and Inv of pressure, Temperature / at 1/2 level
212    DO LL = 2, KLEV
213       PH(:, LL) = EXP((LOG(PP(:, LL)) + LOG(PP(:, LL - 1))) / 2.)
214    end DO
215
216    PH(:, KLEV + 1) = 0.
217    PH(:, 1) = 2. * PP(:, 1) - PH(:, 2)
218
219    ! Launching altitude
220
221    DO LL = 1, NLEV
222       IF (PH(IEQ, LL) / PH(IEQ, 1) > XLAUNCH) LAUNCH = LL
223    ENDDO
224
225    ! Log pressure vert. coordinate (altitude above surface)
[808]226    ZHbis(:,1) = 0.   
[778]227    DO LL = 2, KLEV + 1
[808]228       H0bis(:, LL-1) = RD * TT(:, LL-1) / RG
229       ZHbis(:, LL) = ZHbis(:, LL-1) &
230           + H0bis(:, LL-1)*(PH(:, LL-1)-PH(:,LL))/PP(:, LL-1)
[778]231    end DO
[808]232    ! Log pressure vert. coordinate
233    DO LL = 1, KLEV + 1
234       ZH(:, LL) = H0 * LOG(PR / (PH(:, LL) + PSEC))
235    end DO
[778]236
[808]237
[778]238    ! Winds and BV frequency
239    DO LL = 2, KLEV
240       UH(:, LL) = 0.5 * (UU(:, LL) + UU(:, LL - 1)) ! Zonal wind
241       VH(:, LL) = 0.5 * (VV(:, LL) + VV(:, LL - 1)) ! Meridional wind
242       ! BVSEC: BV Frequency
243! VENUS ATTENTION: CP VARIABLE PSTAB CALCULE EN AMONT DES PARAMETRISATIONS
[808]244       BV(:, LL) = MAX(BVSEC,SQRT(pn2(:,LL)))
[778]245    end DO
246    BV(:, 1) = BV(:, 2)
247    UH(:, 1) = 0.
248    VH(:, 1) = 0.
249    BV(:, KLEV + 1) = BV(:, KLEV)
250    UH(:, KLEV + 1) = UU(:, KLEV)
251    VH(:, KLEV + 1) = VV(:, KLEV)
252
253
254    ! 3. COMPUTE THE FLUXES
255    !--------------------------
256
257    !  3.1  Vertical velocity at launching altitude to ensure
258    !       the correct value to the imposed fluxes.
259    !
260    DO JW = 1, NW
261
262       ! Evaluate intrinsic frequency at launching altitude:
263       ZOP(JW, :) = ZO(JW, :) &
264            - ZK(JW, :) * COS(ZP(JW)) * UH(:, LAUNCH) &
265            - ZK(JW, :) * SIN(ZP(JW)) * VH(:, LAUNCH)
266       ! Vertical velocity at launch level, value to ensure the imposed
267       ! mom flux:
268       WWP(JW, :) = SQRT(ABS(ZOP(JW, :)) / MAX(BV(:, LAUNCH),BVSEC) &
269            * RUW0(JW,:))
270       RUWP(JW, :) = COS(ZP(JW)) * SIGN(1., ZOP(JW, :)) * RUW0(JW, :)
271       RVWP(JW, :) = SIN(ZP(JW)) * SIGN(1., ZOP(JW, :)) * RUW0(JW, :)
272
273    end DO
274
275    !  3.2 Uniform values below the launching altitude
276
277    DO LL = 1, LAUNCH
278       RUW(:, LL) = 0
279       RVW(:, LL) = 0
280       DO JW = 1, NW
281          RUW(:, LL) = RUW(:, LL) + RUWP(JW, :)
282          RVW(:, LL) = RVW(:, LL) + RVWP(JW, :)
283       end DO
284    end DO
285
286    !  3.3 Loop over altitudes, with passage from one level to the
287    !      next done by i) conserving the EP flux, ii) dissipating
288    !      a little, iii) testing critical levels, and vi) testing
289    !      the breaking.
290
291    !Online output
[808]292    write(str2,'(i2)') NW+2
[778]293    outform="("//str2//"(E12.4,1X))"
[808]294    if (output) WRITE(11,outform) ZH(IEQ, 1) / 1000., ZHbis(IEQ, 1) / 1000., &
295               (ZO(JW, IEQ)/ZK(JW, IEQ)*COS(ZP(JW)), JW = 1, NW)
[778]296
297    DO LL = LAUNCH, KLEV - 1
298
299
300       !  W(KB)ARNING: ALL THE PHYSICS IS HERE (PASSAGE FROM ONE LEVEL
301       ! TO THE NEXT)
302       DO JW = 1, NW
303          ZOM(JW, :) = ZOP(JW, :)
304          WWM(JW, :) = WWP(JW, :)
305          ! Intrinsic Frequency
306          ZOP(JW, :) = ZO(JW, :) - ZK(JW, :) * COS(ZP(JW)) * UH(:, LL + 1) &
307               - ZK(JW, :) * SIN(ZP(JW)) * VH(:, LL + 1)
308
309          WWP(JW, :) = MIN( &
310               ! No breaking (Eq.6)
311               WWM(JW, :) &
312               * SQRT(BV(:, LL ) / BV(:, LL+1) &
313               * ABS(ZOP(JW, :)) / MAX(ABS(ZOM(JW, :)), ZOISEC)) &
314               ! Dissipation (Eq. 8):
315               * EXP(- RDISS * PR / (PH(:, LL + 1) + PH(:, LL)) &
316               * ((BV(:, LL + 1) + BV(:, LL)) / 2.)**3 &
317               / MAX(ABS(ZOP(JW, :) + ZOM(JW, :)) / 2., ZOISEC)**4 &
318               * ZK(JW, :)**3 * (ZH(:, LL + 1) - ZH(:, LL))), &
319               ! Critical levels (forced to zero if intrinsic
320               ! frequency changes sign)
321               MAX(0., SIGN(1., ZOP(JW, :) * ZOM(JW, :))) &
322               ! Saturation (Eq. 12)
323               * ZOP(JW, :)**2 / ZK(JW, :)/BV(:, LL+1) &
[808]324               * EXP(-ZH(:, LL + 1)/2./H0) * SAT)
[778]325       end DO
326
327       ! END OF W(KB)ARNING
328       ! Evaluate EP-flux from Eq. 7 and
329       ! Give the right orientation to the stress
330
331       DO JW = 1, NW
332          RUWP(JW, :) = ZOP(JW, :)/MAX(ABS(ZOP(JW, :)), ZOISEC)**2 &
333               *BV(:,LL+1)&
[808]334               * COS(ZP(JW)) *  WWP(JW, :)**2
[778]335          RVWP(JW, :) = ZOP(JW, :)/MAX(ABS(ZOP(JW, :)), ZOISEC)**2 &
336               *BV(:,LL+1)&
[808]337               * SIN(ZP(JW)) *  WWP(JW, :)**2
[778]338       end DO
339       !
340       RUW(:, LL + 1) = 0.
341       RVW(:, LL + 1) = 0.
342
343       DO JW = 1, NW
344          RUW(:, LL + 1) = RUW(:, LL + 1) + RUWP(JW, :)
345          RVW(:, LL + 1) = RVW(:, LL + 1) + RVWP(JW, :)
346       end DO
347       !Online output
[808]348       if (output) then
349         do JW=1,NW
350            if(RUWP(JW, IEQ).gt.0.) then
351              RUWP(JW, IEQ) = max(RUWP(JW, IEQ), 1.e-99)
352            else
353              RUWP(JW, IEQ) = min(RUWP(JW, IEQ), -1.e-99)
354            endif
355         enddo
356                   WRITE(11,outform) ZH(IEQ, LL+1) / 1000., &
357                                  ZHbis(IEQ, LL+1) / 1000., &
358                                  (RUWP(JW, IEQ), JW = 1, NW)
359       endif
[778]360
361    end DO
362
363    !Online output
364    if (output) then
365       CLOSE(11)
366       stop
367    endif
368
369    ! 4 CALCUL DES TENDANCES:
370    !------------------------
371
372    ! 4.1 Rectification des flux au sommet et dans les basses couches:
373
374    RUW(:, KLEV + 1) = 0.
375    RVW(:, KLEV + 1) = 0.
376    RUW(:, 1) = RUW(:, LAUNCH)
377    RVW(:, 1) = RVW(:, LAUNCH)
378    DO LL = 2, LAUNCH
379       RUW(:, LL) = RUW(:, LL - 1) + (RUW(:, LAUNCH + 1) - RUW(:, 1)) * &
380            (PH(:, LL) - PH(:, LL - 1)) / (PH(:, LAUNCH + 1) - PH(:, 1))
381       RVW(:, LL) = RVW(:, LL - 1) + (RVW(:, LAUNCH + 1) - RVW(:, 1)) * &
382            (PH(:, LL) - PH(:, LL - 1)) / (PH(:, LAUNCH + 1) - PH(:, 1))
383    end DO
384
385    ! AR-1 RECURSIVE FORMULA (13) IN VERSION 4
386    DO LL = 1, KLEV
387       d_u(:, LL) = RG * (RUW(:, LL + 1) - RUW(:, LL)) &
388            / (PH(:, LL + 1) - PH(:, LL)) * DTIME
389       d_v(:, LL) = RG * (RVW(:, LL + 1) - RVW(:, LL)) &
390            / (PH(:, LL + 1) - PH(:, LL)) * DTIME
391    ENDDO
[808]392        d_t = 0.
[778]393    ! ON CONSERVE LA MEMOIRE un certain temps AVEC UN SAVE
394        d_u = DTIME/DELTAT/REAL(NW) * d_u + (1.-DTIME/DELTAT) * d_u_sav
395        d_v = DTIME/DELTAT/REAL(NW) * d_v + (1.-DTIME/DELTAT) * d_v_sav
396        d_u_sav = d_u
397        d_v_sav = d_v
398
399    ! Cosmetic: evaluation of the cumulated stress
400
401    ZUSTR(:) = 0.
402    ZVSTR(:) = 0.
403    DO LL = 1, KLEV
404       ZUSTR(:) = ZUSTR(:) + D_U(:, LL) / RG * (PH(:, LL + 1) - PH(:, LL))
405       ZVSTR(:) = ZVSTR(:) + D_V(:, LL) / RG * (PH(:, LL + 1) - PH(:, LL))
406    ENDDO
407
408  END SUBROUTINE FLOTT_GWD_RAN
[808]409
410!===================================================================
411!===================================================================
412!===================================================================
413!===================================================================
414
415      FUNCTION ALEAS (R)
416!***BEGIN PROLOGUE  ALEAS
417!***PURPOSE  Generate a uniformly distributed random number.
418!***LIBRARY   SLATEC (FNLIB)
419!***CATEGORY  L6A21
420!***TYPE      SINGLE PRECISION (ALEAS-S)
421!***KEYWORDS  FNLIB, ALEAS NUMBER, SPECIAL FUNCTIONS, UNIFORM
422!***AUTHOR  Fullerton, W., (LANL)
423!***DESCRIPTION
424!
425!      This pseudo-random number generator is portable among a wide
426! variety of computers.  RAND(R) undoubtedly is not as good as many
427! readily available installation dependent versions, and so this
428! routine is not recommended for widespread usage.  Its redeeming
429! feature is that the exact same random numbers (to within final round-
430! off error) can be generated from machine to machine.  Thus, programs
431! that make use of random numbers can be easily transported to and
432! checked in a new environment.
433!
434!      The random numbers are generated by the linear congruential
435! method described, e.g., by Knuth in Seminumerical Methods (p.9),
436! Addison-Wesley, 1969.  Given the I-th number of a pseudo-random
437! sequence, the I+1 -st number is generated from
438!             X(I+1) = (A*X(I) + C) MOD M,
439! where here M = 2**22 = 4194304, C = 1731 and several suitable values
440! of the multiplier A are discussed below.  Both the multiplier A and
441! random number X are represented in double precision as two 11-bit
442! words.  The constants are chosen so that the period is the maximum
443! possible, 4194304.
444!
445!      In order that the same numbers be generated from machine to
446! machine, it is necessary that 23-bit integers be reducible modulo
447! 2**11 exactly, that 23-bit integers be added exactly, and that 11-bit
448! integers be multiplied exactly.  Furthermore, if the restart option
449! is used (where R is between 0 and 1), then the product R*2**22 =
450! R*4194304 must be correct to the nearest integer.
451!
452!      The first four random numbers should be .0004127026,
453! .6750836372, .1614754200, and .9086198807.  The tenth random number
454! is .5527787209, and the hundredth is .3600893021 .  The thousandth
455! number should be .2176990509 .
456!
457!      In order to generate several effectively independent sequences
458! with the same generator, it is necessary to know the random number
459! for several widely spaced calls.  The I-th random number times 2**22,
460! where I=K*P/8 and P is the period of the sequence (P = 2**22), is
461! still of the form L*P/8.  In particular we find the I-th random
462! number multiplied by 2**22 is given by
463! 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
464! RAND=  0  5*P/8  2*P/8  7*P/8  4*P/8  1*P/8  6*P/8  3*P/8  0
465! Thus the 4*P/8 = 2097152 random number is 2097152/2**22.
466!
467!      Several multipliers have been subjected to the spectral test
468! (see Knuth, p. 82).  Four suitable multipliers roughly in order of
469! goodness according to the spectral test are
470!    3146757 = 1536*2048 + 1029 = 2**21 + 2**20 + 2**10 + 5
471!    2098181 = 1024*2048 + 1029 = 2**21 + 2**10 + 5
472!    3146245 = 1536*2048 +  517 = 2**21 + 2**20 + 2**9 + 5
473!    2776669 = 1355*2048 + 1629 = 5**9 + 7**7 + 1
474!
475!      In the table below LOG10(NU(I)) gives roughly the number of
476! random decimal digits in the random numbers considered I at a time.
477! C is the primary measure of goodness.  In both cases bigger is better.
478!
479!                   LOG10 NU(I)              C(I)
480!       A       I=2  I=3  I=4  I=5    I=2  I=3  I=4  I=5
481!
482!    3146757    3.3  2.0  1.6  1.3    3.1  1.3  4.6  2.6
483!    2098181    3.3  2.0  1.6  1.2    3.2  1.3  4.6  1.7
484!    3146245    3.3  2.2  1.5  1.1    3.2  4.2  1.1  0.4
485!    2776669    3.3  2.1  1.6  1.3    2.5  2.0  1.9  2.6
486!   Best
487!    Possible   3.3  2.3  1.7  1.4    3.6  5.9  9.7  14.9
488!
489!             Input Argument --
490! R      If R=0., the next random number of the sequence is generated.
491!        If R .LT. 0., the last generated number will be returned for
492!          possible use in a restart procedure.
493!        If R .GT. 0., the sequence of random numbers will start with
494!          the seed R mod 1.  This seed is also returned as the value of
495!          RAND provided the arithmetic is done exactly.
496!
497!             Output Value --
498! RAND   a pseudo-random number between 0. and 1.
499!
500!***REFERENCES  (NONE)
501!***ROUTINES CALLED  (NONE)
502!***REVISION HISTORY  (YYMMDD)
503!   770401  DATE WRITTEN
504!   890531  Changed all specific intrinsics to generic.  (WRB)
505!   890531  REVISION DATE from Version 3.2
506!   891214  Prologue converted to Version 4.0 format.  (BAB)
507!***END PROLOGUE  RAND
508      SAVE IA1, IA0, IA1MA0, IC, IX1, IX0
509      DATA IA1, IA0, IA1MA0 /1536, 1029, 507/
510      DATA IC /1731/
511      DATA IX1, IX0 /0, 0/
512!***FIRST EXECUTABLE STATEMENT  RAND
513!
514!           A*X = 2**22*IA1*IX1 + 2**11*(IA1*IX1 + (IA1-IA0)*(IX0-IX1)
515!                   + IA0*IX0) + IA0*IX0
516!
517      IF (R.EQ.0.) THEN
518       IY0 = IA0*IX0
519       IY1 = IA1*IX1 + IA1MA0*(IX0-IX1) + IY0
520       IY0 = IY0 + IC
521       IX0 = MOD (IY0, 2048)
522       IY1 = IY1 + (IY0-IX0)/2048
523       IX1 = MOD (IY1, 2048)
524      ENDIF
525
526      IF (R.GT.0.) THEN
527       IX1 = MOD(R,1.)*4194304. + 0.5
528       IX0 = MOD (IX1, 2048)
529       IX1 = (IX1-IX0)/2048
530      ENDIF
531
532      ALEAS = IX1*2048 + IX0
533      ALEAS = ALEAS / 4194304.
534      RETURN
535
536      END
537
538
Note: See TracBrowser for help on using the repository browser.