source: palm/trunk/SOURCE/random_gauss.f90 @ 1683

Last change on this file since 1683 was 1683, checked in by knoop, 9 years ago

last commit documented

  • Property svn:keywords set to Id
File size: 3.2 KB
RevLine 
[1682]1!> @file random_gauss.f90
[1036]2!--------------------------------------------------------------------------------!
3! This file is part of PALM.
4!
5! PALM is free software: you can redistribute it and/or modify it under the terms
6! of the GNU General Public License as published by the Free Software Foundation,
7! either version 3 of the License, or (at your option) any later version.
8!
9! PALM is distributed in the hope that it will be useful, but WITHOUT ANY
10! WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS FOR
11! A PARTICULAR PURPOSE.  See the GNU General Public License for more details.
12!
13! You should have received a copy of the GNU General Public License along with
14! PALM. If not, see <http://www.gnu.org/licenses/>.
15!
[1310]16! Copyright 1997-2014 Leibniz Universitaet Hannover
[1036]17!--------------------------------------------------------------------------------!
18!
[484]19! Current revisions:
[1]20! -----------------
[1321]21!
[1683]22!
[1321]23! Former revisions:
24! -----------------
25! $Id: random_gauss.f90 1683 2015-10-07 23:57:51Z knoop $
26!
[1683]27! 1682 2015-10-07 23:56:08Z knoop
28! Code annotations made doxygen readable
29!
[1343]30! 1342 2014-03-26 17:04:47Z kanani
31! REAL constants defined as wp-kind
32!
[1321]33! 1320 2014-03-20 08:40:49Z raasch
[1320]34! ONLY-attribute added to USE-statements,
35! kind-parameters added to all INTEGER and REAL declaration statements,
36! kinds are defined in new module kinds,
37! old module precision_kind is removed,
38! revision history before 2012 removed,
39! comment fields (!:) to be used for variable explanations added to
40! all variable declaration statements
[1037]41!
42! 1036 2012-10-22 13:43:42Z raasch
43! code put under GPL (PALM 3.9)
44!
[3]45! RCS Log replace by Id keyword, revision history cleaned up
46!
[1]47! Revision 1.1  1998/03/25 20:09:47  raasch
48! Initial revision
49!
50!
51! Description:
52! ------------
[1682]53!> Generates a gaussian distributed random number (mean value 1, sigma = 1)
54!> This routine is taken from the "numerical recipies".
[1]55!------------------------------------------------------------------------------!
[1682]56 FUNCTION random_gauss( idum, upper_limit )
57 
[1]58
[1320]59    USE kinds
[1]60
[1320]61    USE random_function_mod,                                                   &
62        ONLY:  random_function
63
[1]64    IMPLICIT NONE
65
[1682]66    INTEGER(iwp) ::  idum          !<
67    INTEGER(iwp) ::  iset          !<
[1]68
[1682]69    REAL(wp)     ::  fac           !<
70    REAL(wp)     ::  gset          !<
71    REAL(wp)     ::  random_gauss  !<
72    REAL(wp)     ::  rsq           !<
73    REAL(wp)     ::  upper_limit   !<
74    REAL(wp)     ::  v1            !<
75    REAL(wp)     ::  v2            !<
[1320]76
[1]77    SAVE  iset, gset
78
79    DATA  iset /0/
80
81!
82!-- Random numbers are created as long as they do not fall below the given
83!-- upper limit
84    DO
85
86       IF ( iset == 0 )  THEN
[1342]87          rsq = 0.0_wp
88          DO  WHILE ( rsq >= 1.0_wp  .OR.  rsq == 0.0_wp )
89             v1  = 2.0_wp * random_function( idum ) - 1.0_wp
90             v2  = 2.0_wp * random_function( idum ) - 1.0_wp
[1]91             rsq = v1**2 + v2**2
92          ENDDO
[1342]93          fac          = SQRT( -2.0_wp * LOG( rsq ) / rsq )
[1]94          gset         = v1 * fac
[1342]95          random_gauss = v2 * fac + 1.0_wp
[1]96          iset         = 1
97       ELSE
[1342]98          random_gauss = gset + 1.0_wp
[1]99          iset         = 0
100       ENDIF
101
[1342]102       IF ( ABS( random_gauss - 1.0_wp ) <= upper_limit )  EXIT
[1]103
104    ENDDO
105
106 END FUNCTION random_gauss
Note: See TracBrowser for help on using the repository browser.