Ignore:
Timestamp:
May 22, 2020 1:17:57 PM (4 years ago)
Author:
schwenkel
Message:

Add gaussian random number generator to parallel random generator and using parallel random number in lpm

File:
1 edited

Legend:

Unmodified
Added
Removed
  • palm/trunk/SOURCE/random_generator_parallel_mod.f90

    r4438 r4545  
    2525! -----------------
    2626! $Id$
     27! Add generator (using parallel mode) returning gaussian distributed random
     28! number
     29!
     30! 4438 2020-03-03 20:49:28Z raasch
    2731! - Rename variables to avoid confusion with subdomain grid indices
    2832! - Some formatting adjustments
     
    4549!> ran_parallel returns a uniform random deviate between 0.0 and 1.0
    4650!> (exclusive of the end point values).
     51!> Moreover, it contains a routine returning a normally distributed random number
     52!> with mean zero and unity standard deviation.
    4753!> Additionally it provides the generator with five integer for use as initial state space.
    4854!> The first tree integers (iran, jran, kran) are maintained as non negative values,
     
    95101   END INTERFACE
    96102
     103   INTERFACE random_number_parallel_gauss
     104      MODULE PROCEDURE gasdev_s
     105   END INTERFACE
     106
    97107   INTERFACE random_seed_parallel
    98108      MODULE PROCEDURE random_seed_parallel
     
    114124
    115125   PUBLIC random_number_parallel, random_seed_parallel, random_dummy,          &
    116           id_random_array, seq_random_array, init_parallel_random_generator
     126          id_random_array, seq_random_array, init_parallel_random_generator,   &
     127          random_number_parallel_gauss
    117128
    118129 CONTAINS
     
    248259! Description:
    249260! ------------
     261!> Returns in harvest a normally distributed deviate with zero mean and unit
     262!> variance, using ran0_s as the source of uniform deviates. Following
     263!> Numerical Recipes in Fortran90 (Press et al., 2nd edition, 1996, pp 1152ff).
     264!> Note, instead of ran1_s, ran0_s is used.
     265!------------------------------------------------------------------------------!
     266   SUBROUTINE gasdev_s(harvest)
     267
     268      REAL(wp), INTENT(OUT) ::  harvest   !<
     269
     270      REAL(wp) ::  rsq      !<
     271      REAL(wp) ::  v1       !<
     272      REAL(wp) ::  v2       !<
     273      REAL(wp), SAVE ::  g  !<
     274
     275      LOGICAL, SAVE ::  gaus_stored = .FALSE. !<
     276!
     277!--   We have an extra deviate handy, so return it, and unset the flag.
     278      IF (gaus_stored)  THEN
     279         harvest = g
     280         gaus_stored = .FALSE.
     281!
     282!--   We don’t have an extra deviate handy, so pick two uniform numbers in the
     283!--   square extending from -1 to +1 in each direction
     284      ELSE
     285         DO
     286            CALL ran0_s(v1)
     287            CALL ran0_s(v2)
     288            v1 = 2.0_wp * v1 - 1.0_wp
     289            v2 = 2.0_wp * v2 - 1.0_wp
     290!
     291!--         see if they are in the unit circle
     292            rsq = v1**2 + v2**2
     293!
     294!--         otherwise try again.
     295            IF (rsq > 0.0  .AND.  rsq < 1.0) EXIT
     296         ENDDO
     297!
     298!--      Now make the Box-Muller transformation to get two normal deviates.
     299!--      Return one and save the other for next time. Set flag.
     300         rsq = SQRT(-2.0_sp * LOG(rsq)/rsq)
     301         harvest = v1 * rsq
     302         g = v2 * rsq
     303         gaus_stored = .TRUE.
     304      ENDIF
     305
     306   END SUBROUTINE gasdev_s
     307
     308!------------------------------------------------------------------------------!
     309! Description:
     310! ------------
    250311!> Initialize or reinitialize the random generator state space to vectors of size length.
    251312!> The saved variable seq is hashed (via calls to the module routine ran_hash)
Note: See TracChangeset for help on using the changeset viewer.