|  | DAMASK with grid solvers
    Revision: v2.0.3-2204-gdb1f2151
    The Düsseldorf Advanced Material Simulation Kit with Grid Solvers |  | 
 
 
 
Go to the documentation of this file.    1 # 1 "/home/damask_user/GitLabCI_Pipeline_4301/DAMASK/src/config.f90" 
    4 # 1 "/home/damask_user/GitLabCI_Pipeline_4301/DAMASK/src/config.f90" 
   34   character(len=pStringLen),    
public, 
protected, 
allocatable, 
dimension(:) :: &
 
   55   character(len=pStringLen) :: &
 
   58   character(len=pStringLen), 
dimension(:), 
allocatable :: filecontent
 
   61   write(6,
'(/,a)') 
' <<<+-  config init  -+>>>'; 
flush(6)
 
   67     write(6,
'(/,a)') 
' reading '//trim(
getsolverjobname())//
'.materialConfig'; 
flush(6)
 
   70     inquire(file=
'material.config',exist=fileexists)
 
   71     if(.not. fileexists) 
call io_error(100,ext_msg=
'material.config')
 
   72     write(6,
'(/,a)') 
' reading material.config'; 
flush(6)
 
   76   do i = 1, 
size(filecontent)
 
   77     line = trim(filecontent(i))
 
   79     select case (trim(part))
 
   83         if (verbose) 
write(6,
'(a)') 
' Phase          parsed'; 
flush(6)
 
   85       case (trim(
'microstructure'))
 
   87         if (verbose) 
write(6,
'(a)') 
' Microstructure parsed'; 
flush(6)
 
   89       case (trim(
'crystallite'))
 
   91         if (verbose) 
write(6,
'(a)') 
' Crystallite    parsed'; 
flush(6)
 
   94       case (trim(
'homogenization'))
 
   96         if (verbose) 
write(6,
'(a)') 
' Homogenization parsed'; 
flush(6)
 
   98       case (trim(
'texture'))
 
  100         if (verbose) 
write(6,
'(a)') 
' Texture        parsed'; 
flush(6)
 
  107     call io_error(160,ext_msg=
'<homogenization>')
 
  109     call io_error(160,ext_msg=
'<microstructure>')
 
  111     call io_error(160,ext_msg=
'<phase>')
 
  113     call io_error(160,ext_msg=
'<texture>')
 
  116   inquire(file=
'numerics.config', exist=fileexists)
 
  118     write(6,
'(/,a)') 
' reading numerics.config'; 
flush(6)
 
  123   inquire(file=
'debug.config', exist=fileexists)
 
  125     write(6,
'(/,a)') 
' reading debug.config'; 
flush(6)
 
  139   character(len=*),          
intent(in)                :: filename
 
  140   integer,                   
intent(in), 
optional      :: cnt
 
  141   character(len=pStringLen), 
dimension(:), 
allocatable :: filecontent
 
  142   character(len=pStringLen), 
dimension(:), 
allocatable :: includedcontent
 
  143   character(len=pStringLen)                            :: line
 
  144   character(len=pStringLen), 
parameter                 :: dummy = 
'https://damask2.mpie.de' 
  145   character(len=:),                        
allocatable :: rawdata
 
  150     mytotallines, &                                                                                 !< # lines read from file without include statements
 
  155   if (
present(cnt)) 
then 
  156     if (cnt>10) 
call io_error(106,ext_msg=trim(filename))
 
  161   inquire(file = filename, size=filelength)
 
  162   if (filelength == 0) 
then 
  163     allocate(filecontent(0))
 
  166   open(newunit=fileunit, file=filename, access=
'stream',&
 
  167        status=
'old', position=
'rewind', action=
'read',iostat=mystat)
 
  168   if(mystat /= 0) 
call io_error(100,ext_msg=trim(filename))
 
  169   allocate(
character(len=fileLength)::rawdata)
 
  170   read(fileunit) rawdata
 
  177     if (rawdata(l:l) == 
io_eol) mytotallines = mytotallines+1
 
  179   allocate(filecontent(mytotallines))
 
  186   do while (l <= mytotallines)
 
  187     endpos = merge(startpos + scan(rawdata(startpos:),
io_eol) - 2,len(rawdata),l /= mytotallines)
 
  189       line = rawdata(startpos:startpos+
pstringlen-1)
 
  190       if (.not. warned) 
then 
  191         call io_warning(207,ext_msg=trim(filename),el=l)
 
  195       line = rawdata(startpos:endpos)
 
  197     startpos = endpos + 2                                                                           
 
  199     recursion: 
if (scan(trim(adjustl(line)),
'{') == 1 .and. scan(trim(line),
'}') > 2) 
then 
  201                         merge(cnt,1,
present(cnt)))                                                  
 
  202       filecontent     = [ filecontent(1:l-1), includedcontent, [(dummy,i=1,mytotallines-l)] ]       
 
  203       mytotallines    = mytotallines - 1 + 
size(includedcontent)
 
  204       l               = l            - 1 + 
