28 SUBROUTINE thpout_count(NTHGRP2, ITHGRP, WA_SIZE, INDEX_WA_POUT, IPARG,
33#include "implicit_f.inc"
43 INTEGER,
INTENT(IN) :: SITHBUF
44 INTEGER IPARG(NPARG,*),ITHBUF(SITHBUF)
45 INTEGER,
INTENT(in) :: NTHGRP2
46 INTEGER,
INTENT(inout) :: WA_SIZE
47 INTEGER,
DIMENSION(2*NTHGRP2+1),
INTENT(inout) :: INDEX_WA_POUT
48 INTEGER,
DIMENSION(NITHGR,*),
INTENT(in) :: ITHGRP
53 INTEGER II,I,J,K,L,N,IP,IH,NG,ITY,MTE,LWA,NEL,NFT,KK(3)
54 INTEGER :: J_FIRST,NITER,IAD,NN,IADV,NVAR,ITYP,IJK
55 INTEGER,
DIMENSION(NTHGRP2) :: INDEX_POUT
64 index_pout(1:nthgrp2) = 0
75 DO WHILE (ithbuf(ih+nn) /= ispmd .AND. ih < iad+nn)
78 IF (ih >= iad+nn)
GOTO 666
96 ii = ((ih-1) - iad)*nvar
97 DO WHILE (ithbuf(ih+nn) /= ispmd .AND. ih
100 IF (ih > iad+nn)
GOTO 666
101 wa_size = wa_size + nvar + 1
108 index_pout(niter) = wa_size
115 IF(bool.EQV..true.)
THEN
116 IF( index_pout(i)/=0 )
THEN
126 index_wa_pout(j) = index_pout(j_first)
128 index_wa_pout(j) = j_first
129 DO i=j_first+1,nthgrp2
130 IF( index_pout(i)-index_pout(i-1)>0 )
THEN
132 index_wa_pout(j) = index_pout(i)
138 index_wa_pout(2*nthgrp2+1) = j
subroutine thpout_count(nthgrp2, ithgrp, wa_size, index_wa_pout, iparg, ithbuf, sithbuf)