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

Go to the source code of this file.

Functions/Subroutines

subroutine steadystatedynamicss (inpc, textpart, nmethod, iexpl, istep, istat, n, iline, ipol, inl, ipoinp, inp, iperturb, isolver, xmodal, cs, mcs, ipoinpc, nforc, nload, nbody, iprestr, t0, t1, ithermal, nk, set, nset, cyclicsymmetry)
 

Function/Subroutine Documentation

◆ steadystatedynamicss()

subroutine steadystatedynamicss ( character*1, dimension(*)  inpc,
character*132, dimension(16)  textpart,
integer  nmethod,
integer  iexpl,
integer  istep,
integer  istat,
integer  n,
integer  iline,
integer  ipol,
integer  inl,
integer, dimension(2,*)  ipoinp,
integer, dimension(3,*)  inp,
integer, dimension(2)  iperturb,
integer  isolver,
real*8, dimension(*)  xmodal,
real*8, dimension(17,*)  cs,
integer  mcs,
integer, dimension(0:*)  ipoinpc,
integer  nforc,
integer  nload,
integer  nbody,
integer  iprestr,
real*8, dimension(*)  t0,
real*8, dimension(*)  t1,
integer  ithermal,
integer  nk,
character*81, dimension(*)  set,
integer  nset,
integer  cyclicsymmetry 
)
23 !
24 ! reading the input deck: *STEADY STATE DYNAMICS
25 !
26  implicit none
27 !
28  logical nodalset
29 !
30  character*1 inpc(*)
31  character*3 harmonic
32  character*20 solver
33  character*81 set(*),noset
34  character*132 textpart(16)
35 !
36  integer nmethod,istep,istat,n,key,iexpl,iline,ipol,inl,nset,
37  & ipoinp(2,*),inp(3,*),iperturb(2),isolver,i,ndata,nfour,mcs,
38  & ipoinpc(0:*),nforc,nload,nbody,iprestr,ithermal,j,nk,ipos,
39  & cyclicsymmetry
40 !
41  real*8 fmin,fmax,bias,tmin,tmax,xmodal(*),cs(17,*),t0(*),t1(*)
42 !
43  iexpl=0
44  iperturb(1)=0
45  iperturb(2)=0
46  harmonic='YES'
47  if((mcs.ne.0).and.(cs(2,1).ge.0.d0)) then
48  cyclicsymmetry=1
49  endif
50  nodalset=.false.
51 !
52  if(istep.lt.1) then
53  write(*,*) '*ERROR in steadystatedynamics: *STEADY STATE DYNAMI
54  &CS'
55  write(*,*) ' can only be used within a STEP'
56  call exit(201)
57  endif
58 !
59 ! default solver
60 !
61  solver=' '
62  if(isolver.eq.0) then
63  solver(1:7)='SPOOLES'
64  elseif(isolver.eq.2) then
65  solver(1:16)='ITERATIVESCALING'
66  elseif(isolver.eq.3) then
67  solver(1:17)='ITERATIVECHOLESKY'
68  elseif(isolver.eq.4) then
69  solver(1:3)='SGI'
70  elseif(isolver.eq.5) then
71  solver(1:5)='TAUCS'
72  elseif(isolver.eq.7) then
73  solver(1:7)='PARDISO'
74  endif
75 !
76  do i=2,n
77  if(textpart(i)(1:7).eq.'SOLVER=') then
78  read(textpart(i)(8:27),'(a20)') solver
79  elseif(textpart(i)(1:9).eq.'HARMONIC=') then
80  read(textpart(i)(10:12),'(a3)') harmonic
81  else
82  write(*,*)
83  & '*WARNING in steadystatedynamics: parameter not recognized:'
84  write(*,*) ' ',
85  & textpart(i)(1:index(textpart(i),' ')-1)
86  call inputwarning(inpc,ipoinpc,iline,
87  &"*STEADY STATE DYNAMICS%")
88  endif
89  enddo
90 !
91  if(solver(1:7).eq.'SPOOLES') then
92  isolver=0
93  elseif(solver(1:16).eq.'ITERATIVESCALING') then
94  write(*,*) '*WARNING in steadystatedynamics: the iterative scal
95  &ing'
96  write(*,*) ' procedure is not available for modal'
97  write(*,*) ' dynamic calculations; the default solver'
98  write(*,*) ' is used'
99  elseif(solver(1:17).eq.'ITERATIVECHOLESKY') then
100  write(*,*) '*WARNING in steadystatedynamics: the iterative scal
101  &ing'
102  write(*,*) ' procedure is not available for modal'
103  write(*,*) ' dynamic calculations; the default solver'
104  write(*,*) ' is used'
105  elseif(solver(1:3).eq.'SGI') then
106  isolver=4
107  elseif(solver(1:5).eq.'TAUCS') then
108  isolver=5
109  elseif(solver(1:7).eq.'PARDISO') then
110  isolver=7
111  else
112  write(*,*) '*WARNING in steadystatedynamics: unknown solver;'
113  write(*,*) ' the default solver is used'
114  endif
115 !
116  if((isolver.eq.2).or.(isolver.eq.3)) then
117  write(*,*) '*ERROR in steadystatedynamics: the default solver '
118  & ,solver
119  write(*,*) ' cannot be used for modal dynamic'
120  write(*,*) ' calculations '
121  call exit(201)
122  endif
123 !
124  call getnewline(inpc,textpart,istat,n,key,iline,ipol,inl,
125  & ipoinp,inp,ipoinpc)
126  if((istat.lt.0).or.(key.eq.1)) then
127  write(*,*) '*ERROR in steadystatedynamics: definition not compl
128  &ete'
129  write(*,*) ' '
130  call inputerror(inpc,ipoinpc,iline,
131  &"*STEADY STATE DYNAMICS%")
132  call exit(201)
133  endif
134  read(textpart(1)(1:20),'(f20.0)',iostat=istat) fmin
135  if(istat.gt.0) call inputerror(inpc,ipoinpc,iline,
136  &"*STEADY STATE DYNAMICS%")
137  xmodal(3)=fmin
138  read(textpart(2)(1:20),'(f20.0)',iostat=istat) fmax
139  if(istat.gt.0) call inputerror(inpc,ipoinpc,iline,
140  &"*STEADY STATE DYNAMICS%")
141  xmodal(4)=fmax
142  read(textpart(3)(1:20),'(i10)',iostat=istat) ndata
143  if(istat.gt.0) call inputerror(inpc,ipoinpc,iline,
144  &"*STEADY STATE DYNAMICS%")
145  if(ndata.lt.2) ndata=20
146  xmodal(5)=ndata+0.5
147  read(textpart(4)(1:20),'(f20.0)',iostat=istat) bias
148  if(istat.gt.0) call inputerror(inpc,ipoinpc,iline,
149  &"*STEADY STATE DYNAMICS%")
150  if(bias.lt.1.) bias=3.
151  xmodal(6)=bias
152 !
153  if(harmonic.eq.'YES') then
154  xmodal(7)=-0.5
155  else
156  read(textpart(5)(1:10),'(i10)',iostat=istat) nfour
157  if(istat.gt.0) call inputerror(inpc,ipoinpc,iline,
158  &"*STEADY STATE DYNAMICS%")
159  if(nfour.le.0) nfour=20
160  if(n.ge.6) then
161  read(textpart(6)(1:20),'(f20.0)',iostat=istat) tmin
162  if(istat.gt.0) call inputerror(inpc,ipoinpc,iline,
163  &"*STEADY STATE DYNAMICS%")
164  else
165  tmin=0.d0
166  endif
167  if(n.ge.7) then
168  read(textpart(7)(1:20),'(f20.0)',iostat=istat) tmax
169  if(istat.gt.0) call inputerror(inpc,ipoinpc,iline,
170  &"*STEADY STATE DYNAMICS%")
171  else
172  tmax=1.d0
173  endif
174  xmodal(7)=nfour+0.5
175  xmodal(8)=tmin
176  xmodal(9)=tmax
177  endif
178 !
179 ! removing the present loading
180 !
181  nforc=0
182  nload=0
183  nbody=0
184  iprestr=0
185  if((ithermal.eq.1).or.(ithermal.eq.3)) then
186  do j=1,nk
187  t1(j)=t0(j)
188  enddo
189  endif
190 !
191  nmethod=5
192 !
193 ! correction for cyclic symmetric structures:
194 ! if the present step was not preceded by a frequency step
195 ! no nodal diameter has been selected. To make sure that
196 ! mastructcs is called instead of mastruct a fictitious
197 ! minimum nodal diameter is stored
198 !
199  if((cyclicsymmetry.eq.1).and.(mcs.ne.0).and.(cs(2,1)<0.d0))
200  & cs(2,1)=0.d0
201 !
202  call getnewline(inpc,textpart,istat,n,key,iline,ipol,inl,
203  & ipoinp,inp,ipoinpc)
204 !
205  return
subroutine inputwarning(inpc, ipoinpc, iline, text)
Definition: inputwarning.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
Hosted by OpenAircraft.com, (Michigan UAV, LLC)