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

Go to the source code of this file.

Functions/Subroutines

subroutine dashpots (inpc, textpart, nelcon, nmat, ntmat_, npmat_, plicon, nplicon, ncmat_, elcon, matname, irstrt, istep, istat, n, iline, ipol, inl, ipoinp, inp, nmat_, set, istartset, iendset, ialset, nset, ielmat, ielorien, ipoinpc, mi)
 

Function/Subroutine Documentation

◆ dashpots()

subroutine dashpots ( character*1, dimension(*)  inpc,
character*132, dimension(16)  textpart,
integer, dimension(2,*)  nelcon,
integer  nmat,
integer  ntmat_,
integer  npmat_,
real*8, dimension(0:2*npmat_,ntmat_,*)  plicon,
integer, dimension(0:ntmat_,*)  nplicon,
integer  ncmat_,
real*8, dimension(0:ncmat_,ntmat_,*)  elcon,
character*80, dimension(*)  matname,
integer  irstrt,
integer  istep,
integer  istat,
integer  n,
integer  iline,
integer  ipol,
integer  inl,
integer, dimension(2,*)  ipoinp,
integer, dimension(3,*)  inp,
integer  nmat_,
character*81, dimension(*)  set,
integer, dimension(*)  istartset,
integer, dimension(*)  iendset,
integer, dimension(*)  ialset,
integer  nset,
integer, dimension(mi(3),*)  ielmat,
integer, dimension(mi(3),*)  ielorien,
integer, dimension(0:*)  ipoinpc,
integer, dimension(*)  mi 
)
24 !
25 ! reading the input deck: *DASHPOT
26 !
27  implicit none
28 !
29  logical frequency
30 !
31  character*1 inpc(*)
32  character*80 matname(*)
33  character*81 set(*),elset
34  character*132 textpart(16)
35 !
36  integer nelcon(2,*),nmat,ntmat_,ntmat,npmat_,npmat,istep,mi(*),
37  & n,key,i,nplicon(0:ntmat_,*),ncmat_,istat,istartset(*),
38  & iendset(*),irstrt,iline,ipol,inl,ipoinp(2,*),inp(3,*),nmat_,
39  & ialset(*),ipos,nset,j,k,ielmat(mi(3),*),ielorien(mi(3),*),
40  & ipoinpc(0:*)
41 !
42  real*8 plicon(0:2*npmat_,ntmat_,*),xfreq,temperature,
43  & elcon(0:ncmat_,ntmat_,*)
44 !
45  frequency=.false.
46 !
47  ntmat=0
48  npmat=0
49 !
50  if((istep.gt.0).and.(irstrt.ge.0)) then
51  write(*,*) '*ERROR reading *DASHPOT: *DASHPOT should be placed'
52  write(*,*) ' before all step definitions'
53  call exit(201)
54  endif
55 !
56  nmat=nmat+1
57  if(nmat.gt.nmat_) then
58  write(*,*) '*ERROR reading *DASHPOT: increase nmat_'
59  call exit(201)
60  endif
61  matname(nmat)(1:7)='DASHPOT'
62  do i=8,80
63  matname(nmat)(i:i)=' '
64  enddo
65 !
66  do i=2,n
67  if(textpart(i)(1:6).eq.'ELSET=') then
68  elset=textpart(i)(7:86)
69  elset(81:81)=' '
70  ipos=index(elset,' ')
71  elset(ipos:ipos)='E'
72  else
73  write(*,*)
74  & '*WARNING reading *DASHPOT: parameter not recognized:'
75  write(*,*) ' ',
76  & textpart(i)(1:index(textpart(i),' ')-1)
77  call inputwarning(inpc,ipoinpc,iline,
78  &"*DASHPOT%")
79  endif
80  enddo
81 !
82 ! check for frequency dependency (for steady state dynamics
83 ! calculations)
84 !
85  call getnewline(inpc,textpart,istat,n,key,iline,ipol,inl,
86  & ipoinp,inp,ipoinpc)
87  if((istat.lt.0).or.(key.eq.1)) return
88  read(textpart(2)(1:20),'(f20.0)',iostat=istat)
89  & xfreq
90  if(istat.gt.0) call inputerror(inpc,ipoinpc,iline,
91  &"*DASHPOT%")
92  if(xfreq.gt.0.d0) frequency=.true.
93  iline=iline-1
94 !
95  if(.not.frequency) then
96  nelcon(1,nmat)=2
97 !
98 ! linear dashpot
99 !
100  do
101  call getnewline(inpc,textpart,istat,n,key,iline,ipol,inl,
102  & ipoinp,inp,ipoinpc)
103  if((istat.lt.0).or.(key.eq.1)) exit
104  ntmat=ntmat+1
105  nelcon(2,nmat)=ntmat
106  if(ntmat.gt.ntmat_) then
107  write(*,*) '*ERROR reading *DASHPOT: increase ntmat_'
108  call exit(201)
109  endif
110  do i=1,2
111  read(textpart(i)(1:20),'(f20.0)',iostat=istat)
112  & elcon(i,ntmat,nmat)
113  if(istat.gt.0) call inputerror(inpc,ipoinpc,iline,
114  &"*DASHPOT%")
115  enddo
116  if(textpart(3)(1:1).ne.' ') then
117  read(textpart(3)(1:20),'(f20.0)',iostat=istat)
118  & elcon(0,ntmat,nmat)
119  if(istat.gt.0) call inputerror(inpc,ipoinpc,iline,
120  &"*DASHPOT%")
121  else
122  elcon(0,ntmat,nmat)=0.d0
123  endif
124  enddo
125  else
126  nelcon(1,nmat)=-51
127 !
128 ! kinematic hardening coefficients
129 !
130  do
131  call getnewline(inpc,textpart,istat,n,key,iline,ipol,inl,
132  & ipoinp,inp,ipoinpc)
133  if((istat.lt.0).or.(key.eq.1)) exit
134  read(textpart(3)(1:20),'(f20.0)',iostat=istat) temperature
135  if(istat.gt.0) call inputerror(inpc,ipoinpc,iline,
136  &"*DASHPOT%")
137 !
138 ! first temperature
139 !
140  if(ntmat.eq.0) then
141  npmat=0
142  ntmat=ntmat+1
143  if(ntmat.gt.ntmat_) then
144  write(*,*) '*ERROR reading *DASHPOT: increase ntmat_'
145  call exit(201)
146  endif
147  nplicon(0,nmat)=ntmat
148  plicon(0,ntmat,nmat)=temperature
149 !
150 ! new temperature
151 !
152  elseif(plicon(0,ntmat,nmat).ne.temperature) then
153  npmat=0
154  ntmat=ntmat+1
155  if(ntmat.gt.ntmat_) then
156  write(*,*) '*ERROR reading *DASHPOT: increase ntmat_'
157  call exit(201)
158  endif
159  nplicon(0,nmat)=ntmat
160  plicon(0,ntmat,nmat)=temperature
161  endif
162  do i=1,2
163  read(textpart(i)(1:20),'(f20.0)',iostat=istat)
164  & plicon(2*npmat+i,ntmat,nmat)
165  if(istat.gt.0) call inputerror(inpc,ipoinpc,iline,
166  &"*DASHPOT%")
167  enddo
168  npmat=npmat+1
169  if(npmat.gt.npmat_) then
170  write(*,*) '*ERROR reading *DASHPOT: increase npmat_'
171  call exit(201)
172  endif
173  nplicon(ntmat,nmat)=npmat
174  enddo
175  endif
176 !
177  if(ntmat.eq.0) then
178  write(*,*)'*ERROR reading *DASHPOT: *DASHPOT card without data'
179  call exit(201)
180  endif
181  do i=1,nset
182  if(set(i).eq.elset) exit
183  enddo
184  if(i.gt.nset) then
185  elset(ipos:ipos)=' '
186  write(*,*) '*ERROR reading *DASHPOT: element set ',elset
187  write(*,*) ' has not yet been defined. '
188  call inputerror(inpc,ipoinpc,iline,
189  &"*DASHPOT%")
190  call exit(201)
191  endif
192 !
193 ! assigning the elements of the set the appropriate material
194 !
195  do j=istartset(i),iendset(i)
196  if(ialset(j).gt.0) then
197  ielmat(1,ialset(j))=nmat
198  ielorien(1,ialset(j))=0
199  else
200  k=ialset(j-2)
201  do
202  k=k-ialset(j)
203  if(k.ge.ialset(j-1)) exit
204  ielmat(1,k)=nmat
205  ielorien(1,k)=0
206  enddo
207  endif
208  enddo
209 !
210  return
subroutine inputwarning(inpc, ipoinpc, iline, text)
Definition: inputwarning.f:20
subroutine getnewline(inpc, textpart, istat, n, key, iline, ipol, inl, ipoinp, inp, ipoinpc)
Definition: getnewline.f:21
subroutine inputerror(inpc, ipoinpc, iline, text)
Definition: inputerror.f:20
Hosted by OpenAircraft.com, (Michigan UAV, LLC)