rngtest.f90
Go to the documentation of this file.
1 !#############################################################################
2 !# #
3 !# fosite - 3D hydrodynamical simulation program #
4 !# module: rngtest.f90 #
5 !# #
6 !# Copyright (C) 2015-2018 #
7 !# Manuel Jung <mjung@astrophysik.uni-kiel.de> #
8 !# #
9 !# This program is free software; you can redistribute it and/or modify #
10 !# it under the terms of the GNU General Public License as published by #
11 !# the Free Software Foundation; either version 2 of the License, or (at #
12 !# your option) any later version. #
13 !# #
14 !# This program is distributed in the hope that it will be useful, but #
15 !# WITHOUT ANY WARRANTY; without even the implied warranty of #
16 !# MERCHANTABILITY OR FITNESS FOR A PARTICULAR PURPOSE, GOOD TITLE or #
17 !# NON INFRINGEMENT. See the GNU General Public License for more #
18 !# details. #
19 !# #
20 !# You should have received a copy of the GNU General Public License #
21 !# along with this program; if not, write to the Free Software #
22 !# Foundation, Inc., 675 Mass Ave, Cambridge, MA 02139, USA. #
23 !# #
24 !#############################################################################
25 
26 !----------------------------------------------------------------------------!
32 !----------------------------------------------------------------------------!
33 PROGRAM rngtest
34  USE rngs
35 #ifdef NECSXAURORA
36  USE asl_unified
37 #endif
38 #include "tap.h"
39  IMPLICIT NONE
40  !--------------------------------------------------------------------------!
41  REAL :: rave,rmax,rmin,rnew
42 #ifdef NECSXAURORA
43  REAL, DIMENSION(:), POINTER :: r
44  INTEGER :: rng, imax
45 #else
46  REAL :: r
47  INTEGER(KIND=I8) :: i,x,x0,imax
48 #endif
49  !--------------------------------------------------------------------------!
50 
51 #ifdef NECSXAURORA
52  tap_plan(5)
53 
54  CALL asl_library_initialize()
55  CALL asl_random_create(rng, asl_randommethod_mt19937_64)
56  CALL asl_random_distribute_uniform(rng)
57 
58  imax = 100000000_i8
59 
60  ALLOCATE(r(imax))
61 
62  CALL asl_random_generate_d(rng, imax, r)
63 
64  rave = sum(r)/imax
65  rmin = minval(r)
66  rmax = maxval(r)
67 
68  CALL asl_random_destroy(rng)
69  CALL asl_library_finalize()
70 
71 #else
72  tap_plan(6)
73 
74  ! Check Kiss64
75  DO i=1, 100000000
76  x = kiss64()
77  END DO
78 
79  x0 = 1666297717051644203_i8
80  tap_check(x.EQ.x0,"Kiss64")
81 
82  imax = 100000000_i8
83  r = 0.
84  rmin = 1.
85  rmax = 0.
86  DO i=1, imax
87  rnew = dkiss64()
88  r = r + rnew
89  rmin = min(rmin,rnew)
90  rmax = max(rmax,rnew)
91  END DO
92 
93  rave = r/imax
94 #endif
95 
96 
97  ! Check if the random numbers are in (0,1)
98  ! and if the average is near 0.5
99  tap_check_close(rave,0.5,1.e-4,"Average close to 0.5.")
100  tap_check_ge(rmin,0.,"All are bigger (or equal) than 0.")
101  tap_check_le(rmax,1.,"All are smaller (or equal) than 1.")
102  tap_check_close(rmin,0.,1.e-4,"Lower limit is close to 0.")
103  tap_check_close(rmax,1.,1.e-4,"Upper limit is close to 1.")
104 
105 #ifdef NECSXAURORA
106  DEALLOCATE(r)
107 #endif
108  ! Check SuperKiss64
109  tap_done
110 
111 END PROGRAM rngtest
Definition: rngs.f90:42
real function, public dkiss64()
Definition: rngs.f90:181
integer(kind=i8) function, public kiss64(seed)
Definition: rngs.f90:62
program rngtest
Definition: rngtest.f90:33