Skip to content

Commit 5841796

Browse files
committed
Merge branch '542-support-external-concentrated-loads' into 'development'
Add support for concentrated loads Closes #542 See merge request damask/DAMASK!1138
2 parents 4d0e88b + 35ac601 commit 5841796

File tree

5 files changed

+257
-111
lines changed

5 files changed

+257
-111
lines changed

PRIVATE

src/mesh/DAMASK_mesh.f90

Lines changed: 90 additions & 43 deletions
Original file line numberDiff line numberDiff line change
@@ -41,7 +41,8 @@ program DAMASK_mesh
4141
Delta_t_prev = 0.0_pREAL !< previous time interval
4242
logical :: &
4343
guess, & !< guess along former trajectory
44-
stagIterate
44+
stagIterate, &
45+
printed_bc_type
4546
logical, allocatable, dimension(:) :: &
4647
read_BC_entries
4748
integer :: &
@@ -64,15 +65,16 @@ program DAMASK_mesh
6465
step_discretization
6566
type(tList), pointer :: &
6667
load_steps, &
67-
mech_u, &
68+
mech_u => NULL(), &
69+
mech_f => NULL(), &
6870
step_mech
6971
character(len=pSTRLEN) :: &
7072
incInfo
7173
integer :: &
72-
bc_tag, &
7374
stagItMax, & !< max number of field level staggered iterations
7475
maxCutBack, & !< max number of cutbacks
75-
skip_T1, skip_T2 !< number of characters to skip (T descriptor)
76+
bc_tag, & !< tag used for BC in YAML load file
77+
skip_T1 !< number of characters to skip (T descriptor)
7678

7779
type(tLoadCase), allocatable, dimension(:) :: loadCases !< array of all load cases
7880
type(tSolutionState), allocatable, dimension(:) :: solres
@@ -81,7 +83,7 @@ program DAMASK_mesh
8183
character(len=:), allocatable :: &
8284
fileContent, fname
8385
character(len=pSTRLEN) :: &
84-
bc_label_name
86+
bc_label !< mesh label or generic label for BC
8587

8688

8789
!--------------------------------------------------------------------------------------------------
@@ -126,21 +128,24 @@ program DAMASK_mesh
126128
step_bc => load_step%get_dict('boundary_conditions')
127129
step_mech => step_bc%get_list('mechanical')
128130
allocate(loadCases(l)%mechBC(mesh_Nboundaries))
129-
loadCases(l)%mechBC(:)%nComponents = dimPlex ! X, Y (, Z) displacements
130131
do boundary = 1_pPETSCINT, mesh_Nboundaries
131-
allocate(loadCases(l)%mechBC(boundary)%dot_u(dimPlex), source = 0.0_pREAL)
132-
allocate(loadCases(l)%mechBC(boundary)%active(dimPlex), source = .false.)
132+
allocate(loadCases(l)%mechBC(boundary)%dot_u(dimPlex), source = 0.0_pREAL)
133+
allocate(loadCases(l)%mechBC(boundary)%dot_u_active(dimPlex), source = .false.)
134+
allocate(loadCases(l)%mechBC(boundary)%dot_f(dimPlex), source = 0.0_pREAL)
135+
allocate(loadCases(l)%mechBC(boundary)%dot_f_active(dimPlex), source = .false.)
133136
end do
134137

