38
39
40
47
48
49
50#include "implicit_f.inc"
51
52
53
54#include "com04_c.inc"
55
56
57
58 TYPE(SUBMODEL_DATA),INTENT(IN) :: LSUBMODEL(NSUBMOD)
59 TYPE(DETONATORS_STRUCT_) :: DETONATORS
60
61 TYPE (GROUP_) , DIMENSION(NGRNOD) :: IGRNOD
62
63
64
65 INTEGER SIZ_ECRAN, SIZ_DETCORD
66 INTEGER I,J,K,ID,USER_ID,INTERNAL_ID,NN,STAT
67 INTEGER NNOD_DETCORD, NNOD_WAV_SHA,NUM
68 CHARACTER(LEN=NCHARKEY) :: KEY,KEY2,KEY3
69 CHARACTER(LEN=NCHARTITLE) :: TITR
70 LOGICAL :: IS_AVAILABLE
71
72
73
74 INTEGER NGR2USRN
75
76
77
78
79
80
81
82 detonators%N_DET = 0
83
84 num = detonators%N_DET_POINT
85 detonators%N_DET = detonators%N_DET + num
86 IF(num > 0) ALLOCATE(detonators%POINT(num))
87
88 num = detonators%N_DET_LINE
89 detonators%N_DET = detonators%N_DET + num
90 IF(num > 0) ALLOCATE(detonators%LINE(num))
91
92 num = detonators%N_DET_PLANE
93 detonators%N_DET = detonators%N_DET + num
94 IF(num > 0) ALLOCATE(detonators%PLANE(num))
95
96 num = detonators%N_DET_WAVE_SHAPER
97 detonators%N_DET = detonators%N_DET + num
98 IF(num > 0) ALLOCATE(detonators%WAVE_SHAPER(num))
99
100 num = detonators%N_DET_CORD
101 detonators%N_DET = detonators%N_DET + num
102 IF(num > 0) ALLOCATE(detonators%CORD(num))
103
104
105
107 DO k=1,detonators%N_DET_WAVE_SHAPER
109 CALL hm_get_intv(
'entityid', user_id, is_available, lsubmodel
110 internal_id =
ngr2usrn(user_id,igrnod,ngrnod,nnod_wav_sha)
111 detonators%WAVE_SHAPER(k)%NUMNOD = nnod_wav_sha
112 ALLOCATE(detonators%WAVE_SHAPER(k)%NODES(nnod_wav_sha))
113 ALLOCATE(detonators%WAVE_SHAPER(k)%IORDR(nnod_wav_sha))
114 ALLOCATE(detonators%WAVE_SHAPER(k)%FLAG(nnod_wav_sha))
115 ALLOCATE(detonators%WAVE_SHAPER(k)%TIME(nnod_wav_sha))
116 detonators%WAVE_SHAPER(k)%NODES(:) = 0
117 detonators%WAVE_SHAPER(k)%IORDR(:) = 0
118 detonators%WAVE_SHAPER(k)%FLAG(:) = 0
119 detonators%WAVE_SHAPER(k)%TIME(:) = zero
120 END DO
121
123 DO k=1,detonators%N_DET_CORD
125 CALL hm_get_intv(
'entityid', user_id, is_available, lsubmodel)
126 internal_id =
ngr2usrn(user_id,igrnod,ngrnod,nnod_detcord)
127 detonators%CORD(k)%NUMNOD = nnod_detcord
128 ALLOCATE(detonators%CORD(k)%NODES(nnod_detcord))
129 ALLOCATE(detonators%CORD(k)%TDET_PATH(nnod_detcord))
130 detonators%CORD(k)%NODES(:) = 0
131 detonators%CORD(k)%TDET_PATH(:) = zero
132 ENDDO
133
134
135
136
137
138 RETURN
subroutine hm_get_intv(name, ival, is_available, lsubmodel)
subroutine hm_option_start(entity_type)
integer, parameter nchartitle
integer, parameter ncharkey
integer function ngr2usrn(iu, igrnod, ngrnod, num)