34
35
36
38 USE intbufdef_mod
41
42
43
44#include "implicit_f.inc"
45
46
47
48#include "param_c.inc"
49#include "com04_c.inc"
50#include "scr03_c.inc"
51#include "scr17_c.inc"
52
53
54
55 INTEGER IPARI(NPARI,NINTER),ITAB(*)
57 INTEGER NOM_OPT(LNOPT1,*)
58 TYPE(INTBUF_STRUCT_) INTBUF_TAB(*)
59
60 TYPE (GROUP_) , DIMENSION(NGRNOD) :: IGRNOD
61
62
63
64 INTEGER I, N, NTY , NN0, NSN, ILAGM, NRTS,NRTM, NMN, NAD, IGN
65 INTEGER ID
66 CHARACTER(LEN=NCHARTITLE) :: TITR
67
68 DO n=1,ninter
70 CALL fretitl2(titr,nom_opt(lnopt1-ltitr+1,n),ltitr)
71 nty=ipari(7,n)
72 ilagm=0
73 IF(codvers>=44) ilagm=ipari(33,n)
74 IF(nty==7.AND.ilagm==1) THEN
75 nsn =ipari(5,n)
76 nmn =ipari(6,n)
77 DO i=1,nsn
78 nn0=intbuf_tab(n)%NSV(i)
79 IF(mass(nn0)==0)THEN
81 . msgtype=msgerror,
82 . anmode=aninfo_blind_1,
83 . c1='INTERFACE TYPE7',
85 . c2='INTERFACE TYPE7',
86 . c3=titr,c4='SECONDARY',
87 . i2=itab(nn0))
88 ENDIF
89 ENDDO
90 ELSE
91 IF(nty==16.AND.ilagm==1) THEN
92 ign =ipari(36,n)
93 nrtm =ipari(4,n)
94 nsn =ipari(5,n)
95 nmn =ipari(6,n)
96 DO i=1,nsn
97 nn0=igrnod(ign)%ENTITY(i)
98 IF(mass(nn0)==0)THEN
100 . msgtype=msgerror,
101 . anmode=aninfo_blind_1,
102 . 'INTERFACE TYPE7',
104 . c2='INTERFACE TYPE7',
105 . c3=titr,c4='SECONDARY',
106 . i2=itab(nn0))
107 ENDIF
108 ENDDO
109 ENDIF
110 ENDIF
111 ENDDO
112 RETURN
integer, parameter nchartitle
subroutine ancmsg(msgid, msgtype, anmode, i1, i2, i3, i4, i5, i6, i7, i8, i9, i10, i11, i12, i13, i14, i15, i16, i17, i18, i19, i20, r1, r2, r3, r4, r5, r6, r7, r8, r9, c1, c2, c3, c4, c5, c6, c7, c8, c9, prmode)