FUNCTION random_gauss( idum, upper_limit ) !------------------------------------------------------------------------------! ! Current revisions: ! ----------------- ! ! ! Former revisions: ! ----------------- ! $Id: random_gauss.f90 484 2010-02-05 07:36:54Z maronga $ ! RCS Log replace by Id keyword, revision history cleaned up ! ! Revision 1.4 2006/08/04 15:01:48 raasch ! Range of random number is limited by an upper limit (new second parameter) ! ! Revision 1.1 1998/03/25 20:09:47 raasch ! Initial revision ! ! ! Description: ! ------------ ! Generates a gaussian distributed random number (mean value 1, sigma = 1) ! This routine is taken from the "numerical recipies". !------------------------------------------------------------------------------! USE random_function_mod IMPLICIT NONE INTEGER :: idum, iset REAL :: fac, gset, random_gauss, rsq, upper_limit, v1, v2 SAVE iset, gset DATA iset /0/ ! !-- Random numbers are created as long as they do not fall below the given !-- upper limit DO IF ( iset == 0 ) THEN rsq = 0.0 DO WHILE ( rsq >= 1.0 .OR. rsq == 0.0 ) v1 = 2.0 * random_function( idum ) - 1.0 v2 = 2.0 * random_function( idum ) - 1.0 rsq = v1**2 + v2**2 ENDDO fac = SQRT( -2.0 * LOG( rsq ) / rsq ) gset = v1 * fac random_gauss = v2 * fac + 1.0 iset = 1 ELSE random_gauss = gset + 1.0 iset = 0 ENDIF IF ( ABS( random_gauss - 1.0 ) <= upper_limit ) EXIT ENDDO END FUNCTION random_gauss