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

Go to the source code of this file.

Functions/Subroutines

subroutine massflows (inpc, textpart, set, istartset, iendset, ialset, nset, nelemload, sideload, xload, nload, nload_, iamload, lakon, ne, istep, istat, n, iline, ipol, inl, ipoinp, inp, ipoinpc, idefload, nam)
 

Function/Subroutine Documentation

◆ massflows()

subroutine massflows ( 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(2,*)  nelemload,
character*20, dimension(*)  sideload,
real*8, dimension(2,*)  xload,
integer  nload,
integer  nload_,
integer, dimension(2,*)  iamload,
character*8, dimension(*)  lakon,
integer  ne,
integer  istep,
integer  istat,
integer  n,
integer  iline,
integer  ipol,
integer  inl,
integer, dimension(2,*)  ipoinp,
integer, dimension(3,*)  inp,
integer, dimension(0:*)  ipoinpc,
integer, dimension(*)  idefload,
integer  nam 
)
23 !
24 ! reading the input deck: *MASS FLOW
25 !
26  implicit none
27 !
28  logical surface
29 !
30  character*1 inpc(*)
31  character*8 lakon(*)
32  character*20 sideload(*),label
33  character*81 set(*),elset
34  character*132 textpart(16)
35 !
36  integer istartset(*),iendset(*),ialset(*),nelemload(2,*),
37  & nset,nload,nload_,istep,istat,n,i,j,l,key,idefload(*),
38  & iamload(2,*),nam,iamplitude,ipos,ne,iline,ipol,inl,ipoinp(2,*),
39  & inp(3,*),idelay,isector,
40  & ipoinpc(0:*)
41 !
42  real*8 xload(2,*),xmagnitude
43 !
44  iamplitude=0
45  idelay=0
46  isector=0
47  surface=.false.
48 !
49  if(istep.ne.1) then
50  write(*,*)
51  & '*ERROR reading *MASS FLOW: *MASS FLOW should only be used'
52  write(*,*) ' in the first STEP'
53  call exit(201)
54  endif
55 !
56  do i=2,n
57  write(*,*)
58  & '*WARNING reading *MASS FLOW: parameter not recognized:'
59  write(*,*) ' ',
60  & textpart(i)(1:index(textpart(i),' ')-1)
61  call inputwarning(inpc,ipoinpc,iline,
62  & "*MASS FLOW%")
63  enddo
64 !
65  do
66  call getnewline(inpc,textpart,istat,n,key,iline,ipol,inl,
67  & ipoinp,inp,ipoinpc)
68  if((istat.lt.0).or.(key.eq.1)) return
69 !
70  read(textpart(2)(1:20),'(a20)',iostat=istat) label
71 !
72  read(textpart(3)(1:20),'(f20.0)',iostat=istat) xmagnitude
73  if(xmagnitude.ne.0.d0) then
74  write(*,*) '*WARNING reading *MASS FLOW:'
75  write(*,*) ' magnitude for label: ',label
76  write(*,*) ' is not zero but'
77  write(*,*) ' takes the value: ',xmagnitude
78  write(*,*) ' it is set to zero'
79  xmagnitude=0.d0
80  endif
81 !
82  if(istat.gt.0) call inputerror(inpc,ipoinpc,iline,
83  &"*MASS FLOW%")
84  if((label(1:2).ne.'M1').and.(label(1:2).ne.'M2').and.
85  & (label(1:2).ne.'M ').and.
86  & (label(1:2).ne.'M3').and.(label(1:2).ne.'M4').and.
87  & (label(1:2).ne.'M5').and.(label(1:2).ne.'M6')) then
88  call inputerror(inpc,ipoinpc,iline,
89  &"*MASS FLOW%")
90  endif
91 !
92  read(textpart(1)(1:10),'(i10)',iostat=istat) l
93  if(istat.eq.0) then
94  if(l.gt.ne) then
95  write(*,*) '*ERROR reading *MASS FLOW: element ',l
96  write(*,*) ' is not defined'
97  call exit(201)
98  endif
99 !
100  if(lakon(l)(1:1).ne.'F') then
101  write(*,*) '*ERROR reading *MASS FLOW: element ',l
102  write(*,*) ' is not a fluid element*'
103  call exit(201)
104  endif
105  call loadadd(l,label,xmagnitude,nelemload,sideload,
106  & xload,nload,nload_,iamload,iamplitude,
107  & nam,isector,idefload)
108  else
109  read(textpart(1)(1:80),'(a80)',iostat=istat) elset
110  elset(81:81)=' '
111  ipos=index(elset,' ')
112  elset(ipos:ipos)='E'
113  do i=1,nset
114  if(set(i).eq.elset) exit
115  enddo
116  if(i.gt.nset) then
117 !
118 ! check for facial surface
119 !
120  surface=.true.
121  elset(ipos:ipos)='T'
122  do i=1,nset
123  if(set(i).eq.elset) exit
124  enddo
125  if(i.gt.nset) then
126  elset(ipos:ipos)=' '
127  write(*,*) '*ERROR reading *MASS FLOW: element set '
128  write(*,*) ' or facial surface ',elset
129  write(*,*) ' has not yet been defined. '
130  call inputerror(inpc,ipoinpc,iline,
131  & "*MASS FLOW%")
132  call exit(201)
133  endif
134  endif
135 !
136  l=ialset(istartset(i))
137  if(.not.surface) then
138  if(lakon(l)(1:1).ne.'F') then
139  write(*,*) '*ERROR reading *MASS FLOW: element ',l
140  write(*,*) ' is not a fluid element*'
141  call exit(201)
142  endif
143  else
144  if(lakon(l/10)(1:1).ne.'F') then
145  write(*,*) '*ERROR reading *MASS FLOW: element ',l/10
146  write(*,*) ' is not a fluid element*'
147  call exit(201)
148  endif
149  endif
150 !
151  do j=istartset(i),iendset(i)
152  if(ialset(j).gt.0) then
153  l=ialset(j)
154  if(surface) then
155  write(label(2:2),'(i1)') l-10*(l/10)
156  l=l/10
157  endif
158  call loadadd(l,label,xmagnitude,nelemload,sideload,
159  & xload,nload,nload_,iamload,iamplitude,
160  & nam,isector,idefload)
161  else
162  l=ialset(j-2)
163  do
164  l=l-ialset(j)
165  if(l.ge.ialset(j-1)) exit
166  call loadadd(l,label,xmagnitude,nelemload,
167  & sideload,xload,nload,nload_,
168  & iamload,iamplitude,nam,isector,idefload)
169  enddo
170  endif
171  enddo
172  endif
173  enddo
174 !
175  return
subroutine inputwarning(inpc, ipoinpc, iline, text)
Definition: inputwarning.f:20
subroutine loadadd(nelement, label, value, nelemload, sideload, xload, nload, nload_, iamload, iamplitude, nam, isector, idefload)
Definition: loadadd.f:21
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)