-
Notifications
You must be signed in to change notification settings - Fork 2
/
Copy pathabaqusUEL_fBrickLam.f
311 lines (252 loc) · 9.55 KB
/
abaqusUEL_fBrickLam.f
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
134
135
136
137
138
139
140
141
142
143
144
145
146
147
148
149
150
151
152
153
154
155
156
157
158
159
160
161
162
163
164
165
166
167
168
169
170
171
172
173
174
175
176
177
178
179
180
181
182
183
184
185
186
187
188
189
190
191
192
193
194
195
196
197
198
199
200
201
202
203
204
205
206
207
208
209
210
211
212
213
214
215
216
217
218
219
220
221
222
223
224
225
226
227
228
229
230
231
232
233
234
235
236
237
238
239
240
241
242
243
244
245
246
247
248
249
250
251
252
253
254
255
256
257
258
259
260
261
262
263
264
265
266
267
268
269
270
271
272
273
274
275
276
277
278
279
280
281
282
283
284
285
286
287
288
289
290
291
292
293
294
295
296
297
298
299
300
301
302
303
304
305
306
307
308
309
310
311
!***************************************!
! Abaqus UEL interface of the FNM !
! !
! !
!***************************************!
!------ include FNM modules --------------------------
include 'globals/parameter_module.f90'
include 'globals/global_clock_module.f90'
include 'globals/global_toolkit_module.f90'
include 'object_materials/lamina_material_module.f90'
include 'object_materials/cohesive_material_module.f90'
include 'object_node/fnode_module.f90'
include 'object_elements/base_elements/brickPly_elem_module.f90'
include 'object_elements/base_elements/wedgePly_elem_module.f90'
include 'object_elements/base_elements/coh8Crack_elem_module.f90'
include 'object_elements/base_elements/coh6Delam_elem_module.f90'
include 'object_elements/base_elements/coh8Delam_elem_module.f90'
include 'object_elements/base_elements/abstPly_elem_module.f90'
include 'object_elements/base_elements/abstDelam_elem_module.f90'
include 'object_elements/fBrickPly_elem_module.f90'
include 'object_elements/fCoh8Delam_subelem_module.f90'
include 'object_elements/fCoh8Delam_elem_module.f90'
include 'object_elements/fBrickLam_elem_module.f90'
include 'datalists/material_list_module.f90'
include 'datalists/node_list_module.f90'
include 'datalists/elem_list_module.f90'
include 'inputs/input_module.f90'
include 'outputs/output_module.f90'
!------------------------------------------------------
!write(msg_file,*) 'reach here'
!---------------------------------------------------------!
! Abaqus user subroutine for I/O to external files
!---------------------------------------------------------!
subroutine uexternaldb(lop,lrestart,time,dtime,kstep,kinc)
use parameter_module, only: DP, DIRLENGTH, MSG_FILE, EXIT_FUNCTION
use global_clock_module, only: GLOBAL_CLOCK, set
use input_module, only: set_fnm_nodes, set_fnm_elems, set_fnm_materials
use output_module, only: outdir, output
implicit none
real(kind=DP), intent(in) :: time(2)
real(kind=DP), intent(in) :: dtime
integer, intent(in) :: lop,lrestart,kstep,kinc
! local variables
character(len=DIRLENGTH) :: workdir
integer :: lenworkdir
integer :: freq
!~integer :: istat
!~character(len=MSGLENGTH) :: emsg
workdir = ''
lenworkdir = 0
freq = 0
!~istat = STAT_SUCCESS
!~emsg = ''
! output frequency x: once every x increments
freq = 1
select case (lop)
! start of the analysis
case (0)
! get output directory (global variable defined in output module)
outdir = ''
call getoutdir(workdir, lenworkdir)
if ( DIRLENGTH < lenworkdir+len('/outputs/') ) then
write(MSG_FILE,*)'increase DIRLENGTH parameter to:',lenworkdir+len('/outputs/')
call EXIT_FUNCTION
end if
outdir = trim(workdir)//'/outputs/'
! initialize global clock and list of nodes, edges, elems and materials
call set(GLOBAL_CLOCK, curr_step=0, curr_inc=0)
call set_fnm_nodes
call set_fnm_elems
call set_fnm_materials
! open a file
open(110, file=trim(outdir)//'record.dat', status="replace", action="write")
write(110,'(1X, a)')'reach mark 1'
close(110)
! start of increment
case (1)
call set(GLOBAL_CLOCK, curr_step=kstep, curr_inc=kinc)
! end of increment
case (2)
! print element outputs after certain increment
if ( kinc==1 .or. mod(kinc,freq)==0 ) then
call output(kstep,kinc,outdir)
!~if(istat == STAT_FAILURE)
!~ write(MSG_FILE,*) emsg
!~ call EXIT_FUNCTION
!~end if
end if
! end of analysis
case (3)
call cleanup_all
end select
end subroutine uexternaldb
!---------------------------------------------------------!
! Abaqus user element subroutine
!---------------------------------------------------------!
subroutine uel(rhs,amatrx,svars,energy,ndofel,nrhs,nsvars, &
& props,nprops,coords,mcrd,nnode,u,du,v,a,jtype,time,dtime, &
& kstep,kinc,jelem,params,ndload,jdltyp,adlmag,predef,npredf, &
& lflags,mlvarx,ddlmag,mdload,pnewdt,jprops,njprop,period)
! load FNM modules
use parameter_module, only: NDIM, DP, ZERO, MSG_FILE, MSGLENGTH, STAT_SUCCESS, &
& STAT_FAILURE, EXIT_FUNCTION
use fnode_module, only: fnode, update
use node_list_module, only: node_list
use elem_list_module, only: elem_list, elem_node_connec, layup
use material_list_module, only: UDSinglePly_material, matrixCrack_material, &
& interface_material
use fBrickLam_elem_module,only: fBrickLam_elem, integrate
use output_module
! use Abaqus default implict type declaration for passed-in variables only
include 'aba_param.inc'
dimension rhs(mlvarx,*),amatrx(ndofel,ndofel),props(*)
dimension svars(*),energy(8),coords(mcrd,nnode),u(ndofel)
dimension du(mlvarx,*),v(ndofel),a(ndofel),time(2),params(*)
dimension jdltyp(mdload,*),adlmag(mdload,*),ddlmag(mdload,*)
dimension predef(2,npredf,nnode),lflags(*),jprops(*)
! all local variables
integer :: istat
character(len=MSGLENGTH):: emsg
character(len=MSGLENGTH):: msgloc
real(DP),allocatable :: Kmat(:,:), Fvec(:)
real(DP) :: uj(NDIM,nnode)
!~type(fBrickLam_elem) :: elem
type(fnode) :: nodes(nnode)
integer :: node_cnc(nnode)
integer :: j
character(len=10) :: cjelem
amatrx = ZERO
rhs(:,1) = ZERO
istat = STAT_SUCCESS
emsg = ''
msgloc = ', abaqusUEL_fBrickLam.f'
uj = ZERO
node_cnc = 0
j = 0
write(cjelem,'(i5)') jelem
!~ ! check input validity during first run
!~ if (kstep == 1 .and. kinc == 1) then
!~ ! check lflag(1)
!~ ! for static analysis, lflag(1)=1, 2
!~ if (.not. (lflags(1)==1 .or. lflags(1)==2)) then
!~ istat = STAT_FAILURE
!~ emsg = 'this uel is only for static analysis'//trim(msgloc)
!~ goto 10
!~ end if
!~ ! check lflag(3)
!~ if (lflags(3) /= 1) then
!~ istat = STAT_FAILURE
!~ emsg = 'this uel is only for normal increment'//trim(msgloc)
!~ goto 10
!~ end if
!~ ! check NRHS
!~ ! for static analysis, nrhs = 1
!~ ! for modified riks static analysis, nrhs = 2
!~ if (nrhs /= 1) then
!~ istat = STAT_FAILURE
!~ emsg = 'this uel is NOT for riks method'//trim(msgloc)
!~ goto 10
!~ end if
!~ ! check mcrd
!~ if (mcrd /= NDIM) then
!~ istat = STAT_FAILURE
!~ emsg = 'uel mcrd does not match param NDIM'//trim(msgloc)
!~ goto 10
!~ end if
!~ ! check nnode
!~ if (nnode /= size(elem_node_connec(:,jelem))) then
!~ istat = STAT_FAILURE
!~ emsg = 'uel nnode does not match elem_node_connec size'//trim(msgloc)
!~ goto 10
!~ end if
!~ ! check ndofel
!~ if (ndofel /= NDIM*nnode) then
!~ istat = STAT_FAILURE
!~ emsg = 'uel ndofel does not match NDIM*NNODE'//trim(msgloc)
!~ goto 10
!~ end if
!~
!~10 if (istat == STAT_FAILURE) then
!~ write(MSG_FILE,*) emsg
!~ call cleanup_all
!~ call EXIT_FUNCTION
!~ end if
!~ end if
! extract the node connec of this elem
node_cnc(:) = elem_node_connec(:,jelem)
! extract passed-in nodal solutions obtained by Abaqus Solver
do j=1, nnode
uj(1:NDIM,j) = u( (j-1)*NDIM+1 : j*NDIM )
end do
! update the nodal solutions to global_node_list
do j=1, nnode
call update(node_list(node_cnc(j)),u=uj(:,j))
end do
! extract nodes and edge status from global node and edge lists
nodes = node_list(node_cnc)
!~! debug, check the input to elem
!~call output(kstep,jelem*1000+kinc,outdir)
! debug
! open a file
open(110, file=trim(outdir)//'record.dat', status="replace", action="write")
write(110,'(1X, a)')'reach mark 2'
close(110)
! integrate this element. elem_list(jelem)
call integrate (elem_list(jelem), nodes, layup, UDSinglePly_material, &
& matrixCrack_material, interface_material, Kmat, Fvec, istat, emsg)
if (istat == STAT_FAILURE) then
emsg = trim(emsg)//trim(msgloc)//trim(cjelem)
write(MSG_FILE,*) emsg
!** debug **
node_list(node_cnc) = nodes
call output(kstep,jelem*10000+kinc,outdir)
!***********
call cleanup (Kmat, Fvec)
call cleanup_all
call EXIT_FUNCTION
end if
! open a file
open(110, file=trim(outdir)//'record.dat', status="replace", action="write")
write(110,'(1X, a)')'reach mark 3'
close(110)
! update to global lists
node_list(node_cnc) = nodes
! open a file
open(110, file=trim(outdir)//'record.dat', status="replace", action="write")
write(110,'(1X, a)')'reach mark 4'
close(110)
! in the end, pass Kmat and Fvec to Abaqus UEL amatrx and rhs
amatrx = Kmat
rhs(:,1) = -Fvec(:)
! clean up memory used in local dynamic arrays
call cleanup (Kmat, Fvec)
return
contains
pure subroutine cleanup (Kmat, Fvec)
real(DP),allocatable, intent(inout) :: Kmat(:,:), Fvec(:)
if(allocated(Kmat)) deallocate(Kmat)
if(allocated(Fvec)) deallocate(Fvec)
end subroutine cleanup
end subroutine uel
!---------------------------------------------------------!
! subroutine to clean up all the datalist
!---------------------------------------------------------!
subroutine cleanup_all()
use material_list_module, only: empty_material_list
use node_list_module, only: empty_node_list
use elem_list_module, only: empty_elem_list
call empty_material_list
call empty_node_list
call empty_elem_list
end subroutine cleanup_all