FrontISTR  5.7.0
Large-scale structural analysis program with finit element method
material.f90
Go to the documentation of this file.
1 !-------------------------------------------------------------------------------
2 ! Copyright (c) 2019 FrontISTR Commons
3 ! This software is released under the MIT License, see LICENSE.txt
4 !-------------------------------------------------------------------------------
6 module mmaterial
7  use hecmw_util
8  use m_table
9  use table_dicts
10  implicit none
11 
12  ! Following algorithm type
13  integer(kind=kint), parameter :: infinitesimal = 0
14  integer(kind=kint), parameter :: totallag = 1
15  integer(kind=kint), parameter :: updatelag = 2
16 
17  ! Following material types. All material type number consists with integer of six digits.
18  ! First digit: Indicates physical type
19  ! 1: mechanical deformation analysis
20  ! 2: heat conduct analysis
21  ! ......
22  ! Second digit:
23  ! Mechanical analysis
24  ! 1: Elastic
25  ! 2: Elastoplastic
26  ! 3: Hyperelastic
27  ! 4: Viscoelastic
28  ! 5: Viscoplastic
29  ! 6: Incomp newtonian
30  ! 7: Connector(Spring, Dashpot, Joint etc.)
31  ! Heat conductiovity
32  ! ......
33  ! Third digit:
34  ! For elastic or elastoplastic deformation, elastic
35  ! 0: isotropic ie. 110000
36  ! 1: with transever anisotropity 111000
37  ! For hyperelastic deformation
38  ! 0: Neo-Hooke 130000
39  ! 1: Mooney-Rivlin 131000
40  ! 2: Arruda-Boyce 132000
41  ! For spring or dashpot, joint etc.
42  ! 0: spring dof ie. 170000
43  ! 1: spring axial 171000
44  ! 2: dashpot dof 172000
45  ! 3: dashpot axial 173000
46  ! Fourth digit
47  ! For spring_d or dashpot_d, joint_d etc.
48  ! k: number of dof param (1st digit)
49  ! Fifth digit:
50  ! For elastoplastic deformation, hardening law
51  ! 0: Linear hardening i.e. 120000
52  ! 1: Multilinear hardening 120010
53  ! 2: Swift
54  ! 3: Ramberg-Osgood
55  ! 4: linear kinematic
56  ! 5: combined (linear kinematic + linear isotropic)
57  ! For spring_d or dashpot_d, joint_d etc.
58  ! k: number of dof param (2nd digit)
59  ! Six digit:
60  ! For visco-elastoplastic deformation, visco law
61  ! 0: Norton i.e. 150000
62  ! 1: Striab 150001
63  integer(kind=kint), parameter :: usermaterial = 100000
64 
65  integer(kind=kint), parameter :: elastic = 110000
66  integer(kind=kint), parameter :: mn_orthoelastic = 111000
67  integer(kind=kint), parameter :: userelastic = 112000
68 
69  integer(kind=kint), parameter :: eplastic = 120000
70 
71  integer(kind=kint), parameter :: neohooke = 130000
72  integer(kind=kint), parameter :: mooneyrivlin = 131000
73  integer(kind=kint), parameter :: arrudaboyce = 132000
74  integer(kind=kint), parameter :: userhyperelastic = 133000
75  integer(kind=kint), parameter :: mooneyrivlin_aniso = 134000
76 
77  integer(kind=kint), parameter :: viscoelastic = 140000
78  integer(kind=kint), parameter :: norton = 150000
79 
80  integer(kind=kint), parameter :: incomp_newtonian = 160000
81  integer(kind=kint), parameter :: connector = 170000
82 
83  ! Following section type
84  integer(kind=kint), parameter :: d3 = -1
85  integer(kind=kint), parameter :: planestress = 1
86  integer(kind=kint), parameter :: planestrain = 0
87  integer(kind=kint), parameter :: axissymetric = 2
88  integer(kind=kint), parameter :: shell = 3
89 
90  ! Material constants are saved in an array of size 100 and their physical meaning
91  ! correspond to their position in the array
92  integer(kind=kint), parameter :: m_youngs = 1
93  integer(kind=kint), parameter :: m_poisson = 2
94  integer(kind=kint), parameter :: m_density = 3
95  integer(kind=kint), parameter :: m_thick = 4
96 
97  ! following plastic constitutive parameter
98  integer(kind=kint), parameter :: m_plconst1 = 5
99  integer(kind=kint), parameter :: m_plconst2 = 6
100  integer(kind=kint), parameter :: m_plconst3 = 7
101  integer(kind=kint), parameter :: m_plconst4 = 8
102  integer(kind=kint), parameter :: m_plconst5 = 9
103  integer(kind=kint), parameter :: m_kinehard = 10
104 
105  integer(kind=kint), parameter :: m_exapnsion = 20
106 
107  integer(kind=kint), parameter :: m_alpha_over_mu = 21
108 
109  integer(kind=kint), parameter :: m_beam_radius = 22
110  integer(kind=kint), parameter :: m_beam_angle1 = 23
111  integer(kind=kint), parameter :: m_beam_angle2 = 24
112  integer(kind=kint), parameter :: m_beam_angle3 = 25
113  integer(kind=kint), parameter :: m_beam_angle4 = 26
114  integer(kind=kint), parameter :: m_beam_angle5 = 27
115  integer(kind=kint), parameter :: m_beam_angle6 = 28
116 
117  integer(kind=kint), parameter :: m_viscocity = 29
118 
119  ! additional plastic constitutive parameter
120  integer(kind=kint), parameter :: m_plconst6 = 30
121  integer(kind=kint), parameter :: m_plconst7 = 31
122  integer(kind=kint), parameter :: m_plconst8 = 32
123  integer(kind=kint), parameter :: m_plconst9 = 33
124  integer(kind=kint), parameter :: m_plconst10 = 34
125 
126  integer(kind=kint), parameter :: m_damping_rm = 35
127  integer(kind=kint), parameter :: m_damping_rk = 36
128 
129  integer(kind=kint), parameter :: m_spring_dof = 0
130  integer(kind=kint), parameter :: m_spring_axial = 1
131  integer(kind=kint), parameter :: m_dashpot_dof = 2
132  integer(kind=kint), parameter :: m_dashpot_axial = 3
133 
134  integer(kind=kint), parameter :: m_spring_d_ndoffset = 0
135  integer(kind=kint), parameter :: m_spring_a_ndoffset = 72
136  integer(kind=kint), parameter :: m_dashpot_d_ndoffset = 73
137  integer(kind=kint), parameter :: m_dashpot_a_ndoffset = 145
138 
139  ! Dictionary constants
140  character(len=DICT_KEY_LENGTH) :: mc_isoelastic= 'ISOELASTIC' ! youngs modulus, poisson's ratio
141  character(len=DICT_KEY_LENGTH) :: mc_orthoelastic= 'ORTHOELASTIC' ! ortho elastic modulus
142  character(len=DICT_KEY_LENGTH) :: mc_yield = 'YIELD' ! plastic strain, yield stress
143  character(len=DICT_KEY_LENGTH) :: mc_themoexp = 'THEMOEXP' ! thermo expansion coefficient
144  character(len=DICT_KEY_LENGTH) :: mc_orthoexp = 'ORTHOEXP' ! thermo expansion coefficient
145  character(len=DICT_KEY_LENGTH) :: mc_viscoelastic = 'VISCOELASTIC' ! Prony coeff only curr.
146  character(len=DICT_KEY_LENGTH) :: mc_norton = 'NORTON' ! NOrton's creep law
147  character(len=DICT_KEY_LENGTH) :: mc_incomp_newtonian = 'INCOMP_FLUID' ! viscocity
148  character(len=DICT_KEY_LENGTH) :: mc_spring= 'SPRING' ! spring
149  character(len=DICT_KEY_LENGTH) :: mc_dashpot= 'DASHPOT' ! dashpot
150 
152  integer(kind=kint) :: ortho
153  real(kind=kreal) :: ee
154  real(kind=kreal) :: pp
155  real(kind=kreal) :: ee2
156  real(kind=kreal) :: g12
157  real(kind=kreal) :: g23
158  real(kind=kreal) :: g31
159  real(kind=kreal) :: angle
160  real(kind=kreal) :: rho
161  real(kind=kreal) :: alpha
162  real(kind=kreal) :: alpha_over_mu
163  real(kind=kreal) :: weight
164  end type tshellmat
165 
168  integer(kind=kint) :: nlgeom_flag
169  integer(kind=kint) :: mtype
170  integer(kind=kint) :: nfstatus
171  character(len=30) :: name
172  real(kind=kreal) :: variables(200)
173  integer(kind=kint) :: variables_i(200)
174  type(tshellmat), pointer :: shell_var(:)
175  integer(kind=kint) :: totallyr
176  integer(kind=kint) :: cdsys_id
177  integer(kind=kint) :: n_table
178  real(kind=kreal), pointer :: table(:)=>null()
179  type(dict_struct), pointer :: dict
180  end type tmaterial
181 
182  type(tmaterial), allocatable :: materials(:)
183 
184 contains
185 
187  subroutine initmaterial( material )
188  type( tmaterial ), intent(inout) :: material
189  material%mtype = -1 ! not defined yet
190  material%nfstatus = 0 ! Default: no status
191  material%nlgeom_flag = infinitesimal ! Default: INFINITESIMAL ANALYSIS
192  material%variables = 0.d0 ! not defined yet
193  material%variables_i = 0 ! not defined yet
194  material%totallyr = 0 ! not defined yet
195 
196  call dict_create( material%dict, 'INIT', dict_null )
197  end subroutine
198 
200  subroutine finalizematerial( material )
201  type( tmaterial ), intent(inout) :: material
202  if( associated(material%table) ) deallocate( material%table )
203  if( associated(material%dict) ) call dict_destroy( material%dict )
204  end subroutine finalizematerial
205 
207  subroutine initializematls( nm )
208  integer, intent(in) :: nm
209  integer :: i
210  if( allocated(materials) ) deallocate( materials )
211  allocate( materials( nm ) )
212  do i=1,nm
213  call initmaterial( materials(i) )
214  enddo
215  end subroutine
216 
218  subroutine finalizematls()
219  integer :: i
220  if( allocated( materials ) ) then
221  do i=1,size(materials)
222  call finalizematerial( materials(i) )
223  enddo
224  deallocate( materials )
225  endif
226  end subroutine
227 
229  subroutine modifymatl( n,m,v)
230  integer, intent(in) :: n
231  integer, intent(in) :: m
232  real(kind=kreal), intent(in) :: v
233 
234  if( n>size(materials) .OR. m>100 ) return
235  materials(n)%variables(m) = v
236  end subroutine
237 
239  subroutine printmaterial( nfile, material )
240  integer, intent(in) :: nfile
241  type( tmaterial ), intent(in) :: material
242  integer :: i, nt
243  write( nfile, *) "Material type:",material%mtype,material%nlgeom_flag
244  do i=1,100
245  if( material%variables(i) /= 0.d0 ) write( nfile, *) i,material%variables(i)
246  enddo
247  if( associated( material%table ) ) then
248  nt = size(material%table)
249  write( nfile,* ) "--table--"
250  do i=1,nt
251  write(nfile,*) i,material%table(i)
252  enddo
253  endif
254  call print_tabledata( material%dict, nfile )
255  end subroutine
256 
258  integer function fetchdigit( npos, cnum )
259  integer, intent(in) :: npos
260  integer, intent(in) :: cnum
261  integer :: i, idum,cdum,dd
262  fetchdigit = -1
263  cdum = cnum
264  if( npos<=0 .or. npos>6) return
265  if( cnum<100000 .or. cnum>999999 ) return
266  dd = 100000
267  do i=1,npos-1
268  idum = cdum/dd
269  cdum = cdum-idum*dd
270  dd = dd/10
271  enddo
272  fetchdigit = cdum/10**(6-npos)
273  end function
274 
276  subroutine setdigit( npos, ival, mtype )
277  integer, intent(in) :: npos
278  integer, intent(in) :: ival
279  integer, intent(inout) :: mtype
280  integer :: i, idum,cdum, cdum1, dd
281  cdum = mtype
282  if( npos<=0 .or. npos>6 ) return
283  if( ival<0 .or. ival>9 ) return
284  dd =100000
285  cdum1 = 0
286  do i=1,npos-1
287  idum = cdum/dd
288  cdum1 = cdum1+ idum*dd
289  cdum = cdum-idum*dd
290  dd=dd/10
291  enddo
292  cdum1 = cdum1 + ival*dd
293  idum = cdum/dd
294  cdum = cdum-idum*dd
295  dd=dd/10
296  do i=npos+1,6
297  idum = cdum/dd
298  cdum1 = cdum1+ idum*dd
299  cdum = cdum-idum*dd
300  dd=dd/10
301  enddo
302  mtype = cdum1
303  end subroutine
304 
306  integer function getelastictype( mtype )
307  integer, intent(in) :: mtype
308  integer :: itype
309  getelastictype = -1
310  itype = fetchdigit( 1, mtype )
311  if( itype/=1 ) return ! not defomration problem
312  itype = fetchdigit( 2, mtype )
313  if( itype/=1 .and. itype/=2 ) return ! not defomration problem
314  getelastictype = fetchdigit( 3, mtype )
315  end function
316 
318  integer function getyieldfunction( mtype )
319  integer, intent(in) :: mtype
320  integer :: itype
321  getyieldfunction = -1
322  itype = fetchdigit( 1, mtype )
323  if( itype/=1 ) return ! not defomration problem
324  itype = fetchdigit( 2, mtype )
325  if( itype/=2 ) return ! not elstoplastic problem
326  getyieldfunction = fetchdigit( 4, mtype )
327  end function
328 
330  integer function gethardentype( mtype )
331  integer, intent(in) :: mtype
332  integer :: itype
333  gethardentype = -1
334  itype = fetchdigit( 1, mtype )
335  if( itype/=1 ) return ! not defomration problem
336  itype = fetchdigit( 2, mtype )
337  if( itype/=2 ) return ! not elstoplastic problem
338  gethardentype = fetchdigit( 5, mtype )
339  end function
340 
342  logical function iskinematicharden( mtype )
343  integer, intent(in) :: mtype
344  integer :: itype
345  iskinematicharden = .false.
346  itype = fetchdigit( 5, mtype )
347  if( itype==4 .or. itype==5 ) iskinematicharden = .true.
348  end function
349 
351  logical function iselastic( mtype )
352  integer, intent(in) :: mtype
353  integer :: itype
354  iselastic = .false.
355  itype = fetchdigit( 2, mtype )
356  if( itype==1 ) iselastic = .true.
357  end function
358 
360  logical function iselastoplastic( mtype )
361  integer, intent(in) :: mtype
362  integer :: itype
363  iselastoplastic = .false.
364  itype = fetchdigit( 2, mtype )
365  if( itype==2 ) iselastoplastic = .true.
366  end function
367 
369  logical function ishyperelastic( mtype )
370  integer, intent(in) :: mtype
371  integer :: itype
372  ishyperelastic = .false.
373  itype = fetchdigit( 2, mtype )
374  if( itype==3 ) ishyperelastic = .true.
375  end function
376 
378  logical function isviscoelastic( mtype )
379  integer, intent(in) :: mtype
380  integer :: itype
381  isviscoelastic = .false.
382  itype = fetchdigit( 2, mtype )
383  if( itype==4 ) isviscoelastic = .true.
384  end function
385 
387  subroutine ep2e( mtype )
388  integer, intent(inout) :: mtype
389  if( .not. iselastoplastic( mtype ) ) return
390  call setdigit( 2, 1, mtype )
391  end subroutine
392 
394  integer function getconnectortype( mtype )
395  integer, intent(in) :: mtype
396  integer :: itype
397  getconnectortype = -1
398  itype = fetchdigit( 1, mtype )
399  if( itype/=1 ) return ! not defomration problem
400  itype = fetchdigit( 2, mtype )
401  if( itype/=7 ) return ! not connector
402  getconnectortype = fetchdigit( 3, mtype )
403  end function
404 
406  integer function getnumofspring_dparam( material )
407  type( tmaterial ), intent(in) :: material
408  getnumofspring_dparam = material%variables_i(m_spring_d_ndoffset+1)
409  end function
410 
412  integer function getnumofspring_aparam( material )
413  type( tmaterial ), intent(in) :: material
414  getnumofspring_aparam = material%variables_i(m_spring_a_ndoffset+1)
415  end function
416 
418  integer function getnumofdashpot_dparam( material )
419  type( tmaterial ), intent(in) :: material
420  getnumofdashpot_dparam = material%variables_i(m_dashpot_d_ndoffset+1)
421  end function
422 
424  integer function getnumofdashpot_aparam( material )
425  type( tmaterial ), intent(in) :: material
426  getnumofdashpot_aparam = material%variables_i(m_dashpot_a_ndoffset+1)
427  end function
428 
429 end module
430 
431 
432 
mmaterial::neohooke
integer(kind=kint), parameter neohooke
Definition: material.f90:71
mmaterial::m_plconst10
integer(kind=kint), parameter m_plconst10
Definition: material.f90:124
mmaterial::m_spring_axial
integer(kind=kint), parameter m_spring_axial
Definition: material.f90:130
mmaterial::m_exapnsion
integer(kind=kint), parameter m_exapnsion
Definition: material.f90:105
mmaterial::infinitesimal
integer(kind=kint), parameter infinitesimal
Definition: material.f90:13
mmaterial::mc_viscoelastic
character(len=dict_key_length) mc_viscoelastic
Definition: material.f90:145
mmaterial::m_dashpot_a_ndoffset
integer(kind=kint), parameter m_dashpot_a_ndoffset
Definition: material.f90:137
mmaterial::mc_yield
character(len=dict_key_length) mc_yield
Definition: material.f90:142
mmaterial::totallag
integer(kind=kint), parameter totallag
Definition: material.f90:14
mmaterial::userhyperelastic
integer(kind=kint), parameter userhyperelastic
Definition: material.f90:74
mmaterial::m_spring_dof
integer(kind=kint), parameter m_spring_dof
Definition: material.f90:129
mmaterial::m_beam_angle1
integer(kind=kint), parameter m_beam_angle1
Definition: material.f90:110
mmaterial::m_density
integer(kind=kint), parameter m_density
Definition: material.f90:94
mmaterial::getnumofspring_aparam
integer function getnumofspring_aparam(material)
Get number of spring_a parameters.
Definition: material.f90:413
mmaterial::mc_isoelastic
character(len=dict_key_length) mc_isoelastic
Definition: material.f90:140
mmaterial::mc_incomp_newtonian
character(len=dict_key_length) mc_incomp_newtonian
Definition: material.f90:147
mmaterial::shell
integer(kind=kint), parameter shell
Definition: material.f90:88
mmaterial::axissymetric
integer(kind=kint), parameter axissymetric
Definition: material.f90:87
mmaterial::getnumofdashpot_aparam
integer function getnumofdashpot_aparam(material)
Get number of dashpot_a parameters.
Definition: material.f90:425
mmaterial::printmaterial
subroutine printmaterial(nfile, material)
Print out the material properties.
Definition: material.f90:240
mmaterial::m_beam_angle4
integer(kind=kint), parameter m_beam_angle4
Definition: material.f90:113
m_table
This module provides data structure table which would be dictionaried afterwards.
Definition: ttable.f90:7
mmaterial::mc_spring
character(len=dict_key_length) mc_spring
Definition: material.f90:148
mmaterial::iskinematicharden
logical function iskinematicharden(mtype)
If it is a kinematic hardening material?
Definition: material.f90:343
mmaterial::initmaterial
subroutine initmaterial(material)
Initializer.
Definition: material.f90:188
mmaterial::eplastic
integer(kind=kint), parameter eplastic
Definition: material.f90:69
mmaterial::mooneyrivlin_aniso
integer(kind=kint), parameter mooneyrivlin_aniso
Definition: material.f90:75
mmaterial::m_plconst2
integer(kind=kint), parameter m_plconst2
Definition: material.f90:99
mmaterial::getelastictype
integer function getelastictype(mtype)
Get elastic type.
Definition: material.f90:307
mmaterial::mc_dashpot
character(len=dict_key_length) mc_dashpot
Definition: material.f90:149
mmaterial::incomp_newtonian
integer(kind=kint), parameter incomp_newtonian
Definition: material.f90:80
mmaterial::m_beam_angle2
integer(kind=kint), parameter m_beam_angle2
Definition: material.f90:111
mmaterial::m_plconst6
integer(kind=kint), parameter m_plconst6
Definition: material.f90:120
mmaterial::m_plconst8
integer(kind=kint), parameter m_plconst8
Definition: material.f90:122
mmaterial::m_youngs
integer(kind=kint), parameter m_youngs
Definition: material.f90:92
mmaterial::m_damping_rm
integer(kind=kint), parameter m_damping_rm
Definition: material.f90:126
mmaterial::m_dashpot_dof
integer(kind=kint), parameter m_dashpot_dof
Definition: material.f90:131
mmaterial::m_poisson
integer(kind=kint), parameter m_poisson
Definition: material.f90:93
mmaterial::m_alpha_over_mu
integer(kind=kint), parameter m_alpha_over_mu
Definition: material.f90:107
mmaterial::m_plconst5
integer(kind=kint), parameter m_plconst5
Definition: material.f90:102
mmaterial::viscoelastic
integer(kind=kint), parameter viscoelastic
Definition: material.f90:77
mmaterial::m_spring_a_ndoffset
integer(kind=kint), parameter m_spring_a_ndoffset
Definition: material.f90:135
mmaterial::usermaterial
integer(kind=kint), parameter usermaterial
Definition: material.f90:63
mmaterial::iselastoplastic
logical function iselastoplastic(mtype)
If it is an elastoplastic material?
Definition: material.f90:361
mmaterial::m_plconst3
integer(kind=kint), parameter m_plconst3
Definition: material.f90:100
mmaterial::finalizematls
subroutine finalizematls()
Finalizer.
Definition: material.f90:219
m_table::dict_null
type(ttable), parameter dict_null
Definition: ttable.f90:30
mmaterial::elastic
integer(kind=kint), parameter elastic
Definition: material.f90:65
hecmw_util
I/O and Utility.
Definition: hecmw_util_f.F90:7
mmaterial::m_plconst7
integer(kind=kint), parameter m_plconst7
Definition: material.f90:121
mmaterial::m_beam_angle6
integer(kind=kint), parameter m_beam_angle6
Definition: material.f90:115
mmaterial::userelastic
integer(kind=kint), parameter userelastic
Definition: material.f90:67
mmaterial::m_kinehard
integer(kind=kint), parameter m_kinehard
Definition: material.f90:103
mmaterial::iselastic
logical function iselastic(mtype)
If it is an elastic material?
Definition: material.f90:352
mmaterial::materials
type(tmaterial), dimension(:), allocatable materials
Definition: material.f90:182
mmaterial::m_dashpot_d_ndoffset
integer(kind=kint), parameter m_dashpot_d_ndoffset
Definition: material.f90:136
mmaterial::mc_orthoelastic
character(len=dict_key_length) mc_orthoelastic
Definition: material.f90:141
mmaterial::d3
integer(kind=kint), parameter d3
Definition: material.f90:84
mmaterial::initializematls
subroutine initializematls(nm)
Initializer.
Definition: material.f90:208
mmaterial::updatelag
integer(kind=kint), parameter updatelag
Definition: material.f90:15
mmaterial::m_thick
integer(kind=kint), parameter m_thick
Definition: material.f90:95
mmaterial::m_beam_angle5
integer(kind=kint), parameter m_beam_angle5
Definition: material.f90:114
mmaterial::modifymatl
subroutine modifymatl(n, m, v)
Set value of variable(m) of material n to v.
Definition: material.f90:230
mmaterial::finalizematerial
subroutine finalizematerial(material)
Finalizer.
Definition: material.f90:201
mmaterial::m_beam_radius
integer(kind=kint), parameter m_beam_radius
Definition: material.f90:109
mmaterial::m_plconst1
integer(kind=kint), parameter m_plconst1
Definition: material.f90:98
mmaterial::mn_orthoelastic
integer(kind=kint), parameter mn_orthoelastic
Definition: material.f90:66
mmaterial::m_dashpot_axial
integer(kind=kint), parameter m_dashpot_axial
Definition: material.f90:132
mmaterial::arrudaboyce
integer(kind=kint), parameter arrudaboyce
Definition: material.f90:73
mmaterial::getconnectortype
integer function getconnectortype(mtype)
Get type of connector.
Definition: material.f90:395
mmaterial::mc_orthoexp
character(len=dict_key_length) mc_orthoexp
Definition: material.f90:144
mmaterial::ep2e
subroutine ep2e(mtype)
Set material type of elastoplastic to elastic.
Definition: material.f90:388
mmaterial::setdigit
subroutine setdigit(npos, ival, mtype)
Modify material type.
Definition: material.f90:277
mmaterial::m_spring_d_ndoffset
integer(kind=kint), parameter m_spring_d_ndoffset
Definition: material.f90:134
mmaterial::getyieldfunction
integer function getyieldfunction(mtype)
Get type of yield function.
Definition: material.f90:319
mmaterial::tmaterial
Structure to manage all material related data.
Definition: material.f90:167
mmaterial::m_plconst4
integer(kind=kint), parameter m_plconst4
Definition: material.f90:101
mmaterial::m_viscocity
integer(kind=kint), parameter m_viscocity
Definition: material.f90:117
mmaterial::m_beam_angle3
integer(kind=kint), parameter m_beam_angle3
Definition: material.f90:112
mmaterial::mc_themoexp
character(len=dict_key_length) mc_themoexp
Definition: material.f90:143
mmaterial::planestrain
integer(kind=kint), parameter planestrain
Definition: material.f90:86
mmaterial::tshellmat
Definition: material.f90:151
mmaterial::getnumofdashpot_dparam
integer function getnumofdashpot_dparam(material)
Get number of dashpot_d parameters.
Definition: material.f90:419
mmaterial::isviscoelastic
logical function isviscoelastic(mtype)
If it is an viscoelastic material?
Definition: material.f90:379
mmaterial::m_plconst9
integer(kind=kint), parameter m_plconst9
Definition: material.f90:123
mmaterial::fetchdigit
integer function fetchdigit(npos, cnum)
Fetch material type.
Definition: material.f90:259
mmaterial::getnumofspring_dparam
integer function getnumofspring_dparam(material)
Get number of spring_d parameters.
Definition: material.f90:407
mmaterial::gethardentype
integer function gethardentype(mtype)
Get type of hardening.
Definition: material.f90:331
mmaterial
This module summarizes all information of material properties.
Definition: material.f90:6
mmaterial::m_damping_rk
integer(kind=kint), parameter m_damping_rk
Definition: material.f90:127
table_dicts
This module provides data structure of dictionaried table list.
Definition: ttable.f90:140
mmaterial::norton
integer(kind=kint), parameter norton
Definition: material.f90:78
mmaterial::planestress
integer(kind=kint), parameter planestress
Definition: material.f90:85
mmaterial::mooneyrivlin
integer(kind=kint), parameter mooneyrivlin
Definition: material.f90:72
table_dicts::print_tabledata
subroutine print_tabledata(dict, fname)
Print our the contents of a dictionary.
Definition: ttable.f90:395
mmaterial::connector
integer(kind=kint), parameter connector
Definition: material.f90:81
mmaterial::ishyperelastic
logical function ishyperelastic(mtype)
If it is a hyperelastic material?
Definition: material.f90:370
mmaterial::mc_norton
character(len=dict_key_length) mc_norton
Definition: material.f90:146