54 numnp,numel,nummat,nstart, nend)
86 INTEGER :: numel, numnp, nummat
87 INTEGER,
DIMENSION(1:NumEl) :: mattype
88 INTEGER,
DIMENSION(1:8,1:NumEl) :: nodes
89 REAL*8,
DIMENSION(1:3,1:NumNP) :: coor
90 REAL*8,
DIMENSION(1:NumMat) :: rho
91 REAL*8,
DIMENSION(1:NumNP) :: xm
95 REAL*8,
DIMENSION(1:3,1:8) :: ri = reshape( &
96 (/-0.577350269189626,-0.577350269189626,-0.577350269189626, &
97 0.577350269189626,-0.577350269189626,-0.577350269189626, &
98 0.577350269189626, 0.577350269189626,-0.577350269189626, &
99 -0.577350269189626, 0.577350269189626,-0.577350269189626, &
100 -0.577350269189626,-0.577350269189626, 0.577350269189626, &
101 0.577350269189626,-0.577350269189626, 0.577350269189626, &
102 0.577350269189626, 0.577350269189626, 0.577350269189626, &
103 -0.577350269189626, 0.577350269189626, 0.577350269189626/),(/3,8/) )
105 REAL*8 :: nnn(8), dn(8,3)
107 INTEGER ::
i,imat, igpt
108 INTEGER :: n1,n2,n3,n4,n5,n6,n7,n8
109 REAL*8 :: element_volume
110 REAL*8,
DIMENSION(1:3,1:8) ::
coord
111 REAL*8,
DIMENSION(1:3,1:3) :: jac, jacinv
115 integer :: nstart, nend
135 coord(1,1) = coor(1,n1)
136 coord(2,1) = coor(2,n1)
137 coord(3,1) = coor(3,n1)
139 coord(1,2) = coor(1,n2)
140 coord(2,2) = coor(2,n2)
141 coord(3,2) = coor(3,n2)
143 coord(1,3) = coor(1,n3)
144 coord(2,3) = coor(2,n3)
145 coord(3,3) = coor(3,n3)
147 coord(1,4) = coor(1,n4)
148 coord(2,4) = coor(2,n4)
149 coord(3,4) = coor(3,n4)
151 coord(1,5) = coor(1,n5)
152 coord(2,5) = coor(2,n5)
153 coord(3,5) = coor(3,n5)
155 coord(1,6) = coor(1,n6)
156 coord(2,6) = coor(2,n6)
157 coord(3,6) = coor(3,n6)
159 coord(1,7) = coor(1,n7)
160 coord(2,7) = coor(2,n7)
161 coord(3,7) = coor(3,n7)
163 coord(1,8) = coor(1,n8)
164 coord(2,8) = coor(2,n8)
165 coord(3,8) = coor(3,n8)
172 jac,jacinv,detj,
error)
175 WRITE(*,1000) igpt,
i, detj
179 element_volume = element_volume + detj
182 node_mass = element_volume*rho(imat)*0.125
184 xm(n1 ) = xm(n1 ) + node_mass
185 xm(n2 ) = xm(n2 ) + node_mass
186 xm(n3 ) = xm(n3 ) + node_mass
187 xm(n4 ) = xm(n4 ) + node_mass
188 xm(n5 ) = xm(n5 ) + node_mass
189 xm(n6 ) = xm(n6 ) + node_mass
190 xm(n7 ) = xm(n7 ) + node_mass
191 xm(n8 ) = xm(n8 ) + node_mass
197 1000
FORMAT (/,2
x,
'>>> Fatal error!', &
198 /,6
x,
'Jacobien at gauss point (',i2, &
199 ') of element ',i6,
' is singular with detj =',e15.8)
subroutine v3d8_mass(coor, nodes, MatType, rho, xm, NumNP, NumEl, NumMat, nstart, nend)
int coord[NPANE][NROW *NCOL][3]
subroutine get_jacobien(coords, mcrd, nnode, dn, jac, jacinv, detj, error)
subroutine get_shape(r, n, dn, igpt)