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

Go to the source code of this file.

Functions/Subroutines

subroutine shellsections (inpc, textpart, set, istartset, iendset, ialset, nset, ielmat, matname, nmat, ielorien, orname, norien, thicke, kon, ipkon, offset, irstrt, istep, istat, n, iline, ipol, inl, ipoinp, inp, lakon, iaxial, ipoinpc, mi, icomposite, nelcon)
 

Function/Subroutine Documentation

◆ shellsections()

subroutine shellsections ( character*1, dimension(*)  inpc,
character*132, dimension(16)  textpart,
character*81, dimension(*)  set,
integer, dimension(*)  istartset,
integer, dimension(*)  iendset,
integer, dimension(*)  ialset,
integer  nset,
integer, dimension(mi(3),*)  ielmat,
character*80, dimension(*)  matname,
integer  nmat,
integer, dimension(mi(3),*)  ielorien,
character*80, dimension(*)  orname,
integer  norien,
real*8, dimension(mi(3),*)  thicke,
integer, dimension(*)  kon,
integer, dimension(*)  ipkon,
real*8, dimension(2,*)  offset,
integer  irstrt,
integer  istep,
integer  istat,
integer  n,
integer  iline,
integer  ipol,
integer  inl,
integer, dimension(2,*)  ipoinp,
integer, dimension(3,*)  inp,
character*8, dimension(*)  lakon,
integer  iaxial,
integer, dimension(0:*)  ipoinpc,
integer, dimension(*)  mi,
integer  icomposite,
integer, dimension(2,*)  nelcon 
)
23 !
24 ! reading the input deck: *SHELL SECTION
25 !
26  implicit none
27 !
28  logical nodalthickness,composite
29 !
30  character*1 inpc(*)
31  character*8 lakon(*)
32  character*80 matname(*),orname(*),material,orientation
33  character*81 set(*),elset
34  character*132 textpart(16)
35 !
36  integer mi(*),istartset(*),iendset(*),ialset(*),ielmat(mi(3),*),
37  & ielorien(mi(3),*),kon(*),ipkon(*),indexe,irstrt,nset,nmat,
38  & norien,nlayer,iset,icomposite,nelcon(2,*),
39  & istep,istat,n,key,i,j,k,l,imaterial,iorientation,ipos,
40  & iline,ipol,inl,ipoinp(2,*),inp(3,*),iaxial,ipoinpc(0:*)
41 !
42  real*8 thicke(mi(3),*),thickness,offset(2,*),offset1
43 !
44  if((istep.gt.0).and.(irstrt.ge.0)) then
45  write(*,*)
46  & '*ERROR reading *SHELL SECTION: *SHELL SECTION should'
47  write(*,*) ' be placed before all step definitions'
48  call exit(201)
49  endif
50 !
51  nodalthickness=.false.
52  composite=.false.
53  offset1=0.d0
54  material(1:1)=' '
55  orientation(1:1)=' '
56 !
57  do i=2,n
58  if(textpart(i)(1:9).eq.'MATERIAL=') then
59  material=textpart(i)(10:89)
60  elseif(textpart(i)(1:12).eq.'ORIENTATION=') then
61  orientation=textpart(i)(13:92)
62  elseif(textpart(i)(1:6).eq.'ELSET=') then
63  elset=textpart(i)(7:86)
64  elset(81:81)=' '
65  ipos=index(elset,' ')
66  elset(ipos:ipos)='E'
67  elseif(textpart(i)(1:14).eq.'NODALTHICKNESS') then
68  nodalthickness=.true.
69  elseif(textpart(i)(1:7).eq.'OFFSET=') then
70  read(textpart(i)(8:27),'(f20.0)',iostat=istat) offset1
71  if(istat.gt.0) call inputerror(inpc,ipoinpc,iline,
72  &"*SHELL SECTION%")
73  elseif(textpart(i)(1:9).eq.'COMPOSITE') then
74  composite=.true.
75  else
76  write(*,*)
77  & '*WARNING reading *SHELL SECTION: parameter not recognized:'
78  write(*,*) ' ',
79  & textpart(i)(1:index(textpart(i),' ')-1)
80  call inputwarning(inpc,ipoinpc,iline,
81  &"*SHELL SECTION%")
82  endif
83  enddo
84 !
85 ! check for the existence of the material (not for composites)
86 !
87  if(.not.composite) then
88  do i=1,nmat
89  if(matname(i).eq.material) exit
90  enddo
91  if(i.gt.nmat) then
92  write(*,*)
93  & '*ERROR reading *SHELL SECTION: nonexistent material'
94  call inputerror(inpc,ipoinpc,iline,
95  &"*SHELL SECTION%")
96  call exit(201)
97  endif
98  imaterial=i
99  elseif(material(1:1).ne.' ') then
100  write(*,*) '*ERROR reading *SHELL SECTION: COMPOSITE and'
101  write(*,*) ' MATERIAL are mutually exclusive parameters'
102  call exit(201)
103  endif
104 !
105 ! check for the existence of the orientation, if any
106 !
107  if(orientation(1:1).eq.' ') then
108  iorientation=0
109  elseif(nelcon(1,i).eq.2) then
110  write(*,*) '*INFO reading *SOLID SECTION: an orientation'
111  write(*,*) ' is for isotropic materials irrelevant'
112  call inputinfo(inpc,ipoinpc,iline,
113  &"*SOLID SECTION%")
114  iorientation=0
115  else
116  do i=1,norien
117  if(orname(i).eq.orientation) exit
118  enddo
119  if(i.gt.norien) then
120  write(*,*)
121  & '*ERROR reading *SHELL SECTION: nonexistent orientation'
122  call inputerror(inpc,ipoinpc,iline,
123  &"*SHELL SECTION%")
124  call exit(201)
125  endif
126  iorientation=i
127  endif
128 !
129 ! check for the existence of the element set
130 !
131  do i=1,nset
132  if(set(i).eq.elset) exit
133  enddo
134  if(i.gt.nset) then
135  elset(ipos:ipos)=' '
136  write(*,*) '*ERROR reading *SHELL SECTION: element set ',elset
137  write(*,*) ' has not yet been defined. '
138  call inputerror(inpc,ipoinpc,iline,
139  &"*SHELL SECTION%")
140  call exit(201)
141  endif
142  iset=i
143 !
144  call getnewline(inpc,textpart,istat,n,key,iline,ipol,inl,
145  & ipoinp,inp,ipoinpc)
146 !
147 ! assigning a thickness to the elements
148 !
149  if(.not.composite) then
150  if(.not.nodalthickness) then
151  read(textpart(1)(1:20),'(f20.0)',iostat=istat) thickness
152  if(istat.gt.0) then
153  write(*,*)
154  & '*ERROR reading *SHELL SECTION: shell thickness is lacking'
155  call inputerror(inpc,ipoinpc,iline,
156  &"*SHELL SECTION%")
157  endif
158  if(iaxial.eq.180) thickness=thickness/iaxial
159  do j=istartset(iset),iendset(iset)
160  if(ialset(j).gt.0) then
161  if(lakon(ialset(j))(1:1).ne.'S') then
162  write(*,*)
163  & '*ERROR reading *SHELL SECTION: *SHELL SECTION can'
164  write(*,*)
165  & ' only be used for shell elements.'
166  write(*,*) ' Element ',ialset(j),
167  & ' is not a shell element.'
168  call exit(201)
169  endif
170  indexe=ipkon(ialset(j))
171  do l=1,8
172  thicke(1,indexe+l)=thickness
173  enddo
174  ielmat(1,ialset(j))=imaterial
175  ielorien(1,ialset(j))=iorientation
176  offset(1,ialset(j))=offset1
177  else
178  k=ialset(j-2)
179  do
180  k=k-ialset(j)
181  if(k.ge.ialset(j-1)) exit
182  if(lakon(k)(1:1).ne.'S') then
183  write(*,*)
184  & '*ERROR reading *SHELL SECTION: *SHELL SECTION can'
185  write(*,*)
186  & ' only be used for shell elements.'
187  write(*,*) ' Element ',k,
188  & ' is not a shell element.'
189  call exit(201)
190  endif
191  indexe=ipkon(k)
192  do l=1,8
193  thicke(1,indexe+l)=thickness
194  enddo
195  ielmat(1,k)=imaterial
196  ielorien(1,k)=iorientation
197  offset(1,k)=offset1
198  enddo
199  endif
200  enddo
201  call getnewline(inpc,textpart,istat,n,key,iline,ipol,inl,
202  & ipoinp,inp,ipoinpc)
203  endif
204 !
205  else
206  if(nodalthickness) then
207  write(*,*) '*ERROR reading shellsections: for composite'
208  write(*,*) ' materials is the parameter NODAL'
209  write(*,*) ' THICKNESS not allowed'
210  call exit(201)
211  endif
212 !
213 c icomposite=1
214  nlayer=0
215  do
216  read(textpart(1)(1:20),'(f20.0)',iostat=istat) thickness
217  if(istat.gt.0) then
218  write(*,*)
219  & '*ERROR reading *SHELL SECTION: shell thickness is lacking'
220  call inputerror(inpc,ipoinpc,iline,
221  &"*SHELL SECTION%")
222  endif
223  if(iaxial.eq.180) thickness=thickness/iaxial
224 !
225 ! reading the material name
226 !
227  read(textpart(3)(1:80),'(a80)',iostat=istat) material
228  if(istat.gt.0) then
229  write(*,*)
230  & '*ERROR reading *SHELL SECTION: no material defined'
231  call inputerror(inpc,ipoinpc,iline,
232  &"*SHELL SECTION%")
233  endif
234 !
235 ! check for the existence of the material
236 !
237  do i=1,nmat
238  if(matname(i).eq.material) exit
239  enddo
240  if(i.gt.nmat) then
241  write(*,*)
242  & '*ERROR reading *SHELL SECTION: nonexistent material'
243  call inputerror(inpc,ipoinpc,iline,
244  &"*SHELL SECTION%")
245  call exit(201)
246  endif
247  imaterial=i
248 !
249 ! reading the orientation, if any
250 ! if no orientation is specified, the global orientation defined
251 ! by the ORIENTATION parameter, if any, will be used
252 !
253  read(textpart(4)(1:80),'(a80)',iostat=istat) orientation
254 !
255 c if(orientation(1:1).eq.' ') then
256 c iorientation=0
257 c else
258  if(orientation(1:1).ne.' ') then
259  do i=1,norien
260  if(orname(i).eq.orientation) exit
261  enddo
262  if(i.gt.norien) then
263  write(*,*)
264  & '*ERROR reading *SHELL SECTION: nonexistent orientation'
265  write(*,*) ' '
266  call inputerror(inpc,ipoinpc,iline,
267  &"*SHELL SECTION%")
268  call exit(201)
269  endif
270  iorientation=i
271  endif
272 !
273  nlayer=nlayer+1
274 !
275  do j=istartset(iset),iendset(iset)
276  if(ialset(j).gt.0) then
277  if((lakon(ialset(j))(1:3).ne.'S8R').and.
278  & (lakon(ialset(j))(1:2).ne.'S6')) then
279  write(*,*)
280  & '*ERROR reading *SHELL SECTION: *SHELL SECTION'
281  write(*,*)
282  & ' with the option COMPOSITE can'
283  write(*,*)
284  & ' only be used for S8R or S6 shell elements.'
285  write(*,*) ' Element ',ialset(j),
286  & ' is not a S8R nor a S6 shell element.'
287  call exit(201)
288  endif
289  indexe=ipkon(ialset(j))
290  do l=1,8
291  thicke(nlayer,indexe+l)=thickness
292  enddo
293  ielmat(nlayer,ialset(j))=imaterial
294  ielorien(nlayer,ialset(j))=iorientation
295  offset(1,ialset(j))=offset1
296  if(nlayer.gt.1) lakon(ialset(j))(8:8)='C'
297  else
298  k=ialset(j-2)
299  do
300  k=k-ialset(j)
301  if(k.ge.ialset(j-1)) exit
302  if((lakon(k)(1:3).ne.'S8R').and.
303  & (lakon(k)(1:2).ne.'S6')) then
304  write(*,*)
305  & '*ERROR reading *SHELL SECTION: *SHELL SECTION'
306  write(*,*)
307  & ' with the option COMPOSITE can'
308  write(*,*)
309  & ' only be used for S8R or S6 shell elements.'
310  write(*,*) ' Element ',k,
311  & ' is not a S8R nor a S6 shell element.'
312  call exit(201)
313  endif
314  indexe=ipkon(k)
315  do l=1,8
316  thicke(nlayer,indexe+l)=thickness
317  enddo
318  ielmat(nlayer,k)=imaterial
319  ielorien(nlayer,k)=iorientation
320  offset(1,k)=offset1
321  if(nlayer.gt.1) lakon(k)(8:8)='C'
322  enddo
323  endif
324  enddo
325 !
326  call getnewline(inpc,textpart,istat,n,key,iline,ipol,inl,
327  & ipoinp,inp,ipoinpc)
328  if((istat.lt.0).or.(key.eq.1)) then
329  if(nlayer.gt.1) icomposite=1
330  return
331  endif
332  enddo
333  endif
334 !
335  return
subroutine inputwarning(inpc, ipoinpc, iline, text)
Definition: inputwarning.f:20
subroutine inputinfo(inpc, ipoinpc, iline, text)
Definition: inputinfo.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
subroutine thickness(dgdx, nobject, nodedesiboun, ndesiboun, objectset, xo, yo, zo, x, y, z, nx, ny, nz, co, ifree, ndesia, ndesib, iobject, ndesi, dgdxglob, nk)
Definition: thickness.f:22
Hosted by OpenAircraft.com, (Michigan UAV, LLC)