source: trunk/LMDZ.MARS/libf/phymars/nonoro_gwd_ran_mod.F90 @ 2156

Last change on this file since 2156 was 2149, checked in by emillour, 5 years ago

Mars GCM:
Add F.Lott's non-orographic GW parametrization. Disabled by default for now, activated by setting calllott_nonoro=.true. in callphys.def
GG+EM

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