138+
!--------------------------------------------------------------------------------------------------
139+
! check valid tags/labels
135140
do m = 1, size(step_mech)
136141
mech_BC => step_mech%get_dict(m)
137142
if (mech_BC%contains('label')) then
138-
bc_label_name = mech_BC%get_asStr('label')
139-
boundary = findloc(mesh_BCLabels, bc_label_name, dim = 1)
143+
bc_label = mech_BC%get_asStr('label')
144+
boundary = findloc(mesh_bcLabels, bc_label, dim = 1)
140145
if (boundary == 0) & ! label not defined in mesh file
141-
call IO_error(812_pI16, 'label', trim(bc_label_name), 'not defined', emph = [2])
146+
call IO_error(812_pI16, 'label', trim(bc_label), 'not defined', emph = [2])
142147
if (read_BC_entries(boundary)) & ! duplicated label/tag
143-
call IO_error(812_pI16, 'duplicated entries: label', trim(bc_label_name), 'and tag', &
148+
call IO_error(812_pI16, 'duplicated entries: label', trim(bc_label), 'and tag', &
144149
mesh_boundariesIS(boundary), emph = [2,4])
145150
read_BC_entries(boundary) = .true.
146151
loadCases(l)%mechBC(boundary)%use_label = .true.
@@ -151,25 +156,50 @@ program DAMASK_mesh
151156
call IO_error(812_pI16, 'tag', bc_tag, 'not defined', emph = [2])
152157
if (read_BC_entries(boundary)) & ! duplicated tag/label
153158
call IO_error(812_pI16, 'duplicated entries: tag', bc_tag, 'and label', &
154-
trim(mesh_BCLabels(boundary)), emph = [2, 4])
159+
trim(mesh_bcLabels(boundary)), emph = [2, 4])
155160
read_BC_entries(boundary) = .true.
156161
loadCases(l)%mechBC(boundary)%use_label = .false.
157162
else
158163
call IO_error(812_pI16, 'neither "label" nor "tag" given for boundary condition', m, emph=[2])
159164
end if
160-
mech_u => mech_BC%get_list('dot_u')
161-
do component = 1, dimPlex
162-
if (mech_u%get_asStr(component) /= 'x') then
163-
loadCases(l)%mechBC(boundary)%active(component) = .true.
164-
loadCases(l)%mechBC(boundary)%dot_u(component) = mech_u%get_asReal(component)
165-
end if
166-
end do
165+
! check valid BC definition of dot_u and dot_f, store values
166+
if (mech_BC%contains('dot_u')) mech_u => mech_BC%get_list('dot_u')
167+
if (mech_BC%contains('u_dot')) mech_u => mech_BC%get_list('u_dot')
168+
if (mech_BC%contains('dot_f')) mech_f => mech_BC%get_list('dot_f')
169+
if (mech_BC%contains('f_dot')) mech_f => mech_BC%get_list('f_dot')
170+
171+
if (.not. (associated(mech_u) .or. associated(mech_f))) &
172+
call IO_error(812_pI16, 'dot_u/dot_f missing for boundary condition', m, emph = [2])
173+
174+
associate (BC_mech => loadCases(l)%mechBC(boundary))
175+
do component = 1, dimplex
176+
if (associated(mech_u)) then
177+
if (mech_u%get_asStr(component) /= 'x') then
178+
BC_mech%dot_u(component) = mech_u%get_asReal(component)
179+
BC_mech%dot_u_active(component) = .true.
180+
end if
181+
end if
182+
if (associated(mech_f)) then
183+
if (mech_f%get_asStr(component) /= 'x') then
184+
BC_mech%dot_f(component) = mech_f%get_asReal(component)
185+
BC_mech%dot_f_active(component) = .true.
186+
end if
187+
end if
188+
189+
if (BC_mech%dot_f_active(component) .and. BC_mech%dot_u_active(component)) &
190+
call IO_error(812_pI16, 'displacement and force prescribed in the same DOF', &
191+
IO_EOL, 'in boundary condition', m, emph = [4])
192+
end do
193+
end associate
194+
nullify(mech_u, mech_f)
167195
end do
168196
read_BC_entries = .false.
169197

198+
!--------------------------------------------------------------------------------------------------
199+
! store discretization, time and frequency
170200
step_discretization => load_step%get_dict('discretization')
171201
loadCases(l)%t = step_discretization%get_asReal('t')
172-
loadCases(l)%N = step_discretization%get_asInt ('N')
202+
loadCases(l)%N = step_discretization%get_asInt('N')
173203

174204
if (load_step%get_asStr('f_out',defaultVal='n/a') == 'none') then
175205
loadCases(l)%f_out = huge(0)
@@ -182,39 +212,59 @@ program DAMASK_mesh
182212

183213
!--------------------------------------------------------------------------------------------------
184214
! loadcase parameters checks and output of load case information
185-
skip_T1 = 4+max(len(PETSC_GENERIC_LABELS), maxval(len_trim(mesh_BCLabels)))+2 ! indentation(4)+length_longest_label+blank
186-
skip_T2 = skip_T1+1+floor(log10(real(maxval(mesh_boundariesIS))))+1+1+1 ! T1+"("+NumDigits(floor()+1)+")"+blank
215+
skip_T1 = 4+max(len(PETSC_GENERIC_LABELS), maxval(len_trim(mesh_bcLabels)))+2 ! indentation(4)+length_longest_label+blank
187216
checkLoadcases: do l = 1, size(load_steps)
188217
if (loadCases(l)%N < 1) &
189-
call IO_error(813_pI16, 'loadcase', l, 'has non-positive number of steps ("N")', emph = [2])
218+
call IO_error(301_pI16, 'loadcase', l, 'has non-positive number of steps ("N")', emph = [2])
190219
if (loadCases(l)%f_out < 1) &
191-
call IO_error(813_pI16, 'loadcase', l, 'has non-positive output frequency ("f_out")', emph = [2])
220+
call IO_error(301_pI16, 'loadcase', l, 'has non-positive output frequency ("f_out")', emph = [2])
192221

