correctet random seed generation to work with gfortran.

This commit is contained in:
Martin Diehl 2011-11-04 10:29:35 +00:00
parent ba63d3231f
commit ee7022d8cf
4 changed files with 32 additions and 18 deletions

View File

@ -337,18 +337,18 @@ program DAMASK_spectral
!Output of geom file !Output of geom file
!$OMP CRITICAL (write2out) !$OMP CRITICAL (write2out)
print '(a)', '' print '(a)', ''
print '(a)', '******************************************************' print '(a)', '*************************************************************'
print '(a)', 'DAMASK spectral:' print '(a)', 'DAMASK spectral:'
print '(a)', 'The spectral method boundary value problem solver for' print '(a)', 'The spectral method boundary value problem solver for'
print '(a)', 'the Duesseldorf Advanced Material Simulation Kit' print '(a)', 'the Duesseldorf Advanced Material Simulation Kit'
print '(a)', '******************************************************' print '(a)', '*************************************************************'
print '(a,a)', 'Geom File Name: ',trim(path)//'.geom' print '(a,a)', 'Geom File Name: ',trim(path)//'.geom'
print '(a)', '------------------------------------------------------' print '(a)', '-------------------------------------------------------------'
print '(a,/,i12,i12,i12)','resolution a b c:', resolution print '(a,/,i12,i12,i12)','resolution a b c:', resolution
print '(a,/,f12.5,f12.5,f12.5)','dimension x y z:', geomdimension print '(a,/,f12.5,f12.5,f12.5)','dimension x y z:', geomdimension
print '(a,i5)','homogenization: ',homog print '(a,i5)','homogenization: ',homog
print '(a,L)','spectralPictureMode: ',spectralPictureMode print '(a,L)','spectralPictureMode: ',spectralPictureMode
print '(a)', '******************************************************' print '(a)', '************************************************************'
print '(a,a)','Loadcase File Name: ',trim(getLoadcaseName()) print '(a,a)','Loadcase File Name: ',trim(getLoadcaseName())
!$OMP END CRITICAL (write2out) !$OMP END CRITICAL (write2out)
if (bc_followFormerTrajectory(1)) then if (bc_followFormerTrajectory(1)) then
@ -358,7 +358,7 @@ program DAMASK_spectral
! consistency checks and output of loadcase ! consistency checks and output of loadcase
do loadcase = 1, N_Loadcases do loadcase = 1, N_Loadcases
!$OMP CRITICAL (write2out) !$OMP CRITICAL (write2out)
print '(a)', '------------------------------------------------------' print '(a)', '-------------------------------------------------------------'
print '(a,i5)', 'Loadcase: ', loadcase print '(a,i5)', 'Loadcase: ', loadcase
write (loadcase_string, '(i3)' ) loadcase write (loadcase_string, '(i3)' ) loadcase
if (.not. bc_followFormerTrajectory(loadcase)) & if (.not. bc_followFormerTrajectory(loadcase)) &
@ -784,9 +784,9 @@ program DAMASK_spectral
totalStepsCounter = totalStepsCounter + 1_pInt totalStepsCounter = totalStepsCounter + 1_pInt
!$OMP CRITICAL (write2out) !$OMP CRITICAL (write2out)
if(err_div<=err_div_tol .and. err_stress<=err_stress_tol) then if(err_div<=err_div_tol .and. err_stress<=err_stress_tol) then
print '(3(A,I5.5),A,/)', '== Step ',step, ' of Loadcase ',loadcase,' (Total ', totalStepsCounter,') Converged =====' print '(3(A,I5.5),A,/)', '== Step ',step, ' of Loadcase ',loadcase,' (Total ', totalStepsCounter,') Converged ===='
else else
print '(3(A,I5.5),A,/)', '== Step ',step, ' of Loadcase ',loadcase,' (Total ', totalStepsCounter,') NOT Converged =' print '(3(A,I5.5),A,/)', '== Step ',step, ' of Loadcase ',loadcase,' (Total ', totalStepsCounter,') NOT Converged '
notConvergedCounter = notConvergedCounter + 1 notConvergedCounter = notConvergedCounter + 1
endif endif
!$OMP END CRITICAL (write2out) !$OMP END CRITICAL (write2out)

View File

