41
42 USE my_alloc_mod
49
50
51
52#include "implicit_f.inc"
53
54
55
56#include "com_xfem1.inc"
57
58
59
60 INTEGER ITABM1(*)
61 TYPE (INICRACK_) , DIMENSION(NINICRACK) :: INICRACK
62 TYPE (UNIT_TYPE_),INTENT(IN) ::UNITAB
63 TYPE(SUBMODEL_DATA) LSUBMODEL(*)
64
65
66
67 INTEGER I,J,ID,NSEG,LIST_INICRACK(NINICRACK)
68 INTEGER J2(2)
69 CHARACTER(LEN=NCHARTITLE) :: TITR
70 CHARACTER MESS*40
72 . bid,ratio
73 LOGICAL IS_AVAILABLE
74
75
76
77 INTEGER USR2SYS
78 DATA mess/'INITIAL CRACK DEFINITION '/
79
80
81
82
83
84
85
86
87
88
89 bid = zero
90
91
93
94
95 DO i = 1,ninicrack
96
97
98 titr = ''
101 . option_titr = titr)
102
103
105 inicrack(i)%TITLE = titr
106
107
108 CALL hm_get_intv(
'segmax',nseg,is_available,lsubmodel)
109 inicrack(i)%NSEG = nseg
110
111
112 ALLOCATE(inicrack(i)%SEG(nseg))
113 DO j = 1,nseg
114 CALL my_alloc(inicrack(i)%SEG(j)%NODES,2)
115 ENDDO
116
117
118 DO j = 1,nseg
122 inicrack(i)%SEG(j)%NODES(1) =
usr2sys(j2(1),itabm1,mess,
id)
123 inicrack(i)%SEG(j)%NODES(2) =
usr2sys(j2(2),itabm1,mess,
id)
124 inicrack(i)%SEG(j)%RATIO = ratio
125 ENDDO
126 ENDDO
127
128
129
130 DO j = 1,ninicrack
131 list_inicrack(j) = inicrack(j)%ID
132 ENDDO
133 CALL udouble_igr(list_inicrack,ninicrack,mess,0,bid)
134
135
136
137 RETURN
subroutine hm_get_float_array_index(name, rval, index, is_available, lsubmodel, unitab)
subroutine hm_get_int_array_index(name, ival, index, is_available, lsubmodel)
subroutine hm_get_intv(name, ival, is_available, lsubmodel)
subroutine hm_option_start(entity_type)
integer, parameter nchartitle
integer function usr2sys(iu, itabm1, mess, id)
subroutine udouble_igr(list, nlist, mess, ir, rlist)