63 CHARACTER*200 :: keywd
74 OPEN(io_input,file=
'fractography3d.inp',
status=
'old',iostat=ios)
78 print*,
'Unable to find fractography3d.inp'
79 print*,
' ...Trying RocfracControl.txt'
81 OPEN(io_input,file=
'RocfracControl.txt',
status=
'old',iostat=ios)
83 print*,
'Unable to find RocfracControl.txt'
84 print*,
' ...STOPPING'
94 10
READ(io_input,
'(A)',iostat=ios) keywd
96 print*,
' *END parameter not found - STOPPING'
99 IF(keywd(1:4).EQ.
'*END')
THEN
101 ELSE IF(keywd(1:7).EQ.
'*PREFIX')
THEN
105 ELSE IF(keywd(1:7).EQ.
'*MATVOL'.OR.keywd(1:13).EQ.
'*HYPERELASTIC'.OR. &
106 keywd(1:8).EQ.
'*ELASTIC')
THEN
109 ELSE IF(keywd(1:8).EQ.
'*ELEMENT'.AND.keywd(1:15).NE.
'*ELEMENT OUTPUT')
THEN
115 ELSE IF(keywd(1:9).EQ.
'*IOFORMAT')
THEN
118 ELSE IF(keywd(1:18).EQ.
'*DYNAMIC, IMPLICIT')
THEN
125 40
READ(io_input,
'(A)',iostat=ios) keywd
127 print*,
' *END parameter not found - STOPPING'
130 IF(keywd(1:3).EQ.
'*END')
THEN
135 ELSE IF(keywd(1:9).EQ.
'*MESHSOFT')
THEN
152 READ(io_input,
'(a20)') prefx
153 prefx_lngth = len_trim(prefx)
166 READ(io_input,*) iaux, numvertx
181 REAL*8 :: e, xnu, rho,
alpha
183 READ(io_input,*) numat_vol
187 READ(io_input,*) e, xnu, rho,
alpha
188 cd_fastest =
max( cd_fastest, &
189 sqrt(e*(1.d0-xnu)/rho/(1.d0+xnu)/(1.d0-2.d0*xnu)) )
205 READ(io_input,*) iaux, bc_conditions(
i)%b1, bc_conditions(
i)%b2, bc_conditions(
i)%b3, &
206 bc_conditions(
i)%bc1, bc_conditions(
i)%bc2, bc_conditions(
i)%bc3
220 READ(io_input,*) numnodeio
222 ALLOCATE(nodeio(1:numnodeio))
225 READ(io_input,*) nodeio(
i)
247 IF(chr.EQ.
'T'.OR.chr.EQ.
't')
THEN
249 ELSE IF(chr.EQ.
'A'.OR.chr.EQ.
'a')
THEN
251 ELSE IF(chr.EQ.
'P'.OR.chr.EQ.
'p')
THEN
253 ELSE IF(chr.EQ.
'C'.OR.chr.EQ.
'c')
THEN
255 IF(chr.EQ.
'P'.OR.chr.EQ.
'p')
THEN
257 ELSE IF(chr.EQ.
'T'.OR.chr.EQ.
't')
THEN
261 print*,
' ERROR: MESHING PACKAGE NOT SUPPORTED'
278 READ(io_input,*) ioformat
288 CHARACTER(len=200) :: keywd
291 CHARACTER(len=16) :: eltype
293 CALL
locchr(keywd,
'TYPE ',4,8,k1,k2)
295 eltype = keywd(k1:k2)
297 SELECT CASE (trim(eltype))
316 print*,
'*ELEMENT TYPE NOT FOUND'
subroutine element_sub(glb, keywd)
Vector_n max(const Array_n_const &v1, const Array_n_const &v2)
int status() const
Obtain the status of the attribute.
subroutine matvol_sub(glb, tmp_E, tmp_xnu, tmp_rho, tmp_alpha, tmp_iSolnType)
subroutine readinp(ntime)
subroutine locchr(text, varna, lvari, kpos0, kpos1, kpos2)
subroutine prefix_sub(glb)
subroutine nodeio_sub(myid)
unsigned char alpha() const
subroutine meshsoft_sub()
subroutine ioformat_sub()