DAMASK with grid solvers  Revision: v2.0.3-2204-gdb1f2151
The Düsseldorf Advanced Material Simulation Kit with Grid Solvers
config.f90
Go to the documentation of this file.
1 # 1 "/home/damask_user/GitLabCI_Pipeline_4301/DAMASK/src/config.f90"
2 # 1 "<built-in>"
3 # 1 "<command-line>"
4 # 1 "/home/damask_user/GitLabCI_Pipeline_4301/DAMASK/src/config.f90"
5 !--------------------------------------------------------------------------------------------------
12 !--------------------------------------------------------------------------------------------------
13 module config
14  use prec
16  use io
17  use debug
18  use list
19 
20  implicit none
21  private
22 
23  type(tpartitionedstringlist), public, protected, allocatable, dimension(:) :: &
24  config_phase, &
29 
30  type(tpartitionedstringlist), public, protected :: &
33 
34  character(len=pStringLen), public, protected, allocatable, dimension(:) :: &
35  config_name_phase, & !< name of each phase
36  config_name_homogenization, & !< name of each homogenization
37  config_name_crystallite, & !< name of each crystallite setting
38  config_name_microstructure, & !< name of each microstructure
40 
41  public :: &
42  config_init, &
44 
45 contains
46 
47 !--------------------------------------------------------------------------------------------------
49 !--------------------------------------------------------------------------------------------------
50 subroutine config_init
51 
52  integer :: i
53  logical :: verbose
54 
55  character(len=pStringLen) :: &
56  line, &
57  part
58  character(len=pStringLen), dimension(:), allocatable :: filecontent
59  logical :: fileexists
60 
61  write(6,'(/,a)') ' <<<+- config init -+>>>'; flush(6)
62 
63  verbose = iand(debug_level(debug_material),debug_levelbasic) /= 0
64 
65  inquire(file=trim(getsolverjobname())//'.materialConfig',exist=fileexists)
66  if(fileexists) then
67  write(6,'(/,a)') ' reading '//trim(getsolverjobname())//'.materialConfig'; flush(6)
68  filecontent = read_materialconfig(trim(getsolverjobname())//'.materialConfig')
69  else
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)
73  filecontent = read_materialconfig('material.config')
74  endif
75 
76  do i = 1, size(filecontent)
77  line = trim(filecontent(i))
78  part = io_lc(io_gettag(line,'<','>'))
79  select case (trim(part))
80 
81  case (trim('phase'))
82  call parse_materialconfig(config_name_phase,config_phase,line,filecontent(i+1:))
83  if (verbose) write(6,'(a)') ' Phase parsed'; flush(6)
84 
85  case (trim('microstructure'))
87  if (verbose) write(6,'(a)') ' Microstructure parsed'; flush(6)
88 
89  case (trim('crystallite'))
91  if (verbose) write(6,'(a)') ' Crystallite parsed'; flush(6)
92  deallocate(config_crystallite)
93 
94  case (trim('homogenization'))
96  if (verbose) write(6,'(a)') ' Homogenization parsed'; flush(6)
97 
98  case (trim('texture'))
99  call parse_materialconfig(config_name_texture,config_texture,line,filecontent(i+1:))
100  if (verbose) write(6,'(a)') ' Texture parsed'; flush(6)
101 
102  end select
103 
104  enddo
105 
106  if (.not. allocated(config_homogenization) .or. size(config_homogenization) < 1) &
107  call io_error(160,ext_msg='<homogenization>')
108  if (.not. allocated(config_microstructure) .or. size(config_microstructure) < 1) &
109  call io_error(160,ext_msg='<microstructure>')
110  if (.not. allocated(config_phase) .or. size(config_phase) < 1) &
111  call io_error(160,ext_msg='<phase>')
112  if (.not. allocated(config_texture) .or. size(config_texture) < 1) &
113  call io_error(160,ext_msg='<texture>')
114 
115 
116  inquire(file='numerics.config', exist=fileexists)
117  if (fileexists) then
118  write(6,'(/,a)') ' reading numerics.config'; flush(6)
119  filecontent = io_read_ascii('numerics.config')
121  endif
122 
123  inquire(file='debug.config', exist=fileexists)
124  if (fileexists) then
125  write(6,'(/,a)') ' reading debug.config'; flush(6)
126  filecontent = io_read_ascii('debug.config')
128  endif
129 
130 contains
131 
132 
133 !--------------------------------------------------------------------------------------------------
136 !--------------------------------------------------------------------------------------------------
137 recursive function read_materialconfig(fileName,cnt) result(fileContent)
138 
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
146  integer :: &
147  filelength, &
148  fileunit, &
149  startpos, endpos, &
150  mytotallines, & !< # lines read from file without include statements
151  l,i, &
152  mystat
153  logical :: warned
154 
155  if (present(cnt)) then
156  if (cnt>10) call io_error(106,ext_msg=trim(filename))
157  endif
158 
159 !--------------------------------------------------------------------------------------------------
160 ! read data as stream
161  inquire(file = filename, size=filelength)
162  if (filelength == 0) then
163  allocate(filecontent(0))
164  return
165  endif
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
171  close(fileunit)
172 
173 !--------------------------------------------------------------------------------------------------
174 ! count lines to allocate string array
175  mytotallines = 1
176  do l=1, len(rawdata)
177  if (rawdata(l:l) == io_eol) mytotallines = mytotallines+1
178  enddo
179  allocate(filecontent(mytotallines))
180 
181 !--------------------------------------------------------------------------------------------------
182 ! split raw data at end of line and handle includes
183  warned = .false.
184  startpos = 1
185  l = 1
186  do while (l <= mytotallines)
187  endpos = merge(startpos + scan(rawdata(startpos:),io_eol) - 2,len(rawdata),l /= mytotallines)
188  if (endpos - startpos > pstringlen -1) then
189  line = rawdata(startpos:startpos+pstringlen-1)
190  if (.not. warned) then
191  call io_warning(207,ext_msg=trim(filename),el=l)
192  warned = .true.
193  endif
194  else
195  line = rawdata(startpos:endpos)
196  endif
197  startpos = endpos + 2 ! jump to next line start
198 
199  recursion: if (scan(trim(adjustl(line)),'{') == 1 .and. scan(trim(line),'}') > 2) then
200  includedcontent = read_materialconfig(trim(line(scan(line,'{')+1:scan(line,'}')-1)), &
201  merge(cnt,1,present(cnt))) ! to track recursion depth
202  filecontent = [ filecontent(1:l-1), includedcontent, [(dummy,i=1,mytotallines-l)] ] ! add content and grow array
203  mytotallines = mytotallines - 1 + size(includedcontent)
204  l = l - 1 + size(includedcontent)
205  else recursion
206  filecontent(l) = line
207  l = l + 1
208  endif recursion
209 
210  enddo
211 
212 end function read_materialconfig
213 
214 
215 !--------------------------------------------------------------------------------------------------
217 !--------------------------------------------------------------------------------------------------
218 subroutine parse_materialconfig(sectionNames,part,line, &
219  fileContent)
220 
221  character(len=pStringLen), allocatable, dimension(:), intent(out) :: sectionNames
222  type(tpartitionedstringlist), allocatable, dimension(:), intent(inout) :: part
223  character(len=pStringLen), intent(inout) :: line
224  character(len=pStringLen), dimension(:), intent(in) :: fileContent
225 
226  integer, allocatable, dimension(:) :: partPosition
227  integer :: i, j
228  logical :: echo
229  character(len=pStringLen) :: sectionName
230 
231  echo = .false.
232 
233  if (allocated(part)) call io_error(161,ext_msg=trim(line))
234  allocate(partposition(0))
235 
236  do i = 1, size(filecontent)
237  line = trim(filecontent(i))
238  if (io_gettag(line,'<','>') /= '') exit
239  nextsection: if (io_gettag(line,'[',']') /= '') then
240  partposition = [partposition, i]
241  cycle
242  endif nextsection
243  if (size(partposition) < 1) &
244  echo = (trim(io_gettag(line,'/','/')) == 'echo') .or. echo
245  enddo
246 
247  allocate(sectionnames(size(partposition)))
248  allocate(part(size(partposition)))
249 
250  partposition = [partposition, i] ! needed when actually storing content
251 
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))))
257  enddo
258  if (echo) then
259  write(6,*) 'section',i, '"'//trim(sectionnames(i))//'"'
260  call part(i)%show()
261  endif
262  enddo
263 
264 end subroutine parse_materialconfig
265 
266 
267 !--------------------------------------------------------------------------------------------------
269 !--------------------------------------------------------------------------------------------------
270 subroutine parse_debugandnumericsconfig(config_list, &
271  fileContent)
272 
273  type(tpartitionedstringlist), intent(out) :: config_list
274  character(len=pStringLen), dimension(:), intent(in) :: fileContent
275  integer :: i
276 
277  do i = 1, size(filecontent)
278  call config_list%add(trim(adjustl(filecontent(i))))
279  enddo
280 
281 end subroutine parse_debugandnumericsconfig
282 
283 end subroutine config_init
284 
285 
286 !--------------------------------------------------------------------------------------------------
288 !--------------------------------------------------------------------------------------------------
289 subroutine config_deallocate(what)
290 
291  character(len=*), intent(in) :: what
292 
293  select case(trim(what))
294 
295  case('material.config/phase')
296  deallocate(config_phase)
297 
298  case('material.config/microstructure')
299  deallocate(config_microstructure)
300 
301  case('material.config/homogenization')
302  deallocate(config_homogenization)
303 
304  case('material.config/texture')
305  deallocate(config_texture)
306 
307  case('debug.config')
308  call config_debug%free
309 
310  case('numerics.config')
311  call config_numerics%free
312 
313  case default
314  call io_error(0,ext_msg='config_deallocate')
315 
316  end select
317 
318 end subroutine config_deallocate
319 
320 end module config
io::io_gettag
pure character(len=:) function, allocatable, public io_gettag(string, openChar, closeChar)
get tagged content of string
Definition: IO.f90:175
io::io_read_ascii
character(len=pstringlen) function, dimension(:), allocatable, public io_read_ascii(fileName)
reads an entire ASCII file into an array
Definition: IO.f90:61
io::io_error
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
Definition: IO.f90:305
config::config_phase
type(tpartitionedstringlist), dimension(:), allocatable, public, protected config_phase
Definition: config.f90:23
io::io_eol
character, parameter, public io_eol
end of line character
Definition: IO.f90:20
debug::debug_level
integer, dimension(debug_maxntype+2), public, protected debug_level
Definition: debug.f90:48
config::config_crystallite
type(tpartitionedstringlist), dimension(:), allocatable, public, protected config_crystallite
Definition: config.f90:23
config::config_name_phase
character(len=pstringlen), dimension(:), allocatable, public, protected config_name_phase
name of each phase
Definition: config.f90:34
config
Reads in the material configuration from file.
Definition: config.f90:13
config::config_deallocate
subroutine, public config_deallocate(what)
deallocates the linked lists that store the content of the configuration files
Definition: config.f90:290
prec
setting precision for real and int type
Definition: prec.f90:13
prec::pstringlen
integer, parameter pstringlen
default string length
Definition: prec.f90:27
debug::debug_material
integer, parameter, public debug_material
stores debug level for material part of DAMASK bitwise coded
Definition: debug.f90:32
config::config_name_microstructure
character(len=pstringlen), dimension(:), allocatable, public, protected config_name_microstructure
name of each microstructure
Definition: config.f90:34
parse_materialconfig
subroutine parse_materialconfig(sectionNames, part, line, fileContent)
parses the material.config file
Definition: config.f90:220
io::io_warning
subroutine, public io_warning(warning_ID, el, ip, g, ext_msg)
writes warning statement to standard out
Definition: IO.f90:535
io
input/output functions, partly depending on chosen solver
Definition: IO.f90:12
config::config_name_texture
character(len=pstringlen), dimension(:), allocatable, public, protected config_name_texture
name of each texture
Definition: config.f90:34
debug::debug_levelbasic
integer, parameter, public debug_levelbasic
Definition: debug.f90:19
debug
Reading in and interpretating the debugging settings for the various modules.
Definition: debug.f90:12
config::config_texture
type(tpartitionedstringlist), dimension(:), allocatable, public, protected config_texture
Definition: config.f90:23
config::config_name_homogenization
character(len=pstringlen), dimension(:), allocatable, public, protected config_name_homogenization
name of each homogenization
Definition: config.f90:34
config::config_debug
type(tpartitionedstringlist), public, protected config_debug
Definition: config.f90:30
list::tpartitionedstringlist
Definition: list.f90:20
list
linked list
Definition: list.f90:9
damask_interface
Interfacing between the 1-based solvers and the material subroutines provided by DAMASK.
Definition: DAMASK_interface.f90:22
config::config_numerics
type(tpartitionedstringlist), public, protected config_numerics
Definition: config.f90:30
config::config_name_crystallite
character(len=pstringlen), dimension(:), allocatable, public, protected config_name_crystallite
name of each crystallite setting
Definition: config.f90:34
config::config_microstructure
type(tpartitionedstringlist), dimension(:), allocatable, public, protected config_microstructure
Definition: config.f90:23
config::config_init
subroutine, public config_init
reads material.config and stores its content per part
Definition: config.f90:51
damask_interface::getsolverjobname
character(len=:) function, allocatable, public getsolverjobname()
solver job name (no extension) as combination of geometry and load case name
Definition: DAMASK_interface.f90:1737
io::io_lc
pure character(len=len(string)) function, public io_lc(string)
changes characters in string to lower case
Definition: IO.f90:280
parse_debugandnumericsconfig
subroutine parse_debugandnumericsconfig(config_list, fileContent)
parses the material.config file
Definition: config.f90:272
config::config_homogenization
type(tpartitionedstringlist), dimension(:), allocatable, public, protected config_homogenization
Definition: config.f90:23
read_materialconfig
recursive character(len=pstringlen) function, dimension(:), allocatable read_materialconfig(fileName, cnt)
reads material.config Recursion is triggered by "{path/to/inputfile}" in a line
Definition: config.f90:138