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

Go to the source code of this file.

Functions/Subroutines

subroutine inter_trc_7 (itask, nin, ipari, ind_imp, intbuf_tab, nb_inter_sorted, list_inter_sorted, inter_struct)

Function/Subroutine Documentation

◆ inter_trc_7()

subroutine inter_trc_7 ( integer, intent(in) itask,
integer nin,
integer, dimension(npari,ninter), intent(in) ipari,
integer, dimension(*), intent(inout) ind_imp,
type(intbuf_struct_), dimension(ninter) intbuf_tab,
integer, intent(in) nb_inter_sorted,
integer, dimension(nb_inter_sorted), intent(in) list_inter_sorted,
type(inter_struct_type), dimension(ninter), intent(inout) inter_struct )

Definition at line 33 of file inter_trc_7.F.

35!$COMMENT
36! INTER_TRC_7 description
37! INTER_TRC_7 organization :
38!$ENDCOMMENT
39C============================================================================
40C M o d u l e s
41C-----------------------------------------------
42 USE intbufdef_mod
44C-----------------------------------------------
45C I m p l i c i t T y p e s
46C-----------------------------------------------
47#include "implicit_f.inc"
48#include "comlock.inc"
49C-----------------------------------------------
50C C o m m o n B l o c k s
51C-----------------------------------------------
52#include "com04_c.inc"
53#include "param_c.inc"
54C-----------------------------------------------
55C D u m m y A r g u m e n t s
56C-----------------------------------------------
57 INTEGER, INTENT(in) :: ITASK ! thread id
58 INTEGER, DIMENSION(NPARI,NINTER), INTENT(in) :: IPARI ! interface data
59 INTEGER, DIMENSION(*), INTENT(inout) :: IND_IMP ! index for implicit option (pointer, cannot define the dimension)
60 TYPE(INTBUF_STRUCT_),DIMENSION(NINTER) :: INTBUF_TAB ! interface data
61 INTEGER, INTENT(in) :: NB_INTER_SORTED ! number of interfaces that need to be sorted
62 INTEGER, DIMENSION(NB_INTER_SORTED), INTENT(in) :: LIST_INTER_SORTED ! list of interfaces that need to be sorted
63 TYPE(inter_struct_type), DIMENSION(NINTER), INTENT(inout) :: INTER_STRUCT ! structure for interface
64C-----------------------------------------------
65C L o c a l V a r i a b l e s
66C-----------------------------------------------
67 INTEGER :: NIN
68 INTEGER :: INACTI,IFQ,NSN,NSNROLD,INACIMP
69 INTEGER :: I,N,K,NN,NI,ITIED
70 INTEGER :: I_STOK,CAND_T,CAND_TF
71 INTEGER :: NUM_IMP
72 INTEGER :: KK
73C-----------------------------------------------
74
75 num_imp = 0
76 DO kk=1,nb_inter_sorted
77 nin = list_inter_sorted(kk)
78 inacti = ipari(22,nin)
79 ifq = ipari(31,nin)
80 itied = ipari(85,nin)
81
82 inter_struct(nin)%INACTI=inacti
83 inter_struct(nin)%INACTII = inacti
84
85 nsn =ipari(5,nin)
86 IF( inacti==5.OR.inacti==6.OR.inacti==7.OR.ifq>0.OR.
87 . num_imp>0.OR.itied/=0 )THEN
88 nsnrold = ipari(24,nin)
89 ELSE
90 nsnrold = 0
91 ENDIF
92
93 IF( inacti==5.OR.inacti==6.OR.inacti==7.OR.ifq>0.OR.
94 . num_imp>0.OR.itied/=0)THEN
95 inter_struct(nin)%INACTII=inacti
96 IF (num_imp>0.AND.(inacti/=5.AND.inacti/=6.AND.ifq<=0)) THEN
97 inacimp = 0
98 ELSE
99 inacimp = 1
100 ENDIF
101
102 inter_struct(nin)%I_SK_OLD = intbuf_tab(nin)%I_STOK(1)
103
104 IF( inter_struct(nin)%SIZE_CAND_A<nsn+nsnrold+3) THEN
105 IF(ALLOCATED(inter_struct(nin)%CAND_A)) DEALLOCATE(inter_struct(nin)%CAND_A)
106 ALLOCATE(inter_struct(nin)%CAND_A(nsn+nsnrold+3) )
107 inter_struct(nin)%SIZE_CAND_A=nsn+nsnrold+3
108 ENDIF
109
110C=============================================
111C LES NOEUDS DELETES DEVIENNENT NSN+NSNROLD+1
112C=============================================
113C------for travelling nodes detected in imp_solv-----
114 i_stok = intbuf_tab(nin)%I_STOK(1)
115 CALL i7trc(
116 1 nsn+nsnrold ,inter_struct(nin)%I_SK_OLD,intbuf_tab(nin)%CAND_N,intbuf_tab(nin)%CAND_E,
117 2 intbuf_tab(nin)%CAND_P,intbuf_tab(nin)%FTSAVX,intbuf_tab(nin)%FTSAVY,intbuf_tab(nin)%FTSAVZ,
118 3 inter_struct(nin)%CAND_A,intbuf_tab(nin)%IFPEN ,inacti,ifq,
119 4 num_imp ,ind_imp ,intbuf_tab(nin)%STFNS ,nin ,
120 5 nsn ,itied,intbuf_tab(nin)%CAND_F)
121
122 IF(inter_struct(nin)%I_SK_OLD==0) THEN
123 inter_struct(nin)%INACTI=-abs(inacti)
124 ENDIF
125 intbuf_tab(nin)%I_STOK(1)=inter_struct(nin)%I_SK_OLD
126 ELSE
127 inter_struct(nin)%I_SK_OLD=0
128 intbuf_tab(nin)%I_STOK(1)=0
129 IF(.NOT.ALLOCATED(inter_struct(nin)%CAND_A)) THEN
130 ALLOCATE(inter_struct(nin)%CAND_A(0) )
131 inter_struct(nin)%SIZE_CAND_A=0
132 ENDIF
133 ENDIF
134 ENDDO
135
136 RETURN
subroutine i7trc(nsn, i_stok, cand_n, cand_e, cand_p, cand_fx, cand_fy, cand_fz, cand_a, ifpen, inacti, ifq, num_imp, ind_imp, stfns, nin, nsnl, itied, cand_f)
Definition i7trc.F:38