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

Last change on this file since 1530 was 1530, checked in by emillour, 9 years ago

Venus and Titan GCMs:
Updates in the physics to keep up with updates in LMDZ5 (up to
LMDZ5 trunk, rev 2350) concerning dynamics/physics separation:

  • Adapted makelmdz and makelmdz_fcm script to stop if trying to compile 1d model or newstart or start2archive in parallel.
  • got rid of references to "dimensions.h" in physics. Within physics packages, use nbp_lon (=iim), nbp_lat (=jjmp1) and nbp_lev (=llm) from module mod_grid_phy_lmdz (in phy_common) instead. Only partially done for Titan, because of many hard-coded commons; a necessary first step will be to clean these up (using modules).

EM

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