@ -97,7 +97,7 @@ subroutine DAMASK_interface_init()
length = index(commandLine(start:len(commandLine)),' ',.false.) length = index(commandLine(start:len(commandLine)),' ',.false.)
if(start/=3_pInt) then if(start/=3_pInt) then
read(commandLine(start:start+length),'(I)') restartParameter read(commandLine(start:start+length),'(I12)') restartParameter
if (restartParameter>0) then if (restartParameter>0) then
restart_Read_Interface = .true. restart_Read_Interface = .true.
else else
@ -115,7 +115,7 @@ subroutine DAMASK_interface_init()
if (restart_Read_Interface) then if (restart_Read_Interface) then
write(6,*) 'Restart Read: ', restartParameter write(6,*) 'Restart Read: ', restartParameter
else else
write(6,'(a,I5)') 'Restart Read at Step: ', restart_Read_Interface write(6,'(a,I5)') ' Restart Read at Step: ', restart_Read_Interface
endif endif
write(6,*) write(6,*)
!$OMP END CRITICAL (write2out) !$OMP END CRITICAL (write2out)

View File

@ -142,12 +142,14 @@ real(pReal), dimension(4,36), parameter :: math_symOperations = &
use debug, only: debug_verbosity use debug, only: debug_verbosity
implicit none implicit none
integer(pInt) :: i
real(pReal), dimension(3,3) :: R,R2 real(pReal), dimension(3,3) :: R,R2
real(pReal), dimension(3) :: Eulers real(pReal), dimension(3) :: Eulers
real(pReal), dimension(4) :: q,q2,axisangle real(pReal), dimension(4) :: q,q2,axisangle,randTest
integer(pInt), dimension(8) :: randInit ! gfortran requires "8" to compile ! the following variables are system depented and shound NOT be pInt
! if recalculations of former randomness (with given seed) is necessary integer :: randSize ! gfortran requires a variable length to compile
! set this value back to "1" and use ifort... integer, dimension(:), allocatable :: randInit ! if recalculations of former randomness (with given seed) is necessary
! comment the first random_seed call out, set randSize to 1, and use ifort
!$OMP CRITICAL (write2out) !$OMP CRITICAL (write2out)
write(6,*) write(6,*)
@ -156,20 +158,32 @@ real(pReal), dimension(4,36), parameter :: math_symOperations = &
write(6,*) write(6,*)
!$OMP END CRITICAL (write2out) !$OMP END CRITICAL (write2out)
call random_seed(size=randSize)
allocate(randInit(randSize))
if (fixedSeed > 0_pInt) then if (fixedSeed > 0_pInt) then
randInit = fixedSeed randInit(1:randSize) = int(fixedSeed) ! fixedSeed is of type pInt, randInit not
call random_seed(put=randInit) call random_seed(put=randInit)
else else
call random_seed() call random_seed()
endif endif
call random_seed(get=randInit) call random_seed(get=randInit)
do i = 1, 4
call random_number(randTest(i))
enddo
!$OMP CRITICAL (write2out) !$OMP CRITICAL (write2out)
! this critical block did cause trouble at IWM ! this critical block did cause trouble at IWM
write(6,*) 'random seed: ',randInit(1) write(6,*) 'value of random seed: ', randInit(1)
write(6,*) write(6,*) 'size of random seed: ', randSize
write(6,'(a,4(/,26x,f16.14))') ' start of random sequence: ', randTest
write(6,*) ''
!$OMP END CRITICAL (write2out) !$OMP END CRITICAL (write2out)
call random_seed(put=randInit)
call random_seed(get=randInit)
call halton_seed_set(randInit(1)) call halton_seed_set(randInit(1))
call halton_ndim_set(3) call halton_ndim_set(3)

View File

@ -293,7 +293,7 @@ subroutine numerics_init()
!* Random seeding parameters !* Random seeding parameters
case ('fixed_seed') case ('fixed_seed')
fixedSeed = IO_floatValue(line,positions,2) fixedSeed = IO_intValue(line,positions,2)
endselect endselect
enddo enddo
100 close(fileunit) 100 close(fileunit)
@ -366,7 +366,7 @@ subroutine numerics_init()
write(6,*) write(6,*)
!* Random seeding parameters !* Random seeding parameters
write(6,'(a24,x,i8)') 'fixed_seed: ',fixedSeed write(6,'(a24,x,i16)') 'fixed_seed: ',fixedSeed
write(6,*) write(6,*)
!$OMP END CRITICAL (write2out) !$OMP END CRITICAL (write2out)