32 2 NRTM ,IRECT ,GAP_NM ,GAP_M ,
34 4 GAPMAX_M ,GAPSCALE ,MSEGTYP , THKNOD,
39#include "implicit_f.inc"
49 INTEGER NRTM,IRECT(4,*),
50 . MSR(*),NMN,MSEGTYP(*),ITASK
53 . GAP_NM(4,*),GAP_M(*), GAPMSAV(*), THKNOD(NUMNOD),
54 . gapn_m(*),gapmax_m, gapscale, maxdgap_g
58 INTEGER I,J,K,IW,,I2,I3,MG,M,IP,IGTYP,
59 . ,NMNL,NRTMF,NRTML,IERROR
61 .
DIMENSION(:),
ALLOCATABLE :: WA
67 ALLOCATE(wa(numnod),stat=ierror)
68 nmnf = 1 + itask*nmn / nthread
69 nmnl = (itask+1)*nmn / nthread
70 nrtmf = 1 + itask * nrtm / nthread
71 nrtml = (itask+1) * nrtm / nthread
79#include "vectorize.inc"
82 wa(m)=half*gapscale*thknod(m)
88#include "vectorize.inc"
90 IF (msegtyp(i)==0)
THEN
99#include "vectorize.inc"
102 wa(m) =
min(wa(m),gapmax_m)
108#include "vectorize.inc"
114 gap_m(i) =
max(gap_m(i),wa(m))
118#include "vectorize.inc"
121 maxdgap_l =
max(maxdgap_l,gap_m(i)-gapmsav(i))
128 maxdgap_g =
max(maxdgap_l,maxdgap_g)
129#include "lockoff.inc"
subroutine i25gap3(itask, nrtm, irect, gap_nm, gap_m, nmn, msr, gapn_m, gapmax_m, gapscale, msegtyp, thknod, gapmsav, maxdgap_g)