SUBROUTINE sector (rholst, rhonow, rleft, rright, rmax, isect, nrho) USE Numeric_Kinds_Module ! W A R N I N G W A R N I N G W A R N I N G W A R N I N G ! This code is not ready to propagate in the delves region. ! W A R N I N G W A R N I N G W A R N I N G W A R N I N G ! USE FileUnits_MODULE USE region_MODULE USE Fuzzy_MODULE USE rhovalue_MODULE IMPLICIT NONE INTEGER irhoen, ithcll, ithsub, isect, j, i, jj, nrho, rhosave LOGICAL little, medium, full REAL(Kind=WP_Kind) blast, bkeep, okeep, olast, delrho, rholst REAL(Kind=WP_Kind) deltamin, deltamax, rhonow, rr, rmax, rleft, rright, rbegin SAVE DATA irhoen/9999/ DATA ithcll/0/,ithsub/0/ DATA little/.false./,medium/.false./,full/.FALSE./ CALL popt('sector ',little,medium,full,ithcll,ithsub) little=.true. isect=isect+1 !IF(little)THEN ! WRITE(Out_Unit,'(///A)')"Starting Sector" ! WRITE(Out_Unit,'(A,A)')"Iregion=",Iregion ! WRITE(Out_Unit,'(10x,A,9x,A,10x,A,9x,A,11x,A,3x,A,4x,A)')'rholst', 'rhonow', 'rleft', 'rright', 'rmax', 'isect', 'nrho' ! WRITE(Out_Unit,'(1x,5es15.7,2i8)')rholst, rhonow, rleft, rright, rmax, isect, nrho !ENDIF 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)