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 normals(inpc,textpart,iponor,xnor,ixfree,
20     &  ipkon,kon,nk,nk_,ne,lakon,istep,istat,n,iline,ipol,inl,
21     &  ipoinp,inp,ipoinpc,ier)
22!
23!     reading the input deck: *NORMAL
24!
25      implicit none
26!
27      character*1 inpc(*)
28      character*8 lakon(*)
29      character*132 textpart(16)
30!
31      integer iponor(2,*),ixfree,ipkon(*),kon(*),nk,ipoinpc(0:*),
32     &  nk_,ne,istep,istat,n,ielement,node,j,indexe,i,ier,
33     &  key,iline,ipol,inl,ipoinp(2,*),inp(3,*)
34!
35      real*8 xnor(*),x,y,z,dd
36!
37      if(istep.gt.0) then
38         write(*,*) '*ERROR reading *NORMAL: *NORMAL should be placed'
39         write(*,*) '  before all step definitions'
40         ier=1
41         return
42      endif
43!
44      do i=2,n
45         write(*,*)
46     &        '*WARNING reading *NORMAL: parameter not recognized:'
47         write(*,*) '         ',
48     &        textpart(i)(1:index(textpart(i),' ')-1)
49         call inputwarning(inpc,ipoinpc,iline,
50     &"*NORMAL%")
51      enddo
52!
53      loop:do
54      call getnewline(inpc,textpart,istat,n,key,iline,ipol,inl,
55     &     ipoinp,inp,ipoinpc)
56         if((istat.lt.0).or.(key.eq.1)) exit
57!
58         read(textpart(1)(1:10),'(i10)',iostat=istat) ielement
59         if(istat.gt.0) then
60            call inputerror(inpc,ipoinpc,iline,
61     &           "*NORMAL%",ier)
62            return
63         endif
64         read(textpart(2)(1:10),'(i10)',iostat=istat) node
65         if(istat.gt.0) then
66            call inputerror(inpc,ipoinpc,iline,
67     &           "*NORMAL%",ier)
68            return
69         endif
70         read(textpart(3)(1:20),'(f20.0)',iostat=istat) x
71         if(istat.gt.0) then
72            call inputerror(inpc,ipoinpc,iline,
73     &           "*NORMAL%",ier)
74            return
75         endif
76         if(n.le.3) then
77            y=0.d0
78         else
79            read(textpart(4)(1:20),'(f20.0)',iostat=istat) y
80            if(istat.gt.0) then
81               call inputerror(inpc,ipoinpc,iline,
82     &              "*NORMAL%",ier)
83               return
84            endif
85         endif
86         if(n.le.4) then
87            z=0.d0
88         else
89            read(textpart(5)(1:20),'(f20.0)',iostat=istat) z
90            if(istat.gt.0) then
91               call inputerror(inpc,ipoinpc,iline,
92     &              "*NORMAL%",ier)
93               return
94            endif
95         endif
96!
97!        normalizing the normal
98!
99         dd=dsqrt(x*x+y*y+z*z)
100         x=x/dd
101         y=y/dd
102         z=z/dd
103!
104         if(ielement.gt.ne) then
105            write(*,*) '*ERROR reading *NORMAL: element number',ielement
106            write(*,*) '       exceeds ne'
107            ier=1
108            return
109         endif
110!
111         indexe=ipkon(ielement)
112         do j=1,8
113            if(kon(indexe+j).eq.node) then
114               iponor(1,indexe+j)=ixfree
115               if(lakon(ielement)(1:1).eq.'B') then
116                  xnor(ixfree+4)=x
117                  xnor(ixfree+5)=y
118                  xnor(ixfree+6)=z
119                  ixfree=ixfree+6
120               elseif(lakon(ielement)(1:2).ne.'C3') then
121                  xnor(ixfree+1)=x
122                  xnor(ixfree+2)=y
123                  xnor(ixfree+3)=z
124                  ixfree=ixfree+3
125               else
126                  write(*,*)
127     &               '*WARNING reading *NORMAL: specifying a normal'
128                  write(*,*) '         3-D element does not make sense'
129               endif
130               cycle loop
131            endif
132         enddo
133         write(*,*) '*WARNING: node ',node,' does not belong to'
134         write(*,*) '          element ',ielement
135         write(*,*) '          normal definition discarded'
136!
137      enddo loop
138!
139      return
140      end
141
142
143
144
145
146
147
148
149
150
151