CalculiX  2.13
A Free Software Three-Dimensional Structural Finite Element Program
calcstabletimeinccont.f File Reference

Go to the source code of this file.

Functions/Subroutines

subroutine calcstabletimeinccont (ne, lakon, kon, ipkon, mi, ielmat, elcon, mortar, adb, alpha, nactdof, springarea, ne0, ntmat_, ncmat_, dtcont)
 

Function/Subroutine Documentation

◆ calcstabletimeinccont()

subroutine calcstabletimeinccont ( integer  ne,
character*8, dimension(*)  lakon,
integer, dimension(*)  kon,
integer, dimension(*)  ipkon,
integer, dimension(*)  mi,
integer, dimension(mi(3),*)  ielmat,
real*8, dimension(0:ncmat_,ntmat_,*)  elcon,
integer  mortar,
real*8, dimension(*)  adb,
real*8  alpha,
integer, dimension(0:mi(2),*)  nactdof,
real*8, dimension(2,*)  springarea,
integer  ne0,
integer  ntmat_,
integer  ncmat_,
real*8  dtcont 
)
22 !
23 ! Calculates the critical time increment (CTI) for contact
24 ! spring elements based on the Courant
25 ! Criterion for Explicit Dynamics calculations.
26 !
27  implicit none
28 !
29  character*8 lakon(*),lakonl
30 !
31  integer j,ne,nope,kon(*),ipkon(*),indexe,nelem,
32  & ncmat_,ntmat_,mi(*),ielmat(mi(3),*),imat,mortar,
33  & indexn,nactdof(0:mi(2),*),ne0,nopem
34 !
35  real*8 elcon(0:ncmat_,ntmat_,*),safefac,xk,adb(*),alpha,bet,gam,
36  & critom,damping,springms,springmm,springfac,dtcont,xmacont,
37  & springarea(2,*),areaslav
38 !
39  dtcont=1.d30
40  safefac=0.80d0
41 !
42  xmacont=0.0d0
43 !
44  damping=0
45 !
46  bet=(1.-alpha)*(1.-alpha)/4.
47  gam=0.5-alpha
48 !
49 ! Omega Critical
50 ! Om_cr=dt*freq_max
51 !
52  critom=dsqrt(damping*damping*(1+2*alpha*(1-gam))
53  & *(1+2*alpha*(1-gam))
54  & + 2*(gam+2*alpha*(gam-bet)))
55  critom=0.98*(-damping*(1+2*alpha*(1-gam))+critom)
56  & /(gam+2*alpha*(gam-bet)) !eq 25 miranda
57 !
58 ! ** DO per element
59 !
60  do nelem=ne0+1,ne
61  indexe=ipkon(nelem)
62  lakonl=lakon(nelem)
63  imat=ielmat(1,nelem)
64 !
65  xk=elcon(2,1,imat)
66 !
67  springmm=0.0d0
68  springms=0.0d0
69 !
70  if(mortar.eq.0) then
71 !
72 ! node-to-face
73 !
74 ! nope is the total number of nodes:
75 ! master nodes+1 slave node
76 ! (notice -47 instead of -48)
77 !
78  nope=ichar(lakonl(8:8))-47
79  springfac=1.d0
80 !
81  do indexn=1,nope
82  xmacont=0.0d0
83 !
84  do j=1,3
85  if(nactdof(j,kon(indexe+indexn)).gt.0)then
86  xmacont=max(xmacont,
87  & adb(nactdof(j,kon(indexe+indexn))))
88  endif
89  enddo
90 !
91  if(indexn.eq.nope)then
92  springms=springms+xmacont
93 !
94 ! mean mass at master nodes
95 !
96  springmm=springmm/(nope-1.0d0)
97  else
98  springmm=springmm+xmacont
99  endif
100  enddo
101 !
102  areaslav=springarea(1,kon(indexe+nope+1))
103  xk=xk*areaslav
104 !
105 ! checking whether mass or slave side is constrained
106 !
107  if((springmm.le.0.d0).and.(springms.le.0.d0)) then
108  cycle
109  elseif(springmm.le.0.d0) then
110  springmm=springms
111  elseif(springms.le.0.d0) then
112  springms=springmm
113  endif
114 !
115  elseif(mortar.eq.1) then
116 !
117 ! face-to-face
118 !
119  nopem=ichar(lakonl(8:8))-48
120  springfac=0.1d0
121 !
122  do indexn=1,kon(indexe)
123 !
124  xmacont=0.0d0
125  do j=1,3
126  if(nactdof(j,kon(indexe+indexn)).gt.0)then
127  xmacont=max(xmacont,
128  & adb(nactdof(j,kon(indexe+indexn))))
129  endif
130  enddo
131  if(indexn.gt.nopem)then !slave
132  springms=springms+xmacont
133  else !master
134  springmm=springmm+xmacont
135  endif
136  enddo
137 !
138 ! mean mass at slave and master nodes
139 !
140  springms=springms/(kon(indexe)-nopem)
141  springmm=springmm/nopem
142 !
143  areaslav=springarea(1,kon(1+indexe+kon(indexe)))
144  xk=xk*areaslav
145 !
146 ! checking whether mass or slave side is constrained
147 !
148  if((springmm.le.0.d0).and.(springms.le.0.d0)) then
149  cycle
150  elseif(springmm.le.0.d0) then
151  springmm=springms
152  elseif(springms.le.0.d0) then
153  springms=springmm
154  endif
155  endif
156 !
157 ! linear pressure-overclosure
158 !
159  if(int(elcon(3,1,imat)).eq.2) then
160 !
161  springmm=springmm/2.0d0
162  springms=springms/2.0d0
163 !
164  dtcont =
165  & min(dtcont,
166  & springfac*critom*dsqrt((springmm*springms)/
167  & ((springmm+springms)*xk)))
168 !
169  else
170  write(*,*) '*ERROR in calcstabletimeinccont:'
171  write(*,*) ' in explicit dynamic calculations'
172  write(*,*) ' only linear pressure-overclosure'
173  write(*,*) ' is allowed'
174  call exit(201)
175  endif
176  enddo
177 ! ** ENDDO per element
178 !
179  dtcont=dtcont* safefac
180 !
181  return
#define max(a, b)
Definition: cascade.c:32
#define min(a, b)
Definition: cascade.c:31
Hosted by OpenAircraft.com, (Michigan UAV, LLC)