size(includedcontent)
 
  206       filecontent(l) = line
 
  221   character(len=pStringLen),    
allocatable, 
dimension(:), 
intent(out)   :: sectionNames
 
  223   character(len=pStringLen),                               
intent(inout) :: line
 
  224   character(len=pStringLen),                 
dimension(:), 
intent(in)    :: fileContent
 
  226   integer, 
allocatable, 
dimension(:) :: partPosition
 
  229   character(len=pStringLen) :: sectionName
 
  233   if (
allocated(part)) 
call io_error(161,ext_msg=trim(line))
 
  234   allocate(partposition(0))
 
  236   do i = 1, 
size(filecontent)
 
  237     line = trim(filecontent(i))
 
  239     nextsection: 
if (
io_gettag(line,
'[',
']') /= 
'') 
then 
  240       partposition = [partposition, i]
 
  243     if (
size(partposition) < 1) &
 
  244       echo = (trim(
io_gettag(line,
'/',
'/')) == 
'echo') .or. echo
 
  247   allocate(sectionnames(
size(partposition)))
 
  248   allocate(part(
size(partposition)))
 
  250   partposition = [partposition, i]                                                                  
 
  252   do i = 1, 
size(partposition) -1
 
  253     write(sectionname,
'(i0,a,a)') i,
'_',trim(
io_gettag(filecontent(partposition(i)),
'[',
']'))
 
  254     sectionnames(i) = sectionname
 
  255     do j = partposition(i) + 1,  partposition(i+1) -1
 
  256       call part(i)%add(trim(adjustl(filecontent(j))))
 
  259       write(6,*) 
'section',i, 
'"'//trim(sectionnames(i))//
'"' 
  274   character(len=pStringLen),   
dimension(:), 
intent(in)  :: fileContent
 
  277   do i = 1, 
size(filecontent)
 
  278     call config_list%add(trim(adjustl(filecontent(i))))
 
  291   character(len=*), 
intent(in) :: what
 
  293   select case(trim(what))
 
  295     case(
'material.config/phase')
 
  298     case(
'material.config/microstructure')
 
  301     case(
'material.config/homogenization')
 
  304     case(
'material.config/texture')
 
  310     case(
'numerics.config')
 
  314       call io_error(0,ext_msg=
'config_deallocate')
 
 
 
pure character(len=:) function, allocatable, public io_gettag(string, openChar, closeChar)
get tagged content of string
character(len=pstringlen) function, dimension(:), allocatable, public io_read_ascii(fileName)
reads an entire ASCII file into an array
subroutine, public io_error(error_ID, el, ip, g, instance, ext_msg)
write error statements to standard out and terminate the Marc/spectral run with exit #9xxx
type(tpartitionedstringlist), dimension(:), allocatable, public, protected config_phase
character, parameter, public io_eol
end of line character
integer, dimension(debug_maxntype+2), public, protected debug_level
type(tpartitionedstringlist), dimension(:), allocatable, public, protected config_crystallite
character(len=pstringlen), dimension(:), allocatable, public, protected config_name_phase
name of each phase
Reads in the material configuration from file.
subroutine, public config_deallocate(what)
deallocates the linked lists that store the content of the configuration files
setting precision for real and int type
integer, parameter pstringlen
default string length
integer, parameter, public debug_material
stores debug level for material part of DAMASK bitwise coded
character(len=pstringlen), dimension(:), allocatable, public, protected config_name_microstructure
name of each microstructure
subroutine parse_materialconfig(sectionNames, part, line, fileContent)
parses the material.config file
subroutine, public io_warning(warning_ID, el, ip, g, ext_msg)
writes warning statement to standard out
input/output functions, partly depending on chosen solver
character(len=pstringlen), dimension(:), allocatable, public, protected config_name_texture
name of each texture
integer, parameter, public debug_levelbasic
Reading in and interpretating the debugging settings for the various modules.
type(tpartitionedstringlist), dimension(:), allocatable, public, protected config_texture
character(len=pstringlen), dimension(:), allocatable, public, protected config_name_homogenization
name of each homogenization
type(tpartitionedstringlist), public, protected config_debug
Interfacing between the 1-based solvers and the material subroutines provided by DAMASK.
type(tpartitionedstringlist), public, protected config_numerics
character(len=pstringlen), dimension(:), allocatable, public, protected config_name_crystallite
name of each crystallite setting
type(tpartitionedstringlist), dimension(:), allocatable, public, protected config_microstructure
subroutine, public config_init
reads material.config and stores its content per part
character(len=:) function, allocatable, public getsolverjobname()
solver job name (no extension) as combination of geometry and load case name
pure character(len=len(string)) function, public io_lc(string)
changes characters in string to lower case
subroutine parse_debugandnumericsconfig(config_list, fileContent)
parses the material.config file
type(tpartitionedstringlist), dimension(:), allocatable, public, protected config_homogenization
recursive character(len=pstringlen) function, dimension(:), allocatable read_materialconfig(fileName, cnt)
reads material.config Recursion is triggered by "{path/to/inputfile}" in a line