using default string length

This commit is contained in:
Martin Diehl 2019-12-21 12:37:02 +01:00
parent 1037aa98d3
commit 34af10fac1
14 changed files with 27 additions and 27 deletions

View File

@ -243,12 +243,12 @@ subroutine IO_open_inputFile(fileUnit)
integer, allocatable, dimension(:) :: chunkPos
character(len=65536) :: line,fname
character(len=pStringLen :: line,fname
logical :: createSuccess,fexist
do
read(unit2,'(A65536)',END=220) line
read(unit2,'(A256)',END=220) line
chunkPos = IO_stringPos(line)
if (IO_lc(IO_StringValue(line,chunkPos,1))=='*include') then
@ -884,7 +884,7 @@ end subroutine IO_warning
!--------------------------------------------------------------------------------------------------
function IO_read(fileUnit) result(line)
integer, intent(in) :: fileUnit !< file unit
integer, intent(in) :: fileUnit !< file unit
character(len=pStringLen) :: line
@ -924,7 +924,7 @@ integer function IO_countDataLines(fileUnit)
integer, allocatable, dimension(:) :: chunkPos
character(len=65536) :: line, &
character(len=pStringLen) :: line, &
tmp
IO_countDataLines = 0
@ -956,7 +956,7 @@ integer function IO_countNumericalDataLines(fileUnit)
integer, allocatable, dimension(:) :: chunkPos
character(len=65536) :: line, &
character(len=pStringLen) :: line, &
tmp
IO_countNumericalDataLines = 0
@ -991,7 +991,7 @@ integer function IO_countContinuousIntValues(fileUnit)
integer :: l,c
#endif
integer, allocatable, dimension(:) :: chunkPos
character(len=65536) :: line
character(len=pString) :: line
IO_countContinuousIntValues = 0
line = ''
@ -1048,21 +1048,21 @@ function IO_continuousIntValues(fileUnit,maxN,lookupName,lookupMap,lookupMaxN)
integer, intent(in) :: fileUnit, &
lookupMaxN
integer, dimension(:,:), intent(in) :: lookupMap
character(len=64), dimension(:), intent(in) :: lookupName
character(len=*), dimension(:), intent(in) :: lookupName
integer :: i,first,last
#ifdef Abaqus
integer :: j,l,c
#endif
integer, allocatable, dimension(:) :: chunkPos
character(len=65536) line
logical rangeGeneration
character(len=pStringLen) :: line
logical :: rangeGeneration
IO_continuousIntValues = 0
rangeGeneration = .false.
#if defined(Marc4DAMASK)
do
read(fileUnit,'(A65536)',end=100) line
read(fileUnit,'(A256)',end=100) line
chunkPos = IO_stringPos(line)
if (chunkPos(1) < 1) then ! empty line
exit
@ -1103,14 +1103,14 @@ function IO_continuousIntValues(fileUnit,maxN,lookupName,lookupMap,lookupMaxN)
!--------------------------------------------------------------------------------------------------
! check if the element values in the elset are auto generated
backspace(fileUnit)
read(fileUnit,'(A65536)',end=100) line
read(fileUnit,'(A256)',end=100) line
chunkPos = IO_stringPos(line)
do i = 1,chunkPos(1)
if (IO_lc(IO_stringValue(line,chunkPos,i)) == 'generate') rangeGeneration = .true.
enddo
do l = 1,c
read(fileUnit,'(A65536)',end=100) line
read(fileUnit,'(A256)',end=100) line
chunkPos = IO_stringPos(line)
if (verify(IO_stringValue(line,chunkPos,1),'0123456789') > 0) then ! a non-int, i.e. set names follow on this line
do i = 1,chunkPos(1) ! loop over set names in line

View File

@ -77,7 +77,7 @@ module crystallite
crystallite_localPlasticity !< indicates this grain to have purely local constitutive law
type :: tOutput !< new requested output (per phase)
character(len=65536), allocatable, dimension(:) :: &
character(len=pStringLen), allocatable, dimension(:) :: &
label
end type tOutput
type(tOutput), allocatable, dimension(:) :: output_constituent

View File

@ -44,7 +44,7 @@ contains
subroutine damage_local_init
integer :: maxNinstance,o,NofMyHomog,h
character(len=65536), dimension(:), allocatable :: outputs
character(len=pStringLen), dimension(:), allocatable :: outputs
write(6,'(/,a)') ' <<<+- damage_'//DAMAGE_local_label//' init -+>>>'; flush(6)

View File

@ -49,7 +49,7 @@ contains
subroutine damage_nonlocal_init
integer :: maxNinstance,o,NofMyHomog,h
character(len=65536), dimension(:), allocatable :: outputs
character(len=pStringLen), dimension(:), allocatable :: outputs
write(6,'(/,a)') ' <<<+- damage_'//DAMAGE_nonlocal_label//' init -+>>>'; flush(6)

View File

@ -36,7 +36,7 @@ program DAMASK_spectral
N_t = 0, & !< # of time indicators found in load case file
N_n = 0, & !< # of increment specifiers found in load case file
N_def = 0 !< # of rate of deformation specifiers found in load case file
character(len=65536) :: &
character(len=pStringLen) :: &
line
!--------------------------------------------------------------------------------------------------

View File

@ -77,7 +77,7 @@ module subroutine mech_RGC_init
integer(kind(undefined_ID)) :: &
outputID
character(len=65536), dimension(:), allocatable :: &
character(len=pStringLen), dimension(:), allocatable :: &
outputs
write(6,'(/,a)') ' <<<+- homogenization_'//HOMOGENIZATION_RGC_label//' init -+>>>'

View File

@ -33,7 +33,7 @@ module subroutine mech_isostrain_init
Ninstance, &
h, &
NofMyHomog
character(len=65536) :: &
character(len=pStringLen) :: &
tag = ''
write(6,'(/,a)') ' <<<+- homogenization_'//HOMOGENIZATION_ISOSTRAIN_label//' init -+>>>'

View File

@ -492,7 +492,7 @@ contains
subroutine lattice_init
integer :: Nphases
character(len=65536) :: &
character(len=pStringLen) :: &
tag = ''
integer :: i,p
real(pReal), dimension(:), allocatable :: &

View File

@ -27,7 +27,7 @@ program DAMASK_FEM
integer, allocatable, dimension(:) :: chunkPos ! this is longer than needed for geometry parsing
integer :: &
N_def = 0 !< # of rate of deformation specifiers found in load case file
character(len=65536) :: &
character(len=pStringLen) :: &
line
!--------------------------------------------------------------------------------------------------

View File

@ -79,9 +79,9 @@ module prec
real(pReal), private, parameter :: PREAL_EPSILON = epsilon(0.0_pReal) !< minimum positive number such that 1.0 + EPSILON /= 1.0.
real(pReal), private, parameter :: PREAL_MIN = tiny(0.0_pReal) !< smallest normalized floating point number
integer, dimension(0), parameter, public :: emptyIntArray = [integer::]
real(pReal), dimension(0), parameter, public :: emptyRealArray = [real(pReal)::]
character(len=65536), dimension(0), parameter, public :: emptyStringArray = [character(len=65536)::]
integer, dimension(0), parameter, public :: emptyIntArray = [integer::]
real(pReal), dimension(0), parameter, public :: emptyRealArray = [real(pReal)::]
character(len=pStringLen), dimension(0), parameter, public :: emptyStringArray = [character(len=pStringLen)::]
private :: &
unitTest

View File

@ -74,7 +74,7 @@ subroutine source_damage_anisoBrittle_init
character(len=pStringLen) :: &
extmsg = ''
character(len=65536), dimension(:), allocatable :: &
character(len=pStringLen), dimension(:), allocatable :: &
outputs
write(6,'(/,a)') ' <<<+- source_'//SOURCE_DAMAGE_ANISOBRITTLE_LABEL//' init -+>>>'; flush(6)

View File

@ -67,7 +67,7 @@ subroutine source_damage_anisoDuctile_init
character(len=pStringLen) :: &
extmsg = ''
character(len=65536), dimension(:), allocatable :: &
character(len=pStringLen), dimension(:), allocatable :: &
outputs
write(6,'(/,a)') ' <<<+- source_'//SOURCE_DAMAGE_ANISODUCTILE_LABEL//' init -+>>>'; flush(6)

View File

@ -61,7 +61,7 @@ subroutine source_damage_isoBrittle_init
character(len=pStringLen) :: &
extmsg = ''
character(len=65536), dimension(:), allocatable :: &
character(len=pStringLen), dimension(:), allocatable :: &
outputs
write(6,'(/,a)') ' <<<+- source_'//SOURCE_DAMAGE_ISOBRITTLE_LABEL//' init -+>>>'; flush(6)

View File

@ -58,7 +58,7 @@ subroutine source_damage_isoDuctile_init
character(len=pStringLen) :: &
extmsg = ''
character(len=65536), dimension(:), allocatable :: &
character(len=pStringLen), dimension(:), allocatable :: &
outputs
write(6,'(/,a)') ' <<<+- source_'//SOURCE_DAMAGE_ISODUCTILE_LABEL//' init -+>>>'