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 expansions(inpc,textpart,alcon,nalcon,
20     &  alzero,nmat,ntmat_,irstrt,istep,istat,n,iline,ipol,inl,ipoinp,
21     &  inp,ipoinpc,ier)
22!
23!     reading the input deck: *EXPANSION
24!
25      implicit none
26!
27      character*1 inpc(*)
28      character*132 textpart(16)
29!
30      integer nalcon(2,*),nmat,ntmat,ntmat_,istep,istat,n,
31     &  ipoinpc(0:*),ier,
32     &  i,ityp,key,irstrt(*),iline,ipol,inl,ipoinp(2,*),inp(3,*)
33!
34      real*8 alcon(0:6,ntmat_,*),alzero(*)
35!
36      ntmat=0
37      alzero(nmat)=0.d0
38!
39      if((istep.gt.0).and.(irstrt(1).ge.0)) then
40         write(*,*)
41     &       '*ERROR reading *EXPANSION: *EXPANSION should be placed'
42         write(*,*) '  before all step definitions'
43         ier=1
44         return
45      endif
46!
47      if(nmat.eq.0) then
48         write(*,*)
49     &     '*ERROR reading *EXPANSION: *EXPANSION should be preceded'
50         write(*,*) '  by a *MATERIAL card'
51         ier=1
52         return
53      endif
54!
55      ityp=1
56!
57      do i=2,n
58         if(textpart(i)(1:5).eq.'TYPE=') then
59            if(textpart(i)(6:8).eq.'ISO') then
60               ityp=1
61            elseif(textpart(i)(6:10).eq.'ORTHO') then
62               ityp=3
63            elseif(textpart(i)(6:10).eq.'ANISO') then
64               ityp=6
65            endif
66         elseif(textpart(i)(1:5).eq.'ZERO=') then
67            read(textpart(i)(6:25),'(f20.0)',iostat=istat) alzero(nmat)
68            if(istat.gt.0) then
69               call inputerror(inpc,ipoinpc,iline,
70     &              "*EXPANSION%",ier)
71               return
72            endif
73         else
74            write(*,*)
75     &        '*WARNING reading *EXPANSION: parameter not recognized:'
76            write(*,*) '         ',
77     &                 textpart(i)(1:index(textpart(i),' ')-1)
78            call inputwarning(inpc,ipoinpc,iline,
79     &"*EXPANSION%")
80         endif
81      enddo
82!
83      nalcon(1,nmat)=ityp
84!
85      if(ityp.eq.1) then
86         do
87            call getnewline(inpc,textpart,istat,n,key,iline,ipol,inl,
88     &           ipoinp,inp,ipoinpc)
89            if((istat.lt.0).or.(key.eq.1)) return
90            ntmat=ntmat+1
91            nalcon(2,nmat)=ntmat
92            if(ntmat.gt.ntmat_) then
93               write(*,*) '*ERROR reading *EXPANSION: increase ntmat_'
94               ier=1
95               return
96            endif
97            do i=1,1
98               read(textpart(i)(1:20),'(f20.0)',iostat=istat)
99     &                 alcon(i,ntmat,nmat)
100               if(istat.gt.0) then
101                  call inputerror(inpc,ipoinpc,iline,
102     &                 "*EXPANSION%",ier)
103                  return
104               endif
105            enddo
106            read(textpart(2)(1:20),'(f20.0)',iostat=istat)
107     &                 alcon(0,ntmat,nmat)
108            if(istat.gt.0) then
109               call inputerror(inpc,ipoinpc,iline,
110     &              "*EXPANSION%",ier)
111               return
112            endif
113         enddo
114      elseif(ityp.eq.3) then
115         do
116            call getnewline(inpc,textpart,istat,n,key,iline,ipol,inl,
117     &           ipoinp,inp,ipoinpc)
118            if((istat.lt.0).or.(key.eq.1)) return
119            ntmat=ntmat+1
120            nalcon(2,nmat)=ntmat
121            if(ntmat.gt.ntmat_) then
122               write(*,*) '*ERROR reading *EXPANSION: increase ntmat_'
123               ier=1
124               return
125            endif
126            do i=1,3
127               read(textpart(i)(1:20),'(f20.0)',iostat=istat)
128     &                 alcon(i,ntmat,nmat)
129               if(istat.gt.0) then
130                  call inputerror(inpc,ipoinpc,iline,
131     &                 "*EXPANSION%",ier)
132                  return
133               endif
134            enddo
135            read(textpart(4)(1:20),'(f20.0)',iostat=istat)
136     &                   alcon(0,ntmat,nmat)
137            if(istat.gt.0) then
138               call inputerror(inpc,ipoinpc,iline,
139     &              "*EXPANSION%",ier)
140               return
141            endif
142         enddo
143      elseif(ityp.eq.6) then
144         do
145            call getnewline(inpc,textpart,istat,n,key,iline,ipol,inl,
146     &           ipoinp,inp,ipoinpc)
147            if((istat.lt.0).or.(key.eq.1)) return
148            ntmat=ntmat+1
149            nalcon(2,nmat)=ntmat
150            if(ntmat.gt.ntmat_) then
151               write(*,*) '*ERROR reading *EXPANSION: increase ntmat_'
152               ier=1
153               return
154            endif
155            do i=1,6
156               read(textpart(i)(1:20),'(f20.0)',iostat=istat)
157     &                    alcon(i,ntmat,nmat)
158               if(istat.gt.0) then
159                  call inputerror(inpc,ipoinpc,iline,
160     &                 "*EXPANSION%",ier)
161                  return
162               endif
163            enddo
164            read(textpart(7)(1:20),'(f20.0)',iostat=istat)
165     &                alcon(0,ntmat,nmat)
166            if(istat.gt.0) then
167               call inputerror(inpc,ipoinpc,iline,
168     &              "*EXPANSION%",ier)
169               return
170            endif
171         enddo
172      endif
173!
174      return
175      end
176
177