193222
print'(/,1x,a,1x,i0)', 'load case:', l
194223
if (.not. loadCases(l)%estimate_rate) print'(2x,a)', 'drop guessing along trajectory'
195224
print'(2x,a)', 'Field '//trim(FIELD_MECH_label)
196225

197226
do boundary = 1_pPETSCINT, mesh_Nboundaries
198227
if (loadCases(l)%mechBC(boundary)%use_label) then
199-
bc_label_name = trim(mesh_BCLabels(boundary))
228+
bc_label = mesh_bcLabels(boundary)
200229
else
201230
m = mesh_boundariesIdx(boundary)
202-
if (dimPlex == 2_pPETSCINT .and. m < 4) m = m + 1
203-
bc_label_name = PETSC_GENERIC_LABELS(m)
231+
if (dimPlex == 2_pPETSCINT .and. m < size(PETSC_GENERIC_LABELS)) m = m + 1 ! adjust for 2D (cells -> faces)
232+
bc_label = PETSC_GENERIC_LABELS(m)
204233
end if
205-
do component = 1_pPETSCINT, dimPlex
206-
if (loadCases(l)%mechBC(boundary)%active(component)) &
207-
print'(4x,a,T'//IO_intAsStr(skip_T1)//',a,i0,a,'// &
208-
'T'//IO_intAsStr(skip_T2)//',a,1x,i1,1x,a,1x,f12.7)', &
209-
trim(bc_label_name), '(', mesh_boundariesIS(boundary), ')', &
210-
'Component', component, &
211-
'Value', loadCases(l)%mechBC(boundary)%dot_u(component)
212-
end do
213-
end do
214234

215-
print'(2x,a,T21,g0.6)', 'time:', loadCases(l)%t
216-
print'(2x,a,T21,i0)', 'increments:', loadCases(l)%N
217-
print'(2x,a,T21,i0)', 'output frequency:', loadCases(l)%f_out
235+
printed_bc_type = .false.
236+
if (count(loadCases(l)%mechBC(boundary)%dot_u_active) > 0) then
237+
if (.not. printed_bc_type) then
238+
print'(3x,a,T'//IO_intAsStr(skip_T1)//',a,i0,a)', &
239+
trim(bc_label), '(', mesh_boundariesIS(boundary),')'
240+
printed_bc_type = .true.
241+
end if
242+
print'(4x,a)', 'Rates of Displacement'
243+
do component = 1_pPETSCINT, dimPlex
244+
if (loadCases(l)%mechBC(boundary)%dot_u_active(component)) &
245+
print'(5x,a,1x,i1,a,1x,en12.3e2,2x,a)', &
246+
'Component', component, ':', &
247+
loadCases(l)%mechBC(boundary)%dot_u(component), 'm/s'
248+
end do
249+
end if
250+
if (count(loadCases(l)%mechBC(boundary)%dot_f_active) > 0) then
251+
if (.not. printed_bc_type) then
252+
print'(3x,a,T'//IO_intAsStr(skip_T1)//',a,i0,a)', &
253+
trim(bc_label), '(', mesh_boundariesIS(boundary), ')'
254+
printed_bc_type = .true.
255+
end if
256+
print'(4x,a)', 'Rates of Force'
257+
do component = 1_pPETSCINT, dimPlex
258+
if (loadCases(l)%mechBC(boundary)%dot_f_active(component)) &
259+
print'(5x,a,1x,i1,a,1x,en12.3e2,2x,a)', &
260+
'Component', component, ':', &
261+
loadCases(l)%mechBC(boundary)%dot_f(component), 'N/s'
262+
end do
263+
end if
264+
end do
265+
print'(2x,a,T19,en12.3e2,2x,a)', 'time:', loadCases(l)%t, 's'
266+
print'(2x,a,T22,i0)', 'increments:', loadCases(l)%N
267+
print'(2x,a,T22,i0)', 'output frequency:', loadCases(l)%f_out
218268
end do checkLoadcases
219269

220270
!--------------------------------------------------------------------------------------------------
@@ -317,10 +367,7 @@ program DAMASK_mesh
317367
call FEM_mechanical_updateCoords()
318368
call materialpoint_result(totalIncsCounter,t)
319369
end if
320-
321-
322370
end do incLooping
323-
324371
end do loadCaseLooping
325372

326373

0 commit comments

Comments
 (0)