28 SUBROUTINE thcoq_count(NTHGRP2 , ITHGRP , WA_SIZE, INDEX_WA_COQ,
29 . IPARG ,ITHBUF ,SITHBUF )
36#include "implicit_f.inc"
43#include "tabsiz_c.inc"
47 INTEGER,
INTENT(IN) :: SITHBUF
48 INTEGER IPARG(NPARG,*),ITHBUF(SITHBUF)
49 INTEGER,
INTENT(inout) :: WA_SIZE,NTHGRP2
50 INTEGER,
DIMENSION(2*NTHGRP2+1),
INTENT(inout) :: INDEX_WA_COQ
51 INTEGER,
DIMENSION(NITHGR,*),
INTENT(in) :: ITHGRP
57 INTEGER I,J,K,L,II,JJ,N, IH, NG,ITY,MTE,NEL,NFT
58 INTEGER :: J_FIRST,NITER,IAD,NN,IADV,NVAR,,IJK
59 INTEGER,
DIMENSION(NTHGRP2) :: INDEX_COQ
65 index_coq(1:nthgrp2) = 0
73 IF(ityp==3.OR.ityp
THEN
77 DO WHILE((ithbuf(ih+nn)/=ispmd).AND.(ih<iad+nn))
80 IF (ih>=iad+nn)
GOTO 666
89 IF (mte /= 13 .and. mte /= 0)
THEN
91 IF ((mte>=29.AND.mte<=31).OR.
93 . mte == 44.OR.mte == 45.OR.mte == 48.OR.mte>=50)
THEN
95 ELSEIF (mte == 25)
THEN
107 ii = ((ih-1) - iad)*nvar
108 DO WHILE((ithbuf(ih+nn) /= ispmd) .AND. (ih < iad+nn))
111 IF (ih > iad+nn)
GOTO 666
112 wa_size = wa_size + nvar + 1
122 index_coq(niter) = wa_size
128 IF(bool.EQV..true.)
THEN
129 IF( index_coq(i)/=0 )
THEN
139 index_wa_coq(j) = index_coq(j_first)
141 index_wa_coq(j) = j_first
142 DO i=j_first+1,nthgrp2
143 IF( index_coq(i)-index_coq(i-1)>0 )
THEN
145 index_wa_coq(j) = index_coq(i)
151 index_wa_coq(2*nthgrp2+1) = j
subroutine thcoq_count(nthgrp2, ithgrp, wa_size, index_wa_coq, iparg, ithbuf, sithbuf)