SUBROUTINE sector1(rholst,rhonow,olast,okeep,rleft,rright,rmax,isect,nrho) USE FileUnits_Module USE region_Module USE fuzzy_Module USE rhovalue_Module IMPLICIT NONE INTEGER irhoen, ithcll, ithsub, isect, j, i, jj, nrho REAL(Kind=WP_Kind) blast, okeep, olast, delrho, rholst, bkeep, rbegin REAL(Kind=WP_Kind) deltamin, deltamax, rhonow, rr, rmax, rleft, rright !#include INTEGER rhosave LOGICAL little,medium,full DATA irhoen/9999/ DATA ithcll/0/,ithsub/0/ DATA little/.false./,medium/.false./,full/.false./ CALL popt('sector ',little,medium,full,ithcll,ithsub) isect=isect+1 IF(iregion=='delves '.or.iregion=='djproj ')THEN blast=0.0d0 bkeep=sqrt(2.0d0**1.5d0*log(1.0d0/okeep)) IF(olast/=0.0d0)THEN IF(olast>=0.9999) olast=.99999 blast=sqrt(2.0d0**1.5d0*log(1.0d0/olast)) delrho=delrho*rholst/(rholst-delrho)*bkeep/blast ELSE delrho=.05d0*rholst*bkeep ENDIF IF(delrhodeltamax*rholst)THEN delrho=deltamax*rholst ENDIF rhonow=rholst+delrho rr=(rholst+rhonow)/2.d0 IF(rrfuzz) nrho=nrho+1 ELSE !----------------------------------------------------------------------- ! Find the next sector in the aph region. ! ! We have just finished a sector, so read in the mid-points of ! the next two sectors ! rholst is the mid-point of the next ! sector and rhonow is the mid-point of the sector after that. !----------------------------------------------------------------------- READ(Ovr_Unit,end=32) nrho,rholst,rhonow IF(little)WRITE(Out_Unit,10) nrho,rholst,rhonow rhosave=nrho nrho=irhoen ENDIF !----------------------------------------------------------------------- ! Compute the left and right boundaries of the sector. ! On entry, rleft and rright are the left and right boundaries of the ! sector that was just integrated. !----------------------------------------------------------------------- IF(isect/=1) rleft=rright rright=(rholst+rhonow)/2.d0 !----------------------------------------------------------------------- ! If this is the first time into this routine we have to find the sector ! which brackets the starting distance, rbegin. !----------------------------------------------------------------------- IF(isect==1.AND.iregion=='aph ')THEN rbegin=rleft rleft=2.0d0*rholst-rright IF(little)WRITE(Out_Unit,'(A,3ES23.15)')'rbegin,rleft,rright=', rbegin,rleft,rright IF(rbegin=rleft.or.ABS(rbegin-rleft)=rleft. !----------------------------------------------------------------------- READ(Ovr_Unit,end=31)nrho,rholst,rhonow IF(nrho==rhosave+1)THEN rhosave=nrho goto 25 ENDIF 20 CONTINUE WRITE(Out_Unit,*)' Error: did not find the next sector' WRITE(Out_Unit,*)' Did you use more than 100 lambda in the' WRITE(Out_Unit,*)' abm part of the code?' STOP 'sector' 25 CONTINUE isect=isect+1 rleft=rright rright=0.5*(rholst+rhonow) IF(full)THEN WRITE(Out_Unit,*)'nrho,rholst,rhonow=',nrho,rholst,rhonow WRITE(Out_Unit,*)'isect,rleft,rright=',isect,rleft,rright ENDIF IF(rbegin