*/ */ use *set shift to define different margins for odd and even pages */ in the revised NJOY manual. this is nice for printing, but not so */ nice for online viewing of the pdf file, or ... */ */ ... use *set noshift to center the NJOY manual text on the page. *set shift */ *set noshift */ *ident up1 */ 21mar2013 */ - acefc */ - coding in subroutine first may read a TAB1 function without */ checking if the allocated space is sufficient. revise to */ make sure the minimum necessary space is allocated. *i acefc.225 integer::nwtst,newnw *d acefc.572 if (nsix.gt.0) then call findf(matd,6,0,nendf) isix=0 newnw=0 do while (isix.lt.nsix) isix=isix+1 call contio(nendf,0,0,scr,nb,nw) nk=n1h do ik=1,nk call tab1io(nendf,0,0,scr,nb,nw) law=l2h nwtst=6+2*(nint(scr(5))+nint(scr(6))) if (nwtst.gt.nwscr) then newnw=nwtst endif do while (nb.ne.0) call moreio(nendf,0,0,scr,nb,nw) enddo call skip6(nendf,0,0,scr,law) enddo enddo if (newnw.gt.nwscr) then deallocate(scr) nwscr=newnw allocate(scr(nwscr)) endif call repoz(nendf) call findf(matd,6,0,nendf) endif *ident up1m */ 21mar2013 */ - No NJOY2012 Manual changes are associated with ident up1. *ident up2 */ 06may2013 */ - groupr */ - coding in njoy99.379 to replace use of an expansion for the */ complementary error function with the more accurate SLATEC */ "erfc" routine was implemented incorrectly. */ - we fix that here, plus delete some no longer needed code. */ - thanks to NRG/Petten (Hogenbirk) and LLNL (Mattoon) for */ uncovering this error. *d groupr.10363,groupr.10368 *d groupr.10433,groupr.10434 bot=rp4*(1-erfc(rc))-rc*exp(r4) *d groupr.10440,groupr.10442 top=rl*exp(r3)-rh*exp(r4)-rp4*(erfc(rh)-erfc(rl)) *d groupr.10567,groupr.10585 *d groupr.10618,groupr.10621 fa(1)=1-erfc(abs(aa)) if (aa.lt.zero) fa(1)=-fa(1) fb(1)=1-erfc(abs(bb)) if (bb.lt.zero) fb(1)=-fb(1) *ident up2m */ 06may2013 */ - groupx */ - updates to the GROUPR chapter of the NJOY2012 manual */ consistent with *ident up2's code changes. *d groupx.50 2012.2. *d groupx.4320,groupx.4323 Eqs.~\ref{Eq86} - \ref{Eq115}). The routine uses the SLATEC version of the reduced complementary error function from the NJOY2012 math module. The resulting integral is returned *ident up3 */ 24may2013 */ - mixr */ - need to make a number of variables global. */ - original deficiency reported by Studsvik/Idaho (Wemple). */ - while we're at it, change from hardwired dimension and do loop */ limits to parameter statements. */ - allows for easy future increase on input limits. */ - fix overloading of hollerith and real variables so User file 1 */ comment appears properly in the output file. *i mixr.8 ! global variables integer::ntape integer,parameter::nninmx=10 integer,parameter::nmtmx=20 integer,parameter::nmatmx=nninmx integer,dimension(nninmx)::jtape,nrt,npt,irt,ipt,ip1t,ip2t,nbt,nwt *d mixr.31 ! ... continue for nnin<=nninmx (=10) input units *d mixr.34,mixr.35 ! mtn list of nmt<=nmtmx (=20) mt numbers for ! the output reactions *d mixr.38,mixr.39 ! matn, list of nmat<=nmatmx (=nninmx=10) pairs (matn,wtn) ! wtn of material numbers and associated weighting factors *d mixr.50 ! des description (66 char max) *i mixr.56 integer,parameter::mxlna=300000 *d mixr.59 integer::mtd,je,ne,jend,idis *d mixr.62,mixr.66 character(66)::strng character(4)::str(17) integer,dimension(nninmx)::nin integer,dimension(nmtmx)::mtn integer,dimension(nmatmx)::matn,jscr real(kr),dimension(nmatmx)::wtn real(kr),dimension(mxlna)::a *i mixr.68 equivalence(str(1),des(1)) *d mixr.79 *d mixr.84 do i=1,nninmx *d mixr.87,mixr.88 read(nsysi,*) nout,(nin(i),i=1,nninmx) do i=1,nninmx *d mixr.91 do i=1,nmtmx *d mixr.94,mixr.95 read(nsysi,*) (mtn(i),i=1,nmtmx) do i=1,nmtmx *d mixr.98 do i=1,nmatmx *d mixr.101,mixr.102 read(nsysi,*) (matn(i),wtn(i),i=1,nmatmx) do i=1,nmatmx *d mixr.109 read(strng,'(16a4,a2)') (str(i),i=1,17) *d mixr.372 ! This version will keep track of pointers for up to nninmx units. *d mixr.381 integer::nwtot,nr,np,ip1,ip2,ir,ip,i,ktape,ln *d mixr.384,mixr.385 *ident up3m */ 24may2013 */ - mixx */ - updates to the MIXR chapter of the NJOY2012 manual */ consistent with *ident up3's code changes. *d mixx.48 2012.3. *d mixx.71 ! ... continue for nnin<=nninmx (=10) input units *d mixx.74,mixx.75 ! mtn list of nmt<=nmtmx (=20) mt numbers for ! the output reactions *d mixx.78,mixx.79 ! matn, list of nmat<=nmatmx (=nninmx=10) pairs (matn,wtn) ! wtn, of material numbers and associated weighting factors *d mixx.90 ! des description (66 char max) *d mixx.101 Note that there is a limit of \cword{nninmx}, currently 10, input files. *d mixx.104 The code currently allows up to \cword{nmtmx}, currently 20, *d mixx.279 is initialized for up to \cword{nmtmx} input TAB1 records on up to \cword{nninmx} input tapes *d mixx.297 tables will be found in the subroutine, all with dimension \cword{nninmx}. *ident up4 */ 7jun2013 */ - groupr */ - need to make some local variables global for the flux calculator; */ - need to make some fixed arrays allocatable (fixed size was ok */ when nsigz was restricted to .le. 10). */ - these deficiencies reported by Studsvik/Idaho (Wemple). */ - need global initialization test for panel; *d groupr.24 real(kr)::felo,fehi,sigpot,alpha2,alpha3,beta,sam,gamma *i groupr.87 real(kr),dimension(:),allocatable::falo,fahi integer::ipan *d groupr.171,groupr.172 ! fehi break between computed flux and bondarenko flux ! (must be in the resolved resonance range) *i groupr.359 ipan=0 *d groupr.361 *i groupr.944 if (allocated(falo)) then deallocate(falo) deallocate(fahi) endif *d groupr.3134 read(nsysi,*) fehi,sigpot,nflmax,ninwt,jsigz,& *d groupr.3139 &'' compute flux...fehi, sigpot, nflmax ='',f9.1,f9.2,i8/& *d groupr.3141 fehi,sigpot,nflmax,-ninwt,jsigz *d groupr.3469,groupr.3470 ! The flux is computed between felo (lowest group bound) and ! fehi (must be in resolved range) or until nflmax points *d groupr.3497 real(kr)::e,enext,en,ebot,f1,ej,ejp,f2,f3,f4 *d groupr.3501 real(kr),dimension(:),allocatable::fout *i groupr.3522 nl=lord+1 if (nl.eq.1.and.nsigz.gt.1) nl=2 nfv=1+nl*nsigz+1 allocate(fout(nfv)) *d groupr.3525,groupr.3527 *d groupr.3548,groupr.3550 *d groupr.3558,groupr.3560 felo=egn(1) ebot=felo if (felo.lt.tenth) felo=tenth *d groupr.3581 enext=felo *d groupr.3584 do while (e.lt.fehi.and.ne.lt.nemax) *d groupr.3587 if (e.gt.fehi) e=fehi *d groupr.3599,groupr.3602 fehi=e !--assume nr flux at fehi and above !--calculate contributions below fehi for nr flux *d groupr.3611,groupr.3612 if (e.ge.alpha(k)*fehi) then f1=(1-alpha(k)*fehi/e)*wtf/(1-alpha(k)) *d groupr.3766 &1x,i6,'' points'')') felo,fout(1),net-net1 *i groupr.3816 deallocate(fout) *d groupr.3889 if (e.gt.el*(1-small).and.e.lt.en*(1+small)) go to 230 *d groupr.4050 if (matd.ne.matl.or.mfd.ne.mfl.or.mtd.ne.mtl.or.ipan.eq.0) then ipan=1 *d groupr.4589 *d groupr.4592 save ip *d groupr.4597,groupr.4599 if (allocated(falo)) then deallocate(falo) deallocate(fahi) endif allocate(falo(nfv)) allocate(fahi(nfv)) call finda(1,falo,nfv,nflx,wtbuf,nbuf) call finda(2,fahi,nfv,nflx,wtbuf,nbuf) enext=falo(1) *d groupr.4613,groupr.4614 call finda(ip,falo,nfv,nflx,wtbuf,nbuf) call finda(ip+1,fahi,nfv,nflx,wtbuf,nbuf) *d groupr.4619 do while (e.ge.fahi(1).and.ip.lt.nfp) *d groupr.4621 falo(i)=fahi(i) *d groupr.4624 call finda(ip,fahi,nfv,nflx,wtbuf,nbuf) *d groupr.4634 call terp1(falo(1),falo(l),fahi(1),fahi(l),e,flux(iz,il),2) *d groupr.4637,groupr.4638 call terp1(falo(1),falo(nfv),fahi(1),fahi(nfv),e,xtot,2) enext=fahi(1) *ident up4m */ 7jun2013 */ - groupx */ - updates to the GROUPR chapter of the NJOY2012 manual */ consistent with *ident up4's code changes. *d groupx.836 lower limit of the first group to a specified energy \cword{fehi} or *d groupx.2539,groupx.2540 ! fehi break between computed flux and bondarenko flux ! (must be in resolved resonance range) *d groupx.3031 of parameters given and their values. The parameters \cword{fehi} *d groupx.3546 *d groupx.3728,groupx.3729 A lower energy limit, \cword{felo}, is chosen, and the cross sections are read into storage until a maximum energy, \cword{fehi}, or a *d groupx.3733 is then solved from the break energy down to \cword{felo}. The *d groupx.3736 calculation is finished, fluxes from $10^{-5}$ eV to \cword{felo} are *d groupx.3738 for the Bondarenko option. From \cword{felo} to the energy break point, *ident up5 */ 7aug2013 */ - groupr */ - make unr deallocation conditional (AWE, Cornock) */ - resolve flux calculator issues (Studsvik, Wemple) */ - include additional test in getfwt when searching for e on ninwt */ after 200 continue to overcome possible near duplicate energies */ at the top of the energy mesh; */ - if test revision in up4.68 needs to occur for line groupr.3883; */ - move coding to update el, wl and xl within the 210 continue loop */ to assure correct values are passed to terp1 after 230 continue. *d groupr.892 if (allocated(unr)) deallocate(unr) *i groupr.3529 scr1=0 *i groupr.3563 scr1=0 scr2=0 *i groupr.3823 if (allocated(scr1)) deallocate(scr1) if (allocated(scr2)) deallocate(scr2) *i groupr.3881 if (abs(e-el).lt.el*small.and.en.lt.0) then w=wl xc=xl enext=en go to 250 endif *d groupr.3883 if (e.gt.el*(1-small).and.e.lt.en*(1+small)) go to 230 *i groupr.3886 el=en wl=wn xl=xn *d groupr.3890,groupr.3892 *ident up5m */ 7aug2013 */ - no manual changes *ident up6 */ 8aug2013 */ - purr */ - correct unit number variable used in tab1io and moreio calls */ for urr energy-dependent scattering radius data (Trkov, IJS). *d purr.769 call tab1io(nendf,0,0,arry(inow),nb,nw) *d purr.772 call moreio(nendf,0,0,arry(jj),nb,nw) *ident up6m */ 8aug2013 */ - no manual changes *ident up7 */ 8aug2013 */ - samm */ - need to make a test for possible energy-dependent scattering */ radius more specific (Trkov, IJS). *d samm.271 if (lru.eq.1 .and. lrf.ne.2) call error('s2sammy',& *ident up7m */ 8aug2013 */ - no manual changes *ident up8 */ 8aug2013 */ - groupr */ - make sure we write the last multigroup record to ngout2 even */ when its data are zero, as has always been done in the past */ (issue reported by Martin, Sandia). */ - an improvement in moving from njoy99 to njoy2012 was a */ little too zealous is skipping over groups with zero data. *d groupr.727 if (elo.ge.emaxx.and.ig.ne.ngi) go to 580 *ident up8m */ 8aug2013 */ - no manual changes *ident up9 */ 22aug2013 */ - groupr */ - provide more robust testing for initial and final multigroup number */ in getdis. previous coding could exceed the maximum multigroup and */ produce spurious results (issue reported by Sublet, CCFE). *i groupr.7502 integer::ignow,ngnow,ngn1 *i groupr.7556 ngn1=ngn+1 *i groupr.7589 ngnow=1 ignow=0 *i groupr.7600 if (ng.gt.ngn1) then ng=ngn1 ig=ignow do il=1,nl ff(il,ng)=0 enddo go to 465 endif ngnow=ng *i groupr.7607 if (iglo+ig.gt.ngn1) then ng=ngnow ig=ig-1 go to 465 endif ignow=ig *ident up9m */ 22aug2013 */ - no manual changes *ident up10 */ 3sept2013 */ - gaspr */ - need better checking for allocatable arrays when processing */ files with multiple temperatures (Vanhanen, Aalto U) *i gaspr.474 if (allocated(egas)) then deallocate(egas) deallocate(sgas) endif *ident up10m */ 3sept2013 */ - no manual changes *ident up11 */ 4sept2013 */ - groupr */ - need more storage space for tmp in getsed (Vanhanen, Aalto U). */ - new algorithm starts with a large allocation request and */ tests the allocation status, reducing the array size until */ the request is successful. */ - also tweak identical error message text to make them unique. *i groupr.9901 integer::ier *d groupr.9920,groupr.9921 ier=1 ntmp=100000 do while (ier.ne.0) if (allocated(tmp)) deallocate(tmp) allocate(tmp(ntmp),stat=ier) if (ier.ne.0) then ntmp=ntmp/2 endif enddo *d groupr.9940 'storage for tmp exceeded1',' ') *d groupr.10048 'storage for tmp exceeded2',' ') *ident up11m */ 4sept2013 */ - no manual changes *ident up12 */ 5sept2013 */ - covr */ - need to make sure the array we deallocate was really allocated. */ (Vanhanen, Aalto U). *d covr.462,covr.463 if (allocated(x))deallocate(x) if (allocated(y))deallocate(y) *ident up12m */ 5sept2013 */ - no manual changes *ident up13 */ 19sept2013 */ - errorr */ - increase nwds in covout to match njoy99. */ - increase scr space in colaps to always be at least npage+50. */ - fixes unexplained stop reported by Vanhanen, Aalto U. *d errorr.6900 nwds=10000000 *i errorr.8956 if (nwscr.lt.npage+50) nwscr=npage+50 *ident up13m */ 19sept2013 */ - no manual changes *ident up14 */ 19sept2013 */ - purr */ - increase nsamp to match njoy99. */ - make sure 1 .ge. ibin .ge. nsamp in unrest *i purr.54 ! message flags integer::mflg1,mflg2 *d purr.131 nsamp=10000 *i purr.276 mflg1=0 mflg2=0 *i purr.1727 character(60)::strng *i purr.2189 if (ibin.le.0) then if (mflg1.eq.0) then mflg1=1 write(strng,'(''reset ibin=1, consider larger nsamp'',& &'' or smaller nbin'')') call mess('purr',strng,'') endif ibin=1 endif *i purr.2190 if (ibin.gt.nsamp) then if (mflg2.eq.0) then mflg2=1 write(strng,'(''reset ibin=nsamp,'',& &'' consider smaller nbin'')') call mess('purr',strng,'') endif ibin=nsamp endif *ident up14m */ 19sept2013 */ - correct a typo in the text and related sample output in Section 1; */ - add a new warning message to Section 7. *d purx.101 piece of a PURR output listing shows 16 ladders being processed for *i purx.765 \item[\cword{message from purr---reset ibin=1 (or =nsamp), consider ...}] ~\par The \cword{nbin} size specified is too large for PURR's internal arrays. Either decrease the input \cword{nbin} or increase the PURR's \cword{nsamp} variable. *ident up15 */ 26sept2013 */ - samm */ - there is some confusion in the coding between the maximum */ Legendre order and the number of Legendre orders. This */ change also fixes the message about the maximum Legendre */ order from reconr (rem). *d samm.1415 ncoef=lllmax *ident up15m */ 26sept2013 */ - no manual changes *ident up16 */ 26sept2013 */ - reconr */ - delete coding that closes unit nscrl in rexsx. this unit holds */ elastic scattering (mf4/mt2) data that needs to be accessed if */ the logical variable, "Want_Angular_Dist" is changed to .true. */ - still need to close this unit though ... add coding in reconr */ to do so (ack). *i reconr.145 logical there *i reconr.378 !-- careful, unit number must match nscrl from resxs. inquire(unit=16,exist=there) if (there) call closz(16) *d reconr.2541 *ident up16m */ 26sept2013 */ - no manual changes *ident up17 */ 01oct2013 */ - endf */ - allow more flexibility in findf when searching a gendf tape. *d endf.1544,endf.1545 *ident up17m */ 01oct2013 */ - no manual changes *ident up18 */ 02oct2013 */ - errorr */ - if the user groupr structure extends beyond the range of the */ weight function, then the grpav routine may return with "nan" */ for some cross sections. add coding to (i) warn the user of */ the group structure/weight function mis-match, and (ii) set */ those multigroup cross sections to zero. */ - fixes "nan" issue reported by Vanhanen, Aalto U. */ - indicies used in grpav's scr aren't quite right when the number */ of union groups exceeds npage, we fix them now (ack). *i errorr.38 integer::mwtf *i errorr.452 mwtf=0 *d errorr.8665 integer::ngg=0 *d errorr.8750,errorr.8751 scr(nw+1)=0 nwds=nt+nz+nunion+1+ngg+1 *d errorr.8852 if (ans(1,1,1).ne.zero) then ans(1,1,2)=ans(1,1,2)/ans(1,1,1) else ans(1,1,2)=zero endif *i errorr.10498 !--warn User when the weight function is zero; it most likely means ! the xs energy range extends beyond the weight function energy ! range. if (wtf.eq.zero.and.mwtf.eq.0) then mwtf=1 call mess('egtwtf',& 'xs energy range exceeds weight function range',& 'some multgroup data may be suspect') endif *ident up18m */ 02oct2013 */ - add a new warning message to Section 16. *i errorx.3286 \item[\cword{message from egtwtf---xs energy range exceeds ...}] ~\par The cross section multigroup energy range extends beyond the energy range defined for the weight function. Cross section values in the undefined region will be wrong or \cword{nan}. *ident up19 */ 03oct2013 */ - util */ - delete a couple of redundant lines in closz *d util.229,util.230 *ident up19m */ 03oct2013 */ - no manual changes *ident up20 */ 08oct2013 */ - acer */ - the apparent number of photons can differ for jobs using binary */ tapes versus ascii tapes (Trumbull, KAPL). */ - loss of significant digits when working with ascii tapes makes */ this tricky, particularly when trying to extract the original */ primary photon energy from the sum of primary photon plus */ incident particle energy. This patch works for 1h which has */ a single primary photon over the 20 MeV incident neutron energy */ range while also seeing the two distinct secondary photons of */ 2.112370 MeV and 2.11238 MeV in 50V mt16. */ - NOTE: we strongly recommend use of binary tapes in all njoy */ jobs to maximize the number of significant digits that are */ saved when passing pendf data among the various modules. *d acefc.7846 real(kr),parameter::eps=4.e-6_kr *d acefc.8314 if (r.le.eps) go to 111 *ident up20m */ 08oct2013 */ - no manual changes *ident up21 */ 09oct2013 */ - samm */ - make sure lllmax is defined. needed for array allocation if the */ "Want_Angular_Dist" logical variable is changed from its default */ false value to true. we start with a value believed to always be */ large enough, but after the real, problem dependent, value is */ determined also check that the initial allocation was sufficient. *i samm.31 integer,parameter::lllmaxx=10 *d samm.552 if (nmtres.gt.0) then lllmax=lllmaxx call allo endif *i samm.2078 if (lllmax.gt.lllmaxx) then call error('lmaxxx','need larger lllmaxxx','') endif *ident up21m */ 09oct2013 */ - no manual changes *ident up22 */ 21oct2013 */ - purr */ - need to make sure "init" in unrest is reset to zero when */ executing purr multiple times in the same job, or when */ processing multiple materials (issue reported by Koscheev, */ IPPE). */ - need additional tests to make sure we deallocate all previously */ defined allocatable arrays prior to exiting or prior to reallo- */ cating them with the current nbin, ntemp and nsig0 values. */ - rewind the scratch tape before processing each matd. */ - prior to this last patch, if multiple matd's are processed in */ the same purr job and the ntemp, nsigz and nbin values are the */ same for the first and later matd's it was the first matd's */ data that were retrieved from the scratch tape. *i purr.12 integer::init *i purr.171 init=0 *i purr.173 call repoz(-nscr) *i purr.177 deallocate(sigpl) *i purr.201 if (allocated(tabl)) then deallocate(tabl) deallocate(tval) deallocate(fis) deallocate(cap) deallocate(els) endif *d purr.204,purr.211 if (.not.allocated(er)) allocate(er(nermax)) if (.not.allocated(gnr)) allocate(gnr(nermax)) if (.not.allocated(gfr)) allocate(gfr(nermax)) if (.not.allocated(ggr)) allocate(ggr(nermax)) if (.not.allocated(gxr)) allocate(gxr(nermax)) if (.not.allocated(gt)) allocate(gt(nermax)) if (.not.allocated(es)) allocate(es(nsamp)) if (.not.allocated(xs)) allocate(xs(nsamp)) *d purr.262 if (allocated(heat)) deallocate(heat) allocate(heat(4,nunr,ntemp)) *d purr.344 if (allocated(c)) deallocate(c) allocate(c(nc)) *d purr.346 if (allocated(d)) deallocate(d) allocate(d(nd)) *i purr.634 if (allocated(tabl)) then deallocate(tabl) deallocate(tval) deallocate(er) deallocate(gnr) deallocate(gfr) deallocate(ggr) deallocate(gxr) deallocate(gt) deallocate(es) deallocate(xs) deallocate(fis) deallocate(cap) deallocate(els) endif if (allocated(heat)) deallocate(heat) if (allocated(c)) deallocate(c) if (allocated(d)) deallocate(d) *d purr.1728 *ident up22m */ 21oct2013 */ - no manual changes *ident up23 */ 24oct2013 */ - samm */ - revise per updates in the ORNL SAMRML code. */ - impacts the RML resonance calculations for */ endf/b-vii.1 35Cl (rem). *d samm.1809 ex=abs(eres(ires,ier)-echan(j,ig,ier)) *d samm.3256 *d samm.6355 if (psmall(k,ier).ne.zero) then *d samm.6358,samm.6360 *ident up23m */ 24oct2013 */ - no manual changes *ident up24 */ 18mar2014 */ - acedo */ - fix error message if desired temperature is not found on */ the input tape (Trkov, IAEA); */ - need additional logic to update the xss(lsig...) array if */ multiple sub-sections exist for a specific mf=10/mt (ack). */ - previously the code could crash or, depending upon compiler */ options, run silently to completion. */ - NOTE: If code had run to completion, the resulting ACE */ file will correctly include all sub-sections but */ the standard output will only include the first */ sub-section. */ - increase nmax (the maximum number of mt values that can be */ processed) from 100 to 350. needed when processing selected */ eaf-2010 files. */ - also check if nmax is exceeded; current code runs silently */ to completion but the .##y file contains invalid pointers */ causing an immediate mcnp crash. *d acedo.91 if (math.lt.0)& *d acedo.121 nmax=350 *i acedo.180 if (j.gt.nmax) call error('acedos','too many reactions',& 'need larger nmax') *i acedo.250 if (j.gt.nmax)& call error('acedos','too many reactions',& 'need larger nmax') if (is.ne.ns) xss(lsig-1+j)=l *ident up24m */ 18mar2014 */ - add a new warning message to Section 19. *i acex.2773 \item[\cword{error in acedos***too many reactions, need ...}] ~\par The number of mt values in the ACE output file exceeds acedos's internal limits. Increase the value of \cword{nmax}. *ident up25 */ 07apr2014 */ - errorr */ - we failed to allocate egn for all possible multigroup options */ (reported by Becker, KIT) *i errorr.9985 if(ign.eq.16)allocate(egn(ngn+1)) if(ign.eq.17)allocate(egn(ngn+2)) *i errorr.9999 allocate(egn(ngn+1)) *ident up25m */ 07apr2014 */ - no manual changes *ident up26 */ 07apr2014 */ - groupr */ - cm2lab is running out of space (Orsi, ENEA) */ - an if test in f6cm can be true due to round-off, */ causing epnext to be set to zero and leading to */ an infinite loop in cm2lab. Make the test less */ sensitive. *d groupr.6436 if(epmax*up.lt.xc*e) epn=e*(sqrt(epmax/e)-sqrt(xc))**2 *ident up26m */ 07apr2014 */ - no manual changes *ident up27 */ 08apr2014 */ - purr */ - a simple typo when reading urr data from endf/b-vi 233u */ (the only Adler-Adler format evaluation left, we believe). *d purr.719 call listio(nendf,0,0,a(iscr),nb,nw) *ident up27m */ 08apr2014 */ - no manual changes *ident up28 */ 15apr2014 */ - heatr */ - need a patch in h6cm similar to what we did in groupr's */ f6cm (ack). *d heatr.3363 if(epmax*up.lt.xc*e) epn=e*(sqrt(epmax/e)-sqrt(xc))**2 *ident up28m */ 15apr2014 */ - no manual changes *ident up29 */ 29apr2014 */ - groupr */ - we increased tmp array space in up11 but still need more */ (for jeff-3.2 238u, for example). */ - a difference between njoy2012 and njoy99 is that njoy2012, */ by default (ismooth=1), will expand the low energy portion */ of emission spectra defined in histogram format. we insert */ additional energy points to allow the spectrum to more closely */ follow a sqrt(E) profile. when processing delayed neutron */ spectra (mt=455 only, spectra from other mt values are ok) */ we failed to update a pointer needed to properly define the */ starting location in the tmp array for the now larger TAB1 */ function. */ - both issues reported by wemple/studsvik. */ - we also include additional array bounds tests to assure the */ new TAB1 function fits within the allocated tmp space (ack). *d up11.13 ntmp=250000 *i groupr.9989 if (l1+9+2*mm.gt.ntmp) call error('getsed',& 'storage for tmp exceeded3',' ') *i groupr.10060 if (m1+9+2*mm.gt.ntmp) call error('getsed',& 'storage for tmp exceeded4',' ') *i groupr.10073 m=m1+8+2*mm *ident up29m */ 29apr2014 */ - no manual changes *ident up30 */ 1may2014 */ - groupr */ - when dealing with astrophysics (1.e9 degK) temperatures */ the target nuclide za value was set to zero on the output */ gendf tape. also at these highly elevated temperatures, */ unresolved resonance data, if present, was ignored. */ (Conlin, LANL) *d groupr.472 diff=100000000 *ident up30m */ 1may2014 */ - no manual changes *ident up31 */ 1may2014 */ - acefc */ - need more scratch space in acelcp (ack). *d acefc.8768 integer,parameter::nwscr=500000 *ident up31m */ 1may2014 */ - no manual changes *ident up32 */ 2may2014 */ - groupr */ - the "extending lin-lin as sqrt(E) ..." algorithm in getmf6 */ can produce a zero only emission spectrum under the rare */ condition of an original spectrum defined at two energy */ points, where there is a non-zero probability at zero */ emission energy and zero probability at the maximum allowed */ non-zero energy. subsequently an infinite loop condition */ may occur. */ - we expand the existing "patching low-energy distribution ..." */ algorithm to avoid this issue. (Orsi, ENEA) *d groupr.5822,groupr.5829 if (nn.eq.2.and.lep.eq.2) then j=0 if (tmp(ilo+6+ncyc).lt.tmp(ilo+1)/(awr+1)**2) then j=1 tmp(ilo+7)=0 tmp(ilo+8)=tmp(ilo+1)/(awr+1)**2 tmp(ilo+9)=2/tmp(ilo+8) elseif (tmp(ilo+7).ne.0.and.tmp(ilo+9).eq.0) then j=1 tmp(ilo+9)=tmp(ilo+7) tmp(ilo+7)=0 endif if (j.ne.0) then write(nsyso,'('' patching low-energy distribution at'',& &1p,e10.3)')tmp(ilo+1) endif endif *ident up32m */ 2may2014 */ - no manual changes *ident up33 */ 27jun2014 */ - thermr */ - reduce the delta-temperature tolerance when comparing the user */ requested temperature versus the temperature being read from */ the input tape; allows for creating S(a,b) files on a finer */ temperature grid (ack). */ - a similar change follows in up34 for acefc and aceth. */ ***************************************************************** */ *** NOTE: This tighter tolerance means that test01 with its *** */ *** 300 degK input temperature will fail. We change it *** */ *** to 296 degK to better match the temperature found *** */ *** on the S(a,b) input tape. This will cause changes *** */ *** in the test01 output files. *** */ ***************************************************************** *d thermr.1654 do while (abs(t-temp).gt.temp/500) *ident up33m */ 27jun2014 */ - no manual changes *ident up34 */ 02jul2014 */ - acefc & aceth */ - reduce the delta-temperature tolerance when comparing the user */ requested temperature versus the temperature being read from */ the input tape; allows for creating S(a,b) files on a finer */ temperature grid. */ - these changes made in coordination with up33 (ack). */ - aceth */ - current coding to get nxs(1) in continuous formatted files */ is off by one. a comparison with 99.113, when continuous kernel */ file capability was first introduced, shows a couple of code */ differences which we eliminate now. *d acefc.237 real(kr),parameter::ttol=1 *i aceth.59 real(kr)::delta *i aceth.66 real(kr),parameter::ttol=1 *d aceth.117 delta=ttol do while (delta.ge.ttol) *d aceth.124,aceth.126 delta=abs(temp-tempd) if (delta.ge.ttol) call tomend(nin,0,0,xs) *d aceth.662 len2=len2+itxe-1 *d aceth.664 itce=len2-1 *ident up34m */ 02jul2014 */ - no manual changes *ident up35 */ 05sept2014 */ - unresr */ - eliminate a fixed size array allocation with a calculation */ of the true needed space (issue reported by Orsi, ENEA) *d unresr.178 nb=12+nsigz+nunr*(1+5*nsigz) *ident up35m */ 05sept2014 */ - no manual changes *ident up36 */ 05sept2014 */ - groupr */ - add missing allocation statements in gengpn (issue reported */ by Wemple, Studsvik). */ - need more space in getgyl for some JEFF-3.2 evaluations */ (issue reported by Orsi, ENEA). *i groupr.2689 ngp=ngn+1 allocate(egn(ngp)) *i groupr.2696 ngp=ngn+1 allocate(egn(ngp)) *i groupr.2718 ngp=ngn+1 allocate(egn(ngp)) *i groupr.2725 ngp=ngn+1 allocate(egn(ngp)) *i groupr.2732 ngp=ngn+1 allocate(egn(ngp)) *d groupr.8842 ntmp=99000 *ident up36m */ 05sept2014 */ - no manual changes *ident up37 */ 05sept2014 */ - resxsr */ - fix a couple of njoy99-to-njoy2012 conversion issues */ (reported by Wemple, Studsvik). *d resxsr.411 write(nscr) ha(1),(a(mult+i),i=iscr,iscr+n),ia(nwds-1),ia(nwds) *i resxsr.478 call repoz(-nscr) *d resxsr.498 write(nout)(a(k),k=1,nwds) *ident up37m */ 05sept2014 */ - no manual changes *ident up38 */ 18sept2014 */ - groupr */ - revise argument list passed in displa to be consistent with */ the declared array dimensions (resolves halt in g95 if compiled */ with array bounds checking turned on); */ - NOTE: problems run with an executable produced by the Intel */ Fortran compiler yield the same matricies with or */ without this patch, as the original array allocation */ is correct for the user's problem size. */ - expand the logic in getgyl that checks for constant production */ over low energies to account for histogram interpolation. */ - include logic in getgyl that sets econst to zero when dealing */ with file 13 photon data. *d groupr.750 call displa(ig,prod,nl,nz,jconst,ig2lo,igzero,nlg,ngi) *i groupr.8907 !--if histogram interpolation, start with e equal ! to the second energy point if (nint(tmp(l+7)).eq.1) e=tmp(ll+3) *i groupr.8914 else econst=zero *ident up38m */ 18sept2014 */ - no manual changes *ident up39 */ 18sept2014 */ - acefc */ - coding introduced in up1 to determine the necessary allocation */ for scr when reading file 6 tab1 records is incomplete. this */ modification assures that the largest tab1 size is identified. */ - this issue identified while processing a candidate 235u cielo */ file from ornl (Leal). *d up1.22,up1.24 newnw=max(nwscr,nwtst,newnw) *ident up39m */ 18sept2014 */ - no manual changes *ident up40 */ 14oct2014 */ - reconr */ - correct a message text typo (Koning, Petten). */ - successful execution of the cross section calculation algorithm */ in csunr2 can depend upon failing a "do while" test where we */ expect two real numbers to be equal. due to finite computer */ precision this test can remain true when the comparison is */ false. we revise the test to eliminate this very rare */ false positive condition (Wemple, Studsvik). *d reconr.1902 call mess('lunion',text,'adjusted using jump in xsec') *d reconr.4198 do while (res(i1+6).le.e-small) *ident up40m */ 14oct2014 */ - no manual changes *ident up41 */ 04dec2014 */ - acefc */ - previous coding assumes if an mf3/mt5 section exists, then light */ particle emission spectra will be found in mf6/mt5. */ - if this is not true, pointers in the ace file will be */ incorrect and a subsequent viewr job to plot the ace data */ can enter an infinite write loop (reported by Koning, Petten). */ - we provide coding revisions that define light particle flags */ while processing mt=5 to overcome this deficiency. */ - include an extra contio to up1 coding to read the end-of-section */ record when checking for the laregest tab1 function in mf6. *i up1.29 call contio(nendf,0,0,scr,nb,nw) !read eos record *i acefc.43 integer::mt5n,mt5p,mt5d,mt5t,mt5he3,mt5a *i acefc.312 mt5n=1 !default is no neutron production in mt5 mt5p=1 ! " proton mt5d=1 ! " deuteron mt5t=1 ! " triton mt5he3=1 ! " 3He mt5a=1 ! " alpha *i up1.19 if (mth.eq.5) then !--test for light particle production; 0=yes if (abs(c1h-1).lt.0.0001) mt5n=0 if (abs(c1h-1001).lt.0.0001) mt5p=0 if (abs(c1h-1002).lt.0.0001) mt5d=0 if (abs(c1h-1003).lt.0.0001) mt5t=0 if (abs(c1h-2003).lt.0.0001) mt5he3=0 if (abs(c1h-2004).lt.0.0001) mt5a=0 endif *d acefc.4783 if (mt.ne.1.and.mt.ne.2.and.mt.ne.301.and.& (mt.ne.5.or.(mt.eq.5.and.mt5n.eq.0))) then *d acefc.4801 if (mt.ne.1.and.mt.ne.2.and.& (mt.ne.5.or.(mt.eq.5.and.mt5p.eq.0))) then *d acefc.4822 if (mt.ne.1.and.mt.ne.2.and.& (mt.ne.5.or.(mt.eq.5.and.mt5d.eq.0))) then *d acefc.4839 if (mt.ne.1.and.mt.ne.2.and.& (mt.ne.5.or.(mt.eq.5.and.mt5t.eq.0))) then *d acefc.4856 if (mt.ne.1.and.mt.ne.2.and.& (mt.ne.5.or.(mt.eq.5.and.mt5he3.eq.0))) then *d acefc.4871 if (mt.ne.1.and.mt.ne.2.and.& (mt.ne.5.or.(mt.eq.5.and.mt5a.eq.0))) then *i acefc.5154 if (mt.eq.5.and.mt5n.eq.1) iskip=1 *d acefc.5162 if (mt.eq.2.or.mt.eq.28.or.mt.eq.41.or.& *i acefc.5172 if (mt.eq.5.and.mt5p.eq.0) iskip=0 *d acefc.5175 if (mt.eq.2.or.mt.eq.32.or.mt.eq.35.or.& *i acefc.5181 if (mt.eq.5.and.mt5d.eq.0) iskip=0 *d acefc.5184 if (mt.eq.2.or.mt.eq.33.or.mt.eq.36.or.& *i acefc.5190 if (mt.eq.5.and.mt5t.eq.0) iskip=0 *d acefc.5193 if (mt.eq.2.or.mt.eq.34.or.mt.eq.106.or.& *i acefc.5197 if (mt.eq.5.and.mt5he3.eq.0) iskip=0 *d acefc.5200 if (mt.eq.2.or.(mt.ge.22.and.mt.le.25).or.& *i acefc.5211 if (mt.eq.5.and.mt5a.eq.0) iskip=0 *ident up41m */ 04dec2014 */ - no manual changes *ident up42 */ 05jan2015 */ - acedo */ - mcnp's ace file specification for dosimetry files with multiple */ interpolation ranges says to write the NR NBT values followed */ by the NR INT values but we have always written the NR NBT,INT */ values as pairs. issue identified by Milocco (JET,UK), */ Trkov (IAEA) & Brown (LANL). */ **************************************************************** */ * NOTE: This error has existed in ALL past versions of NJOY * */ **************************************************************** */ * NOTE: All dosimetry files found in the production mcnp_data * */ * 531dos, 532dos and llldos files only contain a single * */ * interpolation interval and therefore are UNAFFECTED * */ * by this error. Also user generated dosimetry files * */ * whose endf source data only contain a single interpo- * */ * lation interval are UNAFFECTED. * */ **************************************************************** *d acedo.162,acedo.163 xss(l+i-1)=scr(5+2*i) xss(l+nr+i-1)=scr(6+2*i) *ident up42m */ 05jan2015 */ - no manual changes *ident up43 */ 08jan2015 - 10feb2015 */ - heatr */ - the variables used when calculating the photon energy "kick" */ are computed in multiple locations. we redefine these as */ global variables and only calculate them once (in nheat). */ - hgam102, introduced to calculated heating when the 1h capture */ data were moved from mf12 to mf6, only included the recoil */ energy. we should have included the photon "kick" to get */ more accurate heating and damage values, particularly at low */ energy, and do so now (issue reported by Konno, JAEA). */ ******************************************************** */ *** NOTE: This error has existed since endf/b-vii.0 *** */ *** files were released, but ONLY for 1h. *** */ ******************************************************** */ */ define emc2, tm and rtm as global variables *i heatr.35 real(kr)::emc2,tm,rtm *i heatr.128 use physics ! provides amassn,amu,ev,clight *i heatr.320 emc2=amassn*amu*clight*clight/ev tm=emc2*(awr+1) rtm=1/tm */ */ delete emc2, tm and rtm local variable definitions from */ nheat, capdam, tabsq6, gheat, tabsqr and disgam *d heatr.900 *d heatr.909 real(kr)::qs,q0,ebar,dame,yld,qsave *d heatr.1016,heatr.1018 *d heatr.1622 *d heatr.1629 real(kr)::e,zx,ax,denom,z,en,aw1fac *d heatr.1642 save zx,ax,denom,z,aw1fac *d heatr.1647,heatr.1651 *d heatr.4010 *d heatr.4016 real(kr)::ein,rein,x,y,xr,awc,xh,yh,xl,yl,dx,s *d heatr.4024,heatr.4025 ein=2*tm *d heatr.4934 *d heatr.4942 real(kr)::afact,aw1fac,z,e,dame *d heatr.4968,heatr.4970 *d heatr.5458 *d heatr.5464 real(kr)::ein,rein,xl,yl,xh,yh,dx,x,y,xr,s *d heatr.5472,heatr.5473 ein=2*tm *d heatr.5519 *d heatr.5523 *d heatr.5525 *d heatr.5528,heatr.5530 return */ end of changes to make emc2, tm and rtm global */ */ revise ebar in hgam102 to include the photon energy "kick" *i heatr.4915 ! internals real(kr)::er,eg2 *d heatr.4917 *d heatr.4922,heatr.4923 !--include recoil energy plus photon "kick" energy er=e/(awr+1) eg2=disc102*disc102*rtm/2 ebar=er+eg2 dame=df(ebar,zp,ap,zt,at) *ident up43m */ 08jan2015 */ - heatx */ - equation 198 contains a 2/3 exponent that should really be 3/2, */ per eqn 2.10 in Lindhard et al, Mat.Fys.Medd.DanFid.Selsk 33, */ no.14 (1963). The NJOY code has always been correct, just a */ typo in this, and the earlier njoy91, manual (reported by Pat */ Griffin, SNL). *d heatx.656 F_L&=&\frac{0.0793Z_R^{2/3}Z_L^{1/2}\left(A_R+A_L\right)^{3/2}} *ident up44 */ 12jan2015 */ - samm */ - reposition an integer declaration statement (mostly a cosmetic */ change as we typically declare integers prior to reals but had */ not done so in this instance; and especially when some of those */ integers appear in subsequent real declaration statements). */ - keeps the Visual Digital Fortran 6.6A compiler happy (per */ Cabellos, NEA). *i samm.85 integer::nmtres,ncoef,nresp,ier *d samm.88 *ident up44m */ 12jan2015 */ - no manual changes *ident up45 */ 12jan2015 */ - acefc */ - even though we now allocate many arrays there are still fixed */ array dimensions that become too small over time. we increase */ a couple of them here to support efforts related to the CIELO */ Project and the IAEA pfns crp (Trkov, IAEA). *d acefc.1830 nt1w=4200 *d up31.6 integer,parameter::nwscr=800000 *ident up45m */ 12jan2015 */ - no manual changes *ident up46 */ 27jan2015 */ - groupr */ - tweak array definition coding in getmf6 so usage is consistent */ with similar coding elsewhere in this routine. */ - revise array specification for p(7) in f6cm to be consistent */ with njoy99. depending upon compiler options, users specifying */ lord>6 in their input may have suffered a silent array overflow */ (both issues reported by Bunde, DOE/Idaho). *d groupr.5861 tmp(ilo+6+ncyc)=sigfig(tmp(ilo+6+ncyc),7,0) *d groupr.6396 *i groupr.6398 real(kr)::p(mxlg) *ident up46m */ 27jan2015 */ - no manual changes *ident up47 */ 29jan2015 */ - heatr */ - we recently noticed that some evaluated nuclear data files */ contain photon production data for a given mt in both mf6 */ and one or more of mf12 through mf15. this causes njoy to */ incorrectly combine the "direct" and "energy-balance" methods */ when calculating heating. we set a flag when reading mf6 */ photon production data so that the corresponding mt in one or */ more of mf12 through mf15 is not processed. */ - an information message identifying the mf/mt section is */ included in njoy's standard output. *i heatr.29 integer::i6p,mt6yp(maxmf6) *i heatr.739 if (nint(zap).eq.0) then i6p=i6p+1 mt6yp(i6p)=mth endif *i heatr.4957 integer::mf6flg character(len=70)::strng1,strng2 *i heatr.5004 ! skip over this mf/mt if photon data were already found in mf6 if (i6p.gt.0) then mf6flg=0 do i=1,i6p if (mt6yp(i).ne.mth) cycle mf6flg=1 exit enddo if (mf6flg.ne.0) then write(strng1,'(''skipping mf'',i2,''/mt = '',i3)')mfh,mth write(strng2,'(''photons were already processed in mf6'')') call mess('gheat ',strng1,strng2) call tosend(nscr,0,0,scr) go to 105 endif endif *ident up47m */ 29jan2015 */ - add a new warning message to Section 11. *i heatx.2632 \item[\cword{message from gheat---skipping ... processed in mf6}] ~\par NJOY has found photon data for a given mt in both mf6 and mf12 - mf15. Only the mf6 data are used. *ident up48 */ 5feb2015 */ - acefc */ - in unionx we open scratch units iold and inew, and leave them */ open for subsequent use in gamsum (where they are closed). if */ there are no photon data, gamsum is not called and these units */ remain open. if a later module tries to open these unit numbers */ we crash. */ - add conditional coding in unionx to make sure these units */ are closed (issue reported by Cabellos, NEA). *i acefc.1767 if (ngmt.eq.0) then !will close these in gamsum when ngmt != 0 call closz(iold) call closz(inew) endif *ident up48m */ 5feb2015 */ - no manual changes *ident up49 */ 10feb2015 */ - errorr */ - an array overflow error was observed when attempting to process */ the tendl-2013 83Kr file (reported by Cabellos, NEA). */ - the issue appears to be a evaluation error as the mf2/mt151 */ urr region data are given for 2 l-states while the mf32/mt151 */ urr region data are given for 3 l-states. njoy utilizes the */ mf2/mt151 l-state value when reading mf32/mt151 and so can't */ properly read this section. */ - we add a test and error stop when encountering this condition. */ - we also allow the mf32 nls be less than mf2, but advise the */ user that these covariance data are incomplete. *i errorr.3076 if (n1h.gt.nls) then call error('resprx',& 'mf2/mf32 l-state mis-match',& 'probable evaluation file error') else if (n1h.lt.nls) then write(strng1,'(''mf2 nls='',i1,'', but mf32 nls='',i1)')& nls, n1h call mess('resprx',strng1,& 'continue with partial urr covariance data') nls=n1h endif *ident up49m */ 10feb2015 */ - add a new error and warning messages to Section 16. *i errorx.3068 \item[\cword{error in resprx***mf2/mf32 l-state mismatch ...}] ~\par The \cword{nls} value for mf32 URR data is larger than that specified in mf2. This is likely an evaluation file error. \item[\cword{message from resprx---mf2 nls=I, but mf32 nls=J ...}] ~\par The \cword{nls} value for mf32 URR data is smaller than that specified in mf2. Processing will continue but covariance data for the complete set of mf2 URR parameters is incomplete. *ident up50 */ 12feb2015 */ - acefc */ - the suite of standard ace plots is sometimes incomplete with some */ emitted neutron angular distribution and secondary neutron spectra */ plots missing (reported by Trkov, IAEA). */ - a global variable used to keep track of the number of neutron */ emitting reactions was erroneously used as a local variable */ for delayed neutron related data processing. this does not */ impact the underlying ace file since we have already written */ out the correct value and associated arrays, but did impact */ the do loop range used to control production of selected ace */ file plots. *d acefc.13184 nrr=nint(xss(l)) *d acefc.13187,acefc.13188 if (nrr.ne.0) then n=2*nrr *d acefc.13207 nrr=nint(xss(l)) *d acefc.13210,acefc.13211 if (nrr.ne.0) then n=2*nrr *d acefc.13239 nrr=nint(xss(l)) *d acefc.13242,acefc.13243 if (nrr.ne.0) then n=2*nrr *d acefc.13258 nrr=nint(xss(l)) *d acefc.13261,acefc.13262 if (nrr.ne.0) then n=2*nrr *ident up50m */ 12feb2015 */ - no manual changes *ident newv */ 12feb2015 */ - njoy, vers and locale */ - update version info */ - update organization and machine/compiler info *d njoy.6 ! Version 2012.50 *d vers.7,vers.8 character(8),public::vers='2012.50' character(8),public::vday='12feb15' *d locale.15,locale.16 character(8),public::lab='lanl t2' character(8),public::mx='pc-ifort' *ident nwvM */ 12feb2015 */ - NJOY2012 Manual title page and document ID update *d njoy12.42 \fancyhead[R]{LA-UR-12-27079 Rev} % *d njoy12.173 \fancyhead[RO,LE]{LA-UR-12-27079 Rev} *d njoy12.76,njoy12.78 \\ \\ Original Issue: December 20, 2012\\ \\ \\ Updated for NJOY2012.50 \\} \date{February 12, 2015}