Civil Engineering Reference
In-Depth Information
Modal superposition (Program 11.2)
Theta (Program 11.3)
Wilson (Program 11.4)
0
10
20
30
40
50
60
70
80
90
100
t
Figure 11.7
Cantilever tip displacement computed by Programs 11.2, 11.3 and 11.4
Program 11.3 Forced vibration analysis of an elastic solid in plane strain using rect-
angular 8-node quadrilaterals. Lumped or consistent mass. Mesh numbered in x -or
y -direction. Implicit time integration using the “theta” method.
PROGRAM p113
!-------------------------------------------------------------------------
! Program 11.3 Forced vibration analysis of an elastic solid in plane
! strain using rectangular 8-node quadrilaterals. Lumped or
! consistent mass. Mesh numbered in x- or y-direction.
! Implicit time integration using the "theta" method.
!-------------------------------------------------------------------------
USE main; USE geom; IMPLICIT NONE
INTEGER,PARAMETER::iwp=SELECTED_REAL_KIND(15)
INTEGER::i,j,iel,k,loaded_nodes,ndim=2,ndof=16,nels,neq,nip=9,nn,nod=8, &
nodof=2,npri,nprops=3,np_types,nr,nres,nst=3,nstep,nxe,nye
REAL(iwp)::area,c1,c2,c3,c4,det,dtim,fk,fm,one=1.0_iwp,theta,time,
&
zero=0.0_iwp
CHARACTER(LEN=15)::element='quadrilateral'; LOGICAL::consistent=.FALSE.
!-----------------------dynamic arrays------------------------------------
INTEGER,ALLOCATABLE::etype(:),g(:),g_g(:,:),g_num(:,:),kdiag(:),nf(:,:), &
node(:),num(:)
REAL(iwp),ALLOCATABLE::bee(:,:),coord(:,:),dee(:,:),der(:,:),deriv(:,:), &
d1x0(:),d1x1(:),d2x0(:),d2x1(:),ecm(:,:),fun(:),f1(:),g_coord(:,:),
&
jac(:,:),km(:,:),kv(:),loads(:),mm(:,:),mv(:),points(:,:),prop(:,:),
&
val(:,:),weights(:),x0(:),x1(:),x_coords(:),y_coords(:)
!-----------------------input and initialisation--------------------------
OPEN(10,FILE='fe95.dat'); OPEN(11,FILE='fe95.res')
READ(10,*)nxe,nye,np_types; CALL mesh_size(element,nod,nels,nn,nxe,nye)
ALLOCATE(nf(nodof,nn),points(nip,ndim),g(ndof),g_coord(ndim,nn), &
dee(nst,nst),coord(nod,ndim),jac(ndim,ndim),weights(nip),der(ndim,nod),&
deriv(ndim,nod),bee(nst,ndof),km(ndof,ndof),num(nod),g_num(nod,nels), &
g_g(ndof,nels),mm(ndof,ndof),ecm(ndof,ndof),fun(nod),etype(nels),
&
 
Search WWH ::




Custom Search