1!
2!     CalculiX - A 3-dimensional finite element program
3!     Copyright (C) 1998-2021 Guido Dhondt
4!
5!     This program is free software; you can redistribute it and/or
6!     modify it under the terms of the GNU General Public License as
7!     published by the Free Software Foundation(version 2);
8!
9!
10!     This program is distributed in the hope that it will be useful,
11!     but WITHOUT ANY WARRANTY; without even the implied warranty of
12!     MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
13!     GNU General Public License for more details.
14!
15!     You should have received a copy of the GNU General Public License
16!     along with this program; if not, write to the Free Software
17!     Foundation, Inc., 675 Mass Ave, Cambridge, MA 02139, USA.
18!
19      subroutine shellsections(inpc,textpart,set,istartset,iendset,
20     &     ialset,nset,ielmat,matname,nmat,ielorien,orname,norien,
21     &     thicke,kon,ipkon,offset,irstrt,istep,istat,n,iline,ipol,
22     &     inl,ipoinp,inp,lakon,iaxial,ipoinpc,mi,icomposite,nelcon,ier)
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,*),ier,numnod,id,
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(1).ge.0)) then
45        write(*,*)
46     &       '*ERROR reading *SHELL SECTION: *SHELL SECTION should'
47        write(*,*) '  be placed before all step definitions'
48        ier=1
49        return
50      endif
51!
52      nodalthickness=.false.
53      composite=.false.
54      offset1=0.d0
55      material(1:1)=' '
56      orientation(1:1)=' '
57!
58      do i=2,n
59        if(textpart(i)(1:9).eq.'MATERIAL=') then
60          material=textpart(i)(10:89)
61        elseif(textpart(i)(1:12).eq.'ORIENTATION=') then
62          orientation=textpart(i)(13:92)
63        elseif(textpart(i)(1:6).eq.'ELSET=') then
64          elset=textpart(i)(7:86)
65          elset(81:81)=' '
66          ipos=index(elset,' ')
67          elset(ipos:ipos)='E'
68        elseif(textpart(i)(1:14).eq.'NODALTHICKNESS') then
69          nodalthickness=.true.
70        elseif(textpart(i)(1:7).eq.'OFFSET=') then
71          read(textpart(i)(8:27),'(f20.0)',iostat=istat) offset1
72          if(istat.gt.0) then
73            call inputerror(inpc,ipoinpc,iline,
74     &           "*SHELL SECTION%",ier)
75            return
76          endif
77        elseif(textpart(i)(1:9).eq.'COMPOSITE') then
78          composite=.true.
79        else
80          write(*,*)
81     &     '*WARNING reading *SHELL SECTION: parameter not recognized:'
82          write(*,*) '         ',
83     &         textpart(i)(1:index(textpart(i),' ')-1)
84          call inputwarning(inpc,ipoinpc,iline,
85     &         "*SHELL SECTION%")
86        endif
87      enddo
88!
89!     check for the existence of the material (not for composites)
90!
91      if(.not.composite) then
92        do i=1,nmat
93          if(matname(i).eq.material) exit
94        enddo
95        if(i.gt.nmat) then
96          write(*,*)
97     &         '*ERROR reading *SHELL SECTION: nonexistent material'
98          call inputerror(inpc,ipoinpc,iline,
99     &         "*SHELL SECTION%",ier)
100          return
101        endif
102        imaterial=i
103      elseif(material(1:1).ne.' ') then
104        write(*,*) '*ERROR reading *SHELL SECTION: COMPOSITE and'
105        write(*,*) '       MATERIAL are mutually exclusive parameters'
106        ier=1
107        return
108      endif
109!
110!     check for the existence of the orientation, if any
111!
112      if(orientation(1:1).eq.' ') then
113        iorientation=0
114      else
115        do i=1,norien
116          if(orname(i).eq.orientation) exit
117        enddo
118        if(i.gt.norien) then
119          write(*,*)
120     &         '*ERROR reading *SHELL SECTION: nonexistent orientation'
121          call inputerror(inpc,ipoinpc,iline,
122     &         "*SHELL SECTION%",ier)
123          return
124        endif
125        iorientation=i
126      endif
127!
128!     check for the existence of the element set
129!
130c      do i=1,nset
131c        if(set(i).eq.elset) exit
132c      enddo
133      call cident81(set,elset,nset,id)
134      i=nset+1
135      if(id.gt.0) then
136        if(elset.eq.set(id)) then
137          i=id
138        endif
139      endif
140      if(i.gt.nset) then
141        elset(ipos:ipos)=' '
142        write(*,*) '*ERROR reading *SHELL SECTION: element set ',elset
143        write(*,*) '       has not yet been defined. '
144        call inputerror(inpc,ipoinpc,iline,
145     &       "*SHELL SECTION%",ier)
146        return
147      endif
148      iset=i
149!
150c     if(.not.nodalthickness) then
151      call getnewline(inpc,textpart,istat,n,key,iline,ipol,inl,
152     &     ipoinp,inp,ipoinpc)
153c     endif
154!
155!     assigning a thickness to the elements
156!
157      if(.not.composite) then
158        if(.not.nodalthickness) then
159          read(textpart(1)(1:20),'(f20.0)',iostat=istat) thickness
160          if(istat.gt.0) then
161            write(*,*)
162     &       '*ERROR reading *SHELL SECTION: shell thickness is lacking'
163            call inputerror(inpc,ipoinpc,iline,
164     &           "*SHELL SECTION%",ier)
165            return
166          endif
167          if(thickness.le.0.d0) then
168            write(*,*)
169     &       '*ERROR reading *SHELL SECTION: shell thickness is zero'
170            write(*,*) '       or negative'
171            call inputerror(inpc,ipoinpc,iline,
172     &           "*SHELL SECTION%",ier)
173          endif
174          if(iaxial.eq.180) thickness=thickness/iaxial
175        else
176!
177!     for those elements for which nodal thickness is activated
178!     the thickness is set to -1.d0
179!
180          thickness=-1.d0
181        endif
182        do j=istartset(iset),iendset(iset)
183          if(ialset(j).gt.0) then
184            if((lakon(ialset(j))(1:1).ne.'S').and.
185     &         (lakon(ialset(j))(1:1).ne.'U')) then
186              write(*,*)
187     &             '*ERROR reading *SHELL SECTION: *SHELL SECTION can'
188              write(*,*)
189     &             '       only be used for shell or user elements.'
190              write(*,*) '       Element ',ialset(j),
191     &             ' is not a shell nor a user element.'
192              ier=1
193              return
194            endif
195            indexe=ipkon(ialset(j))
196            if(lakon(ialset(j))(1:1).eq.'S') then
197              read(lakon(ialset(j))(2:2),'(i1)') numnod
198              do l=1,numnod
199                thicke(1,indexe+l)=thickness
200              enddo
201              offset(1,ialset(j))=offset1
202           else
203              numnod=ichar(lakon(ialset(j))(8:8))
204            endif
205c            do l=1,numnod
206c              thicke(1,indexe+l)=thickness
207c            enddo
208            ielmat(1,ialset(j))=imaterial
209            ielorien(1,ialset(j))=iorientation
210c            offset(1,ialset(j))=offset1
211          else
212            k=ialset(j-2)
213            do
214              k=k-ialset(j)
215              if(k.ge.ialset(j-1)) exit
216              if((lakon(k)(1:1).ne.'S').and.
217     &           (lakon(k)(1:1).ne.'U')) then
218                write(*,*)
219     &               '*ERROR reading *SHELL SECTION: *SHELL SECTION can'
220                write(*,*)
221     &               '       only be used for shell or user elements.'
222                write(*,*) '       Element ',k,
223     &               ' is not a shell nor a user element.'
224                ier=1
225                return
226              endif
227              indexe=ipkon(k)
228              if(lakon(k)(1:1).eq.'S') then
229                read(lakon(k)(2:2),'(i1)') numnod
230                do l=1,numnod
231                  thicke(1,indexe+l)=thickness
232                enddo
233                offset(1,k)=offset1
234              else
235                numnod=ichar(lakon(ialset(j))(8:8))
236              endif
237c              do l=1,numnod
238c                thicke(1,indexe+l)=thickness
239c              enddo
240              ielmat(1,k)=imaterial
241              ielorien(1,k)=iorientation
242c              offset(1,k)=offset1
243            enddo
244          endif
245        enddo
246        call getnewline(inpc,textpart,istat,n,key,iline,ipol,inl,
247     &       ipoinp,inp,ipoinpc)
248!
249      else
250        if(nodalthickness) then
251          write(*,*) '*ERROR reading shellsections: for composite'
252          write(*,*) '       materials is the parameter NODAL'
253          write(*,*) '       THICKNESS not allowed'
254          ier=1
255          return
256        endif
257!
258        nlayer=0
259        do
260          read(textpart(1)(1:20),'(f20.0)',iostat=istat) thickness
261          if(istat.gt.0) then
262            write(*,*)
263     &       '*ERROR reading *SHELL SECTION: shell thickness is lacking'
264            call inputerror(inpc,ipoinpc,iline,
265     &           "*SHELL SECTION%",ier)
266            return
267          endif
268          if(iaxial.eq.180) thickness=thickness/iaxial
269!
270!     reading the material name
271!
272          read(textpart(3)(1:80),'(a80)',iostat=istat) material
273          if(istat.gt.0) then
274            write(*,*)
275     &           '*ERROR reading *SHELL SECTION: no material defined'
276            call inputerror(inpc,ipoinpc,iline,
277     &           "*SHELL SECTION%",ier)
278            return
279          endif
280!
281!     check for the existence of the material
282!
283          do i=1,nmat
284            if(matname(i).eq.material) exit
285          enddo
286          if(i.gt.nmat) then
287            write(*,*)
288     &           '*ERROR reading *SHELL SECTION: nonexistent material'
289            call inputerror(inpc,ipoinpc,iline,
290     &           "*SHELL SECTION%",ier)
291            return
292          endif
293          imaterial=i
294!
295!     reading the orientation, if any
296!     if no orientation is specified, the global orientation defined
297!     by the ORIENTATION parameter, if any, will be used
298!
299          read(textpart(4)(1:80),'(a80)',iostat=istat) orientation
300!
301          if(orientation(1:1).ne.' ') then
302            do i=1,norien
303              if(orname(i).eq.orientation) exit
304            enddo
305            if(i.gt.norien) then
306              write(*,*)
307     &         '*ERROR reading *SHELL SECTION: nonexistent orientation'
308              write(*,*) '  '
309              call inputerror(inpc,ipoinpc,iline,
310     &             "*SHELL SECTION%",ier)
311              return
312            endif
313            iorientation=i
314          endif
315!
316          nlayer=nlayer+1
317!
318          do j=istartset(iset),iendset(iset)
319            if(ialset(j).gt.0) then
320              if((lakon(ialset(j))(1:3).ne.'S8R').and.
321     &             (lakon(ialset(j))(1:2).ne.'S6')) then
322                write(*,*)
323     &               '*ERROR reading *SHELL SECTION: *SHELL SECTION'
324                write(*,*)
325     &               '       with the option COMPOSITE can'
326                write(*,*)
327     &               '       only be used for S8R or S6 shell elements.'
328                write(*,*) '       Element ',ialset(j),
329     &               ' is not a S8R nor a S6 shell element.'
330                ier=1
331                return
332              endif
333              indexe=ipkon(ialset(j))
334              read(lakon(ialset(j))(2:2),'(i1)') numnod
335              do l=1,numnod
336                thicke(nlayer,indexe+l)=thickness
337              enddo
338              ielmat(nlayer,ialset(j))=imaterial
339              ielorien(nlayer,ialset(j))=iorientation
340              offset(1,ialset(j))=offset1
341              if(nlayer.gt.1) lakon(ialset(j))(8:8)='C'
342            else
343              k=ialset(j-2)
344              do
345                k=k-ialset(j)
346                if(k.ge.ialset(j-1)) exit
347                if((lakon(k)(1:3).ne.'S8R').and.
348     &               (lakon(k)(1:2).ne.'S6')) then
349                  write(*,*)
350     &                 '*ERROR reading *SHELL SECTION: *SHELL SECTION'
351                  write(*,*)
352     &                 '    with the option COMPOSITE can'
353                  write(*,*)
354     &              '       only be used for S8R or S6 shell elements.'
355                  write(*,*) '       Element ',k,
356     &                 ' is not a S8R nor a S6 shell element.'
357                  ier=1
358                  return
359                endif
360                indexe=ipkon(k)
361                read(lakon(k)(2:2),'(i1)') numnod
362                do l=1,numnod
363                  thicke(nlayer,indexe+l)=thickness
364                enddo
365                ielmat(nlayer,k)=imaterial
366                ielorien(nlayer,k)=iorientation
367                offset(1,k)=offset1
368                if(nlayer.gt.1) lakon(k)(8:8)='C'
369              enddo
370            endif
371          enddo
372!
373          call getnewline(inpc,textpart,istat,n,key,iline,ipol,inl,
374     &         ipoinp,inp,ipoinpc)
375          if((istat.lt.0).or.(key.eq.1)) then
376            if(nlayer.gt.1) icomposite=1
377            return
378          endif
379        enddo
380      endif
381!
382      return
383      end
384
385