OpenRadioss 2025.1.11
OpenRadioss project
Loading...
Searching...
No Matches
prelecdet.F File Reference
#include "implicit_f.inc"
#include "com04_c.inc"

Go to the source code of this file.

Functions/Subroutines

subroutine prelecdet (igrnod, lsubmodel, detonators)

Function/Subroutine Documentation

◆ prelecdet()

subroutine prelecdet ( type (group_), dimension(ngrnod) igrnod,
type(submodel_data), dimension(nsubmod), intent(in) lsubmodel,
type(detonators_struct_) detonators )

Definition at line 37 of file prelecdet.F.

38C-----------------------------------------------
39C M o d u l e s
40C-----------------------------------------------
41 USE groupdef_mod
43 USE submodel_mod
47C-----------------------------------------------
48C I m p l i c i t T y p e s
49C-----------------------------------------------
50#include "implicit_f.inc"
51C-----------------------------------------------
52C C o m m o n B l o c k s
53C-----------------------------------------------
54#include "com04_c.inc"
55C-----------------------------------------------
56C D u m m y A r g u m e n t s
57C-----------------------------------------------
58 TYPE(SUBMODEL_DATA),INTENT(IN) :: LSUBMODEL(NSUBMOD)
59 TYPE(DETONATORS_STRUCT_) :: DETONATORS
60C-----------------------------------------------
61 TYPE (GROUP_) , DIMENSION(NGRNOD) :: IGRNOD
62C-----------------------------------------------
63C L o c a l V a r i a b l e s
64C-----------------------------------------------
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
71C-----------------------------------------------
72C E x t e r n a l F u n c t i o n s
73C-----------------------------------------------
74 INTEGER NGR2USRN
75C-----------------------------------------------
76C S o u r c e L i n e s
77C-----------------------------------------------
78
79! Allocation for /DFS/WAV_SHA & /DFS/DETCORD
80
81 !ALLOCATE NUMBER OF DETONATORS IN DATA STRUCTURE
82 detonators%N_DET = 0 !total number of detonators
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 !---SPECIFIC ALLOCATIONS (WAV_SHA & DETCORD)
105 !- /dfs/wav_sha
106 CALL hm_option_start('/DFS/WAV_SHA')
107 DO k=1,detonators%N_DET_WAVE_SHAPER
108 CALL hm_option_read_key(lsubmodel,option_id=id,keyword2= key)
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
122 CALL hm_option_start('/DFS/DETCORD')
123 DO k=1,detonators%N_DET_CORD
124 CALL hm_option_read_key(lsubmodel,option_id=id,keyword2= key)
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
137C-------------------------------------------
138 RETURN
subroutine hm_get_intv(name, ival, is_available, lsubmodel)
subroutine hm_option_start(entity_type)
initmumps id
integer, parameter nchartitle
integer, parameter ncharkey
integer function ngr2usrn(iu, igrnod, ngrnod, num)
Definition nintrr.F:407