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

Go to the source code of this file.

Functions/Subroutines

subroutine readforce (zc, neq, nev, nactdof, ikmpc, nmpc, ipompc, nodempc, mi, coefmpc, jobnamef, a, igeneralizedforce)
 

Function/Subroutine Documentation

◆ readforce()

subroutine readforce ( complex*16, dimension(neq,*)  zc,
integer  neq,
integer  nev,
integer, dimension(0:mi(2),*)  nactdof,
integer, dimension(*)  ikmpc,
integer  nmpc,
integer, dimension(*)  ipompc,
integer, dimension(3,*)  nodempc,
integer, dimension(*)  mi,
real*8, dimension(*)  coefmpc,
character*132  jobnamef,
complex*16, dimension(nev,*)  a,
integer  igeneralizedforce 
)
21 !
22 ! reads a complex force (e.g. response of a fluid to a harmonic
23 ! structural excitation)
24 ! the force has to be stored in file 'dummy' in the form:
25 !
26 ! node,Fx-real,Fx-imag,Fy-real,Fy-imag,Fz-real,Fz-imag
27 !
28 ! only nodes in which a force is applied have to be stored. Modes
29 ! have to be separated by line starting with **
30 !
31 ! for cyclic symmetric structures the eigenmodes come in pairs
32 ! forces must be given for the first mode of each pair only
33 !
34  implicit none
35 !
36  logical exi
37 !
38  character*132 jobnamef
39  character*144 name
40 !
41  integer mi(*),neq,nev,i,j,k,nactdof(0:mi(2),*),ikmpc(*),nmpc,
42  & jdof,id,ist,ipompc(*),index,nodempc(3,*),node,istat,
43  & igeneralizedforce
44 !
45  real*8 coefmpc(*),comp(6)
46 !
47  complex*16 zc(neq,*),force(3),a(nev,*)
48 !
49  igeneralizedforce=0
50 !
51 ! creating name for force file
52 !
53  do i=1,132
54  if(jobnamef(i:i).eq.' ') exit
55  name(i:i)=jobnamef(i:i)
56  enddo
57  i=i-1
58  name(i+1:i+6)='_force'
59  do j=i+7,144
60  name(j:j)=' '
61  enddo
62 !
63 ! if a force file exists, it is read. If it does not exist,
64 ! a generalized force file is looked for (= product of the
65 ! force due to eigenmode i with eigenmode j, leading to the
66 ! nev x nev a-matrix).
67 !
68  inquire(file=name,exist=exi)
69 !
70  if(exi) then
71  open(27,file=name,status='unknown')
72 !
73  do i=1,nev
74  do
75  read(27,*,iostat=istat) node,(comp(k),k=1,6)
76  if(istat.ne.0) then
77  exit
78  endif
79 !
80  do k=1,3
81  force(k)=comp(2*k-1)*(1.d0,0.d0)+comp(2*k)*(0.d0,1.d0)
82  enddo
83 !
84  do k=1,3
85  jdof=nactdof(k,node)
86  if(jdof.gt.0) then
87  zc(jdof,i)=zc(jdof,i)-force(k)
88  else
89 !
90 ! node is a dependent node of a MPC: distribute
91 ! the forces among the independent nodes
92 ! (proportional to their coefficients)
93 !
94  jdof=8*(node-1)+k
95  call nident(ikmpc,jdof,nmpc,id)
96  if(id.gt.0) then
97  if(ikmpc(id).eq.jdof) then
98  ist=ipompc(id)
99  index=nodempc(3,ist)
100  if(index.eq.0) cycle
101  do
102  jdof=nactdof(nodempc(2,index),
103  & nodempc(1,index))
104  if(jdof.gt.0) then
105  zc(jdof,i)=zc(jdof,i)-
106  & coefmpc(index)*force(k)/coefmpc(ist)
107  endif
108  index=nodempc(3,index)
109  if(index.eq.0) exit
110  enddo
111  endif
112  endif
113  endif
114  enddo
115  enddo
116  enddo
117 !
118  close(27)
119  else
120 !
121 ! creating name for generalized force file
122 !
123  do i=1,132
124  if(jobnamef(i:i).eq.' ') exit
125  name(i:i)=jobnamef(i:i)
126  enddo
127  i=i-1
128  name(i+1:i+9)='_genforce'
129  do j=i+10,144
130  name(j:j)=' '
131  enddo
132 !
133  inquire(file=name,exist=exi)
134 !
135  if(exi) then
136 !
137  igeneralizedforce=1
138 !
139  open(27,file=name,status='unknown')
140  do
141  read(27,*,iostat=istat)i,j,a(i,j)
142  if(istat.ne.0) exit
143  enddo
144  close(27)
145  else
146  write(*,*) '*ERROR in readforce: neither a force file'
147  write(*,*) ' nor a generalized force file exists'
148  call exit(201)
149  endif
150  endif
151 !
152  return
subroutine nident(x, px, n, id)
Definition: nident.f:26
Hosted by OpenAircraft.com, (Michigan UAV, LLC)