trying to have descriptive names
This commit is contained in:
parent
a1fdbd1d5e
commit
e0a6b79b14
|
@ -62,6 +62,8 @@ subroutine CPFEM_initAll(el,ip)
|
||||||
numerics_init
|
numerics_init
|
||||||
use debug, only: &
|
use debug, only: &
|
||||||
debug_init
|
debug_init
|
||||||
|
use config_material, only: &
|
||||||
|
config_material_init
|
||||||
use FEsolving, only: &
|
use FEsolving, only: &
|
||||||
FE_init
|
FE_init
|
||||||
use math, only: &
|
use math, only: &
|
||||||
|
@ -93,6 +95,7 @@ subroutine CPFEM_initAll(el,ip)
|
||||||
call IO_init
|
call IO_init
|
||||||
call numerics_init
|
call numerics_init
|
||||||
call debug_init
|
call debug_init
|
||||||
|
call config_material_init
|
||||||
call math_init
|
call math_init
|
||||||
call FE_init
|
call FE_init
|
||||||
call mesh_init(ip, el) ! pass on coordinates to alter calcMode of first ip
|
call mesh_init(ip, el) ! pass on coordinates to alter calcMode of first ip
|
||||||
|
|
11
src/IO.f90
11
src/IO.f90
|
@ -1550,6 +1550,17 @@ subroutine IO_error(error_ID,el,ip,g,instance,ext_msg)
|
||||||
case (136_pInt)
|
case (136_pInt)
|
||||||
msg = 'zero entry on stiffness diagonal for transformed phase'
|
msg = 'zero entry on stiffness diagonal for transformed phase'
|
||||||
|
|
||||||
|
!--------------------------------------------------------------------------------------------------
|
||||||
|
! errors related to the parsing of material.config
|
||||||
|
case (140_pInt)
|
||||||
|
msg = 'key not found'
|
||||||
|
case (141_pInt)
|
||||||
|
msg = 'number of chunks in string differs'
|
||||||
|
case (142_pInt)
|
||||||
|
msg = 'empty list'
|
||||||
|
case (143_pInt)
|
||||||
|
msg = 'no value found for key'
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
! material error messages and related messages in mesh
|
! material error messages and related messages in mesh
|
||||||
case (150_pInt)
|
case (150_pInt)
|
||||||
|
|
|
@ -4,9 +4,10 @@
|
||||||
!> @details List of files needed by MSC.Marc, Abaqus/Explicit, and Abaqus/Standard
|
!> @details List of files needed by MSC.Marc, Abaqus/Explicit, and Abaqus/Standard
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
#include "IO.f90"
|
#include "IO.f90"
|
||||||
#include "list.f90"
|
|
||||||
#include "numerics.f90"
|
#include "numerics.f90"
|
||||||
#include "debug.f90"
|
#include "debug.f90"
|
||||||
|
#include "list.f90"
|
||||||
|
#include "config_material.f90"
|
||||||
#include "math.f90"
|
#include "math.f90"
|
||||||
#include "FEsolving.f90"
|
#include "FEsolving.f90"
|
||||||
#include "mesh.f90"
|
#include "mesh.f90"
|
||||||
|
|
378
src/list.f90
378
src/list.f90
|
@ -1,3 +1,7 @@
|
||||||
|
!--------------------------------------------------------------------------------------------------
|
||||||
|
!> @author Martin Dieh, Max-Planck-Institut für Eisenforschung GmbH
|
||||||
|
!> @brief Chained list to store string together with position of delimiters
|
||||||
|
!--------------------------------------------------------------------------------------------------
|
||||||
module chained_list
|
module chained_list
|
||||||
use prec, only: &
|
use prec, only: &
|
||||||
pReal, &
|
pReal, &
|
||||||
|
@ -17,9 +21,13 @@ module chained_list
|
||||||
contains
|
contains
|
||||||
procedure :: add => add
|
procedure :: add => add
|
||||||
procedure :: show => show
|
procedure :: show => show
|
||||||
|
|
||||||
|
procedure :: keyExists => keyExists
|
||||||
|
procedure :: countKeys => countKeyAppearances
|
||||||
|
procedure :: getStringsRaw => strings
|
||||||
|
|
||||||
procedure :: getRaw => getRaw
|
procedure :: getRaw => getRaw
|
||||||
procedure :: getRaws => getRaws
|
procedure :: getRaws => getRaws
|
||||||
procedure :: getStringsRaw => getStringsRaw
|
|
||||||
|
|
||||||
procedure :: getFloat => getFloat
|
procedure :: getFloat => getFloat
|
||||||
procedure :: getFloatArray => getFloatArray
|
procedure :: getFloatArray => getFloatArray
|
||||||
|
@ -29,8 +37,6 @@ module chained_list
|
||||||
|
|
||||||
procedure :: getString => getString
|
procedure :: getString => getString
|
||||||
procedure :: getStrings => getStrings
|
procedure :: getStrings => getStrings
|
||||||
procedure :: keyExists => keyExists
|
|
||||||
procedure :: countKeys => countKeys
|
|
||||||
|
|
||||||
end type tPartitionedStringList
|
end type tPartitionedStringList
|
||||||
|
|
||||||
|
@ -40,7 +46,9 @@ contains
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
!> @brief add element
|
!> @brief add element
|
||||||
!> @details adds raw string and start/end position of chunks in this string
|
!> @details Adds a string together with the start/end position of chunks in this string. The new
|
||||||
|
!! element is added at the end of the list. Empty strings are not added. All strings are converted
|
||||||
|
!! to lower case
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
subroutine add(this,string)
|
subroutine add(this,string)
|
||||||
use IO, only: &
|
use IO, only: &
|
||||||
|
@ -49,16 +57,14 @@ subroutine add(this,string)
|
||||||
IO_stringPos
|
IO_stringPos
|
||||||
|
|
||||||
implicit none
|
implicit none
|
||||||
class(tPartitionedStringList), target :: this
|
class(tPartitionedStringList), target, intent(in) :: this
|
||||||
character(len=*), intent(in) :: string
|
character(len=*), intent(in) :: string
|
||||||
|
type(tPartitionedStringList), pointer :: new, tmp
|
||||||
integer(pInt), allocatable,dimension(:) :: p
|
|
||||||
type(tPartitionedStringList), pointer :: new, tmp
|
|
||||||
|
|
||||||
if (IO_isBlank(string)) return
|
if (IO_isBlank(string)) return
|
||||||
|
|
||||||
allocate(new)
|
allocate(new)
|
||||||
new%string%val=trim(string)
|
new%string%val=IO_lc(trim(string))
|
||||||
new%string%pos=IO_stringPos(trim(string))
|
new%string%pos=IO_stringPos(trim(string))
|
||||||
|
|
||||||
tmp => this
|
tmp => this
|
||||||
|
@ -71,10 +77,11 @@ end subroutine add
|
||||||
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
!> @brief add element
|
!> @brief prints all elements
|
||||||
!> @details adds raw string and start/end position of chunks in this string
|
!> @details Strings are printed in order of insertion (FIFO)
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
subroutine show(this)
|
subroutine show(this)
|
||||||
|
|
||||||
implicit none
|
implicit none
|
||||||
class(tPartitionedStringList) :: this
|
class(tPartitionedStringList) :: this
|
||||||
type(tPartitionedStringList), pointer :: tmp
|
type(tPartitionedStringList), pointer :: tmp
|
||||||
|
@ -88,8 +95,117 @@ subroutine show(this)
|
||||||
|
|
||||||
end subroutine show
|
end subroutine show
|
||||||
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
!> @brief gets raw data
|
!> @brief deallocates all elements of a given list
|
||||||
|
!> @details Strings are printed in order of insertion (FIFO)
|
||||||
|
!--------------------------------------------------------------------------------------------------
|
||||||
|
! subroutine free_all()
|
||||||
|
! implicit none
|
||||||
|
!
|
||||||
|
! type(node), pointer :: tmp
|
||||||
|
!
|
||||||
|
! do
|
||||||
|
! tmp => first
|
||||||
|
!
|
||||||
|
! if (associated(tmp) .eqv. .FALSE.) exit
|
||||||
|
!
|
||||||
|
! first => first%next
|
||||||
|
! deallocate(tmp)
|
||||||
|
! end do
|
||||||
|
! end subroutine free_all
|
||||||
|
|
||||||
|
|
||||||
|
!--------------------------------------------------------------------------------------------------
|
||||||
|
!> @brief reports wether a given key (string value at first position) exists in the list
|
||||||
|
!--------------------------------------------------------------------------------------------------
|
||||||
|
logical function keyExists(this,key)
|
||||||
|
use IO, only: &
|
||||||
|
IO_stringValue
|
||||||
|
|
||||||
|
implicit none
|
||||||
|
class(tPartitionedStringList), intent(in) :: this
|
||||||
|
character(len=*), intent(in) :: key
|
||||||
|
type(tPartitionedStringList), pointer :: tmp
|
||||||
|
|
||||||
|
keyExists = .false.
|
||||||
|
|
||||||
|
tmp => this%next
|
||||||
|
do
|
||||||
|
if (.not. associated(tmp)) exit
|
||||||
|
if (trim(IO_stringValue(tmp%string%val,tmp%string%pos,1))==trim(key)) then
|
||||||
|
keyExists = .true.
|
||||||
|
exit
|
||||||
|
endif
|
||||||
|
tmp => tmp%next
|
||||||
|
end do
|
||||||
|
|
||||||
|
end function keyExists
|
||||||
|
|
||||||
|
|
||||||
|
!--------------------------------------------------------------------------------------------------
|
||||||
|
!> @brief prints all elements
|
||||||
|
!> @details Strings are printed in order of insertion (FIFO)
|
||||||
|
!--------------------------------------------------------------------------------------------------
|
||||||
|
integer(pInt) function countKeyAppearances(this,key)
|
||||||
|
use IO, only: &
|
||||||
|
IO_stringValue
|
||||||
|
|
||||||
|
implicit none
|
||||||
|
|
||||||
|
class(tPartitionedStringList), intent(in) :: this
|
||||||
|
character(len=*), intent(in) :: key
|
||||||
|
type(tPartitionedStringList), pointer :: tmp
|
||||||
|
integer(pInt) :: i
|
||||||
|
|
||||||
|
countKeyAppearances = 0_pInt
|
||||||
|
|
||||||
|
tmp => this%next
|
||||||
|
do
|
||||||
|
if (.not. associated(tmp)) exit
|
||||||
|
if (trim(IO_stringValue(tmp%string%val,tmp%string%pos,1))==trim(key)) then
|
||||||
|
countKeyAppearances = countKeyAppearances + 1_pInt
|
||||||
|
endif
|
||||||
|
tmp => tmp%next
|
||||||
|
end do
|
||||||
|
|
||||||
|
end function countKeyAppearances
|
||||||
|
|
||||||
|
|
||||||
|
!--------------------------------------------------------------------------------------------------
|
||||||
|
!> @brief returns all strings in the list
|
||||||
|
!> @details returns raw string without start/end position of chunks
|
||||||
|
!--------------------------------------------------------------------------------------------------
|
||||||
|
function strings(this)
|
||||||
|
use IO, only: &
|
||||||
|
IO_error, &
|
||||||
|
IO_stringValue
|
||||||
|
|
||||||
|
implicit none
|
||||||
|
class(tPartitionedStringList), intent(in) :: this
|
||||||
|
character(len=65536), dimension(:), allocatable :: strings
|
||||||
|
character(len=65536) :: stringTmp
|
||||||
|
type(tPartitionedStringList), pointer :: tmp
|
||||||
|
|
||||||
|
tmp => this%next
|
||||||
|
do
|
||||||
|
if (.not. associated(tmp)) then
|
||||||
|
if(size(strings) < 0_pInt) call IO_error(142_pInt)
|
||||||
|
exit
|
||||||
|
endif
|
||||||
|
stringTmp = tmp%string%val
|
||||||
|
GfortranBug86033: if (.not. allocated(strings)) then
|
||||||
|
allocate(strings(1),source=stringTmp)
|
||||||
|
else GfortranBug86033
|
||||||
|
strings = [strings,stringTmp]
|
||||||
|
endif GfortranBug86033
|
||||||
|
tmp => tmp%next
|
||||||
|
end do
|
||||||
|
end function strings
|
||||||
|
|
||||||
|
|
||||||
|
!--------------------------------------------------------------------------------------------------
|
||||||
|
!> @brief gets first string that matches given key (i.e. first chunk)
|
||||||
!> @details returns raw string and start/end position of chunks in this string
|
!> @details returns raw string and start/end position of chunks in this string
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
subroutine getRaw(this,key,string,stringPos)
|
subroutine getRaw(this,key,string,stringPos)
|
||||||
|
@ -98,15 +214,15 @@ subroutine getRaw(this,key,string,stringPos)
|
||||||
IO_stringValue
|
IO_stringValue
|
||||||
|
|
||||||
implicit none
|
implicit none
|
||||||
class(tPartitionedStringList), intent(in) :: this
|
class(tPartitionedStringList), intent(in) :: this
|
||||||
character(len=*), intent(in) :: key
|
character(len=*), intent(in) :: key
|
||||||
integer(pInt), dimension(:),allocatable, intent(out) :: stringPos
|
integer(pInt), dimension(:), allocatable, intent(out) :: stringPos
|
||||||
character(len=*), intent(out) :: string
|
character(len=*), intent(out) :: string
|
||||||
type(tPartitionedStringList), pointer :: tmp
|
type(tPartitionedStringList), pointer :: tmp
|
||||||
|
|
||||||
tmp => this%next
|
tmp => this%next
|
||||||
do
|
do
|
||||||
if (.not. associated(tmp)) call IO_error(1_pInt,ext_msg=key)
|
if (.not. associated(tmp)) call IO_error(140_pInt,ext_msg=key)
|
||||||
foundKey: if (trim(IO_stringValue(tmp%string%val,tmp%string%pos,1))==trim(key)) then
|
foundKey: if (trim(IO_stringValue(tmp%string%val,tmp%string%pos,1))==trim(key)) then
|
||||||
stringPos = tmp%string%pos
|
stringPos = tmp%string%pos
|
||||||
string = tmp%string%val
|
string = tmp%string%val
|
||||||
|
@ -118,8 +234,9 @@ end subroutine getRaw
|
||||||
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
!> @brief gets raw data
|
!> @brief gets all strings that matches given key (i.e. first chunk)
|
||||||
!> @details returns raw string and start/end position of chunks in this string
|
!> @details returns raw strings and start/end positions of chunks in these strings. Will fail if
|
||||||
|
! number of positions in strings differs
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
subroutine getRaws(this,key,string,stringPos)
|
subroutine getRaws(this,key,string,stringPos)
|
||||||
use IO, only: &
|
use IO, only: &
|
||||||
|
@ -127,20 +244,21 @@ subroutine getRaws(this,key,string,stringPos)
|
||||||
IO_stringValue
|
IO_stringValue
|
||||||
|
|
||||||
implicit none
|
implicit none
|
||||||
class(tPartitionedStringList), intent(in) :: this
|
class(tPartitionedStringList), intent(in) :: this
|
||||||
character(len=*), intent(in) :: key
|
character(len=*), intent(in) :: key
|
||||||
integer(pInt), dimension(:,:),allocatable, intent(out) :: stringPos
|
integer(pInt), dimension(:,:), allocatable, intent(out) :: stringPos
|
||||||
character(len=256), dimension(:),allocatable, intent(out) :: string
|
character(len=65536), dimension(:), allocatable, intent(out) :: string
|
||||||
character(len=256) :: stringTmp
|
|
||||||
integer(pInt) :: posSize
|
character(len=65536) :: stringTmp
|
||||||
integer(pInt), dimension(:),allocatable :: stringPosFlat
|
integer(pInt) :: posSize
|
||||||
type(tPartitionedStringList), pointer :: tmp
|
integer(pInt), dimension(:), allocatable :: stringPosFlat
|
||||||
|
type(tPartitionedStringList), pointer :: tmp
|
||||||
|
|
||||||
posSize = -1_pInt
|
posSize = -1_pInt
|
||||||
tmp => this%next
|
tmp => this%next
|
||||||
do
|
do
|
||||||
if (.not. associated(tmp)) then
|
if (.not. associated(tmp)) then
|
||||||
if(posSize < 0_pInt) call IO_error(1_pInt,ext_msg=key)
|
if(posSize < 0_pInt) call IO_error(140_pInt,ext_msg=key)
|
||||||
stringPos = reshape(stringPosFlat,[posSize,size(string)])
|
stringPos = reshape(stringPosFlat,[posSize,size(string)])
|
||||||
exit
|
exit
|
||||||
endif
|
endif
|
||||||
|
@ -151,7 +269,8 @@ subroutine getRaws(this,key,string,stringPos)
|
||||||
allocate(string(1))
|
allocate(string(1))
|
||||||
string(1) = tmp%string%val
|
string(1) = tmp%string%val
|
||||||
else
|
else
|
||||||
if (size(tmp%string%pos) /= posSize) call IO_error(1_pInt,ext_msg=key)
|
if (size(tmp%string%pos) /= posSize) &
|
||||||
|
call IO_error(141_pInt,ext_msg=trim(tmp%string%val),el=posSize)
|
||||||
stringPosFlat = [stringPosFlat,tmp%string%pos]
|
stringPosFlat = [stringPosFlat,tmp%string%pos]
|
||||||
stringTmp = tmp%string%val
|
stringTmp = tmp%string%val
|
||||||
string = [string,stringTmp]
|
string = [string,stringTmp]
|
||||||
|
@ -159,43 +278,13 @@ subroutine getRaws(this,key,string,stringPos)
|
||||||
endif foundKey
|
endif foundKey
|
||||||
tmp => tmp%next
|
tmp => tmp%next
|
||||||
end do
|
end do
|
||||||
|
|
||||||
end subroutine getRaws
|
end subroutine getRaws
|
||||||
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
!> @brief gets raw data
|
!> @brief gets float value of first string that matches given key (i.e. first chunk)
|
||||||
!> @details returns raw string and start/end position of chunks in this string
|
!> @details gets one float value. If key is not found exits with error unless default is given
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
function getStringsRaw(this)
|
|
||||||
use IO, only: &
|
|
||||||
IO_error, &
|
|
||||||
IO_stringValue
|
|
||||||
|
|
||||||
implicit none
|
|
||||||
class(tPartitionedStringList), intent(in) :: this
|
|
||||||
character(len=256), dimension(:),allocatable :: getStringsRaw
|
|
||||||
character(len=256) :: stringTmp
|
|
||||||
type(tPartitionedStringList), pointer :: tmp
|
|
||||||
|
|
||||||
tmp => this%next
|
|
||||||
do
|
|
||||||
if (.not. associated(tmp)) then
|
|
||||||
if(size(getStringsRaw) < 0_pInt) call IO_error(1_pInt,ext_msg='getallraw empty list')
|
|
||||||
exit
|
|
||||||
endif
|
|
||||||
stringTmp = tmp%string%val
|
|
||||||
if (.not. allocated(getStringsRaw)) then
|
|
||||||
allocate(getStringsRaw(1),source=stringTmp)
|
|
||||||
else
|
|
||||||
getStringsRaw = [getStringsRaw,stringTmp]
|
|
||||||
endif
|
|
||||||
tmp => tmp%next
|
|
||||||
end do
|
|
||||||
end function getStringsRaw
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
!> @brief gets float value for given key
|
|
||||||
!> @details if key is not found exits with error unless default is given
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
real(pReal) function getFloat(this,key,defaultVal)
|
real(pReal) function getFloat(this,key,defaultVal)
|
||||||
use IO, only : &
|
use IO, only : &
|
||||||
|
@ -216,22 +305,23 @@ real(pReal) function getFloat(this,key,defaultVal)
|
||||||
getFloat = defaultVal
|
getFloat = defaultVal
|
||||||
exit
|
exit
|
||||||
else
|
else
|
||||||
call IO_error(1_pInt,ext_msg=key)
|
call IO_error(140_pInt,ext_msg=key)
|
||||||
endif
|
endif
|
||||||
endif endOfList
|
endif endOfList
|
||||||
foundKey: if (trim(IO_stringValue(tmp%string%val,tmp%string%pos,1))==trim(key)) then
|
foundKey: if (trim(IO_stringValue(tmp%string%val,tmp%string%pos,1))==trim(key)) then
|
||||||
if (tmp%string%pos(1) < 2_pInt) call IO_error(1_pInt,ext_msg=key)
|
if (tmp%string%pos(1) < 2_pInt) call IO_error(143_pInt,ext_msg=key)
|
||||||
getFloat = IO_FloatValue(tmp%string%val,tmp%string%pos,2)
|
getFloat = IO_FloatValue(tmp%string%val,tmp%string%pos,2)
|
||||||
exit
|
exit
|
||||||
endif foundKey
|
endif foundKey
|
||||||
tmp => tmp%next
|
tmp => tmp%next
|
||||||
end do
|
end do
|
||||||
|
|
||||||
end function getFloat
|
end function getFloat
|
||||||
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
!> @brief gets float value for given key
|
!> @brief gets integer value for given key
|
||||||
!> @details if key is not found exits with error unless default is given
|
!> @details gets one integer value. If key is not found exits with error unless default is given
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
integer(pInt) function getInt(this,key,defaultVal)
|
integer(pInt) function getInt(this,key,defaultVal)
|
||||||
use IO, only: &
|
use IO, only: &
|
||||||
|
@ -252,16 +342,17 @@ integer(pInt) function getInt(this,key,defaultVal)
|
||||||
getInt = defaultVal
|
getInt = defaultVal
|
||||||
exit
|
exit
|
||||||
else
|
else
|
||||||
call IO_error(1_pInt,ext_msg=key)
|
call IO_error(140_pInt,ext_msg=key)
|
||||||
endif
|
endif
|
||||||
endif endOfList
|
endif endOfList
|
||||||
foundKey: if (trim(IO_stringValue(tmp%string%val,tmp%string%pos,1))==trim(key)) then
|
foundKey: if (trim(IO_stringValue(tmp%string%val,tmp%string%pos,1))==trim(key)) then
|
||||||
if (tmp%string%pos(1) < 2_pInt) call IO_error(1_pInt,ext_msg=key)
|
if (tmp%string%pos(1) < 2_pInt) call IO_error(143_pInt,ext_msg=key)
|
||||||
getInt = IO_IntValue(tmp%string%val,tmp%string%pos,2)
|
getInt = IO_IntValue(tmp%string%val,tmp%string%pos,2)
|
||||||
exit
|
exit
|
||||||
endif foundKey
|
endif foundKey
|
||||||
tmp => tmp%next
|
tmp => tmp%next
|
||||||
end do
|
end do
|
||||||
|
|
||||||
end function getInt
|
end function getInt
|
||||||
|
|
||||||
|
|
||||||
|
@ -269,7 +360,7 @@ end function getInt
|
||||||
!> @brief gets string value for given key
|
!> @brief gets string value for given key
|
||||||
!> @details if key is not found exits with error unless default is given
|
!> @details if key is not found exits with error unless default is given
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
character(len=64) function getString(this,key,defaultVal)
|
character(len=65536) function getString(this,key,defaultVal)
|
||||||
use IO, only: &
|
use IO, only: &
|
||||||
IO_error, &
|
IO_error, &
|
||||||
IO_stringValue
|
IO_stringValue
|
||||||
|
@ -277,7 +368,7 @@ character(len=64) function getString(this,key,defaultVal)
|
||||||
implicit none
|
implicit none
|
||||||
class(tPartitionedStringList), intent(in) :: this
|
class(tPartitionedStringList), intent(in) :: this
|
||||||
character(len=*), intent(in) :: key
|
character(len=*), intent(in) :: key
|
||||||
character(len=64), intent(in), optional :: defaultVal
|
character(len=65536), intent(in), optional :: defaultVal
|
||||||
type(tPartitionedStringList), pointer :: tmp
|
type(tPartitionedStringList), pointer :: tmp
|
||||||
|
|
||||||
tmp => this%next
|
tmp => this%next
|
||||||
|
@ -287,18 +378,55 @@ character(len=64) function getString(this,key,defaultVal)
|
||||||
getString = defaultVal
|
getString = defaultVal
|
||||||
exit
|
exit
|
||||||
else
|
else
|
||||||
call IO_error(1_pInt,ext_msg=key)
|
call IO_error(140_pInt,ext_msg=key)
|
||||||
endif
|
endif
|
||||||
endif endOfList
|
endif endOfList
|
||||||
foundKey: if (trim(IO_stringValue(tmp%string%val,tmp%string%pos,1))==trim(key)) then
|
foundKey: if (trim(IO_stringValue(tmp%string%val,tmp%string%pos,1))==trim(key)) then
|
||||||
if (tmp%string%pos(1) < 2_pInt) call IO_error(1_pInt,ext_msg=key)
|
if (tmp%string%pos(1) < 2_pInt) call IO_error(143_pInt,ext_msg=key)
|
||||||
getString = IO_StringValue(tmp%string%val,tmp%string%pos,2)
|
getString = IO_StringValue(tmp%string%val,tmp%string%pos,2)
|
||||||
exit
|
exit
|
||||||
endif foundKey
|
endif foundKey
|
||||||
tmp => tmp%next
|
tmp => tmp%next
|
||||||
end do
|
end do
|
||||||
|
|
||||||
end function getString
|
end function getString
|
||||||
|
|
||||||
|
|
||||||
|
function getStrings(this,key)
|
||||||
|
use IO
|
||||||
|
|
||||||
|
implicit none
|
||||||
|
character(len=64),dimension(:),allocatable :: getStrings
|
||||||
|
character(len=64) :: str
|
||||||
|
|
||||||
|
class(tPartitionedStringList), intent(in) :: this
|
||||||
|
character(len=*), intent(in) :: key
|
||||||
|
type(tPartitionedStringList), pointer :: tmp
|
||||||
|
integer(pInt) :: i
|
||||||
|
|
||||||
|
|
||||||
|
tmp => this%next
|
||||||
|
do
|
||||||
|
if (.not. associated(tmp)) then
|
||||||
|
if (.not. allocated(getStrings)) allocate(getStrings(0),source=str)
|
||||||
|
exit
|
||||||
|
endif
|
||||||
|
if (trim(IO_stringValue(tmp%string%val,tmp%string%pos,1))==trim(key)) then
|
||||||
|
if (tmp%string%pos(1) < 2) print*, "NOT WORKKING"
|
||||||
|
str = IO_StringValue(tmp%string%val,tmp%string%pos,2)
|
||||||
|
|
||||||
|
GfortranBug86033: if (.not. allocated(getStrings)) then
|
||||||
|
allocate(getStrings(1),source=str)
|
||||||
|
else GfortranBug86033
|
||||||
|
getStrings = [getStrings,str]
|
||||||
|
endif GfortranBug86033
|
||||||
|
endif
|
||||||
|
tmp => tmp%next
|
||||||
|
end do
|
||||||
|
end function
|
||||||
|
|
||||||
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
!> @brief gets array of int values for given key
|
!> @brief gets array of int values for given key
|
||||||
!> @details if key is not found exits with error unless default is given
|
!> @details if key is not found exits with error unless default is given
|
||||||
|
@ -326,11 +454,11 @@ function getIntArray(this,key,defaultVal)
|
||||||
getIntArray = defaultVal
|
getIntArray = defaultVal
|
||||||
exit
|
exit
|
||||||
else
|
else
|
||||||
call IO_error(1_pInt,ext_msg=key)
|
call IO_error(140_pInt,ext_msg=key)
|
||||||
endif
|
endif
|
||||||
endif endOfList
|
endif endOfList
|
||||||
foundKey: if (trim(IO_stringValue(tmp%string%val,tmp%string%pos,1))==trim(key)) then
|
foundKey: if (trim(IO_stringValue(tmp%string%val,tmp%string%pos,1))==trim(key)) then
|
||||||
if (tmp%string%pos(1) < 2_pInt) call IO_error(1_pInt,ext_msg=key)
|
if (tmp%string%pos(1) < 2_pInt) call IO_error(143_pInt,ext_msg=key)
|
||||||
do i = 2_pInt, tmp%string%pos(1)
|
do i = 2_pInt, tmp%string%pos(1)
|
||||||
getIntArray = [getIntArray,IO_IntValue(tmp%string%val,tmp%string%pos,i)]
|
getIntArray = [getIntArray,IO_IntValue(tmp%string%val,tmp%string%pos,i)]
|
||||||
enddo
|
enddo
|
||||||
|
@ -369,11 +497,11 @@ function getFloatArray(this,key,defaultVal)
|
||||||
getFloatArray = defaultVal
|
getFloatArray = defaultVal
|
||||||
exit
|
exit
|
||||||
else
|
else
|
||||||
call IO_error(1_pInt,ext_msg=key)
|
call IO_error(140_pInt,ext_msg=key)
|
||||||
endif
|
endif
|
||||||
endif endOfList
|
endif endOfList
|
||||||
foundKey: if (trim(IO_stringValue(tmp%string%val,tmp%string%pos,1))==trim(key)) then
|
foundKey: if (trim(IO_stringValue(tmp%string%val,tmp%string%pos,1))==trim(key)) then
|
||||||
if (tmp%string%pos(1) < 2_pInt) call IO_error(1_pInt,ext_msg=key)
|
if (tmp%string%pos(1) < 2_pInt) call IO_error(143_pInt,ext_msg=key)
|
||||||
do i = 2_pInt, tmp%string%pos(1)
|
do i = 2_pInt, tmp%string%pos(1)
|
||||||
getFloatArray = [getFloatArray,IO_FloatValue(tmp%string%val,tmp%string%pos,i)]
|
getFloatArray = [getFloatArray,IO_FloatValue(tmp%string%val,tmp%string%pos,i)]
|
||||||
enddo
|
enddo
|
||||||
|
@ -383,98 +511,6 @@ function getFloatArray(this,key,defaultVal)
|
||||||
end do
|
end do
|
||||||
end function getFloatArray
|
end function getFloatArray
|
||||||
|
|
||||||
! reports wether a key exists at least once
|
|
||||||
function keyExists(this,key)
|
|
||||||
use IO
|
|
||||||
|
|
||||||
implicit none
|
|
||||||
logical :: keyExists
|
|
||||||
|
|
||||||
class(tPartitionedStringList), intent(in) :: this
|
|
||||||
character(len=*), intent(in) :: key
|
|
||||||
type(tPartitionedStringList), pointer :: tmp
|
|
||||||
|
|
||||||
keyExists = .false.
|
|
||||||
|
|
||||||
tmp => this%next
|
|
||||||
do
|
|
||||||
if (.not. associated(tmp)) exit
|
|
||||||
if (trim(IO_stringValue(tmp%string%val,tmp%string%pos,1))==trim(key)) then
|
|
||||||
keyExists = .true.
|
|
||||||
exit
|
|
||||||
endif
|
|
||||||
tmp => tmp%next
|
|
||||||
end do
|
|
||||||
end function
|
|
||||||
|
|
||||||
|
|
||||||
integer(pInt) function countKeys(this,key)
|
|
||||||
use IO
|
|
||||||
|
|
||||||
implicit none
|
|
||||||
class(tPartitionedStringList), intent(in) :: this
|
|
||||||
character(len=*), intent(in) :: key
|
|
||||||
type(tPartitionedStringList), pointer :: tmp
|
|
||||||
integer(pInt) :: i
|
|
||||||
|
|
||||||
countKeys = 0_pInt
|
|
||||||
|
|
||||||
tmp => this%next
|
|
||||||
do
|
|
||||||
if (.not. associated(tmp)) exit
|
|
||||||
if (trim(IO_stringValue(tmp%string%val,tmp%string%pos,1))==trim(key)) then
|
|
||||||
countKeys = countKeys + 1_pInt
|
|
||||||
endif
|
|
||||||
tmp => tmp%next
|
|
||||||
end do
|
|
||||||
end function
|
|
||||||
|
|
||||||
function getStrings(this,key)
|
|
||||||
use IO
|
|
||||||
|
|
||||||
implicit none
|
|
||||||
character(len=64),dimension(:),allocatable :: getStrings
|
|
||||||
character(len=64) :: str
|
|
||||||
|
|
||||||
class(tPartitionedStringList), intent(in) :: this
|
|
||||||
character(len=*), intent(in) :: key
|
|
||||||
type(tPartitionedStringList), pointer :: tmp
|
|
||||||
integer(pInt) :: i
|
|
||||||
|
|
||||||
|
|
||||||
tmp => this%next
|
|
||||||
do
|
|
||||||
if (.not. associated(tmp)) then
|
|
||||||
if (.not. allocated(getStrings)) allocate(getStrings(0),source=str)
|
|
||||||
exit
|
|
||||||
endif
|
|
||||||
if (trim(IO_stringValue(tmp%string%val,tmp%string%pos,1))==trim(key)) then
|
|
||||||
if (tmp%string%pos(1) < 2) print*, "NOT WORKKING"
|
|
||||||
str = IO_StringValue(tmp%string%val,tmp%string%pos,2)
|
|
||||||
|
|
||||||
GfortranBug86033: if (.not. allocated(getStrings)) then
|
|
||||||
allocate(getStrings(1),source=str)
|
|
||||||
else GfortranBug86033
|
|
||||||
getStrings = [getStrings,str]
|
|
||||||
endif GfortranBug86033
|
|
||||||
endif
|
|
||||||
tmp => tmp%next
|
|
||||||
end do
|
|
||||||
end function
|
|
||||||
|
|
||||||
! subroutine free_all()
|
|
||||||
! implicit none
|
|
||||||
!
|
|
||||||
! type(node), pointer :: tmp
|
|
||||||
!
|
|
||||||
! do
|
|
||||||
! tmp => first
|
|
||||||
!
|
|
||||||
! if (associated(tmp) .eqv. .FALSE.) exit
|
|
||||||
!
|
|
||||||
! first => first%next
|
|
||||||
! deallocate(tmp)
|
|
||||||
! end do
|
|
||||||
! end subroutine free_all
|
|
||||||
|
|
||||||
end module chained_list
|
end module chained_list
|
||||||
|
|
Loading…
Reference in New Issue