Merge branch 'master' into reconnection
This commit is contained in:
commit
29743f732d
@ -401,8 +401,8 @@ module boundaries
|
||||
use coordinates , only : ib, ie, ibl
|
||||
use coordinates , only : jb, je, jbl
|
||||
use coordinates , only : kb, ke, kbl
|
||||
#ifdef MPI
|
||||
use equations , only : nv
|
||||
#ifdef MPI
|
||||
use mpitools , only : nprocs, nproc, npmax
|
||||
use mpitools , only : send_real_array, receive_real_array
|
||||
#endif /* MPI */
|
||||
@ -1073,7 +1073,7 @@ module boundaries
|
||||
|
||||
! local variables
|
||||
!
|
||||
integer :: i, j, k, n
|
||||
integer :: i, j, k, n, m
|
||||
!
|
||||
!-------------------------------------------------------------------------------
|
||||
!
|
||||
@ -1114,6 +1114,11 @@ module boundaries
|
||||
!
|
||||
if (.not. periodic(n)) then
|
||||
|
||||
! calculate the edge direction (in 2D we don't have face neighbors, so we have
|
||||
! to use edge neighbors)
|
||||
!
|
||||
m = 3 - n
|
||||
|
||||
! iterate over all corners
|
||||
!
|
||||
do j = 1, nsides
|
||||
@ -1121,8 +1126,8 @@ module boundaries
|
||||
|
||||
! if the face neighbor is not associated, apply specific boundaries
|
||||
!
|
||||
if (.not. associated(pmeta%edges(i,j,n)%ptr)) &
|
||||
call block_boundary_specific(i, j, k, 3 - n &
|
||||
if (.not. associated(pmeta%edges(i,j,m)%ptr)) &
|
||||
call block_boundary_specific(i, j, k, n &
|
||||
, pmeta%data%q(1:nv,1:im,1:jm,1:km))
|
||||
|
||||
end do ! i = 1, sides
|
||||
@ -1223,9 +1228,7 @@ module boundaries
|
||||
use coordinates , only : ie , je , ke
|
||||
use coordinates , only : ibl, jbl, kbl
|
||||
use coordinates , only : ieu, jeu, keu
|
||||
#ifdef MPI
|
||||
use equations , only : nv
|
||||
#endif /* MPI */
|
||||
use mpitools , only : nproc, nprocs, npmax
|
||||
#ifdef MPI
|
||||
use mpitools , only : send_real_array, receive_real_array
|
||||
@ -1773,9 +1776,7 @@ module boundaries
|
||||
use coordinates , only : ie , je , ke
|
||||
use coordinates , only : ibl, jbl, kbl
|
||||
use coordinates , only : ieu, jeu, keu
|
||||
#ifdef MPI
|
||||
use equations , only : nv
|
||||
#endif /* MPI */
|
||||
use mpitools , only : nproc, nprocs, npmax
|
||||
#ifdef MPI
|
||||
use mpitools , only : send_real_array, receive_real_array
|
||||
@ -2323,9 +2324,7 @@ module boundaries
|
||||
use coordinates , only : ie , je , ke
|
||||
use coordinates , only : ibl, jbl, kbl
|
||||
use coordinates , only : ieu, jeu, keu
|
||||
#ifdef MPI
|
||||
use equations , only : nv
|
||||
#endif /* MPI */
|
||||
use mpitools , only : nproc, nprocs, npmax
|
||||
#ifdef MPI
|
||||
use mpitools , only : send_real_array, receive_real_array
|
||||
@ -2900,9 +2899,7 @@ module boundaries
|
||||
use coordinates , only : ie , je , ke
|
||||
use coordinates , only : ibl, jbl, kbl
|
||||
use coordinates , only : ieu, jeu, keu
|
||||
#ifdef MPI
|
||||
use equations , only : nv
|
||||
#endif /* MPI */
|
||||
use mpitools , only : nproc, nprocs, npmax
|
||||
#ifdef MPI
|
||||
use mpitools , only : send_real_array, receive_real_array
|
||||
@ -3479,9 +3476,7 @@ module boundaries
|
||||
use coordinates , only : ie , je , ke
|
||||
use coordinates , only : ibl, jbl, kbl
|
||||
use coordinates , only : ieu, jeu, keu
|
||||
#ifdef MPI
|
||||
use equations , only : nv
|
||||
#endif /* MPI */
|
||||
use mpitools , only : nproc, nprocs, npmax
|
||||
#ifdef MPI
|
||||
use mpitools , only : send_real_array, receive_real_array
|
||||
@ -4058,9 +4053,7 @@ module boundaries
|
||||
use coordinates , only : ie , je , ke
|
||||
use coordinates , only : ibl, jbl, kbl
|
||||
use coordinates , only : ieu, jeu, keu
|
||||
#ifdef MPI
|
||||
use equations , only : nv
|
||||
#endif /* MPI */
|
||||
use mpitools , only : nproc, nprocs, npmax
|
||||
#ifdef MPI
|
||||
use mpitools , only : send_real_array, receive_real_array
|
||||
@ -4648,9 +4641,7 @@ module boundaries
|
||||
use coordinates , only : im , jm , km
|
||||
use coordinates , only : ibl, jbl, kbl
|
||||
use coordinates , only : ieu, jeu, keu
|
||||
#ifdef MPI
|
||||
use equations , only : nv
|
||||
#endif /* MPI */
|
||||
use mpitools , only : nproc, nprocs, npmax
|
||||
#ifdef MPI
|
||||
use mpitools , only : send_real_array, receive_real_array
|
||||
@ -5109,9 +5100,7 @@ module boundaries
|
||||
use coordinates , only : im , jm , km
|
||||
use coordinates , only : ibl, jbl, kbl
|
||||
use coordinates , only : ieu, jeu, keu
|
||||
#ifdef MPI
|
||||
use equations , only : nv
|
||||
#endif /* MPI */
|
||||
use mpitools , only : nproc, nprocs, npmax
|
||||
#ifdef MPI
|
||||
use mpitools , only : send_real_array, receive_real_array
|
||||
@ -5569,9 +5558,7 @@ module boundaries
|
||||
use coordinates , only : im , jm , km
|
||||
use coordinates , only : ibl, jbl, kbl
|
||||
use coordinates , only : ieu, jeu, keu
|
||||
#ifdef MPI
|
||||
use equations , only : nv
|
||||
#endif /* MPI */
|
||||
use mpitools , only : nproc, nprocs, npmax
|
||||
#ifdef MPI
|
||||
use mpitools , only : send_real_array, receive_real_array
|
||||
|
@ -154,7 +154,7 @@ module domains
|
||||
! local variables
|
||||
!
|
||||
integer :: i, j, k, n, p, ic, jc, kc
|
||||
real :: xl, xmn, xmx, yl, ymn, ymx, zl, zmn, zmx
|
||||
real(kind=8) :: xl, xmn, xmx, yl, ymn, ymx, zl, zmn, zmx
|
||||
|
||||
! local arrays
|
||||
!
|
||||
|
@ -85,7 +85,7 @@ program amun
|
||||
integer, dimension(3) :: div = 1
|
||||
logical, dimension(3) :: per = .true.
|
||||
integer :: nmax = huge(1), ndat = 1
|
||||
real :: tmax = 0.0d+00, trun = 9.999d+03, tsav = 3.0d+01
|
||||
real(kind=8) :: tmax = 0.0d+00, trun = 9.999d+03, tsav = 3.0d+01
|
||||
real(kind=8) :: dtnext = 0.0d+00
|
||||
|
||||
! flag to adjust time precisely to the snapshots
|
||||
@ -118,7 +118,7 @@ program amun
|
||||
integer :: nsteps = 1
|
||||
character(len=80) :: fmt, tmp
|
||||
|
||||
real :: tbeg, thrs
|
||||
real(kind=8) :: tbeg, thrs
|
||||
real(kind=8) :: tm_curr, tm_exec, tm_conv
|
||||
|
||||
#ifdef INTEL
|
||||
@ -593,7 +593,7 @@ program amun
|
||||
|
||||
! calculate days, hours, seconds
|
||||
!
|
||||
ec = int(tm_curr * (tmax - time) / max(1.0e-8, time - tbeg), kind = 4)
|
||||
ec = int(tm_curr * (tmax - time) / max(1.0d-08, time - tbeg), kind = 4)
|
||||
es = max(0, int(mod(ec, 60)))
|
||||
em = int(mod(ec / 60, 60))
|
||||
eh = int(ec / 3600)
|
||||
|
@ -1145,7 +1145,7 @@ module equations
|
||||
! local variables
|
||||
!
|
||||
integer :: i
|
||||
real :: ek, ei
|
||||
real(kind=8) :: ek, ei
|
||||
!
|
||||
!-------------------------------------------------------------------------------
|
||||
!
|
||||
@ -1210,7 +1210,7 @@ module equations
|
||||
! local variables
|
||||
!
|
||||
integer :: i
|
||||
real :: ek, ei
|
||||
real(kind=8) :: ek, ei
|
||||
!
|
||||
!-------------------------------------------------------------------------------
|
||||
!
|
||||
|
@ -41,19 +41,19 @@ module evolution
|
||||
|
||||
! evolution parameters
|
||||
!
|
||||
real , save :: cfl = 0.5d+00
|
||||
real(kind=8), save :: cfl = 0.5d+00
|
||||
|
||||
! coefficient controlling the decay of scalar potential ѱ
|
||||
!
|
||||
real , save :: alpha = 2.0d+00
|
||||
real , save :: decay = 1.0d+00
|
||||
real(kind=8), save :: alpha = 2.0d+00
|
||||
real(kind=8), save :: decay = 1.0d+00
|
||||
|
||||
! time variables
|
||||
!
|
||||
integer, save :: step = 0
|
||||
real , save :: time = 0.0d+00
|
||||
real , save :: dt = 1.0d+00
|
||||
real , save :: dtn = 1.0d+00
|
||||
integer , save :: step = 0
|
||||
real(kind=8), save :: time = 0.0d+00
|
||||
real(kind=8), save :: dt = 1.0d+00
|
||||
real(kind=8), save :: dtn = 1.0d+00
|
||||
|
||||
! by default everything is private
|
||||
!
|
||||
@ -225,7 +225,7 @@ module evolution
|
||||
|
||||
! input variables
|
||||
!
|
||||
real, intent(in) :: dtnext
|
||||
real(kind=8), intent(in) :: dtnext
|
||||
!
|
||||
!-------------------------------------------------------------------------------
|
||||
!
|
||||
@ -309,7 +309,7 @@ module evolution
|
||||
|
||||
! input variables
|
||||
!
|
||||
real, intent(in) :: dtnext
|
||||
real(kind=8), intent(in) :: dtnext
|
||||
|
||||
! local pointers
|
||||
!
|
||||
@ -319,11 +319,11 @@ module evolution
|
||||
!
|
||||
integer :: iret
|
||||
integer(kind=4) :: lev
|
||||
real :: cm, dx_min
|
||||
real(kind=8) :: cm, dx_min
|
||||
|
||||
! local parameters
|
||||
!
|
||||
real, parameter :: eps = tiny(cmax)
|
||||
real(kind=8), parameter :: eps = tiny(cmax)
|
||||
!
|
||||
!-------------------------------------------------------------------------------
|
||||
!
|
||||
@ -432,7 +432,7 @@ module evolution
|
||||
|
||||
! local arrays
|
||||
!
|
||||
real, dimension(nv,im,jm,km) :: du
|
||||
real(kind=8), dimension(nv,im,jm,km) :: du
|
||||
!
|
||||
!-------------------------------------------------------------------------------
|
||||
!
|
||||
@ -517,7 +517,7 @@ module evolution
|
||||
|
||||
! local arrays
|
||||
!
|
||||
real, dimension(nv,im,jm,km) :: du
|
||||
real(kind=8), dimension(nv,im,jm,km) :: du
|
||||
!
|
||||
!-------------------------------------------------------------------------------
|
||||
!
|
||||
@ -642,7 +642,7 @@ module evolution
|
||||
|
||||
! local vectors
|
||||
!
|
||||
real, dimension(3) :: dx
|
||||
real(kind=8), dimension(3) :: dx
|
||||
|
||||
! local variables
|
||||
!
|
||||
|
@ -16,10 +16,14 @@ FC = gfortran
|
||||
endif
|
||||
LD = $(FC)
|
||||
|
||||
# preprocessor prefix (used by IBM Fortran, e.g.)
|
||||
#
|
||||
CPPPREFIX =
|
||||
|
||||
# compiler and linker flags
|
||||
#
|
||||
ifeq ($(DEBUG),Y)
|
||||
FFLAGS = -g -O2 -DDEBUG
|
||||
FFLAGS = -g -O2 $(CPPPREFIX)-DDEBUG
|
||||
else
|
||||
FFLAGS = -O2
|
||||
endif
|
||||
@ -37,13 +41,11 @@ LDFLAGS += -static
|
||||
endif
|
||||
|
||||
ifeq ($(SIGNALS),Y)
|
||||
FFLAGS += -DSIGNALS
|
||||
FFLAGS += $(CPPPREFIX)-DSIGNALS
|
||||
endif
|
||||
|
||||
FFLAGS += -default-real-8 -default-double-8
|
||||
|
||||
ifeq ($(MPI),Y)
|
||||
FFLAGS += -DMPI
|
||||
FFLAGS += $(CPPPREFIX)-DMPI
|
||||
endif
|
||||
|
||||
ifeq ($(OUTPUT),HDF5)
|
||||
|
@ -142,13 +142,18 @@ module integrals
|
||||
|
||||
! create a new integrals file
|
||||
!
|
||||
#ifdef GNU
|
||||
open (newunit = funit, file = fname, form = 'formatted' &
|
||||
, status = 'replace')
|
||||
#endif /* GNU */
|
||||
#ifdef INTEL
|
||||
open (newunit = funit, file = fname, form = 'formatted' &
|
||||
, status = 'replace', buffered = 'yes')
|
||||
#else /* INTEL */
|
||||
open (newunit = funit, file = fname, form = 'formatted' &
|
||||
, status = 'replace')
|
||||
#endif /* INTEL */
|
||||
#ifdef IBM
|
||||
open (unit = funit, file = fname, form = 'formatted' &
|
||||
, status = 'replace')
|
||||
#endif /* IBM */
|
||||
|
||||
! write the integral file header
|
||||
!
|
||||
@ -163,13 +168,18 @@ module integrals
|
||||
|
||||
! create a new statistics file
|
||||
!
|
||||
#ifdef GNU
|
||||
open (newunit = sunit, file = fname, form = 'formatted' &
|
||||
, status = 'replace')
|
||||
#endif /* GNU */
|
||||
#ifdef INTEL
|
||||
open (newunit = sunit, file = fname, form = 'formatted' &
|
||||
, status = 'replace', buffered = 'yes')
|
||||
#else /* INTEL */
|
||||
open (newunit = sunit, file = fname, form = 'formatted' &
|
||||
, status = 'replace')
|
||||
#endif /* INTEL */
|
||||
#ifdef IBM
|
||||
open (unit = sunit, file = fname, form = 'formatted' &
|
||||
, status = 'replace')
|
||||
#endif /* IBM */
|
||||
|
||||
! write the integral file header
|
||||
!
|
||||
|
@ -453,7 +453,7 @@ module interpolations
|
||||
|
||||
! selection weights
|
||||
!
|
||||
real, parameter :: dp = 2.0d+00 / 3.0d+00, dm = 1.0d+00 / 3.0d+00
|
||||
real(kind=8), parameter :: dp = 2.0d+00 / 3.0d+00, dm = 1.0d+00 / 3.0d+00
|
||||
!
|
||||
!-------------------------------------------------------------------------------
|
||||
!
|
||||
@ -1555,8 +1555,8 @@ module interpolations
|
||||
! subroutine arguments
|
||||
!
|
||||
integer , intent(in) :: n
|
||||
real, dimension(n), intent(in) :: f
|
||||
real, dimension(n), intent(inout) :: fl, fr
|
||||
real(kind=8), dimension(n), intent(in) :: f
|
||||
real(kind=8), dimension(n), intent(inout) :: fl, fr
|
||||
|
||||
! local variables
|
||||
!
|
||||
|
14
src/io.F90
14
src/io.F90
@ -117,9 +117,9 @@ module io
|
||||
integer(kind=4) , save :: irest = 1
|
||||
integer(kind=4) , save :: isnap = 0
|
||||
integer(kind=4) , save :: ishift = 0
|
||||
real , save :: hrest = 6.0e+00
|
||||
real , save :: hsnap = 1.0e+00
|
||||
real , save :: tsnap = 0.0e+00
|
||||
real(kind=8) , save :: hrest = 6.0e+00
|
||||
real(kind=8) , save :: hsnap = 1.0e+00
|
||||
real(kind=8) , save :: tsnap = 0.0e+00
|
||||
|
||||
! flags to determine the way of data writing
|
||||
!
|
||||
@ -374,9 +374,9 @@ module io
|
||||
|
||||
! input and output arguments
|
||||
!
|
||||
real , intent(in) :: thrs
|
||||
integer, intent(in) :: nrun
|
||||
integer, intent(out) :: iret
|
||||
real(kind=8), intent(in) :: thrs
|
||||
integer , intent(in) :: nrun
|
||||
integer , intent(out) :: iret
|
||||
!
|
||||
!-------------------------------------------------------------------------------
|
||||
!
|
||||
@ -475,7 +475,7 @@ module io
|
||||
!
|
||||
!===============================================================================
|
||||
!
|
||||
real function next_tout()
|
||||
real(kind=8) function next_tout()
|
||||
|
||||
! local variables are not implicit by default
|
||||
!
|
||||
|
@ -51,20 +51,20 @@ endif
|
||||
#
|
||||
# compiler
|
||||
#
|
||||
FFLAGS += -D${COMPILER}
|
||||
FFLAGS += ${CPPPREFIX}-D${COMPILER}
|
||||
|
||||
# number of dimensions
|
||||
#
|
||||
FFLAGS += -DNDIMS=${NDIMS}
|
||||
FFLAGS += ${CPPPREFIX}-DNDIMS=${NDIMS}
|
||||
|
||||
# output data format
|
||||
#
|
||||
FFLAGS += -D${OUTPUT}
|
||||
FFLAGS += ${CPPPREFIX}-D${OUTPUT}
|
||||
|
||||
# compression
|
||||
#
|
||||
ifneq ($(COMPRESS),NONE)
|
||||
FFLAGS += -DCOMPRESS -D${COMPRESS}
|
||||
FFLAGS += ${CPPPREFIX}-DCOMPRESS ${CPPPREFIX}-D${COMPRESS}
|
||||
endif
|
||||
|
||||
#-------------------------------------------------------------------------------
|
||||
|
@ -1058,7 +1058,7 @@ module mesh
|
||||
integer :: i, j, k, q, p
|
||||
integer :: il, iu, jl, ju, kl, ku
|
||||
integer :: ic, jc, kc, ip, jp, kp
|
||||
real :: dul, dur, dux, duy, duz, du1, du2, du3, du4
|
||||
real(kind=8) :: dul, dur, dux, duy, duz, du1, du2, du3, du4
|
||||
|
||||
! local pointers
|
||||
!
|
||||
@ -1071,7 +1071,7 @@ module mesh
|
||||
|
||||
! local allocatable arrays
|
||||
!
|
||||
real, dimension(:,:,:,:), allocatable :: u
|
||||
real(kind=8), dimension(:,:,:,:), allocatable :: u
|
||||
|
||||
!-------------------------------------------------------------------------------
|
||||
!
|
||||
|
@ -457,8 +457,8 @@ module mpitools
|
||||
|
||||
! subroutine arguments
|
||||
!
|
||||
real , intent(inout) :: rbuf
|
||||
integer, intent(inout) :: iret
|
||||
real(kind=8), intent(inout) :: rbuf
|
||||
integer , intent(inout) :: iret
|
||||
!
|
||||
!-------------------------------------------------------------------------------
|
||||
!
|
||||
@ -604,12 +604,12 @@ module mpitools
|
||||
|
||||
! subroutine arguments
|
||||
!
|
||||
real , intent(inout) :: rbuf
|
||||
integer, intent(out) :: iret
|
||||
real(kind=8), intent(inout) :: rbuf
|
||||
integer , intent(out) :: iret
|
||||
|
||||
! local variables
|
||||
!
|
||||
real :: tbuf
|
||||
real(kind=8) :: tbuf
|
||||
!
|
||||
!-------------------------------------------------------------------------------
|
||||
!
|
||||
@ -715,12 +715,12 @@ module mpitools
|
||||
|
||||
! subroutine arguments
|
||||
!
|
||||
real , intent(inout) :: rbuf
|
||||
integer, intent(out) :: iret
|
||||
real(kind=8), intent(inout) :: rbuf
|
||||
integer , intent(out) :: iret
|
||||
|
||||
! local variables
|
||||
!
|
||||
real :: tbuf
|
||||
real(kind=8) :: tbuf
|
||||
!
|
||||
!-------------------------------------------------------------------------------
|
||||
!
|
||||
@ -825,12 +825,12 @@ module mpitools
|
||||
|
||||
! subroutine arguments
|
||||
!
|
||||
real , intent(inout) :: rbuf
|
||||
integer, intent(out) :: iret
|
||||
real(kind=8), intent(inout) :: rbuf
|
||||
integer , intent(out) :: iret
|
||||
|
||||
! local variables
|
||||
!
|
||||
real :: tbuf
|
||||
real(kind=8) :: tbuf
|
||||
!
|
||||
!-------------------------------------------------------------------------------
|
||||
!
|
||||
@ -882,7 +882,7 @@ module mpitools
|
||||
! subroutine arguments
|
||||
!
|
||||
integer , intent(in) :: n
|
||||
real , dimension(n), intent(inout) :: rbuf
|
||||
real(kind=8), dimension(n), intent(inout) :: rbuf
|
||||
integer , intent(out) :: iret
|
||||
|
||||
! local variables
|
||||
@ -939,7 +939,7 @@ module mpitools
|
||||
! subroutine arguments
|
||||
!
|
||||
integer , intent(in) :: n
|
||||
real , dimension(n), intent(inout) :: rbuf
|
||||
real(kind=8), dimension(n), intent(inout) :: rbuf
|
||||
integer , intent(out) :: iret
|
||||
|
||||
! local variables
|
||||
@ -1053,7 +1053,7 @@ module mpitools
|
||||
! subroutine arguments
|
||||
!
|
||||
integer , intent(in) :: n
|
||||
real , dimension(n), intent(inout) :: rbuf
|
||||
real(kind=8), dimension(n), intent(inout) :: rbuf
|
||||
integer , intent(out) :: iret
|
||||
|
||||
! local variables
|
||||
@ -1177,7 +1177,7 @@ module mpitools
|
||||
! subroutine arguments
|
||||
!
|
||||
integer , intent(in) :: n, dst, tag
|
||||
real , dimension(n), intent(in) :: rbuf
|
||||
real(kind=8), dimension(n), intent(in) :: rbuf
|
||||
integer , intent(out) :: iret
|
||||
!
|
||||
!-------------------------------------------------------------------------------
|
||||
@ -1233,7 +1233,7 @@ module mpitools
|
||||
! subroutine arguments
|
||||
!
|
||||
integer , intent(in) :: n, src, tag
|
||||
real , dimension(n), intent(out) :: rbuf
|
||||
real(kind=8), dimension(n), intent(out) :: rbuf
|
||||
integer , intent(out) :: iret
|
||||
|
||||
! local variables
|
||||
|
@ -550,7 +550,7 @@ module parameters
|
||||
! subroutine arguments
|
||||
!
|
||||
character(len=*), intent(in) :: name
|
||||
real , intent(inout) :: value
|
||||
real(kind=8) , intent(inout) :: value
|
||||
|
||||
! local parameter counter
|
||||
!
|
||||
|
@ -97,7 +97,7 @@ module random
|
||||
! local variables
|
||||
!
|
||||
integer :: i
|
||||
real :: r
|
||||
real(kind=4) :: r
|
||||
!
|
||||
!-------------------------------------------------------------------------------
|
||||
!
|
||||
@ -218,7 +218,7 @@ module random
|
||||
! local variables
|
||||
!
|
||||
integer :: i, l
|
||||
real :: r
|
||||
real(kind=4) :: r
|
||||
!
|
||||
!-------------------------------------------------------------------------------
|
||||
!
|
||||
@ -326,7 +326,7 @@ module random
|
||||
|
||||
! output variables
|
||||
!
|
||||
real :: val
|
||||
real(kind=8) :: val
|
||||
|
||||
! local variables
|
||||
!
|
||||
@ -349,7 +349,7 @@ module random
|
||||
|
||||
seeds(kp) = jsr
|
||||
|
||||
val = 0.5 + 0.23283064365e-9 * (jz + jsr)
|
||||
val = 0.5d+00 + 0.23283064365d-09 * (jz + jsr)
|
||||
|
||||
#ifdef PROFILE
|
||||
! stop accounting time for the random number generation
|
||||
@ -380,7 +380,7 @@ module random
|
||||
|
||||
! output variables
|
||||
!
|
||||
real :: val
|
||||
real(kind=8) :: val
|
||||
|
||||
! local variables
|
||||
!
|
||||
@ -403,7 +403,7 @@ module random
|
||||
|
||||
seeds(kp) = jsr
|
||||
|
||||
val = 0.23283064365e-9 * (jz + jsr)
|
||||
val = 0.23283064365d-09 * (jz + jsr)
|
||||
|
||||
#ifdef PROFILE
|
||||
! stop accounting time for the random number generation
|
||||
@ -434,7 +434,7 @@ module random
|
||||
|
||||
! output variables
|
||||
!
|
||||
real :: val
|
||||
real(kind=8) :: val
|
||||
|
||||
! local variables
|
||||
!
|
||||
@ -457,7 +457,7 @@ module random
|
||||
|
||||
seeds(kp) = jsr
|
||||
|
||||
val = 0.46566128730e-9 * (jz + jsr)
|
||||
val = 0.46566128730d-09 * (jz + jsr)
|
||||
|
||||
#ifdef PROFILE
|
||||
! stop accounting time for the random number generation
|
||||
|
Loading…
x
Reference in New Issue
Block a user