├── .gitignore
├── README.md
├── Makefile
├── example.f90
├── LICENSE_XOROSHIRO128PLUS
├── parallel_test.f90
├── performance_test.f90
├── m_random.f90
└── LICENSE
/.gitignore:
--------------------------------------------------------------------------------
1 | /example
2 | /performance_test
3 | /m_random.mod
4 | /m_random.o
5 | /parallel_test
6 |
--------------------------------------------------------------------------------
/README.md:
--------------------------------------------------------------------------------
1 | # rng_fortran
2 |
3 | A module for generating (pseudo) random numbers. Internally, the
4 | xoroshiro128plus generator is used. The following types of random numbers are
5 | currently supported:
6 |
7 | * 8 byte random integers
8 | * 4 byte random integers
9 | * (0,1] uniform random numbers
10 | * Normal random numbers (in pairs of two)
11 | * Poisson-distributed random numbers
12 | * Random points on a circle
13 | * Random points on a sphere
14 |
15 | A usage example is given in `example.f90`.
16 |
--------------------------------------------------------------------------------
/Makefile:
--------------------------------------------------------------------------------
1 | FC := gfortran
2 | FFLAGS := -O3 -flto -g -std=f2008 -Wall -Wextra -fopenmp
3 | OBJS := m_random.o
4 | TESTS := example performance_test parallel_test
5 |
6 | .PHONY: all clean
7 |
8 | all: $(TESTS)
9 |
10 | clean:
11 | $(RM) $(TESTS) $(OBJS) $(OBJS:.o=.mod)
12 |
13 | # Dependency information
14 | $(TESTS): $(OBJS)
15 |
16 | # How to get .o object files from .f90 source files
17 | %.o: %.f90
18 | $(FC) -c -o $@ $< $(FFLAGS)
19 |
20 | # How to get executables from .o object files
21 | %: %.o
22 | $(FC) -o $@ $^ $(FFLAGS)
23 |
--------------------------------------------------------------------------------
/example.f90:
--------------------------------------------------------------------------------
1 | program example
2 | use m_random
3 |
4 | ! Define double precision real type
5 | integer, parameter :: dp = kind(0.0d0)
6 |
7 | ! Create a random number generator
8 | type(RNG_t) :: rng
9 |
10 | ! Set the initial seed for the generator
11 | call rng%set_random_seed()
12 |
13 | ! Print some random numbers
14 | print *, "Uniform random number: ", rng%unif_01()
15 | print *, "8-byte random integer: ", rng%int_64()
16 | print *, "4-byte random integer: ", rng%int_32()
17 | print *, "Two normal numbers: ", rng%two_normals()
18 | print *, "Poisson(10.0) deviate: ", rng%poisson(10.0_dp)
19 | print *, "Point on unit circle: ", rng%circle(1.0_dp)
20 | print *, "Point on unit sphere: ", rng%sphere(1.0_dp)
21 | end program example
22 |
--------------------------------------------------------------------------------
/LICENSE_XOROSHIRO128PLUS:
--------------------------------------------------------------------------------
1 | ** License for the xoroshiro128plus random number generator **
2 |
3 | Written in 2016 by David Blackman and Sebastiano Vigna (vigna@acm.org)
4 | Translated to Fortran 2008 by Jannis Teunissen
5 |
6 | To the extent possible under law, the author has dedicated all copyright
7 | and related and neighboring rights to this software to the public domain
8 | worldwide. This software is distributed without any warranty.
9 |
10 | See .
11 |
12 | This is the successor to xorshift128+. It is the fastest full-period
13 | generator passing BigCrush without systematic failures, but due to the
14 | relatively short period it is acceptable only for applications with a
15 | mild amount of parallelism; otherwise, use a xorshift1024* generator.
16 |
17 | Beside passing BigCrush, this generator passes the PractRand test suite
18 | up to (and included) 16TB, with the exception of binary rank tests,
19 | which fail due to the lowest bit being an LFSR; all other bits pass all
20 | tests. We suggest to use a sign test to extract a random Boolean value.
21 |
22 | Note that the generator uses a simulated rotate operation, which most C
23 | compilers will turn into a single instruction. In Java, you can use
24 | Long.rotateLeft(). In languages that do not make low-level rotation
25 | instructions accessible xorshift128+ could be faster.
26 |
27 | The state must be seeded so that it is not everywhere zero. If you have
28 | a 64-bit seed, we suggest to seed a splitmix64 generator and use its
29 | output to fill s.
--------------------------------------------------------------------------------
/parallel_test.f90:
--------------------------------------------------------------------------------
1 | program test_parallel
2 | use m_random
3 | use omp_lib
4 |
5 | implicit none
6 | integer, parameter :: dp = kind(0.0d0)
7 | integer, parameter :: i8 = selected_int_kind(18)
8 | integer, parameter :: n_samples = 100*1000*1000
9 | integer :: n, tid
10 | integer :: time_start, time_end, count_rate
11 | real(dp) :: mean, variance
12 | real(dp), allocatable :: rand_results(:)
13 | type(RNG_t) :: rng
14 | type(PRNG_t) :: prng
15 |
16 | print *, "Testing parallel random number generation"
17 | print *, "Number of threads", omp_get_max_threads()
18 |
19 | allocate(rand_results(n_samples))
20 |
21 | call rng%set_seed([89732_i8, 1892342989_i8])
22 | call prng%init_parallel(omp_get_max_threads(), rng)
23 | call system_clock(time_start, count_rate)
24 |
25 | !$omp parallel private(n, tid, rng)
26 | tid = omp_get_thread_num() + 1
27 | !$omp do
28 | do n = 1, n_samples
29 | rand_results(n) = prng%rngs(tid)%unif_01()
30 | end do
31 | !$omp end do
32 | !$omp end parallel
33 |
34 | ! Update the rng seed afterwards, using the 'evolved' prng state
35 | call prng%update_seed(rng)
36 |
37 | call system_clock(time_end)
38 |
39 | mean = sum(rand_results) / n_samples
40 | variance = sum((rand_results - mean)**2) / n_samples
41 |
42 | print *, ""
43 | print *, "For uniform random numbers (unif_01), the result is:"
44 | print *, "nanoseconds per number (upper bound)", &
45 | (1.0e9_dp/count_rate) * (time_end - time_start) / n_samples
46 | print *, "mean/", mean/0.5_dp
47 | print *, "std dev/", sqrt(variance)*sqrt(12.0_dp)
48 |
49 | end program test_parallel
50 |
--------------------------------------------------------------------------------
/performance_test.f90:
--------------------------------------------------------------------------------
1 | program test_m_random
2 | use iso_fortran_env, only: int64, real64
3 | use m_random
4 |
5 | implicit none
6 | integer, parameter :: dp = real64
7 | integer, parameter :: n_samples = 10*1000*1000
8 | integer :: nn, rng_seed
9 | real(dp) :: mean, variance, p
10 | real(dp), parameter :: poisson_lambda = 15.0_dp
11 | real(dp) :: time_start, time_end
12 | real(dp), allocatable :: rand_results(:)
13 | integer(int64), allocatable :: int64_results(:)
14 | type(RNG_t) :: rng
15 |
16 | allocate(rand_results(n_samples))
17 | allocate(int64_results(n_samples))
18 |
19 | print *, "Testing implementation of m_random.f90"
20 | print *, "This is just checking whether everything works, and by no means"
21 | print *, "a test of the 'randomness' of the pseudo random number generator."
22 | print *, "For these tests, ", n_samples, " values are used"
23 |
24 | call system_clock(count=rng_seed)
25 |
26 | call cpu_time(time_start)
27 | call random_number(rand_results)
28 | call cpu_time(time_end)
29 | mean = sum(rand_results) / n_samples
30 | variance = sum((rand_results - mean)**2) / n_samples
31 |
32 | print *, ""
33 | print *, "For uniform random numbers (built-in), the result is:"
34 | print *, "nanoseconds per number (upper bound)", 1.0e9_dp * (time_end - time_start) / n_samples
35 | print *, "mean/", mean/0.5_dp
36 | print *, "std dev/", sqrt(variance)*sqrt(12.0_dp)
37 |
38 | call rng%set_random_seed()
39 |
40 | call cpu_time(time_start)
41 | do nn = 1, n_samples
42 | rand_results(nn) = rng%unif_01()
43 | end do
44 | call cpu_time(time_end)
45 | mean = sum(rand_results) / n_samples
46 | variance = sum((rand_results - mean)**2) / n_samples
47 |
48 | print *, ""
49 | print *, "For uniform random numbers (unif_01), the result is:"
50 | print *, "nanoseconds per number (upper bound)", 1.0e9_dp * (time_end - time_start) / n_samples
51 | print *, "mean/", mean/0.5_dp
52 | print *, "std dev/", sqrt(variance)*sqrt(12.0_dp)
53 |
54 | call cpu_time(time_start)
55 | do nn = 1, n_samples
56 | rand_results(nn) = rng%normal()
57 | end do
58 | call cpu_time(time_end)
59 | rand_results = rand_results + 1
60 | mean = sum(rand_results) / n_samples
61 | variance = sum((rand_results - mean)**2) / n_samples
62 |
63 | print *, ""
64 | print *, "For normal/Gaussian random numbers, the result is:"
65 | print *, "nanoseconds per number (upper bound)", 1.0e9_dp * (time_end - time_start) / n_samples
66 | print *, "mean/", mean/1.0_dp ! Above we add one to RNG_normal()
67 | print *, "std dev/", sqrt(variance)
68 |
69 | call cpu_time(time_start)
70 | do nn = 1, n_samples
71 | rand_results(nn) = rng%poisson(poisson_lambda)
72 | end do
73 | call cpu_time(time_end)
74 | mean = sum(rand_results) / n_samples
75 | variance = sum((rand_results - mean)**2) / n_samples
76 |
77 | print *, ""
78 | print *, "For Poisson random numbers, the result is:"
79 | print *, "nanoseconds per number (upper bound)", 1.0e9_dp * (time_end - time_start) / n_samples
80 | print *, "mean/", mean/poisson_lambda ! Above we add one to RNG_normal()
81 | print *, "std dev/", sqrt(variance/poisson_lambda)
82 |
83 | call cpu_time(time_start)
84 | do nn = 1, n_samples
85 | rand_results(nn) = rng%exponential(1.0_dp)
86 | end do
87 | call cpu_time(time_end)
88 | mean = sum(rand_results) / n_samples
89 | variance = sum((rand_results - mean)**2) / n_samples
90 |
91 | print *, ""
92 | print *, "For exponential random numbers, the result is:"
93 | print *, "nanoseconds per number (upper bound)", 1.0e9_dp * (time_end - time_start) / n_samples
94 | print *, "mean/", mean
95 | print *, "std dev/", sqrt(variance)
96 |
97 | p = 1e-10_dp
98 | call cpu_time(time_start)
99 | do nn = 1, n_samples
100 | int64_results(nn) = rng%geometric(p)
101 | end do
102 | call cpu_time(time_end)
103 | mean = sum(real(int64_results, dp)) / n_samples
104 | variance = sum((int64_results - mean)**2) / n_samples
105 |
106 | if (minval(int64_results) < 1) &
107 | error stop "Got negative sample from geometric distribution"
108 |
109 | print *, ""
110 | print *, "For geometric random numbers, the result is:"
111 | print *, "nanoseconds per number (upper bound)", 1.0e9_dp * (time_end - time_start) / n_samples
112 | print *, "mean/", mean * p
113 | print *, "std dev/", sqrt(variance) / sqrt((1-p) / p**2)
114 |
115 | end program test_m_random
116 |
--------------------------------------------------------------------------------
/m_random.f90:
--------------------------------------------------------------------------------
1 | !> Module for pseudo random number generation. The internal pseudo random
2 | !> generator is the xoroshiro128plus method.
3 | module m_random
4 | use iso_fortran_env, only: int32, int64, real64
5 |
6 | implicit none
7 | private
8 |
9 | ! A 64 bit floating point type
10 | integer, parameter :: dp = real64
11 |
12 | !> Random number generator type, which contains the state
13 | type rng_t
14 | !> The rng state (always use your own seed)
15 | integer(int64), private :: s(2) = [123456789_int64, 987654321_int64]
16 | integer(int64), private :: separator(32) ! Separate cache lines (parallel use)
17 | real(dp), private :: stored_normal
18 | logical, private :: have_stored_normal = .false.
19 | logical, private :: initialized = .false.
20 | contains
21 | procedure, non_overridable :: set_seed ! Seed the generator
22 | procedure, non_overridable :: set_random_seed ! Use a random seed
23 | procedure, non_overridable :: jump ! Jump function (see below)
24 | procedure, non_overridable :: int_32 ! 4-byte random integer
25 | procedure, non_overridable :: int_64 ! 8-byte random integer
26 | procedure, non_overridable :: unif_01 ! Uniform (0,1] real
27 | procedure, non_overridable :: normal ! One normal(0,1) sample
28 | procedure, non_overridable :: two_normals ! Two normal(0,1) samples
29 | procedure, non_overridable :: poisson ! Sample from Poisson-dist.
30 | procedure, non_overridable :: poisson_knuth ! Sample from Poisson-dist.
31 | procedure, non_overridable :: poisson_reject ! Sample from Poisson-dist.
32 | procedure, non_overridable :: exponential_standard ! Sample from standard exponential dist.
33 | procedure, non_overridable :: exponential ! Sample from exponential dist.
34 | procedure, non_overridable :: geometric ! Sample from geometric distribution
35 | procedure, non_overridable :: circle ! Sample on a circle
36 | procedure, non_overridable :: sphere ! Sample on a sphere
37 | procedure, non_overridable :: next ! Internal method
38 | procedure, non_overridable, nopass :: log1p ! Internal method
39 | end type rng_t
40 |
41 | !> Parallel random number generator type
42 | type prng_t
43 | type(rng_t), allocatable :: rngs(:)
44 | contains
45 | procedure, non_overridable :: init_parallel
46 | procedure, non_overridable :: update_seed
47 | end type prng_t
48 |
49 | public :: rng_t
50 | public :: prng_t
51 |
52 | contains
53 |
54 | !> Initialize a collection of rng's for parallel use
55 | subroutine init_parallel(self, n_proc, rng)
56 | class(prng_t), intent(inout) :: self
57 | type(rng_t), intent(inout) :: rng
58 | integer, intent(in) :: n_proc
59 | integer :: n
60 |
61 | if (n_proc < 1) error stop "init_parallel: n_proc < 1"
62 |
63 | allocate(self%rngs(n_proc))
64 | self%rngs(1) = rng
65 | call self%rngs(1)%jump()
66 |
67 | do n = 2, n_proc
68 | self%rngs(n) = self%rngs(n-1)
69 | call self%rngs(n)%jump()
70 | end do
71 | end subroutine init_parallel
72 |
73 | !> Parallel RNG instances are often used temporarily. This routine can
74 | !> afterwards be used to update the seed of the user's sequential RNG.
75 | subroutine update_seed(self, rng)
76 | class(prng_t), intent(inout) :: self
77 | type(rng_t), intent(inout) :: rng
78 | integer :: n
79 |
80 | do n = 1, size(self%rngs)
81 | ! Perform exclusive-or with each parallel rng
82 | rng%s(1) = ieor(rng%s(1), self%rngs(n)%s(1))
83 | rng%s(2) = ieor(rng%s(2), self%rngs(n)%s(2))
84 | end do
85 | end subroutine update_seed
86 |
87 | !> Set a seed for the rng
88 | subroutine set_seed(self, the_seed)
89 | class(rng_t), intent(inout) :: self
90 | integer(int64), intent(in) :: the_seed(2)
91 |
92 | self%s = the_seed
93 |
94 | ! Simulate calls to next() to improve randomness of first number
95 | call self%jump()
96 | end subroutine set_seed
97 |
98 | subroutine set_random_seed(self)
99 | class(rng_t), intent(inout) :: self
100 | integer :: i
101 | real(dp) :: rr
102 | integer(int64) :: time
103 |
104 | ! Get a random seed from the system (this does not always work)
105 | call random_seed()
106 |
107 | ! Get some count of the time
108 | call system_clock(time)
109 |
110 | do i = 1, 2
111 | call random_number(rr)
112 | self%s(i) = ieor(transfer(rr, 1_int64), transfer(time, 1_int64))
113 | end do
114 |
115 | ! Simulate calls to next() to improve randomness of first number
116 | call self%jump()
117 | end subroutine set_random_seed
118 |
119 | ! This is the jump function for the generator. It is equivalent
120 | ! to 2^64 calls to next(); it can be used to generate 2^64
121 | ! non-overlapping subsequences for parallel computations.
122 | subroutine jump(self)
123 | class(rng_t), intent(inout) :: self
124 | integer :: i, b
125 | integer(int64) :: t(2), dummy
126 |
127 | ! The signed equivalent of the unsigned constants
128 | integer(int64), parameter :: jmp_c(2) = &
129 | (/-4707382666127344949_int64, -2852180941702784734_int64/)
130 |
131 | t = 0
132 | do i = 1, 2
133 | do b = 0, 63
134 | if (iand(jmp_c(i), shiftl(1_int64, b)) /= 0) then
135 | t = ieor(t, self%s)
136 | end if
137 | dummy = self%next()
138 | end do
139 | end do
140 |
141 | self%s = t
142 | end subroutine jump
143 |
144 | !> Return 4-byte integer
145 | integer(int32) function int_32(self)
146 | class(rng_t), intent(inout) :: self
147 | int_32 = int(self%next(), int32)
148 | end function int_32
149 |
150 | !> Return 8-byte integer
151 | integer(int64) function int_64(self)
152 | class(rng_t), intent(inout) :: self
153 | int_64 = self%next()
154 | end function int_64
155 |
156 | !> Get a uniform [0,1) random real (double precision)
157 | real(dp) function unif_01(self)
158 | class(rng_t), intent(inout) :: self
159 | integer(int64) :: x
160 | real(dp) :: tmp
161 |
162 | x = self%next()
163 | x = ior(shiftl(1023_int64, 52), shiftr(x, 12))
164 | unif_01 = transfer(x, tmp) - 1.0_dp
165 | end function unif_01
166 |
167 | !> Return normal random variate with mean 0 and variance 1
168 | real(dp) function normal(self)
169 | class(rng_t), intent(inout) :: self
170 | real(dp) :: two_normals(2)
171 |
172 | if (self%have_stored_normal) then
173 | normal = self%stored_normal
174 | self%have_stored_normal = .false.
175 | else
176 | two_normals = self%two_normals()
177 | normal = two_normals(1)
178 | self%stored_normal = two_normals(2)
179 | self%have_stored_normal = .true.
180 | end if
181 | end function normal
182 |
183 | !> Return two normal random variates with mean 0 and variance 1.
184 | !> http://en.wikipedia.org/wiki/Marsaglia_polar_method
185 | function two_normals(self) result(rands)
186 | class(rng_t), intent(inout) :: self
187 | real(dp) :: rands(2), sum_sq
188 |
189 | do
190 | rands(1) = 2 * self%unif_01() - 1
191 | rands(2) = 2 * self%unif_01() - 1
192 | sum_sq = sum(rands**2)
193 | if (sum_sq < 1.0_dp .and. sum_sq > 0.0_dp) exit
194 | end do
195 | rands = rands * sqrt(-2 * log(sum_sq) / sum_sq)
196 | end function two_normals
197 |
198 | !> Compute log(1+x) with good accuracy, see "What Every Computer Scientist
199 | !> Should Know About Floating-Point Arithmetic"
200 | real(dp) function log1p(x)
201 | real(dp), intent(in) :: x
202 |
203 | if (1.0_dp + abs(x) > 1.0_dp) then
204 | log1p = log(1.0_dp + x) * x / ((1.0_dp + x) - 1.0_dp)
205 | else
206 | log1p = x
207 | endif
208 | end function log1p
209 |
210 | !> Return exponential random variate with a rate of one
211 | real(dp) function exponential_standard(self)
212 | class(rng_t), intent(inout) :: self
213 | real(dp) :: unif_01
214 |
215 | ! It is assumes 1 - unif_01 is in (0, 1], so we avoid log(0.) below
216 | unif_01 = self%unif_01()
217 |
218 | if (unif_01 < 0.5_dp) then
219 | exponential_standard = -log1p(-unif_01)
220 | else
221 | exponential_standard = -log(1 - unif_01)
222 | end if
223 | end function exponential_standard
224 |
225 | !> Return exponential random variate with rate lambda
226 | real(dp) function exponential(self, lambda)
227 | class(rng_t), intent(inout) :: self
228 | real(dp), intent(in) :: lambda
229 | exponential = self%exponential_standard()/lambda
230 | end function exponential
231 |
232 | !> Sample from geometric distribution with Pr(X = k) = (1 - p)^(k-1) * p
233 | integer(int64) function geometric(self, p)
234 | class(rng_t), intent(inout) :: self
235 | real(dp), intent(in) :: p
236 | real(dp) :: tmp
237 | real(dp), parameter :: threshold = real(huge(1_int64) - 1, dp)
238 |
239 | ! Perform inversion sampling X = ceiling(log(U)/log(1-p))
240 | tmp = -self%exponential_standard() / log1p(-p)
241 |
242 | ! Avoid overflow
243 | if (tmp < threshold) then
244 | geometric = ceiling(tmp, int64)
245 | else
246 | geometric = huge(1_int64)
247 | end if
248 |
249 | end function geometric
250 |
251 | !> Return Poisson random variate with rate lambda. Works well for lambda < 30
252 | !> or so. For lambda >> 1 it can produce wrong results due to roundoff error.
253 | function poisson_knuth(self, lambda) result(rr)
254 | class(rng_t), intent(inout) :: self
255 | real(dp), intent(in) :: lambda
256 | integer(int32) :: rr
257 | real(dp) :: expl, p
258 |
259 | expl = exp(-lambda)
260 | rr = 0
261 | p = self%unif_01()
262 |
263 | do while (p > expl)
264 | rr = rr + 1
265 | p = p * self%unif_01()
266 | end do
267 | end function poisson_knuth
268 |
269 | !> The transformed rejection method for generating Poisson random variables
270 | !>
271 | !> Translated from Numpy C code at:
272 | !> https://github.com/numpy/numpy/blob/main/numpy/random/src/distributions/distributions.c
273 | !>
274 | !> W. Hoermann
275 | !> Insurance: Mathematics and Economics 12, 39-45 (1993)
276 | function poisson_reject(self, lambda) result(k)
277 | class(rng_t), intent(inout) :: self
278 | real(dp), intent(in) :: lambda
279 | integer(int32) :: k
280 | real(dp) :: U, V, sqrt_lambda, log_lambda
281 | real(dp) :: a, b, invalpha, vr, us
282 |
283 | sqrt_lambda = sqrt(lambda)
284 | log_lambda = log(lambda)
285 |
286 | b = 0.931_dp + 2.53_dp * sqrt_lambda
287 | a = -0.059_dp + 0.02483_dp * b
288 | invalpha = 1.1239_dp + 1.1328_dp / (b - 3.4_dp)
289 | vr = 0.9277_dp - 3.6224_dp / (b - 2)
290 |
291 | do
292 | U = self%unif_01() - 0.5_dp
293 | V = 1.0_dp - self%unif_01() ! Avoid 0
294 | us = 0.5_dp - abs(U);
295 |
296 | k = floor((2 * a / us + b) * U + lambda + 0.43_dp);
297 |
298 | if (us >= 0.07_dp .and. V <= vr) return
299 | if (k < 0 .or. us < 0.013_dp .and. V > us) cycle
300 |
301 | if ((log(V) + log(invalpha) - log(a / (us * us) + b)) <= &
302 | (-lambda + k * log_lambda - log_gamma(k + 1.0_dp))) return
303 | end do
304 | end function poisson_reject
305 |
306 | !> Return Poisson random variate with rate lambda
307 | function poisson(self, lambda) result(rr)
308 | class(rng_t), intent(inout) :: self
309 | real(dp), intent(in) :: lambda
310 | integer(int32) :: rr
311 |
312 | if (lambda < 10) then
313 | ! Algorithm for small value of lambda
314 | rr = self%poisson_knuth(lambda)
315 | else
316 | ! Rejection sampling
317 | rr = self%poisson_reject(lambda)
318 | end if
319 | end function poisson
320 |
321 | !> Sample point on a circle with given radius
322 | function circle(self, radius) result(xy)
323 | class(rng_t), intent(inout) :: self
324 | real(dp), intent(in) :: radius
325 | real(dp) :: rands(2), xy(2)
326 | real(dp) :: sum_sq
327 |
328 | ! Method for uniform sampling on circle
329 | do
330 | rands(1) = 2 * self%unif_01() - 1
331 | rands(2) = 2 * self%unif_01() - 1
332 | sum_sq = sum(rands**2)
333 | if (sum_sq <= 1) exit
334 | end do
335 |
336 | xy(1) = (rands(1)**2 - rands(2)**2) / sum_sq
337 | xy(2) = 2 * rands(1) * rands(2) / sum_sq
338 | xy = xy * radius
339 | end function circle
340 |
341 | !> Sample point on a sphere with given radius
342 | function sphere(self, radius) result(xyz)
343 | class(rng_t), intent(inout) :: self
344 | real(dp), intent(in) :: radius
345 | real(dp) :: rands(2), xyz(3)
346 | real(dp) :: sum_sq, tmp_sqrt
347 |
348 | ! Marsaglia method for uniform sampling on sphere
349 | do
350 | rands(1) = 2 * self%unif_01() - 1
351 | rands(2) = 2 * self%unif_01() - 1
352 | sum_sq = sum(rands**2)
353 | if (sum_sq <= 1) exit
354 | end do
355 |
356 | tmp_sqrt = sqrt(1 - sum_sq)
357 | xyz(1:2) = 2 * rands(1:2) * tmp_sqrt
358 | xyz(3) = 1 - 2 * sum_sq
359 | xyz = xyz * radius
360 | end function sphere
361 |
362 | !> Interal routine: get the next value (returned as 64 bit signed integer)
363 | function next(self) result(res)
364 | class(rng_t), intent(inout) :: self
365 | integer(int64) :: res
366 | integer(int64) :: t(2)
367 |
368 | t = self%s
369 | res = t(1) + t(2)
370 | t(2) = ieor(t(1), t(2))
371 | self%s(1) = ieor(ieor(rotl(t(1), 55), t(2)), shiftl(t(2), 14))
372 | self%s(2) = rotl(t(2), 36)
373 | end function next
374 |
375 | !> Helper function for next()
376 | pure function rotl(x, k) result(res)
377 | integer(int64), intent(in) :: x
378 | integer, intent(in) :: k
379 | integer(int64) :: res
380 |
381 | res = ior(shiftl(x, k), shiftr(x, 64 - k))
382 | end function rotl
383 |
384 | end module m_random
385 |
--------------------------------------------------------------------------------
/LICENSE:
--------------------------------------------------------------------------------
1 | GNU GENERAL PUBLIC LICENSE
2 | Version 3, 29 June 2007
3 |
4 | Copyright (C) 2007 Free Software Foundation, Inc.
5 | Everyone is permitted to copy and distribute verbatim copies
6 | of this license document, but changing it is not allowed.
7 |
8 | Preamble
9 |
10 | The GNU General Public License is a free, copyleft license for
11 | software and other kinds of works.
12 |
13 | The licenses for most software and other practical works are designed
14 | to take away your freedom to share and change the works. By contrast,
15 | the GNU General Public License is intended to guarantee your freedom to
16 | share and change all versions of a program--to make sure it remains free
17 | software for all its users. We, the Free Software Foundation, use the
18 | GNU General Public License for most of our software; it applies also to
19 | any other work released this way by its authors. You can apply it to
20 | your programs, too.
21 |
22 | When we speak of free software, we are referring to freedom, not
23 | price. Our General Public Licenses are designed to make sure that you
24 | have the freedom to distribute copies of free software (and charge for
25 | them if you wish), that you receive source code or can get it if you
26 | want it, that you can change the software or use pieces of it in new
27 | free programs, and that you know you can do these things.
28 |
29 | To protect your rights, we need to prevent others from denying you
30 | these rights or asking you to surrender the rights. Therefore, you have
31 | certain responsibilities if you distribute copies of the software, or if
32 | you modify it: responsibilities to respect the freedom of others.
33 |
34 | For example, if you distribute copies of such a program, whether
35 | gratis or for a fee, you must pass on to the recipients the same
36 | freedoms that you received. You must make sure that they, too, receive
37 | or can get the source code. And you must show them these terms so they
38 | know their rights.
39 |
40 | Developers that use the GNU GPL protect your rights with two steps:
41 | (1) assert copyright on the software, and (2) offer you this License
42 | giving you legal permission to copy, distribute and/or modify it.
43 |
44 | For the developers' and authors' protection, the GPL clearly explains
45 | that there is no warranty for this free software. For both users' and
46 | authors' sake, the GPL requires that modified versions be marked as
47 | changed, so that their problems will not be attributed erroneously to
48 | authors of previous versions.
49 |
50 | Some devices are designed to deny users access to install or run
51 | modified versions of the software inside them, although the manufacturer
52 | can do so. This is fundamentally incompatible with the aim of
53 | protecting users' freedom to change the software. The systematic
54 | pattern of such abuse occurs in the area of products for individuals to
55 | use, which is precisely where it is most unacceptable. Therefore, we
56 | have designed this version of the GPL to prohibit the practice for those
57 | products. If such problems arise substantially in other domains, we
58 | stand ready to extend this provision to those domains in future versions
59 | of the GPL, as needed to protect the freedom of users.
60 |
61 | Finally, every program is threatened constantly by software patents.
62 | States should not allow patents to restrict development and use of
63 | software on general-purpose computers, but in those that do, we wish to
64 | avoid the special danger that patents applied to a free program could
65 | make it effectively proprietary. To prevent this, the GPL assures that
66 | patents cannot be used to render the program non-free.
67 |
68 | The precise terms and conditions for copying, distribution and
69 | modification follow.
70 |
71 | TERMS AND CONDITIONS
72 |
73 | 0. Definitions.
74 |
75 | "This License" refers to version 3 of the GNU General Public License.
76 |
77 | "Copyright" also means copyright-like laws that apply to other kinds of
78 | works, such as semiconductor masks.
79 |
80 | "The Program" refers to any copyrightable work licensed under this
81 | License. Each licensee is addressed as "you". "Licensees" and
82 | "recipients" may be individuals or organizations.
83 |
84 | To "modify" a work means to copy from or adapt all or part of the work
85 | in a fashion requiring copyright permission, other than the making of an
86 | exact copy. The resulting work is called a "modified version" of the
87 | earlier work or a work "based on" the earlier work.
88 |
89 | A "covered work" means either the unmodified Program or a work based
90 | on the Program.
91 |
92 | To "propagate" a work means to do anything with it that, without
93 | permission, would make you directly or secondarily liable for
94 | infringement under applicable copyright law, except executing it on a
95 | computer or modifying a private copy. Propagation includes copying,
96 | distribution (with or without modification), making available to the
97 | public, and in some countries other activities as well.
98 |
99 | To "convey" a work means any kind of propagation that enables other
100 | parties to make or receive copies. Mere interaction with a user through
101 | a computer network, with no transfer of a copy, is not conveying.
102 |
103 | An interactive user interface displays "Appropriate Legal Notices"
104 | to the extent that it includes a convenient and prominently visible
105 | feature that (1) displays an appropriate copyright notice, and (2)
106 | tells the user that there is no warranty for the work (except to the
107 | extent that warranties are provided), that licensees may convey the
108 | work under this License, and how to view a copy of this License. If
109 | the interface presents a list of user commands or options, such as a
110 | menu, a prominent item in the list meets this criterion.
111 |
112 | 1. Source Code.
113 |
114 | The "source code" for a work means the preferred form of the work
115 | for making modifications to it. "Object code" means any non-source
116 | form of a work.
117 |
118 | A "Standard Interface" means an interface that either is an official
119 | standard defined by a recognized standards body, or, in the case of
120 | interfaces specified for a particular programming language, one that
121 | is widely used among developers working in that language.
122 |
123 | The "System Libraries" of an executable work include anything, other
124 | than the work as a whole, that (a) is included in the normal form of
125 | packaging a Major Component, but which is not part of that Major
126 | Component, and (b) serves only to enable use of the work with that
127 | Major Component, or to implement a Standard Interface for which an
128 | implementation is available to the public in source code form. A
129 | "Major Component", in this context, means a major essential component
130 | (kernel, window system, and so on) of the specific operating system
131 | (if any) on which the executable work runs, or a compiler used to
132 | produce the work, or an object code interpreter used to run it.
133 |
134 | The "Corresponding Source" for a work in object code form means all
135 | the source code needed to generate, install, and (for an executable
136 | work) run the object code and to modify the work, including scripts to
137 | control those activities. However, it does not include the work's
138 | System Libraries, or general-purpose tools or generally available free
139 | programs which are used unmodified in performing those activities but
140 | which are not part of the work. For example, Corresponding Source
141 | includes interface definition files associated with source files for
142 | the work, and the source code for shared libraries and dynamically
143 | linked subprograms that the work is specifically designed to require,
144 | such as by intimate data communication or control flow between those
145 | subprograms and other parts of the work.
146 |
147 | The Corresponding Source need not include anything that users
148 | can regenerate automatically from other parts of the Corresponding
149 | Source.
150 |
151 | The Corresponding Source for a work in source code form is that
152 | same work.
153 |
154 | 2. Basic Permissions.
155 |
156 | All rights granted under this License are granted for the term of
157 | copyright on the Program, and are irrevocable provided the stated
158 | conditions are met. This License explicitly affirms your unlimited
159 | permission to run the unmodified Program. The output from running a
160 | covered work is covered by this License only if the output, given its
161 | content, constitutes a covered work. This License acknowledges your
162 | rights of fair use or other equivalent, as provided by copyright law.
163 |
164 | You may make, run and propagate covered works that you do not
165 | convey, without conditions so long as your license otherwise remains
166 | in force. You may convey covered works to others for the sole purpose
167 | of having them make modifications exclusively for you, or provide you
168 | with facilities for running those works, provided that you comply with
169 | the terms of this License in conveying all material for which you do
170 | not control copyright. Those thus making or running the covered works
171 | for you must do so exclusively on your behalf, under your direction
172 | and control, on terms that prohibit them from making any copies of
173 | your copyrighted material outside their relationship with you.
174 |
175 | Conveying under any other circumstances is permitted solely under
176 | the conditions stated below. Sublicensing is not allowed; section 10
177 | makes it unnecessary.
178 |
179 | 3. Protecting Users' Legal Rights From Anti-Circumvention Law.
180 |
181 | No covered work shall be deemed part of an effective technological
182 | measure under any applicable law fulfilling obligations under article
183 | 11 of the WIPO copyright treaty adopted on 20 December 1996, or
184 | similar laws prohibiting or restricting circumvention of such
185 | measures.
186 |
187 | When you convey a covered work, you waive any legal power to forbid
188 | circumvention of technological measures to the extent such circumvention
189 | is effected by exercising rights under this License with respect to
190 | the covered work, and you disclaim any intention to limit operation or
191 | modification of the work as a means of enforcing, against the work's
192 | users, your or third parties' legal rights to forbid circumvention of
193 | technological measures.
194 |
195 | 4. Conveying Verbatim Copies.
196 |
197 | You may convey verbatim copies of the Program's source code as you
198 | receive it, in any medium, provided that you conspicuously and
199 | appropriately publish on each copy an appropriate copyright notice;
200 | keep intact all notices stating that this License and any
201 | non-permissive terms added in accord with section 7 apply to the code;
202 | keep intact all notices of the absence of any warranty; and give all
203 | recipients a copy of this License along with the Program.
204 |
205 | You may charge any price or no price for each copy that you convey,
206 | and you may offer support or warranty protection for a fee.
207 |
208 | 5. Conveying Modified Source Versions.
209 |
210 | You may convey a work based on the Program, or the modifications to
211 | produce it from the Program, in the form of source code under the
212 | terms of section 4, provided that you also meet all of these conditions:
213 |
214 | a) The work must carry prominent notices stating that you modified
215 | it, and giving a relevant date.
216 |
217 | b) The work must carry prominent notices stating that it is
218 | released under this License and any conditions added under section
219 | 7. This requirement modifies the requirement in section 4 to
220 | "keep intact all notices".
221 |
222 | c) You must license the entire work, as a whole, under this
223 | License to anyone who comes into possession of a copy. This
224 | License will therefore apply, along with any applicable section 7
225 | additional terms, to the whole of the work, and all its parts,
226 | regardless of how they are packaged. This License gives no
227 | permission to license the work in any other way, but it does not
228 | invalidate such permission if you have separately received it.
229 |
230 | d) If the work has interactive user interfaces, each must display
231 | Appropriate Legal Notices; however, if the Program has interactive
232 | interfaces that do not display Appropriate Legal Notices, your
233 | work need not make them do so.
234 |
235 | A compilation of a covered work with other separate and independent
236 | works, which are not by their nature extensions of the covered work,
237 | and which are not combined with it such as to form a larger program,
238 | in or on a volume of a storage or distribution medium, is called an
239 | "aggregate" if the compilation and its resulting copyright are not
240 | used to limit the access or legal rights of the compilation's users
241 | beyond what the individual works permit. Inclusion of a covered work
242 | in an aggregate does not cause this License to apply to the other
243 | parts of the aggregate.
244 |
245 | 6. Conveying Non-Source Forms.
246 |
247 | You may convey a covered work in object code form under the terms
248 | of sections 4 and 5, provided that you also convey the
249 | machine-readable Corresponding Source under the terms of this License,
250 | in one of these ways:
251 |
252 | a) Convey the object code in, or embodied in, a physical product
253 | (including a physical distribution medium), accompanied by the
254 | Corresponding Source fixed on a durable physical medium
255 | customarily used for software interchange.
256 |
257 | b) Convey the object code in, or embodied in, a physical product
258 | (including a physical distribution medium), accompanied by a
259 | written offer, valid for at least three years and valid for as
260 | long as you offer spare parts or customer support for that product
261 | model, to give anyone who possesses the object code either (1) a
262 | copy of the Corresponding Source for all the software in the
263 | product that is covered by this License, on a durable physical
264 | medium customarily used for software interchange, for a price no
265 | more than your reasonable cost of physically performing this
266 | conveying of source, or (2) access to copy the
267 | Corresponding Source from a network server at no charge.
268 |
269 | c) Convey individual copies of the object code with a copy of the
270 | written offer to provide the Corresponding Source. This
271 | alternative is allowed only occasionally and noncommercially, and
272 | only if you received the object code with such an offer, in accord
273 | with subsection 6b.
274 |
275 | d) Convey the object code by offering access from a designated
276 | place (gratis or for a charge), and offer equivalent access to the
277 | Corresponding Source in the same way through the same place at no
278 | further charge. You need not require recipients to copy the
279 | Corresponding Source along with the object code. If the place to
280 | copy the object code is a network server, the Corresponding Source
281 | may be on a different server (operated by you or a third party)
282 | that supports equivalent copying facilities, provided you maintain
283 | clear directions next to the object code saying where to find the
284 | Corresponding Source. Regardless of what server hosts the
285 | Corresponding Source, you remain obligated to ensure that it is
286 | available for as long as needed to satisfy these requirements.
287 |
288 | e) Convey the object code using peer-to-peer transmission, provided
289 | you inform other peers where the object code and Corresponding
290 | Source of the work are being offered to the general public at no
291 | charge under subsection 6d.
292 |
293 | A separable portion of the object code, whose source code is excluded
294 | from the Corresponding Source as a System Library, need not be
295 | included in conveying the object code work.
296 |
297 | A "User Product" is either (1) a "consumer product", which means any
298 | tangible personal property which is normally used for personal, family,
299 | or household purposes, or (2) anything designed or sold for incorporation
300 | into a dwelling. In determining whether a product is a consumer product,
301 | doubtful cases shall be resolved in favor of coverage. For a particular
302 | product received by a particular user, "normally used" refers to a
303 | typical or common use of that class of product, regardless of the status
304 | of the particular user or of the way in which the particular user
305 | actually uses, or expects or is expected to use, the product. A product
306 | is a consumer product regardless of whether the product has substantial
307 | commercial, industrial or non-consumer uses, unless such uses represent
308 | the only significant mode of use of the product.
309 |
310 | "Installation Information" for a User Product means any methods,
311 | procedures, authorization keys, or other information required to install
312 | and execute modified versions of a covered work in that User Product from
313 | a modified version of its Corresponding Source. The information must
314 | suffice to ensure that the continued functioning of the modified object
315 | code is in no case prevented or interfered with solely because
316 | modification has been made.
317 |
318 | If you convey an object code work under this section in, or with, or
319 | specifically for use in, a User Product, and the conveying occurs as
320 | part of a transaction in which the right of possession and use of the
321 | User Product is transferred to the recipient in perpetuity or for a
322 | fixed term (regardless of how the transaction is characterized), the
323 | Corresponding Source conveyed under this section must be accompanied
324 | by the Installation Information. But this requirement does not apply
325 | if neither you nor any third party retains the ability to install
326 | modified object code on the User Product (for example, the work has
327 | been installed in ROM).
328 |
329 | The requirement to provide Installation Information does not include a
330 | requirement to continue to provide support service, warranty, or updates
331 | for a work that has been modified or installed by the recipient, or for
332 | the User Product in which it has been modified or installed. Access to a
333 | network may be denied when the modification itself materially and
334 | adversely affects the operation of the network or violates the rules and
335 | protocols for communication across the network.
336 |
337 | Corresponding Source conveyed, and Installation Information provided,
338 | in accord with this section must be in a format that is publicly
339 | documented (and with an implementation available to the public in
340 | source code form), and must require no special password or key for
341 | unpacking, reading or copying.
342 |
343 | 7. Additional Terms.
344 |
345 | "Additional permissions" are terms that supplement the terms of this
346 | License by making exceptions from one or more of its conditions.
347 | Additional permissions that are applicable to the entire Program shall
348 | be treated as though they were included in this License, to the extent
349 | that they are valid under applicable law. If additional permissions
350 | apply only to part of the Program, that part may be used separately
351 | under those permissions, but the entire Program remains governed by
352 | this License without regard to the additional permissions.
353 |
354 | When you convey a copy of a covered work, you may at your option
355 | remove any additional permissions from that copy, or from any part of
356 | it. (Additional permissions may be written to require their own
357 | removal in certain cases when you modify the work.) You may place
358 | additional permissions on material, added by you to a covered work,
359 | for which you have or can give appropriate copyright permission.
360 |
361 | Notwithstanding any other provision of this License, for material you
362 | add to a covered work, you may (if authorized by the copyright holders of
363 | that material) supplement the terms of this License with terms:
364 |
365 | a) Disclaiming warranty or limiting liability differently from the
366 | terms of sections 15 and 16 of this License; or
367 |
368 | b) Requiring preservation of specified reasonable legal notices or
369 | author attributions in that material or in the Appropriate Legal
370 | Notices displayed by works containing it; or
371 |
372 | c) Prohibiting misrepresentation of the origin of that material, or
373 | requiring that modified versions of such material be marked in
374 | reasonable ways as different from the original version; or
375 |
376 | d) Limiting the use for publicity purposes of names of licensors or
377 | authors of the material; or
378 |
379 | e) Declining to grant rights under trademark law for use of some
380 | trade names, trademarks, or service marks; or
381 |
382 | f) Requiring indemnification of licensors and authors of that
383 | material by anyone who conveys the material (or modified versions of
384 | it) with contractual assumptions of liability to the recipient, for
385 | any liability that these contractual assumptions directly impose on
386 | those licensors and authors.
387 |
388 | All other non-permissive additional terms are considered "further
389 | restrictions" within the meaning of section 10. If the Program as you
390 | received it, or any part of it, contains a notice stating that it is
391 | governed by this License along with a term that is a further
392 | restriction, you may remove that term. If a license document contains
393 | a further restriction but permits relicensing or conveying under this
394 | License, you may add to a covered work material governed by the terms
395 | of that license document, provided that the further restriction does
396 | not survive such relicensing or conveying.
397 |
398 | If you add terms to a covered work in accord with this section, you
399 | must place, in the relevant source files, a statement of the
400 | additional terms that apply to those files, or a notice indicating
401 | where to find the applicable terms.
402 |
403 | Additional terms, permissive or non-permissive, may be stated in the
404 | form of a separately written license, or stated as exceptions;
405 | the above requirements apply either way.
406 |
407 | 8. Termination.
408 |
409 | You may not propagate or modify a covered work except as expressly
410 | provided under this License. Any attempt otherwise to propagate or
411 | modify it is void, and will automatically terminate your rights under
412 | this License (including any patent licenses granted under the third
413 | paragraph of section 11).
414 |
415 | However, if you cease all violation of this License, then your
416 | license from a particular copyright holder is reinstated (a)
417 | provisionally, unless and until the copyright holder explicitly and
418 | finally terminates your license, and (b) permanently, if the copyright
419 | holder fails to notify you of the violation by some reasonable means
420 | prior to 60 days after the cessation.
421 |
422 | Moreover, your license from a particular copyright holder is
423 | reinstated permanently if the copyright holder notifies you of the
424 | violation by some reasonable means, this is the first time you have
425 | received notice of violation of this License (for any work) from that
426 | copyright holder, and you cure the violation prior to 30 days after
427 | your receipt of the notice.
428 |
429 | Termination of your rights under this section does not terminate the
430 | licenses of parties who have received copies or rights from you under
431 | this License. If your rights have been terminated and not permanently
432 | reinstated, you do not qualify to receive new licenses for the same
433 | material under section 10.
434 |
435 | 9. Acceptance Not Required for Having Copies.
436 |
437 | You are not required to accept this License in order to receive or
438 | run a copy of the Program. Ancillary propagation of a covered work
439 | occurring solely as a consequence of using peer-to-peer transmission
440 | to receive a copy likewise does not require acceptance. However,
441 | nothing other than this License grants you permission to propagate or
442 | modify any covered work. These actions infringe copyright if you do
443 | not accept this License. Therefore, by modifying or propagating a
444 | covered work, you indicate your acceptance of this License to do so.
445 |
446 | 10. Automatic Licensing of Downstream Recipients.
447 |
448 | Each time you convey a covered work, the recipient automatically
449 | receives a license from the original licensors, to run, modify and
450 | propagate that work, subject to this License. You are not responsible
451 | for enforcing compliance by third parties with this License.
452 |
453 | An "entity transaction" is a transaction transferring control of an
454 | organization, or substantially all assets of one, or subdividing an
455 | organization, or merging organizations. If propagation of a covered
456 | work results from an entity transaction, each party to that
457 | transaction who receives a copy of the work also receives whatever
458 | licenses to the work the party's predecessor in interest had or could
459 | give under the previous paragraph, plus a right to possession of the
460 | Corresponding Source of the work from the predecessor in interest, if
461 | the predecessor has it or can get it with reasonable efforts.
462 |
463 | You may not impose any further restrictions on the exercise of the
464 | rights granted or affirmed under this License. For example, you may
465 | not impose a license fee, royalty, or other charge for exercise of
466 | rights granted under this License, and you may not initiate litigation
467 | (including a cross-claim or counterclaim in a lawsuit) alleging that
468 | any patent claim is infringed by making, using, selling, offering for
469 | sale, or importing the Program or any portion of it.
470 |
471 | 11. Patents.
472 |
473 | A "contributor" is a copyright holder who authorizes use under this
474 | License of the Program or a work on which the Program is based. The
475 | work thus licensed is called the contributor's "contributor version".
476 |
477 | A contributor's "essential patent claims" are all patent claims
478 | owned or controlled by the contributor, whether already acquired or
479 | hereafter acquired, that would be infringed by some manner, permitted
480 | by this License, of making, using, or selling its contributor version,
481 | but do not include claims that would be infringed only as a
482 | consequence of further modification of the contributor version. For
483 | purposes of this definition, "control" includes the right to grant
484 | patent sublicenses in a manner consistent with the requirements of
485 | this License.
486 |
487 | Each contributor grants you a non-exclusive, worldwide, royalty-free
488 | patent license under the contributor's essential patent claims, to
489 | make, use, sell, offer for sale, import and otherwise run, modify and
490 | propagate the contents of its contributor version.
491 |
492 | In the following three paragraphs, a "patent license" is any express
493 | agreement or commitment, however denominated, not to enforce a patent
494 | (such as an express permission to practice a patent or covenant not to
495 | sue for patent infringement). To "grant" such a patent license to a
496 | party means to make such an agreement or commitment not to enforce a
497 | patent against the party.
498 |
499 | If you convey a covered work, knowingly relying on a patent license,
500 | and the Corresponding Source of the work is not available for anyone
501 | to copy, free of charge and under the terms of this License, through a
502 | publicly available network server or other readily accessible means,
503 | then you must either (1) cause the Corresponding Source to be so
504 | available, or (2) arrange to deprive yourself of the benefit of the
505 | patent license for this particular work, or (3) arrange, in a manner
506 | consistent with the requirements of this License, to extend the patent
507 | license to downstream recipients. "Knowingly relying" means you have
508 | actual knowledge that, but for the patent license, your conveying the
509 | covered work in a country, or your recipient's use of the covered work
510 | in a country, would infringe one or more identifiable patents in that
511 | country that you have reason to believe are valid.
512 |
513 | If, pursuant to or in connection with a single transaction or
514 | arrangement, you convey, or propagate by procuring conveyance of, a
515 | covered work, and grant a patent license to some of the parties
516 | receiving the covered work authorizing them to use, propagate, modify
517 | or convey a specific copy of the covered work, then the patent license
518 | you grant is automatically extended to all recipients of the covered
519 | work and works based on it.
520 |
521 | A patent license is "discriminatory" if it does not include within
522 | the scope of its coverage, prohibits the exercise of, or is
523 | conditioned on the non-exercise of one or more of the rights that are
524 | specifically granted under this License. You may not convey a covered
525 | work if you are a party to an arrangement with a third party that is
526 | in the business of distributing software, under which you make payment
527 | to the third party based on the extent of your activity of conveying
528 | the work, and under which the third party grants, to any of the
529 | parties who would receive the covered work from you, a discriminatory
530 | patent license (a) in connection with copies of the covered work
531 | conveyed by you (or copies made from those copies), or (b) primarily
532 | for and in connection with specific products or compilations that
533 | contain the covered work, unless you entered into that arrangement,
534 | or that patent license was granted, prior to 28 March 2007.
535 |
536 | Nothing in this License shall be construed as excluding or limiting
537 | any implied license or other defenses to infringement that may
538 | otherwise be available to you under applicable patent law.
539 |
540 | 12. No Surrender of Others' Freedom.
541 |
542 | If conditions are imposed on you (whether by court order, agreement or
543 | otherwise) that contradict the conditions of this License, they do not
544 | excuse you from the conditions of this License. If you cannot convey a
545 | covered work so as to satisfy simultaneously your obligations under this
546 | License and any other pertinent obligations, then as a consequence you may
547 | not convey it at all. For example, if you agree to terms that obligate you
548 | to collect a royalty for further conveying from those to whom you convey
549 | the Program, the only way you could satisfy both those terms and this
550 | License would be to refrain entirely from conveying the Program.
551 |
552 | 13. Use with the GNU Affero General Public License.
553 |
554 | Notwithstanding any other provision of this License, you have
555 | permission to link or combine any covered work with a work licensed
556 | under version 3 of the GNU Affero General Public License into a single
557 | combined work, and to convey the resulting work. The terms of this
558 | License will continue to apply to the part which is the covered work,
559 | but the special requirements of the GNU Affero General Public License,
560 | section 13, concerning interaction through a network will apply to the
561 | combination as such.
562 |
563 | 14. Revised Versions of this License.
564 |
565 | The Free Software Foundation may publish revised and/or new versions of
566 | the GNU General Public License from time to time. Such new versions will
567 | be similar in spirit to the present version, but may differ in detail to
568 | address new problems or concerns.
569 |
570 | Each version is given a distinguishing version number. If the
571 | Program specifies that a certain numbered version of the GNU General
572 | Public License "or any later version" applies to it, you have the
573 | option of following the terms and conditions either of that numbered
574 | version or of any later version published by the Free Software
575 | Foundation. If the Program does not specify a version number of the
576 | GNU General Public License, you may choose any version ever published
577 | by the Free Software Foundation.
578 |
579 | If the Program specifies that a proxy can decide which future
580 | versions of the GNU General Public License can be used, that proxy's
581 | public statement of acceptance of a version permanently authorizes you
582 | to choose that version for the Program.
583 |
584 | Later license versions may give you additional or different
585 | permissions. However, no additional obligations are imposed on any
586 | author or copyright holder as a result of your choosing to follow a
587 | later version.
588 |
589 | 15. Disclaimer of Warranty.
590 |
591 | THERE IS NO WARRANTY FOR THE PROGRAM, TO THE EXTENT PERMITTED BY
592 | APPLICABLE LAW. EXCEPT WHEN OTHERWISE STATED IN WRITING THE COPYRIGHT
593 | HOLDERS AND/OR OTHER PARTIES PROVIDE THE PROGRAM "AS IS" WITHOUT WARRANTY
594 | OF ANY KIND, EITHER EXPRESSED OR IMPLIED, INCLUDING, BUT NOT LIMITED TO,
595 | THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR
596 | PURPOSE. THE ENTIRE RISK AS TO THE QUALITY AND PERFORMANCE OF THE PROGRAM
597 | IS WITH YOU. SHOULD THE PROGRAM PROVE DEFECTIVE, YOU ASSUME THE COST OF
598 | ALL NECESSARY SERVICING, REPAIR OR CORRECTION.
599 |
600 | 16. Limitation of Liability.
601 |
602 | IN NO EVENT UNLESS REQUIRED BY APPLICABLE LAW OR AGREED TO IN WRITING
603 | WILL ANY COPYRIGHT HOLDER, OR ANY OTHER PARTY WHO MODIFIES AND/OR CONVEYS
604 | THE PROGRAM AS PERMITTED ABOVE, BE LIABLE TO YOU FOR DAMAGES, INCLUDING ANY
605 | GENERAL, SPECIAL, INCIDENTAL OR CONSEQUENTIAL DAMAGES ARISING OUT OF THE
606 | USE OR INABILITY TO USE THE PROGRAM (INCLUDING BUT NOT LIMITED TO LOSS OF
607 | DATA OR DATA BEING RENDERED INACCURATE OR LOSSES SUSTAINED BY YOU OR THIRD
608 | PARTIES OR A FAILURE OF THE PROGRAM TO OPERATE WITH ANY OTHER PROGRAMS),
609 | EVEN IF SUCH HOLDER OR OTHER PARTY HAS BEEN ADVISED OF THE POSSIBILITY OF
610 | SUCH DAMAGES.
611 |
612 | 17. Interpretation of Sections 15 and 16.
613 |
614 | If the disclaimer of warranty and limitation of liability provided
615 | above cannot be given local legal effect according to their terms,
616 | reviewing courts shall apply local law that most closely approximates
617 | an absolute waiver of all civil liability in connection with the
618 | Program, unless a warranty or assumption of liability accompanies a
619 | copy of the Program in return for a fee.
620 |
621 | END OF TERMS AND CONDITIONS
622 |
623 | How to Apply These Terms to Your New Programs
624 |
625 | If you develop a new program, and you want it to be of the greatest
626 | possible use to the public, the best way to achieve this is to make it
627 | free software which everyone can redistribute and change under these terms.
628 |
629 | To do so, attach the following notices to the program. It is safest
630 | to attach them to the start of each source file to most effectively
631 | state the exclusion of warranty; and each file should have at least
632 | the "copyright" line and a pointer to where the full notice is found.
633 |
634 | {one line to give the program's name and a brief idea of what it does.}
635 | Copyright (C) {year} {name of author}
636 |
637 | This program is free software: you can redistribute it and/or modify
638 | it under the terms of the GNU General Public License as published by
639 | the Free Software Foundation, either version 3 of the License, or
640 | (at your option) any later version.
641 |
642 | This program is distributed in the hope that it will be useful,
643 | but WITHOUT ANY WARRANTY; without even the implied warranty of
644 | MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
645 | GNU General Public License for more details.
646 |
647 | You should have received a copy of the GNU General Public License
648 | along with this program. If not, see .
649 |
650 | Also add information on how to contact you by electronic and paper mail.
651 |
652 | If the program does terminal interaction, make it output a short
653 | notice like this when it starts in an interactive mode:
654 |
655 | {project} Copyright (C) {year} {fullname}
656 | This program comes with ABSOLUTELY NO WARRANTY; for details type `show w'.
657 | This is free software, and you are welcome to redistribute it
658 | under certain conditions; type `show c' for details.
659 |
660 | The hypothetical commands `show w' and `show c' should show the appropriate
661 | parts of the General Public License. Of course, your program's commands
662 | might be different; for a GUI interface, you would use an "about box".
663 |
664 | You should also get your employer (if you work as a programmer) or school,
665 | if any, to sign a "copyright disclaimer" for the program, if necessary.
666 | For more information on this, and how to apply and follow the GNU GPL, see
667 | .
668 |
669 | The GNU General Public License does not permit incorporating your program
670 | into proprietary programs. If your program is a subroutine library, you
671 | may consider it more useful to permit linking proprietary applications with
672 | the library. If this is what you want to do, use the GNU Lesser General
673 | Public License instead of this License. But first, please read
674 | .
675 |
--------------------------------------------------------------------------------