34 1 INTBUF_TAB,NB_INTER_SORTED,LIST_INTER_SORTED,INTER_STRUCT)
47#include "implicit_f.inc"
57 INTEGER,
INTENT(in) :: ITASK
58 INTEGER,
DIMENSION(NPARI,NINTER),
INTENT(in) :: IPARI
59 INTEGER,
DIMENSION(*),
INTENT(inout) :: IND_IMP
60 TYPE(intbuf_struct_),
DIMENSION(NINTER) :: INTBUF_TAB
61 INTEGER,
INTENT(in) :: NB_INTER_SORTED
62 INTEGER,
DIMENSION(NB_INTER_SORTED),
INTENT(in) :: LIST_INTER_SORTED
68 INTEGER :: INACTI,IFQ,NSN,NSNROLD,INACIMP
69 INTEGER :: I,N,K,NN,NI,ITIED
70 INTEGER :: I_STOK,CAND_T,CAND_TF
76 DO kk=1,nb_inter_sorted
77 nin = list_inter_sorted(kk)
78 inacti = ipari(22,nin)
82 inter_struct(nin)%INACTI=inacti
83 inter_struct(nin)%INACTII = inacti
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)
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
102 inter_struct(nin)%I_SK_OLD = intbuf_tab(nin)%I_STOK(1)
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
114 i_stok = intbuf_tab(nin)%I_STOK(1)
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)
122 IF(inter_struct(nin)%I_SK_OLD==0)
THEN
123 inter_struct(nin)%INACTI=-abs(inacti)
125 intbuf_tab(nin)%I_STOK(1)=inter_struct(nin)%I_SK_OLD
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
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)
subroutine inter_trc_7(itask, nin, ipari, ind_imp, intbuf_tab, nb_inter_sorted, list_inter_sorted, inter_struct)