started to implement restart facilities for spectral solver.

restart write is on per default
restart read is switched on by using --restart or -r INT where INT gives step at which the calculation should restart
setting INT to a value <1 will turn restart write off
This commit is contained in:
Martin Diehl 2011-11-03 19:32:11 +00:00
parent eb7f856df8
commit c2eac36b48
6 changed files with 184 additions and 175 deletions

View File

@ -92,7 +92,7 @@ subroutine CPFEM_initAll(Temperature,element,IP)
call crystallite_init(Temperature) ! (have to) use temperature of first IP for whole model
call homogenization_init(Temperature)
call CPFEM_init()
call DAMASK_interface_init()
if (trim(FEsolver)/='Spectral') call DAMASK_interface_init() ! Spectral solver is doing initialization earlier
CPFEM_init_done = .true.
CPFEM_init_inProgress = .false.
else ! loser, loser...

View File

@ -1,7 +1,7 @@
! Copyright 2011 Max-Planck-Institut fuer Eisenforschung GmbH
!
! This file is part of DAMASK,
! the Duesseldorf Advanced MAterial Simulation Kit.
! the Duesseldorf Advanced Material Simulation Kit.
!
! DAMASK is free software: you can redistribute it and/or modify
! it under the terms of the GNU General Public License as published by
@ -128,49 +128,41 @@ program DAMASK_spectral
complex(pReal), dimension(3,3) :: temp33_Complex
real(pReal), dimension(3,3) :: temp33_Real
integer(pInt) :: i, j, k, l, m, n, p
integer(pInt) :: N_Loadcases, loadcase, step, iter, ielem, CPFEM_mode, ierr, notConvergedCounter, writtenOutCounter
integer(pInt) :: N_Loadcases, loadcase, step, iter, ielem, CPFEM_mode, ierr, notConvergedCounter, totalStepsCounter
logical errmatinv
!Initializing
!$ call omp_set_num_threads(DAMASK_NumThreadsInt) ! set number of threads for parallel execution set by DAMASK_NUM_THREADS
print*, ''
print*, '<<<+- DAMASK_spectral init -+>>>'
print*, '$Id$'
print*, ''
if (.not.(command_argument_count()==4 .or. command_argument_count()==6)) call IO_error(error_ID=102) ! check for correct number of given arguments
myUnit = 234_pInt
call DAMASK_interface_init()
!$OMP CRITICAL (write2out)
print '(a)', ''
print '(a,a)', '<<<+- DAMASK_spectral init -+>>>'
print '(a,a)', '$Id$'
print '(a)', ''
print '(a,a)', 'Working Directory: ',trim(getSolverWorkingDirectoryName())
print '(a,a)', 'Solver Job Name: ',trim(getSolverJobName())
print '(a)', ''
!$OMP END CRITICAL (write2out)
! Reading the loadcase file and allocate variables
myUnit = 234_pInt
path = getLoadcaseName()
if (.not. IO_open_file(myUnit,path)) call IO_error(error_ID=30,ext_msg = trim(path))
N_l = 0_pInt
N_Fdot = 0_pInt
N_t = 0_pInt
N_n = 0_pInt
time = 0.0_pReal
notConvergedCounter = 0_pInt
writtenOutCounter = 0_pInt
resolution = 1_pInt
geomdimension = 0.0_pReal
if (command_argument_count() /= 4) call IO_error(error_ID=102) ! check for correct number of given arguments
! Reading the loadcase file and allocate variables
path = getLoadcaseName()
!$OMP CRITICAL (write2out)
print '(a)', '******************************************************'
print '(a,a)', 'Working Directory: ',trim(getSolverWorkingDirectoryName())
print '(a,a)', 'Solver Job Name: ',trim(getSolverJobName())
print '(a)', '******************************************************'
!$OMP END CRITICAL (write2out)
if (.not. IO_open_file(myUnit,path)) call IO_error(error_ID=30,ext_msg = trim(path))
rewind(myUnit)
do
read(myUnit,'(a1024)',END = 100) line
if (IO_isBlank(line)) cycle ! skip empty lines
if (IO_isBlank(line)) cycle ! skip empty lines
posLoadcase = IO_stringPos(line,maxNchunksLoadcase)
do i = 1, maxNchunksLoadcase, 1 ! reading compulsory parameters for loadcase
do i = 1, maxNchunksLoadcase, 1 ! reading compulsory parameters for loadcase
select case (IO_lc(IO_stringValue(line,posLoadcase,i)))
case('l', 'velocitygrad', 'velgrad','velocitygradient')
N_l = N_l+1
@ -181,11 +173,11 @@ program DAMASK_spectral
case('n', 'incs', 'increments', 'steps', 'logincs', 'logsteps')
N_n = N_n+1
end select
enddo ! count all identifiers to allocate memory and do sanity check
enddo ! count all identifiers to allocate memory and do sanity check
enddo
100 N_Loadcases = N_n
if ((N_l + N_Fdot /= N_n) .or. (N_n /= N_t)) & ! sanity check
if ((N_l + N_Fdot /= N_n) .or. (N_n /= N_t)) & ! sanity check
call IO_error(error_ID=37,ext_msg = trim(path)) ! error message for incomplete loadcase
allocate (bc_deformation(3,3,N_Loadcases)); bc_deformation = 0.0_pReal
@ -221,7 +213,7 @@ program DAMASK_spectral
enddo
bc_mask(:,:,1,loadcase) = transpose(reshape(bc_maskvector(1:9,1,loadcase),(/3,3/)))
bc_deformation(:,:,loadcase) = math_plain9to33(valueVector)
case('s', 'stress', 'pk1', 'piolakirchhoff')
case('p', 'pk1', 'piolakirchhoff', 'stress')
valueVector = 0.0_pReal
forall (k = 1:9) bc_maskvector(k,2,loadcase) = IO_stringValue(line,posLoadcase,j+k) /= '*'
do k = 1,9
@ -268,6 +260,8 @@ program DAMASK_spectral
gotDimension =.false.
gotHomogenization = .false.
spectralPictureMode = .false.
resolution = 1_pInt
geomdimension = 0.0_pReal
path = getModelName()
if (.not. IO_open_file(myUnit,trim(path)//InputFileExtension))&
@ -342,6 +336,11 @@ program DAMASK_spectral
!Output of geom file
!$OMP CRITICAL (write2out)
print '(a)', ''
print '(a)', '******************************************************'
print '(a)', 'DAMASK spectral:'
print '(a)', 'The spectral method boundary value problem solver for'
print '(a)', 'the Duesseldorf Advanced Material Simulation Kit'
print '(a)', '******************************************************'
print '(a,a)', 'Geom File Name: ',trim(path)//'.geom'
print '(a)', '------------------------------------------------------'
@ -533,12 +532,15 @@ program DAMASK_spectral
bc_steps(1)= bc_steps(1) + 1_pInt
write(538), 'increments', bc_steps ! one entry per loadcase ToDo: rename keyword to steps
bc_steps(1)= bc_steps(1) - 1_pInt
write(538), 'startingIncrement', writtenOutCounter
write(538), 'startingIncrement', totalStepsCounter
write(538), 'eoh' ! end of header
write(538), materialpoint_results(:,1,:) ! initial (non-deformed) results
!$OMP END CRITICAL (write2out)
! Initialization done
time = 0.0_pReal
notConvergedCounter = 0_pInt
totalStepsCounter = 1_pInt
!*************************************************************
! Loop over loadcases defined in the loadcase file
do loadcase = 1, N_Loadcases
@ -778,13 +780,13 @@ program DAMASK_spectral
!ToDo: Incfluence for next loadcase
if (mod(step,bc_frequency(loadcase)) == 0_pInt) then ! at output frequency
write(538), materialpoint_results(:,1,:) ! write result to file
writtenOutCounter = writtenOutCounter + 1_pInt
endif
totalStepsCounter = totalStepsCounter + 1_pInt
!$OMP CRITICAL (write2out)
if(err_div<=err_div_tol .and. err_stress<=err_stress_tol) then
print '(2(A,I5.5),A,/)', '== Step = ',step, ' of Loadcase = ',loadcase, ' Converged =============='
print '(3(A,I5.5),A,/)', '== Step ',step, ' of Loadcase ',loadcase,' (Total ', totalStepsCounter,') Converged ====='
else
print '(2(A,I5.5),A,/)', '== Step = ',step, ' of Loadcase = ',loadcase, ' NOT Converged =========='
print '(3(A,I5.5),A,/)', '== Step ',step, ' of Loadcase ',loadcase,' (Total ', totalStepsCounter,') NOT Converged ='
notConvergedCounter = notConvergedCounter + 1
endif
!$OMP END CRITICAL (write2out)
@ -794,8 +796,7 @@ program DAMASK_spectral
enddo ! end looping over loadcases
!$OMP CRITICAL (write2out)
print '(A,/)', '############################################################'
print '(a,i5.5,a)', 'A Total of ', notConvergedCounter, ' Steps did not Converge!'
print '(a,i5.5,a)', 'A Total of ', writtenOutCounter, ' Steps are written to File!'
print '(a,i5.5,a,i5.5,a)', 'Of ', totalStepsCounter, ' Total Steps,', notConvergedCounter, ' Steps did not Converge!'
!$OMP END CRITICAL (write2out)
close(538)
call dfftw_destroy_plan(fftw_plan(1)); call dfftw_destroy_plan(fftw_plan(2))

View File

@ -22,10 +22,14 @@
MODULE DAMASK_interface
use prec, only: pInt, pReal
implicit none
character(len=64), parameter :: FEsolver = 'Spectral'
character(len=5), parameter :: InputFileExtension = '.geom'
character(len=4), parameter :: LogFileExtension = '.log' !until now, we don't have a log file. But IO.f90 requires it
logical :: restart_Write_Interface, restart_Read_Interface
character(len=1024) :: geometryParameter,loadcaseParameter
integer(pInt) :: restartParameter
CONTAINS
!********************************************************************
@ -34,10 +38,87 @@ CONTAINS
!********************************************************************
subroutine DAMASK_interface_init()
implicit none
character(len=1024) commandLine
integer(pInt):: i, start, length
start = 0_pInt
length= 0_pInt
restart_Write_Interface =.true.
restart_Read_Interface = .false.
call get_command(commandLine)
do i=1,len(commandLine) ! remove capitals
if(64<iachar(commandLine(i:i)) .and. iachar(commandLine(i:i))<91) commandLine(i:i) =achar(iachar(commandLine(i:i))+32)
enddo
start = index(commandLine,'-g',.true.) + 3_pInt ! search for '-g' and jump to first char of geometry
if (index(commandLine,'--geom',.true.)>0) then ! if '--geom' is found, use that (contains '-g')
start = index(commandLine,'--geom',.true.) + 7_pInt
endif
if (index(commandLine,'--geometry',.true.)>0) then ! again, now searching for --geometry'
start = index(commandLine,'--geometry',.true.) + 11_pInt
endif
if(start==3_pInt) stop 'No Geometry specified, terminating DAMASK'! Could not find valid keyword. Functions from IO.f90 are not available
length = index(commandLine(start:len(commandLine)),' ',.false.)
call get_command(commandLine) ! may contain capitals
geometryParameter = '' ! should be empty
geometryParameter(1:length)=commandLine(start:start+length)
call get_command(commandLine)
do i=1,len(commandLine) ! remove capitals
if(64<iachar(commandLine(i:i)) .and. iachar(commandLine(i:i))<91) commandLine(i:i) =achar(iachar(commandLine(i:i))+32)
enddo
start = index(commandLine,'-l',.true.) + 3_pInt ! search for '-l' and jump forward to given name
if (index(commandLine,'--load',.true.)>0) then ! if '--load' is found, use that (contains '-l')
start = index(commandLine,'--load',.true.) + 7_pInt
endif
if (index(commandLine,'--loadcase',.true.)>0) then ! again, now searching for --loadcase'
start = index(commandLine,'--loadcase',.true.) + 11_pInt
endif
if(start==3_pInt) stop 'No Loadcase specified, terminating DAMASK'! Could not find valid keyword functions from IO.f90 are not available
length = index(commandLine(start:len(commandLine)),' ',.false.)
call get_command(commandLine) ! may contain capitals
loadcaseParameter = '' ! should be empty
loadcaseParameter(1:length)=commandLine(start:start+length)
do i=1,len(commandLine) ! remove capitals
if(64<iachar(commandLine(i:i)) .and. iachar(commandLine(i:i))<91) commandLine(i:i) =achar(iachar(commandLine(i:i))+32)
enddo
start = index(commandLine,'-r',.true.) + 3_pInt ! search for '-r' and jump forward to given name
if (index(commandLine,'--restart',.true.)>0) then ! if '--restart' is found, use that (contains '-r')
start = index(commandLine,'--restart',.true.) + 10_pInt
endif
length = index(commandLine(start:len(commandLine)),' ',.false.)
if(start/=3_pInt) then
read(commandLine(start:start+length),'(I)') restartParameter
if (restartParameter>0) then
restart_Read_Interface = .true.
else
restart_Write_Interface =.false.
endif
endif
!$OMP CRITICAL (write2out)
write(6,*)
write(6,*) '<<<+- DAMASK_spectral_interface init -+>>>'
write(6,*) '$Id$'
write(6,*)
write(6,*) 'Geometry Parameter: ', trim(geometryParameter)
write(6,*) 'Loadcase Parameter: ', trim(loadcaseParameter)
write(6,*) 'Restart Write: ', restart_Write_Interface
if (restart_Read_Interface) then
write(6,*) 'Restart Read: ', restartParameter
else
write(6,'(a,I5)') 'Restart Read at Step: ', restart_Read_Interface
endif
write(6,*)
!$OMP END CRITICAL (write2out)
endsubroutine DAMASK_interface_init
@ -50,34 +131,14 @@ function getSolverWorkingDirectoryName()
use prec, only: pInt
implicit none
character(len=1024) cwd,commandLine,outName,getSolverWorkingDirectoryName
character(len=*), parameter :: pathSep = achar(47)//achar(92) ! forwardslash, backwardslash
integer(pInt):: i, start, length
call get_command(commandLine)
do i=1,len(commandLine) ! remove capitals
if(64<iachar(commandLine(i:i)) .and. iachar(commandLine(i:i))<91) commandLine(i:i) =achar(iachar(commandLine(i:i))+32)
enddo
start = index(commandLine,'-g',.true.) + 3_pInt ! search for '-g' and jump to first char of geometry
if (index(commandLine,'--geom',.true.)>0) then ! if '--geom' is found, use that (contains '-g')
start = index(commandLine,'--geom',.true.) + 7_pInt
endif
if (index(commandLine,'--geometry',.true.)>0) then ! again, now searching for --geometry'
start = index(commandLine,'--geometry',.true.) + 11_pInt
endif
if(start==3_pInt) stop 'No Geometry Specified, terminating DAMASK'! Could not find valid keyword functions from IO.f90 are not available
length = index(commandLine(start:len(commandLine)),' ',.false.)
character(len=1024) cwd,getSolverWorkingDirectoryName
character(len=*), parameter :: pathSep = achar(47) //achar(92) !forwardslash, backwardslash
call get_command(commandLine) ! may contain capitals
outName = ' ' ! should be empty
outName(1:length)=commandLine(start:start+length)
if (scan(outName,pathSep) == 1) then ! absolute path given as command line argument
getSolverWorkingDirectoryName = outName(1:scan(outName,pathSep,back=.true.))
if (scan(geometryParameter,pathSep) == 1) then ! absolute path given as command line argument
getSolverWorkingDirectoryName = geometryParameter(1:scan(geometryParameter,pathSep,back=.true.))
else
call getcwd(cwd)
getSolverWorkingDirectoryName = trim(cwd)//'/'//outName(1:scan(outName,pathSep,back=.true.))
getSolverWorkingDirectoryName = trim(cwd)//'/'//geometryParameter(1:scan(geometryParameter,pathSep,back=.true.))
endif
getSolverWorkingDirectoryName = rectifyPath(getSolverWorkingDirectoryName)
@ -91,6 +152,7 @@ endfunction getSolverWorkingDirectoryName
function getSolverJobName()
implicit none
character(1024) :: getSolverJobName
getSolverJobName = trim(getModelName())//'_'//trim(getLoadCase())
@ -107,34 +169,15 @@ function getModelName()
implicit none
character(1024) getModelName, outName, cwd, commandLine
character(1024) getModelName, cwd
character(len=*), parameter :: pathSep = achar(47)//achar(92) ! forwardslash, backwardslash
integer(pInt) :: i,posExt,posSep,start,length
integer(pInt) :: posExt,posSep
call get_command(commandLine)
do i=1,len(commandLine) ! remove capitals
if(64<iachar(commandLine(i:i)) .and. iachar(commandLine(i:i))<91) commandLine(i:i) =achar(iachar(commandLine(i:i))+32)
enddo
start = index(commandLine,'-g',.true.) + 3_pInt ! search for '-g' and jump to first char of geometry
if (index(commandLine,'--geom',.true.)>0) then ! if '--geom' is found, use that (contains '-g')
start = index(commandLine,'--geom',.true.) + 7_pInt
endif
if (index(commandLine,'--geometry',.true.)>0) then ! again, now searching for --geometry'
start = index(commandLine,'--geometry',.true.) + 11_pInt
endif
if(start==3_pInt) stop 'No Geometry Specified, terminating DAMASK'! Could not find valid keyword functions from IO.f90 are not available
length = index(commandLine(start:len(commandLine)),' ',.false.)
call get_command(commandLine) ! may contain capitals
getModelName = ' '
outName = ' ' ! should be empty
outName(1:length)=commandLine(start:start+length)
posExt = scan(outName,'.',back=.true.)
posSep = scan(outName,pathSep,back=.true.)
posExt = scan(geometryParameter,'.',back=.true.)
posSep = scan(geometryParameter,pathSep,back=.true.)
if (posExt <= posSep) posExt = len_trim(outName)+1 ! no extension present
getModelName = outName(1:posExt-1) ! path to geometry file (excl. extension)
if (posExt <= posSep) posExt = len_trim(geometryParameter)+1 ! no extension present
getModelName = geometryParameter(1:posExt-1) ! path to geometry file (excl. extension)
if (scan(getModelName,pathSep) /= 1) then ! relative path given as command line argument
call getcwd(cwd)
@ -158,34 +201,15 @@ function getLoadCase()
implicit none
character(1024) getLoadCase, outName, commandLine
character(1024) getLoadCase
character(len=*), parameter :: pathSep = achar(47)//achar(92) ! forwardslash, backwardslash
integer(pInt) posExt,posSep,i,start,length
integer(pInt) posExt,posSep
call get_command(commandLine)
do i=1,len(commandLine) ! remove capitals
if(64<iachar(commandLine(i:i)) .and. iachar(commandLine(i:i))<91) commandLine(i:i) =achar(iachar(commandLine(i:i))+32)
enddo
start = index(commandLine,'-l',.true.) + 3_pInt ! search for '-l' and jump forward to given name
if (index(commandLine,'--load',.true.)>0) then ! if '--load' is found, use that (contains '-l')
start = index(commandLine,'--load',.true.) + 7_pInt
endif
if (index(commandLine,'--loadcase',.true.)>0) then ! again, now searching for --loadcase'
start = index(commandLine,'--loadcase',.true.) + 11_pInt
endif
if(start==3_pInt) stop 'No Loadcase Specified, terminating DAMASK'! Could not find valid keyword functions from IO.f90 are not available
length = index(commandLine(start:len(commandLine)),' ',.false.)
call get_command(commandLine) ! may contain capitals
getLoadCase = ''
outName = ' ' ! should be empty
outName(1:length)=commandLine(start:start+length)
posExt = scan(outName,'.',back=.true.)
posSep = scan(outName,pathSep,back=.true.)
posExt = scan(loadcaseParameter,'.',back=.true.)
posSep = scan(loadcaseParameter,pathSep,back=.true.)
if (posExt <= posSep) posExt = len_trim(outName)+1 ! no extension present
getLoadCase = outName(posSep+1:posExt-1) ! name of load case file exluding extension
if (posExt <= posSep) posExt = len_trim(loadcaseParameter)+1 ! no extension present
getLoadCase = loadcaseParameter(posSep+1:posExt-1) ! name of load case file exluding extension
endfunction getLoadCase
@ -200,30 +224,12 @@ function getLoadcaseName()
implicit none
character(len=1024) getLoadcaseName, cwd, commandLine
character(len=1024) getLoadcaseName,cwd
character(len=*), parameter :: pathSep = achar(47)//achar(92) ! forwardslash, backwardslash
integer(pInt) posExt,posSep,i,start,length
posExt = 0
call get_command(commandLine)
do i=1,len(commandLine) ! remove capitals
if(64<iachar(commandLine(i:i)) .and. iachar(commandLine(i:i))<91) commandLine(i:i) =achar(iachar(commandLine(i:i))+32)
enddo
start = index(commandLine,'-l',.true.) + 3_pInt ! search for '-l' and jump forward to given name
if (index(commandLine,'--load',.true.)>0) then ! if '--load' is found, use that (contains '-l')
start = index(commandLine,'--load',.true.) + 7_pInt
endif
if (index(commandLine,'--loadcase',.true.)>0) then ! again, now searching for --loadcase'
start = index(commandLine,'--loadcase',.true.) + 11_pInt
endif
if(start==3_pInt) stop 'No Loadcase Specified, terminating DAMASK'! Could not find valid keyword functions from IO.f90 are not available
length = index(commandLine(start:len(commandLine)),' ',.false.)
call get_command(commandLine) ! may contain capitals
getLoadCaseName = ' '
getLoadCaseName(1:length)=commandLine(start:start+length)
integer(pInt) posExt,posSep
posExt = 0_pInt
getLoadcaseName = loadcaseParameter
posExt = scan(getLoadcaseName,'.',back=.true.)
posSep = scan(getLoadcaseName,pathSep,back=.true.)

View File

@ -48,7 +48,7 @@
use prec, only: pInt
use debug, only: debug_verbosity
use DAMASK_interface, only: getModelName, FEsolver
use DAMASK_interface
use IO
implicit none
@ -60,41 +60,43 @@
character(len=1024) line
FEmodelGeometry = getModelName()
if (IO_open_inputFile(fileunit,FEmodelGeometry)) then
rewind(fileunit)
do
read (fileunit,'(a1024)',END=100) line
positions = IO_stringPos(line,maxNchunks)
tag = IO_lc(IO_stringValue(line,positions,1)) ! extract key
select case(tag)
case ('solver')
read (fileunit,'(a1024)',END=100) line ! next line
positions = IO_stringPos(line,maxNchunks)
symmetricSolver = (IO_intValue(line,positions,2) /= 1_pInt)
case ('restart')
read (fileunit,'(a1024)',END=100) line ! next line
positions = IO_stringPos(line,maxNchunks)
restartWrite = iand(IO_intValue(line,positions,1),1_pInt) > 0_pInt
restartRead = iand(IO_intValue(line,positions,1),2_pInt) > 0_pInt
case ('*restart')
do i=2,positions(1)
restartWrite = (IO_lc(IO_StringValue(line,positions,i)) == 'write') .or. restartWrite
restartRead = (IO_lc(IO_StringValue(line,positions,i)) == 'read') .or. restartRead
enddo
if(restartWrite) then
if(trim(FEsolver)=='Spectral') then
restartWrite = restart_Write_Interface
restartRead = restart_Read_Interface
else
rewind(fileunit)
do
read (fileunit,'(a1024)',END=100) line
positions = IO_stringPos(line,maxNchunks)
tag = IO_lc(IO_stringValue(line,positions,1)) ! extract key
select case(tag)
case ('solver')
read (fileunit,'(a1024)',END=100) line ! next line
positions = IO_stringPos(line,maxNchunks)
symmetricSolver = (IO_intValue(line,positions,2) /= 1_pInt)
case ('restart')
read (fileunit,'(a1024)',END=100) line ! next line
positions = IO_stringPos(line,maxNchunks)
restartWrite = iand(IO_intValue(line,positions,1),1_pInt) > 0_pInt
restartRead = iand(IO_intValue(line,positions,1),2_pInt) > 0_pInt
case ('*restart')
do i=2,positions(1)
restartWrite = (IO_lc(IO_StringValue(line,positions,i)) /= 'frequency=0') .and. restartWrite
restartWrite = (IO_lc(IO_StringValue(line,positions,i)) == 'write') .or. restartWrite
restartRead = (IO_lc(IO_StringValue(line,positions,i)) == 'read') .or. restartRead
enddo
endif
end select
enddo
if(restartWrite) then
do i=2,positions(1)
restartWrite = (IO_lc(IO_StringValue(line,positions,i)) /= 'frequency=0') .and. restartWrite
enddo
endif
end select
enddo
endif
else
call IO_error(101) ! cannot open input file
endif
100 close(fileunit)
100 close(fileunit)
if (restartRead) then
if(FEsolver == 'Marc' .and. IO_open_logFile(fileunit)) then

View File

@ -1171,7 +1171,7 @@ endfunction
case (101)
msg = 'opening input file'
case (102)
msg = 'DAMASK_spectral misses arguments'
msg = 'DAMASK_spectral has wrong number of arguments'
case (103)
msg = 'odd resolution given'
case (104)

View File

@ -19,8 +19,8 @@
# OPENMP = TRUE (FALSE): OpenMP multiprocessor support
# ACMLPATH =/opt/acml4.4.0/ifort64/lib (...) Path to ACML Library, choose according to your system
# ACMLPATH =/opt/acml4.4.0/ifort64_mp/lib (...) Path to ACML Library with multicore support, choose according to your system
# FFTWOPTIONS =include/libfftw3.a include/libfftw3_threads.a -lpthread (...) Path to FFTW library files with Linux threads (multicore) support
# FFTWOPTIONS =include/libfftw3.a (...) Path to FFTW library files without Linux threads (multicore) support
# FFTWOPTIONS =./../lib/libfftw3.a include/libfftw3_threads.a -lpthread (...) Path to FFTW library files with Linux threads (multicore) support
# FFTWOPTIONS =./../lib/libfftw3.a (...) Path to FFTW library files without Linux threads (multicore) support
# FFTWOPTIONS is different for single and double precision. Choose the options to use OpenMP instead of pthreads support or change the directory
# PREFIX: specify an arbitrary prefix
# SUFFIX: specify an arbitrary suffix
@ -75,9 +75,9 @@ ACMLPATH =/opt/acml4.4.0/ifort64_mp/lib
endif
ifndef FFTWOPTIONS
ifeq ($(PRECISION),single)
FFTWOPTIONS =include/libfftw3f_threads.a include/libfftw3f.a -lpthread
FFTWOPTIONS =./../lib/libfftw3f_threads.a ./../lib/libfftw3f.a -lpthread
else
FFTWOPTIONS =include/libfftw3_threads.a include/libfftw3.a -lpthread
FFTWOPTIONS =./../lib/libfftw3_threads.a ./../lib/libfftw3.a -lpthread
endif
endif
BLAS_ifort =-L $(ACMLPATH) -lacml_mp
@ -88,9 +88,9 @@ ACMLPATH =/opt/acml4.4.0/ifort64/lib
endif
ifndef FFTWOPTIONS
ifeq ($(PRECISION),single)
FFTWOPTIONS =include/libfftw3f.a
FFTWOPTIONS =./../lib/libfftw3f.a
else
FFTWOPTIONS =include/libfftw3.a
FFTWOPTIONS =./../lib/libfftw3.a
endif
endif
BLAS_ifort =-L $(ACMLPATH) -lacml