OpenRadioss 2025.1.11
OpenRadioss project
Loading...
Searching...
No Matches
read_dfs_wave_shaper.F File Reference
#include "implicit_f.inc"
#include "com04_c.inc"
#include "units_c.inc"
#include "param_c.inc"
#include "tabsiz_c.inc"

Go to the source code of this file.

Functions/Subroutines

subroutine read_dfs_wave_shaper (detonators, igrnod, ipm, itabm1, unitab, lsubmodel, itab)

Function/Subroutine Documentation

◆ read_dfs_wave_shaper()

subroutine read_dfs_wave_shaper ( type(detonators_struct_), intent(inout), target detonators,
type (group_), dimension(ngrnod), intent(in) igrnod,
integer, dimension(npropmi,nummat), intent(in) ipm,
integer, dimension(sitabm1), intent(in) itabm1,
type (unit_type_), intent(in) unitab,
type(submodel_data), dimension(nsubmod), intent(in) lsubmodel,
integer, dimension(numnod), intent(in) itab )

Definition at line 46 of file read_dfs_wave_shaper.F.

47C-----------------------------------------------
48C M o d u l e s
49C-----------------------------------------------
50 USE unitab_mod
51 USE message_mod
53 USE groupdef_mod
55 USE submodel_mod
58 USE format_mod , ONLY : fmw_10i
59C-----------------------------------------------
60C I m p l i c i t T y p e s
61C-----------------------------------------------
62#include "implicit_f.inc"
63C-----------------------------------------------
64C C o m m o n B l o c k s
65C-----------------------------------------------
66#include "com04_c.inc"
67#include "units_c.inc"
68#include "param_c.inc"
69#include "tabsiz_c.inc"
70C-----------------------------------------------
71C D u m m y A r g u m e n t s
72C-----------------------------------------------
73 TYPE (UNIT_TYPE_),INTENT(IN) :: UNITAB
74 INTEGER,INTENT(IN) :: ITABM1(SITABM1),ITAB(NUMNOD)
75 INTEGER,INTENT(IN) :: IPM(NPROPMI,NUMMAT)
76 TYPE(SUBMODEL_DATA),INTENT(IN) :: LSUBMODEL(NSUBMOD)
77 TYPE(DETONATORS_STRUCT_),INTENT(INOUT),TARGET :: DETONATORS
78 TYPE (GROUP_),DIMENSION(NGRNOD),INTENT(IN) :: IGRNOD
79C-----------------------------------------------
80C L o c a l V a r i a b l e s
81C-----------------------------------------------
82 INTEGER :: I, MAT, J, K,IGU,IGS,JJ,MDET,DET_ID,IDET
83 INTEGER :: IBID, NODE_ID1, NODE_ID2,uID1,uID2, IOPT, IUNIT, UID
84 INTEGER :: FLAG_FMT,IMAT,IFLAGUNIT,UNUSED
85 INTEGER :: STAT,NPE
86 my_real :: xc, yc, zc, alt, xc1, yc1, zc1, xc2, yc2, zc2, nx, ny, nz, bid, vcj, vdet
87 CHARACTER*40 :: MESS
88 CHARACTER*64 :: chain1,chain2
89 CHARACTER(LEN=NCHARKEY) :: KEY, KEY2
90 CHARACTER(LEN=NCHARTITLE) :: TITR
91 LOGICAL :: IS_ENCRYPTED, IS_AVAILABLE
92 INTEGER,POINTER,DIMENSION(:) :: IECRAN
93 my_real,POINTER,DIMENSION(:) :: decran
94 INTEGER :: NDETPS,NDETSG,NECRAN,NDETPL,NDETCORD
95C-----------------------------------------------
96C E x t e r n a l F u n c t i o n s
97C-----------------------------------------------
98 INTEGER,EXTERNAL :: NODGRNR5, USR2SYS, NINTRI
99 INTEGER :: UNUSED_MAT_DETONATOR
100 DATA mess/'DETONATORS DEFINITION '/
101C-----------------------------------------------
102C S o u r c e L i n e s
103C-----------------------------------------------
104
105 CALL hm_option_start('/DFS/WAV_SHA')
106
107 DO idet=1,detonators%N_DET_WAVE_SHAPER
108
109 CALL hm_option_read_key(lsubmodel,option_id=det_id, unit_id=uid,keyword2=key,keyword3=key2)
110 IF (len_trim(key) > 0) key = key(1:7)
111 IF (len_trim(key2) > 0) key2 = key2(1:4)
112
113 iecran => detonators%WAVE_SHAPER(idet)%NODES(1:)
114 decran => detonators%WAVE_SHAPER(idet)%TIME(1:)
115
116 is_encrypted= .false.
117 is_available = .false.
118 CALL hm_option_is_encrypted(is_encrypted)
119 !---------------------------------!
120 ! READING !
121 !---------------------------------!
122 CALL hm_get_floatv('rad_det_locationA_X', vdet, is_available, lsubmodel, unitab)
123 CALL hm_get_floatv('rad_det_locationa_y', YC1, IS_AVAILABLE, LSUBMODEL, UNITAB)
124 CALL HM_GET_FLOATV('rad_det_locationa_z', ZC1, IS_AVAILABLE, LSUBMODEL, UNITAB)
125 CALL HM_GET_FLOATV('rad_det_time', ALT, IS_AVAILABLE, LSUBMODEL,UNITAB)
126 CALL HM_GET_INTV('rad_det_materialid', MAT, IS_AVAILABLE, LSUBMODEL)
127 CALL HM_GET_INTV('entityid', IGU, IS_AVAILABLE, LSUBMODEL)
128 !---------------------------------!
129 ! CHECKING USER FLAGS !
130 ! +INTERNAL ID !
131 !---------------------------------!
132 MDET=MAT !bak
133 IF (ALT > INFINITY) ALT=INFINITY
134 IF(MAT > 0)UNUSED=UNUSED_MAT_DETONATOR(MAT,NUMMAT,IPM)
135 UNUSED=0
136 IF (MAT < 0) THEN
137 CALL ANCMSG(MSGID=102,MSGTYPE=MSGERROR,ANMODE=ANINFO,
138 . I1=DET_ID,
139 . C1='detonator is referring to a negative material id',
140 . C2='/dfs/wav_sha',
141 . I2=MDET)
142 ELSEIF (UNUSED==1) THEN
143 CALL ANCMSG(MSGID=102,MSGTYPE=MSGERROR,ANMODE=ANINFO,
144 . I1=DET_ID,
145 . C1='detonator is referring to an unknown material id',
146 . C2='/dfs/wav_sha',
147 . I2=MDET)
148 ELSEIF (UNUSED==2) THEN
149 CALL ANCMSG(MSGID=102,MSGTYPE=MSGERROR,ANMODE=ANINFO,
150 . I1=DET_ID,
151 . C1='detonator must refer to a jwl material law(laws 5, 51, 97, 151)',
152 . C2='/dfs/wav_sha',
153 . I2=MDET)
154 ELSE
155 !---------------------------------!
156 ! LISTING PRINTOUT !
157 !---------------------------------!
158 NPE = NODGRNR5(IGU ,IGS,IECRAN(1),IGRNOD ,ITABM1 ,MESS)
159 !Nodes in group are ordered from 1 to NPE. last point is the nearest from the detonation origin. Points are composing the screen lines (guard lines). Screen lines is the boundary of the obstacle (shadow area
160 IF(IS_ENCRYPTED) WRITE(IOUT,1001)
161.NOT. IF(IS_ENCRYPTED)WRITE(IOUT,1550) DET_ID,VDET,YC1,ZC1,ALT,MDET,IGU,NPE
162.NOT. IF(IS_ENCRYPTED)WRITE(IOUT,FMT=FMW_10I) (ITAB(IECRAN(I)),I=1,NPE)
163 DO I=1,NPE
164 CALL IFRONTPLUS(IECRAN(I),1)
165 END DO
166 DETONATORS%WAVE_SHAPER(IDET)%TDET = ALT
167 DETONATORS%WAVE_SHAPER(IDET)%MAT = MAT
168 DETONATORS%WAVE_SHAPER(IDET)%VDET = VDET
169 DETONATORS%WAVE_SHAPER(IDET)%XDET = ZERO
170 DETONATORS%WAVE_SHAPER(IDET)%YDET = YC1
171 DETONATORS%WAVE_SHAPER(IDET)%ZDET = ZC1
172 DETONATORS%WAVE_SHAPER(IDET)%NUMNOD = NPE
173 END IF
174
175 ENDDO !next IDET
176C-----------------------------------------------
177C O u t p u t F o r m a t
178C-----------------------------------------------
179 1001 FORMAT(///5X,
180 & 'shadow line detonation ',I10,/5X,
181 & '---------------------- ',/5X,
182 & 'confidential data')
183 1550 FORMAT(///5X,
184 & 'shadow line detonation =',I10,/5X,
185 & '---------------------- ',/5X,
186 & 'OPTIONAL velocity =',1PG20.13,/5X,
187 & 'y-coordinate =',1PG20.13,/5X,
188 & 'z-coordinate =',1PG20.13,/5X,
189 & 'lighting time =',1PG20.13,/5X,
190 & 'explosive material number =',I10,/5X,
191 & 'shadow line node group id =',I10,/5X,
192 & 'number of points(shadow) =',I10,/5X,
193 & 'shadow line definition : ')
194
195C-----------------------------------------------
#define my_real
Definition cppsort.cpp:32
subroutine hm_get_floatv(name, rval, is_available, lsubmodel, unitab)
subroutine hm_option_is_encrypted(is_encrypted)
subroutine hm_option_start(entity_type)
subroutine jwl(iflag, nel, pm, off, eint, mu, mu2, espe, dvol, df, vnew, mat, psh, pnew, dpdm, dpde)
Definition jwl.F:32
initmumps id
integer, parameter nchartitle
integer, parameter ncharkey