Back to home page

Project CMSSW displayed by LXR

 
 

    


File indexing completed on 2024-04-06 12:14:01

0001 c-----------------------------------------------------------------------
0002       subroutine decayall(n)
0003 c-----------------------------------------------------------------------
0004 c  decay of objects n to nptl, including their children
0005 c-----------------------------------------------------------------------
0006       include 'epos.inc'
0007       common/cttaus/tpro,zpro,ttar,ztar,ttaus,detap,detat
0008       double precision tpro,zpro,ttar,ztar,ttaus,detap,detat
0009       ttaus=1
0010       np1=n
0011  1    np2=nptl
0012       do ip=np1,np2
0013          if(istptl(ip).eq.0)then  !consider last generation particles
0014             call hdecas(ip,iret)
0015             if(iret.eq.1)stop'error in hdecas detected in decay'
0016          endif
0017       enddo
0018       np1=np2+1
0019       if(np1.le.nptl)goto1
0020       end
0021 
0022 
0023 c-----------------------------------------------------------------------
0024       subroutine hdecas(i,iret)
0025 c-----------------------------------------------------------------------
0026 c  decay of object i  (main decay routine)
0027 c-----------------------------------------------------------------------
0028 
0029       include 'epos.inc'
0030       double precision tpro,zpro,ttar,ztar,ttaus,detap,detat,zor,tor
0031       common/cttaus/tpro,zpro,ttar,ztar,ttaus,detap,detat
0032       double precision ttaux,ttauz
0033       integer jcdu(nflav,2)
0034 
0035       iret=0
0036       nptlb=nptl
0037 
0038 c no last generation -> no decay
0039 
0040       if(istptl(i).ne.0)return
0041 
0042       if(nptl.gt.mxptl-10)then
0043         call alist('end&',1,nptl)
0044         call utstop('hdecas: mxptl too small&')
0045       endif
0046 c entry
0047 
0048       call utpri('hdecas',ish,ishini,5)
0049       ttauz=ttaus
0050 
0051 
0052 c skip nuclei
0053 
0054       if(idptl(i).gt.1e9)return
0055 
0056 c small droplet decay
0057 
0058       if(iabs(idptl(i)).gt.1e8)then
0059         stop'hdecas: no longer supported (2).       '
0060       endif
0061 
0062 c  ordinary decay
0063 
0064       call idmass(111,amrho0)
0065       call idmass(221,amomeg)
0066       ioi=iorptl(i)
0067       if(ioi.gt.0.and.(idptl(i).eq.111.or.idptl(i).eq.221))then
0068         if(.not.(iabs(idptl(ioi)).lt.10000
0069      *       .and.jorptl(i).eq.0))then
0070 
0071           if(iLHC.eq.1.and.((ityptl(i).ge.20.and.ityptl(i).le.39)
0072      *        .or.ityptl(i).eq.42.or.ityptl(i).eq.52))then
0073 c mix rho and omegas only from string production and if not decay product
0074             if(idptl(i).eq.111)idptl(i)=221
0075             if(idptl(i).eq.221.and.ityptl(i).ge.30.and.ityptl(i).le.39
0076      *         .and.rangen().gt.0.5)idptl(i)=111
0077           elseif(iLHC.eq.0.and..not.(ityptl(i).eq.60))then
0078             if(idptl(i).eq.111)idptl(i)=221
0079             if(idptl(i).eq.221.and.rangen().gt.0.5)idptl(i)=111
0080           endif
0081 
0082         endif
0083       endif
0084 
0085       if(ctaumin.gt.0.)then
0086         call idtau(idptl(i),1.,1.,ctau)       !ctau in fm
0087         if(ctau*1.e-13.gt.ctaumin)goto 1000   !ctaumin in cm
0088       endif
0089 
0090       ida=iabs(idptl(i))
0091 
0092       if(.not.(iappl.eq.7.and.i.eq.1))then
0093       if(mod(ndecay        ,10).eq.1
0094      *.and.ida.ne.0.and.ida.lt.10000)goto1000
0095       if(mod(ndecay/10     ,10).eq.1.and.ida.eq.  20)goto1000
0096       if(mod(ndecay/100    ,10).eq.1.and.ida.eq.2130)goto1000
0097       if(mod(ndecay/1000   ,10).eq.1.and.ida.eq.1130)goto1000
0098       if(mod(ndecay/1000   ,10).eq.1.and.ida.eq.2230)goto1000
0099       if(mod(ndecay/10000  ,10).eq.1.and.ida.eq.2330)goto1000
0100       if(mod(ndecay/10000  ,10).eq.1.and.ida.eq.1330)goto1000
0101       if(mod(ndecay/100000 ,10).eq.1.and.ida.eq.3331)goto1000
0102       if(mod(ndecay/1000000,10).eq.1.and.ida.eq. 110)goto1000
0103 
0104       if(nrnody.gt.0)then
0105       do nod=1,nrnody
0106       if(idptl(i).eq.nody(nod))goto 1000
0107       enddo
0108       endif
0109 
0110 
0111       endif
0112 
0113       call hdecay(i,iret)
0114       if(iret.eq.1)goto1000
0115       if(nptl.le.nptlb)then
0116         iret=-1
0117         goto 1000
0118       endif
0119 
0120 c ---successful decay---
0121 
0122       istptl(i)=1
0123       ifrptl(1,i)=nptlb+1
0124       ifrptl(2,i)=nptl
0125 
0126       t=tivptl(2,i)
0127       x=xorptl(1,i)+(t-xorptl(4,i))*pptl(1,i)/pptl(4,i)
0128       y=xorptl(2,i)+(t-xorptl(4,i))*pptl(2,i)/pptl(4,i)
0129       z=xorptl(3,i)+(t-xorptl(4,i))*pptl(3,i)/pptl(4,i)
0130       call jtaux(t,z,ttaux)
0131       ttaus=ttaux
0132       if( ttaus.gt.0d0 ) then
0133         call jtauin
0134         call jtaus(z,ttest,sz)
0135         if (abs(t-ttest).gt.1e-5.and.ish.ge.1) then
0136           call utmsg('hdecas')
0137           write(ifch,*)'*****  t /= ttest'
0138           write(ifch,*)t,ttest,i,z,t,xorptl(3,i),xorptl(4,i)
0139      $         ,pptl(3,i),pptl(4,i)
0140           call utmsgf
0141         endif
0142       endif
0143 
0144 c loop over decay products
0145 
0146       do 20 n=nptlb+1,nptl
0147       iorptl(n)=i
0148       jorptl(n)=0
0149       istptl(n)=0
0150       ifrptl(1,n)=0
0151       ifrptl(2,n)=0
0152       rad=0
0153       phi=0
0154       ti=t
0155       zi=z
0156       xorptl(1,n)=x + rad*cos(phi)
0157       xorptl(2,n)=y + rad*sin(phi)
0158       xorptl(3,n)=zi
0159       xorptl(4,n)=ti
0160       io=n
0161 1     io=iorptl(io)
0162       if(ish.ge.4)write(ifch,*)'io = ',io,'  origin: ',iorptl(io)
0163       if(io.eq.iorptl(io))call utmsg("Strange iorptl in hdecas&")
0164 c security to avoid infinite loop
0165       if(iorptl(io).gt.0.and.io.ne.iorptl(io))goto 1  
0166       if(ish.ge.4)write(ifch,*)'origin: ',io,idptl(io)
0167       zor=xorptl(3,io)
0168       tor=xorptl(4,io)
0169       call idquac(io,nq,ndummy1,ndummy2,jcdu)
0170       r=rangen()
0171       tauran=-taurea*alog(r)
0172       call jtaix(n,tauran,zor,tor,zis,tis)
0173       tivptl(1,n)=amax1(ti,tis)
0174       call idtau(idptl(n),pptl(4,n),pptl(5,n),taugm)
0175       r=rangen()
0176       tivptl(2,n)=t+taugm*(-alog(r))
0177       ityptl(n)=ityptl(i)
0178       radptl(n)=0.
0179       dezptl(n)=0.
0180       itsptl(n)=itsptl(i)
0181       rinptl(n)=rinptl(i)
0182 20    continue
0183 
0184       if(iabs(idptl(nptlb+1)).le.6) then
0185         call gakli2(0,0)
0186         write (*,*) 'nptlb+1,nptl:',nptlb+1,nptl
0187         istptl(nptlb+1)=1
0188         do n=nptlb+2,nptl
0189           istptl(n)=20
0190         enddo
0191         call gakfra(0,iret)
0192         if(iret.eq.1)goto1000
0193         call gakli2(0,0)
0194       endif
0195 
0196 1000  continue
0197       ttaus=ttauz
0198       call jtauin
0199       call utprix('hdecas',ish,ishini,5)
0200       return
0201       end
0202 
0203 c-----------------------------------------------------------------------
0204       subroutine hdecay(ip,iret)
0205 c-----------------------------------------------------------------------
0206 c  decays particle ip from /cptl/
0207 c  for ip being no resonance: call StaHad
0208 c  for ip being resonance: standard resonance decay  procedure
0209 c-----------------------------------------------------------------------
0210       include 'epos.inc'
0211       double precision tpro,zpro,ttar,ztar,ttaus,detap,detat
0212       common/cttaus/tpro,zpro,ttar,ztar,ttaus,detap,detat
0213       common/wco/wmass2,wgam2
0214       parameter (mxlook=10000,mxdky=2000)
0215       common/dkytab/look(mxlook),cbr(mxdky),mode(5,mxdky)
0216       dimension pgen(5,10),rnd(10),u(3),beta(3)
0217      1     ,reduce(10)
0218       dimension prest(4,10),kno(10)
0219       data reduce/1.,1.,2.,5.,15.,60.,250.,1500.,1.2E4,1.2E5/
0220       data twome/1.022006e-3/
0221 
0222 c          fctn definitions
0223       dot(i1,i2)=prest(4,i1)*prest(4,i2)-prest(1,i1)*prest(1,i2)
0224      *-prest(2,i1)*prest(2,i2)-prest(3,i1)*prest(3,i2)
0225 c          charged w propagator.
0226       wprop(z)=(z-wmass2**2)**2+(wmass2*wgam2)**2
0227 
0228       call utpri('hdecay',ish,ishini,5)
0229 
0230       ipp=ip
0231       iret=0
0232       nptlb=nptl
0233 
0234       if(ish.ge.5)write(ifch,*)'ip,id,mass: ',ip,idptl(ip),pptl(5,ip)
0235 
0236 
0237       if(model.eq.4.and.iappl.eq.7)then
0238         if(abs(idptl(ipp)).gt.13.and.abs(idptl(ipp)).ne.1120
0239      &.and.abs(idptl(ipp)).ne.15)call decaymod(ipp,iret)
0240         if(iret.gt.0)goto 1000
0241         naddptl=0
0242         goto 900 
0243       endif
0244 
0245 c     no k_long decay
0246 c     ---------------
0247 c     if(idptl(ip).eq.-20)goto1000
0248 
0249 c     select decay mode
0250 c     -----------------
0251       ntry=0
0252 2     ntry=ntry+1
0253            if(ntry.gt.100)then
0254       if(ish.ge.1)then
0255       call utmsg('hdecay')
0256       write(ifch,*)'*****  decay not possible. iret = 1.'
0257       call utmsgf
0258       endif
0259       iret=1
0260       goto1000
0261            endif
0262       idlv1=idptl(ip)
0263       amss=pptl(5,ip)
0264 
0265 c Decay of deuteron
0266 
0267       if(abs(idlv1).eq.17)then
0268         amss=1.01*amss
0269         naddptl=2
0270         call idmass(1120,amnew)
0271         pptl(5,nptl+1)=amnew
0272         idptl(nptl+1)=sign(1120,idlv1)
0273         sum=amnew
0274         call idmass(1220,amnew)
0275         pptl(5,nptl+2)=amnew
0276         idptl(nptl+2)=sign(1220,idlv1)
0277         sum=sum+amnew
0278         goto 111
0279       endif
0280 
0281 c Decay of triton
0282 
0283       if(abs(idlv1).eq.18)then
0284         amss=1.01*amss
0285         naddptl=3
0286         call idmass(1120,amnew)
0287         pptl(5,nptl+1)=amnew
0288         idptl(nptl+1)=sign(1120,idlv1)
0289         sum=amnew
0290         call idmass(1220,amnew)
0291         pptl(5,nptl+2)=amnew
0292         idptl(nptl+2)=sign(1220,idlv1)
0293         sum=sum+amnew
0294         call idmass(1220,amnew)
0295         pptl(5,nptl+3)=amnew
0296         idptl(nptl+3)=sign(1220,idlv1)
0297         sum=sum+amnew
0298          goto 111
0299       endif
0300 
0301 c Decay of alpha
0302 
0303       if(abs(idlv1).eq.19)then
0304         amss=1.01*amss
0305         naddptl=4
0306         call idmass(1120,amnew)
0307         pptl(5,nptl+1)=amnew
0308         idptl(nptl+1)=sign(1120,idlv1)
0309         sum=amnew
0310         call idmass(1220,amnew)
0311         pptl(5,nptl+2)=amnew
0312         idptl(nptl+2)=sign(1220,idlv1)
0313         sum=sum+amnew
0314         call idmass(1120,amnew)
0315         pptl(5,nptl+3)=amnew
0316         idptl(nptl+3)=sign(1120,idlv1)
0317         sum=sum+amnew
0318         call idmass(1220,amnew)
0319         pptl(5,nptl+4)=amnew
0320         idptl(nptl+4)=sign(1220,idlv1)
0321         sum=sum+amnew
0322         goto 111
0323       endif
0324 
0325 c  select one of the decay channel
0326       ipoint=look(iabs(idlv1))-1
0327       if(idlv1.eq.-20)ipoint=look(320)-1
0328       if(ipoint.lt.0) goto1000
0329       try=rangen()
0330 100   ipoint=ipoint+1
0331       if(ish.ge.4)write(ifch,*)'ipoint,cbr,try',ipoint,cbr(ipoint),try
0332       if(try.gt.cbr(ipoint)) goto100
0333       naddptl=0
0334       sum=0.
0335 c      nstart=nptl+1                  !?????????????????unused
0336       new=0
0337       do 110 i=1,5         !store id and mass of products
0338         if(mode(i,ipoint).eq.0) goto 110
0339         if(nptl+naddptl+1.gt.mxptl) goto 9999
0340         if(iabs( mode(1,ipoint)) .le. 6.and.i.eq.2)then   !decay into quark ???
0341           call vedi(mode(1,ipoint),mode(2,ipoint),k3,idlv1)
0342           idptl(new)=idlv1
0343           call idmass(idlv1,amnew)
0344           pptl(5,new)=amnew
0345           sum=pptl(5,new)
0346         else                                 !decay into particles
0347           naddptl=naddptl+1
0348           new=nptl+naddptl
0349           idptl(new)=mode(i,ipoint)
0350           idlv1=idptl(new)
0351           call idmass(idlv1,pptl(5,new))
0352           sum=sum+pptl(5,new)
0353         endif
0354  110  continue
0355  111  continue
0356       if(naddptl.ne.1.and.sum.ge.amss)goto 2
0357  112  naddptl1=naddptl-1
0358       do 120 j=1,5
0359       pgen(j,1)=pptl(j,ip)
0360 120   continue
0361       pgen(5,1)=amss !needed because of deuteron, triton and alpha decay and OK
0362 
0363       pgen(5,naddptl)=pptl(5,nptl+naddptl)
0364       if(naddptl.eq.1) goto 700            !one body decay
0365       if(naddptl.eq.2) goto 400            !two body decay
0366 
0367       if(ish.ge.4)write(ifch,*)'>= 3 body decay'
0368 
0369 c     use kroll-wada distribution for pi0 and eta dalitz decays.
0370 c     ----------------------------------------------
0371       if(.not.((idptl(ip).eq.110.or.idptl(ip).eq.220).and.
0372      1iabs(idptl(nptl+2)).eq.12)) goto 130
0373       ntry=0             !decay of pi0 or eta into electron
0374 125   ntry=ntry+1
0375            if(ntry.gt.10)then
0376       if(ish.ge. 0)then
0377       call utmsg('hdecay')
0378       write(ifch,*)'*****  ntry > 10. iret = 1.'
0379       write(ifch,*)'***** amee,ree,wtee',amee,ree,wtee
0380       call utmsgf
0381       endif
0382       iret=1
0383       goto1000
0384            endif
0385       amee=twome*(pptl(5,ip)/twome)**rangen()
0386       ree=(twome/amee)**2
0387       wtee=(1.-(amee/pptl(5,ip))**2)**3*sqrt(1.-ree)*(1.+.5*ree)
0388       if(wtee.lt.rangen()) goto125
0389       pgen(5,2)=amee
0390       goto400
0391 130   continue
0392 
0393 c     calculate maximum phase-space weight
0394 c     ------------------------------------
0395       wtmax=1./reduce(naddptl)
0396       sum1=pgen(5,1)
0397       sum2=sum-pptl(5,nptl+1)
0398       do 200 i=1,naddptl1
0399       wtmax=wtmax*utpcm(sum1,sum2,pptl(5,nptl+i))
0400       sum1=sum1-pptl(5,nptl+i)
0401       sum2=sum2-pptl(5,nptl+i+1)
0402 200   continue
0403 
0404 c     generate uniform naddptl-body phase space
0405 c     --------------------------------------
0406       ntry=0
0407 300   ntry=ntry+1
0408            if(ntry.gt.10000)then
0409       if(ish.ge. 0)then
0410       call utmsg('hdecay')
0411       write(ifch,*)'*****  infinite loop (2). iret = 1.'
0412       write(ifch,*)'***** ip,idptl(ip),pptl(5,ip):'
0413      *,ip,idptl(ip),pptl(5,ip)
0414       write(ifch,*)'***** wt,wtmax:',wt,wtmax
0415       write(ifch,*)'***** i,pgen(5,i),pptl(5,nptl+i),idptl(nptl+i):'
0416       do i=1,naddptl
0417       write(ifch,*)i,pgen(5,i),pptl(5,nptl+i),idptl(nptl+i)
0418       enddo
0419       call utmsgf
0420       endif
0421       iret=1
0422       goto1000
0423            endif
0424       rnd(1)=1.
0425       jsave=1
0426       do 310 i=2,naddptl1
0427       rnew=rangen()
0428       i1=i-1
0429       do 320 jj1=1,i1
0430       j=i-jj1
0431       jsave=j+1
0432       if(rnew.le.rnd(j)) goto310
0433       rnd(jsave)=rnd(j)
0434 320   continue
0435 310   rnd(jsave)=rnew
0436       rnd(naddptl)=0.
0437       wt=1.
0438       sum1=sum
0439       do 330 i=2,naddptl
0440       sum1=sum1-pptl(5,nptl+i-1)
0441       pgen(5,i)=sum1+rnd(i)*(pgen(5,1)-sum)
0442       a=pgen(5,i-1)
0443       b=pgen(5,i)
0444       c=pptl(5,nptl+i-1)
0445       wt=wt*utpcm(a,b,c)
0446 330   continue
0447       if(wt.lt.rangen()*wtmax) goto300
0448 
0449 c     carry out two-body decays in pgen frames
0450 c     ----------------------------------------
0451 400   continue
0452       if(ish.ge.4)write(ifch,*)'2 body decay'
0453       do 410 i=1,naddptl1
0454       qcm=utpcm(pgen(5,i),pgen(5,i+1),pptl(5,nptl+i))
0455       u(3)=2.*rangen()-1.
0456       phi=2.*pi*rangen()
0457       u(1)=sqrt(1.-u(3)**2)*cos(phi)
0458       u(2)=sqrt(1.-u(3)**2)*sin(phi)
0459       do 420 j=1,3
0460       pptl(j,nptl+i)=qcm*u(j)
0461       pgen(j,i+1)=-pptl(j,nptl+i)
0462 420   continue
0463       pptl(4,nptl+i)=sqrt(qcm**2+pptl(5,nptl+i)**2)
0464       pgen(4,i+1)=sqrt(qcm**2+pgen(5,i+1)**2)
0465 410   continue
0466       do 430 j=1,4
0467       pptl(j,nptl+naddptl)=pgen(j,naddptl)
0468 430   continue
0469 
0470 c     boost pgen frames to lab frame
0471 c          also save momenta in rest frame (last frame)
0472 c     -------------------------------------------------
0473       do 500 ii=1,naddptl1
0474       i=naddptl-ii
0475       do 510 j=1,3
0476       beta(j)=pgen(j,i)/pgen(4,i)
0477 510   continue
0478       gamma=pgen(4,i)/pgen(5,i)
0479       do 520 k=i,naddptl
0480       k1=nptl+k
0481       bp=beta(1)*pptl(1,k1)+beta(2)*pptl(2,k1)+beta(3)*pptl(3,k1)
0482       do 530 j=1,3
0483       prest(j,k)=pptl(j,k1)
0484       pptl(j,k1)=pptl(j,k1)+gamma*beta(j)*(pptl(4,k1)
0485      1+bp*gamma/(gamma+1.))
0486 530   continue
0487       prest(4,k)=pptl(4,k1)
0488       pptl(4,k1)=gamma*(pptl(4,k1)+bp)
0489       if(pptl(4,k1).lt.1.d-5)then
0490         pptl(4,k1)=sqrt(pptl(1,k1)*pptl(1,k1)+pptl(2,k1)*pptl(2,k1)
0491      &                 +pptl(3,k1)*pptl(3,k1))
0492       endif
0493 520   continue
0494 500   continue
0495 
0496 c     matrix elements
0497 c     ---------------
0498         if(iabs(idptl(ip)).eq.14)then                  !muon decay
0499           goto 650
0500         elseif(naddptl.eq.3)then
0501           if(idptl(ip).eq.221.or.idptl(ip).eq.331)then  !omeg and phi decay
0502             goto 610
0503           elseif(iabs(idptl(ip)).eq.130.or.       !Kl and K decay
0504      1       idptl(ip).eq.-20)then
0505             if(iabs(idptl(nptl+2)).lt.20)then   !semi-leptonic
0506               goto 630
0507             else                                !hadronic
0508               goto 640
0509             endif
0510           elseif(iabs(idptl(nptl+1)).lt.20.and. !other semi-leptonic decay
0511      1       idptl(nptl+1).ne.10)then
0512             goto 620
0513           elseif(iabs(idptl(nptl+2)).le.6)then
0514             goto 605            !decay into quark
0515           else
0516             goto 800
0517           endif
0518         else
0519          goto 800
0520         endif
0521 
0522  605    wt=pptl(5,ip)*pptl(5,nptl+1)*dot(2,3)
0523         IF(wt.LT.rangen()*pptl(5,ip)**4/16.) goto 300
0524         ams=sqrt(dot(2,2)+dot(3,3)+2.*dot(2,3))
0525         kno(1)=idptl(nptl+2)
0526         kno(2)=idptl(nptl+3)
0527         if(ammin(kno(1),kno(2)).gt.ams)then
0528           call vedi(kno(1),kno(2),iddum,idlv2)
0529           idptl(nptl+2)=idlv2
0530           call idmass(idlv2,amnew2)
0531           pptl(5,nptl+2)=amnew2
0532           naddptl=2
0533           goto 112
0534         endif
0535 c......multiplicity
0536         PS =sqrt(dot(2,2))
0537         psq=sqrt(dot(3,3))
0538 c        PSP=PS                  !!???????????????unused
0539         np=0                    !!!!?????
0540         nq=2
0541         CNDE=4.5*LOG(MAX((ams-PS-PSQ)/0.7,1.1))
0542 c        IF(MMAT.EQ.12) CNDE=CNDE+PARJ(63)
0543  769    NTRY=NTRY+1
0544         IF(NTRY.GT.1000) THEN
0545           write(*,*)'hdecay caught in infinite loop'
0546           write(ifch,*)'hdecay caught in infinite loop'
0547           iret=1
0548           goto 1000
0549         ENDIF
0550         GAUSS=SQRT(-2.*CNDE*LOG(MAX(1E-10,rangen())))*
0551      &       SIN(2.*pi*rangen())
0552         ND=0.5+0.5*NP+0.25*NQ+CNDE+GAUSS
0553         IF(ND.LT.NP+NQ/2.OR.ND.LT.2.OR.ND.GT.10) GOTO 769
0554 
0555 
0556 c......choose hadrons
0557 
0558 
0559         kno(3)=kno(1)
0560         kno(4)=kno(2)
0561 
0562         CONTINUE
0563         IF(ND.EQ.NP+NQ/2) GOTO 773
0564         DO I=nptl+2,nptl+2+nd-nq/2-1
0565           JT=2+1+INT((NQ-1) * rangen() )
0566           CALL vedi(kno(JT),0,KFL2,idlv3)
0567           idptl(i)=idlv3
0568 c          IF(K(I,2).EQ.0) GOTO 769
0569           kno(JT)=-KFL2
0570         enddo
0571  773    CONTINUE
0572         CALL vedi(kno(3),kno(4),KFLDMP,idlv4)
0573         idptl(nptl+2+nd-nq/2)=idlv4
0574         sum=0.
0575         do i=nptl+2,nptl+2+nd-nq/2
0576           call idmass(idptl(i),am)
0577           pptl(5,i)=am
0578           sum=sum+am
0579         enddo
0580         if(sum.gt.ams) goto 769
0581 c......goto phase space dis....
0582         ip=nptl+2+nd-nq/2+1
0583         do j=1,4
0584           pptl(j,ip)=pptl(j,ipp)-pptl(j,nptl+1)
0585         enddo
0586         pptl(5,ip)=ams
0587         idptl(ip)=sign(80,idptl(ipp))
0588         nptl=nptl+1
0589         naddptl=nd
0590         goto 112
0591 
0592 
0593 c     omeg and phi decay
0594 c          use vectors in rest frame
0595 c     ------------------------------
0596 610   wt=(pptl(5,nptl+1)*pptl(5,nptl+2)*pptl(5,nptl+3))**2
0597      1-(pptl(5,nptl+1)*dot(2,3))**2
0598      2-(pptl(5,nptl+2)*dot(1,3))**2
0599      3-(pptl(5,nptl+3)*dot(1,2))**2
0600      4+2.*dot(1,2)*dot(2,3)*dot(1,3)
0601       if(wt.lt.rangen()*pptl(5,ip)**6/108.) goto300
0602       goto800
0603 
0604 c     semileptonic and quark decays
0605 c          use vectors in rest frame, where ip has (m,0,0,0)
0606 c          include w propagator
0607 c     ------------------------------------------------------
0608 620   wt=(pptl(5,ip)*prest(4,2))*dot(1,3)
0609       s12=pptl(5,nptl+1)**2+pptl(5,nptl+2)**2+2.*dot(1,2)
0610       s12max=pptl(5,ip)**2
0611       wt=wt*wprop(s12max)/wprop(s12)
0612       if(wt.lt.rangen()*pptl(5,ip)**4/16.) goto 300
0613       goto 800
0614 
0615 c     semileptonic kaon decays
0616 c          use vectors in rest frame, where ip has (m,0,0,0)
0617 c          include form factor FML
0618 c     ------------------------------------------------------
0619 630   if(iabs(idptl(ip)).eq.130)then
0620         if(iabs(idptl(nptl+2)).eq.12)then
0621           ncha=1          !K   -> Pi0 + e + Nu
0622         else
0623           ncha=2          !K   -> Pi0 + Mu + Nu
0624         endif
0625       else
0626         if(iabs(idptl(nptl+2)).eq.12)then
0627           ncha=3          !K0  -> Pi + e + Nu
0628         else
0629           ncha=4          !K0  -> Pi + Mu + Nu
0630         endif
0631       endif
0632 
0633       wt=FML(ncha,pptl(5,ip),pptl(5,nptl+1),pptl(5,nptl+2)
0634      &       ,prest(4,1),prest(4,2),prest(4,3))
0635       if(wt.lt.rangen()) goto 300
0636       goto 800
0637 
0638 c     hadronic kaon decays
0639 c          use vectors in rest frame, where ip has (m,0,0,0)
0640 c          include form factor FM
0641 c     ------------------------------------------------------
0642 640   if(iabs(idptl(ip)).eq.130)then
0643         if(iabs(idptl(nptl+3)).eq.120)then
0644           ncha=1          !K   -> 3 Pi
0645         else
0646           ncha=2          !K   ->  Pi + 2 Pi0
0647         endif
0648       else
0649         if(iabs(idptl(nptl+1)).eq.110)then
0650           ncha=3          !K0  -> 3 Pi0
0651         else
0652           ncha=4          !K0  -> 2 Pi + Pi0
0653         endif
0654       endif
0655       S0=(pptl(5,ip)**2+pptl(5,nptl+1)**2+pptl(5,nptl+2)**2
0656      &   +pptl(5,nptl+3)**2)/3.d0
0657       S1=pptl(5,ip)**2+pptl(5,nptl+1)**2-2.*prest(4,1)*pptl(5,ip)
0658       S2=pptl(5,ip)**2+pptl(5,nptl+2)**2-2.*prest(4,2)*pptl(5,ip)
0659       S3=pptl(5,ip)**2+pptl(5,nptl+3)**2-2.*prest(4,3)*pptl(5,ip)
0660       wt=FM(ncha,S0,S1,S2,S3)
0661       if(wt.lt.rangen()) goto 300
0662       goto 800
0663 
0664 c     muon decays
0665 c          use vectors in rest frame, where ip has (m,0,0,0)
0666 c          include form factor FMU
0667 c     ------------------------------------------------------
0668 650   xxx=2.*prest(4,1)/pptl(5,ip)            !reduced energy of electron
0669       if(xxx.gt.1.) goto 300
0670       wt=FMU(xxx)
0671       rrr=rangen()
0672       if(wt.lt.rrr) goto 300
0673       goto 800
0674 
0675 c     one-particle decays
0676 c     -------------------
0677 700   continue
0678       do 710 j=1,5
0679       pptl(j,nptl+1)=pptl(j,ip)
0680 710   continue
0681 
0682 c     swap particles and antiparticles if idptl(ip)<0
0683 c     -----------------------------------------------
0684  800    continue
0685         if(iabs(idptl(ip)).eq.80)then
0686           nptl=nptl-1
0687           naddptl=naddptl+1
0688         endif
0689         if(idptl(ipp).ge.0.or.iabs(idptl(ipp)).eq.20) goto 900
0690         do 810 i=1,naddptl
0691           idabs=iabs(idptl(nptl+i))
0692           ifl1=idabs/1000
0693           ifl2=mod(idabs/100,10)
0694           ifl3=mod(idabs/10,10)
0695           if(ifl1.eq.0.and.ifl2.ne.0.and.ifl2.eq.ifl3) goto 810
0696           if(idabs.eq.9.or.idabs.eq.10.or.idabs.eq.20) goto 810
0697           if(idabs.eq.29.or.idabs.eq.30.or.idabs.eq.40) goto 810
0698           idptl(nptl+i)=-idptl(nptl+i)
0699  810    continue
0700 
0701  900    continue
0702         nptl=nptl+naddptl
0703         if(nptl.gt.mxptl)call utstop('hdecay: nptl>mxptl&')
0704 c        nqk=0           !???????????????????unused
0705         if(iabs(idptl(nptl)).lt.10.or.mod(idptl(nptl),100).eq.0)then
0706 c          call utstop('hdecay: decay ptcl is parton&')
0707         endif
0708 
0709 c     print
0710 c     -----
0711 
0712       if(ish.ge.3)then
0713       write(ifch,140)sngl(ttaus)
0714   140 format(/' ----------------------------'/
0715      *'    decay  at tau =',f6.2/
0716      *' ----------------------------')
0717       write(ifch,*)'decaying object:'
0718       call alist('&',ip,ip)
0719       write(ifch,*)'decay products:'
0720       call alist('&',nptlb+1,nptl)
0721       endif
0722       if(ish.ge.5)then
0723       write(ifch,*)'momentum sum:'
0724       do kk=1,5
0725       pptl(kk,nptl+1)=0
0726       do ii=nptlb+1,nptl
0727       pptl(kk,nptl+1)=pptl(kk,nptl+1)+pptl(kk,ii)
0728       enddo
0729       enddo
0730       call alist('&',nptl+1,nptl+1)
0731       endif
0732 
0733 c     exit
0734 c     ----
0735 
0736  1000 continue
0737       ip=ipp
0738       if(iret.ne.0.and.ish.ge.1)then
0739         write(ifmt,'(a)')'hdecay: redo event'
0740         write(ifch,'(a)')'hdecay: redo event'
0741       endif
0742       call utprix('hdecay',ish,ishini,5)
0743       return
0744 
0745  9999   call utstop('hdecay: mxptl too small&')
0746         end
0747 
0748 c---------------------------------------------------------------------
0749       subroutine vedi(k1,k2,k3,id)
0750 c---------------------------------------------------------------------
0751       include 'epos.inc'
0752       if(k2.eq.0)then
0753         if(rangen().lt.pdiqua.and.iabs(k1).lt.6)then
0754           ifl1=int(rangen()/pud)+1
0755           ifl2=int(rangen()/pud)+1
0756           k3=-min(ifl1,ifl2)*1000-max(ifl1,ifl2)*100
0757         else
0758           k3=int(rangen()/pud)+1
0759         endif
0760         if(k1.gt.0.and.k1.le.6)k3=-k3
0761         if(k1.lt.-1000)k3=-k3
0762       else
0763         k3=k2
0764       endif
0765       id=idsp(k1,k3)
0766       if(iabs(id).le.999) then
0767         ids=max(mod(iabs(id)/100,10),mod(iabs(id)/10,10))
0768         if(ids.le.2)then
0769           idr=sign(iabs(id)+int(rangen()+0.5),id)
0770         elseif(ids.eq.3)then
0771           idr=sign(iabs(id)+int(rangen()+0.6),id)
0772         else
0773           idr=sign(iabs(id)+int(rangen()+0.75),id)
0774         endif
0775       else
0776         idr=sign(iabs(id)+int(0.5+rangen()),id)
0777       endif
0778       id=idr
0779       if(ish.ge.5)write(ifch,*) 'Flavor:',k1,k2,k3,id
0780       end
0781 
0782 c-----------------------------------------------------------------------
0783       subroutine hdecin(lprint)
0784 c-----------------------------------------------------------------------
0785 c     sets up /dkytab/
0786 c-----------------------------------------------------------------------
0787       include 'epos.inc'
0788       common/wco/wmass2,wgam2
0789       dimension imode(6)
0790       character*8 idlabl,lmode(6),lres
0791       character*8 iblank
0792       logical lprint
0793       parameter (mxlook=10000,mxdky=2000)
0794       common/dkytab/look(mxlook),cbr(mxdky),mode(5,mxdky)
0795       common/nodcay/nodcay,noeta,nopi0,nonunu,noevol,nohadr
0796       logical nodcay,noeta,nopi0,nonunu,noevol,nohadr
0797       parameter (ndectb=1193)
0798       real dectab(7,ndectb)
0799 
0800       data ((dectab(i,j),i=1,7),j=  1, 18)/
0801      *  110., .98850,  10.,  10.,   0.,   0.,   0.
0802      *, 110.,1.00000,  10.,  12., -12.,   0.,   0.
0803      *, 220., .38000,  10.,  10.,   0.,   0.,   0.
0804      *, 220., .71000, 110., 110., 110.,   0.,   0.
0805      *, 220., .94600, 120.,-120., 110.,   0.,   0.
0806      *, 220., .99500, 120.,-120.,  10.,   0.,   0.
0807      *, 220.,1.00000,  10.,  12., -12.,   0.,   0.
0808      *, 330., .44100, 220., 120.,-120.,   0.,   0.
0809      *, 330., .66100, 220., 110., 110.,   0.,   0.
0810      *, 330., .95900, 111.,  10.,   0.,   0.,   0.
0811      *, 330., .98000, 221.,  10.,   0.,   0.,   0.
0812      *, 330.,1.00000,  10.,  10.,   0.,   0.,   0.
0813      *, 121.,1.00000, 120., 110.,   0.,   0.,   0.
0814      *, 111., .99989, 120.,-120.,   0.,   0.,   0.
0815      *, 111., .99993,  12., -12.,   0.,   0.,   0.
0816      *, 111.,1.00000,  14., -14.,   0.,   0.,   0.
0817      *, 221., .89900, 120.,-120., 110.,   0.,   0.
0818      *, 221., .91200, 120.,-120.,   0.,   0.,   0./
0819       data ((dectab(i,j),i=1,7),j= 19, 36)/
0820      *  221., .99992, 110.,  10.,   0.,   0.,   0.
0821      *, 221.,1.00000,  12., -12.,   0.,   0.,   0.
0822      *, 331., .48600, 130.,-130.,   0.,   0.,   0.
0823      *, 331., .83700, 230.,-230.,   0.,   0.,   0.
0824      *, 331., .98400, 120.,-120., 110.,   0.,   0.
0825      *, 331., .99944, 220.,  10.,   0.,   0.,   0.
0826      *, 331., .99975,  12., -12.,   0.,   0.,   0.
0827      *, 331.,1.00000,  14., -14.,   0.,   0.,   0.
0828      *, 230., .50000,  20.,   0.,   0.,   0.,   0.
0829      *, 230.,1.00000, -20.,   0.,   0.,   0.,   0.
0830      *, 131., .66670, 230., 120.,   0.,   0.,   0.
0831      *, 131.,1.00000, 130., 110.,   0.,   0.,   0.
0832      *, 231., .66670, 130.,-120.,   0.,   0.,   0.
0833      *, 231.,1.00000, 230., 110.,   0.,   0.,   0.
0834      *, 240., .11000,  12., -11., 230.,   0.,   0.
0835      *, 240., .17000,  12., -11., 231.,   0.,   0.
0836      *, 240., .28000,  14., -13., 230.,   0.,   0.
0837      *, 240., .34000,  14., -13., 231.,   0.,   0./
0838       data ((dectab(i,j),i=1,7),j= 37, 54)/
0839      *  240., .37800, 230.,-120.,   0.,   0.,   0.
0840      *, 240., .56300, 230.,-121.,   0.,   0.,   0.
0841      *, 240., .60800, 231.,-120.,   0.,   0.,   0.
0842      *, 240., .62100, 230.,-120., 110.,   0.,   0.
0843      *, 240., .71000, 130.,-120.,-120.,   0.,   0.
0844      *, 240., .80100, 230.,-120.,-120., 120.,   0.
0845      *, 240., .87900, 130.,-120.,-120., 110.,   0.
0846      *, 240., .95400, 230.,-120., 110., 110.,   0.
0847      *, 240., .96600, 230.,-130.,   0.,   0.,   0.
0848      *, 240., .97600, 331.,-120.,   0.,   0.,   0.
0849      *, 240., .98800,-130., 231.,   0.,   0.,   0.
0850      *, 240.,1.00000,-131., 230.,   0.,   0.,   0.
0851      *, 140., .04500, -12.,  11., 130.,   0.,   0.
0852      *, 140., .07500, -12.,  11., 131.,   0.,   0.
0853      *, 140., .12000, -14.,  13., 130.,   0.,   0.
0854      *, 140., .15000, -14.,  13., 131.,   0.,   0.
0855      *, 140., .20300, 130.,-120.,   0.,   0.,   0.
0856      *, 140., .22700, 230., 110.,   0.,   0.,   0./
0857       data ((dectab(i,j),i=1,7),j= 55, 72)/
0858      *  140., .24700, 230., 220.,   0.,   0.,   0.
0859      *, 140., .28900, 230., 221.,   0.,   0.,   0.
0860      *, 140., .45100, 130.,-121.,   0.,   0.,   0.
0861      *, 140., .53600, 131.,-120.,   0.,   0.,   0.
0862      *, 140., .56200, 231., 110.,   0.,   0.,   0.
0863      *, 140., .57600, 230., 111.,   0.,   0.,   0.
0864      *, 140., .58700, 130.,-120., 110.,   0.,   0.
0865      *, 140., .60300, 230.,-120., 120.,   0.,   0.
0866      *, 140., .72700, 130.,-120.,-120., 120.,   0.
0867      *, 140., .87600, 230.,-120., 120., 110.,   0.
0868      *, 140., .96900, 130.,-120., 110., 110.,   0.
0869      *, 140.,1.00000, 230., 110., 110., 110.,   0.
0870      *, 340., .03250,  12., -11., 220.,   0.,   0.
0871      *, 340., .06500,  12., -11., 331.,   0.,   0.
0872      *, 340., .09750,  14., -13., 220.,   0.,   0.
0873      *, 340., .13000,  14., -13., 331.,   0.,   0.
0874      *, 340., .17900,-130., 230.,   0.,   0.,   0.
0875      *, 340., .22800,-120., 220.,   0.,   0.,   0./
0876       data ((dectab(i,j),i=1,7),j= 73, 90)/
0877      *  340., .33800,-131., 230.,   0.,   0.,   0.
0878      *, 340., .44800,-130., 231.,   0.,   0.,   0.
0879      *, 340., .55800,-120., 331.,   0.,   0.,   0.
0880      *, 340., .57500,-130., 230., 110.,   0.,   0.
0881      *, 340., .59200,-230., 230.,-120.,   0.,   0.
0882      *, 340., .69400,-130., 230.,-120., 120.,   0.
0883      *, 340., .79600,-130., 230., 110., 110.,   0.
0884      *, 340., .89800,-130., 130.,-120., 110.,   0.
0885      *, 340.,1.00000,-230., 230.,-120., 110.,   0.
0886      *, 241., .64000, 140.,-120.,   0.,   0.,   0.
0887      *, 241., .92000, 240., 110.,   0.,   0.,   0.
0888      *, 241.,1.00000, 240.,  10.,   0.,   0.,   0.
0889      *, 141., .55000, 140., 110.,   0.,   0.,   0.
0890      *, 141.,1.00000, 140.,  10.,   0.,   0.,   0.
0891      *, 341.,1.00000, 340.,  10.,   0.,   0.,   0.
0892      *, 441., .07400,  12., -12.,   0.,   0.,   0.
0893      *, 441., .14800,  14., -14.,   0.,   0.,   0.
0894      *, 441., .15210,-121., 120.,   0.,   0.,   0./
0895       data ((dectab(i,j),i=1,7),j= 91,108)/
0896      *  441., .15620, 111., 110.,   0.,   0.,   0.
0897      *, 441., .16020, 121.,-120.,   0.,   0.,   0.
0898      *, 441., .16300,-121., 111., 120.,   0.,   0.
0899      *, 441., .16580, 121.,-121., 110.,   0.,   0.
0900      *, 441., .16860, 121., 111.,-120.,   0.,   0.
0901      *, 441., .28740, 120.,-120., 130.,-130.,   0.
0902      *, 441., .40620, 110., 110., 130.,-130.,   0.
0903      *, 441., .52500, 120.,-120., 120.,-120.,   0.
0904      *, 441., .64380, 120.,-120., 110., 110.,   0.
0905      *, 441., .76260, 110., 110., 110., 110.,   0.
0906      *, 441., .88130, 120.,-120., 230.,-230.,   0.
0907      *, 441.,1.00000, 110., 110., 230., 230.,   0.
0908      *, 150., .06000, -12.,  11., 140.,   0.,   0.
0909      *, 150., .12000, -12.,  11., 141.,   0.,   0.
0910      *, 150., .18000, -14.,  13., 140.,   0.,   0.
0911      *, 150., .24000, -14.,  13., 141.,   0.,   0.
0912      *, 150., .25500, -16.,  15., 140.,   0.,   0.
0913      *, 150., .27000, -16.,  15., 141.,   0.,   0./
0914       data ((dectab(i,j),i=1,7),j=109,122)/
0915      *  150., .28050, 140., 120.,   0.,   0.,   0.
0916      *, 150., .29100, 140., 121.,   0.,   0.,   0.
0917      *, 150., .30150, 141., 120.,   0.,   0.,   0.
0918      *, 150., .31200, 141., 121.,   0.,   0.,   0.
0919      *, 150., .32650, 140.,-340.,   0.,   0.,   0.
0920      *, 150., .34100, 140.,-341.,   0.,   0.,   0.
0921      *, 150., .35550, 141.,-340.,   0.,   0.,   0.
0922      *, 150., .37000, 141.,-341.,   0.,   0.,   0.
0923      *, 150., 0.820  ,   1.,  -4.,   1.,  -2.,   0.
0924      *, 150., 0.920  ,   1.,  -2.,   1.,  -4.,   0.
0925      *, 150., 0.975  ,   1.,  -4.,   4.,  -3.,   0.
0926      *, 150., 0.985  ,   1.,  -3.,   4.,  -4.,   0.
0927      *, 150., 0.995  ,   1.,  -1.,   1.,  -2.,   0.
0928      *, 150., 1.     ,   1.,  -1.,   4.,  -3.,   0./
0929       data ((dectab(i,j),i=1,7),j=123,142)
0930      */ 250., .06000, -12.,  11., 240.,   0.,   0.
0931      *, 250., .12000, -12.,  11., 241.,   0.,   0.
0932      *, 250., .18000, -14.,  13., 240.,   0.,   0.
0933      *, 250., .24000, -14.,  13., 241.,   0.,   0.
0934      *, 250., .25500, -16.,  15., 240.,   0.,   0.
0935      *, 250., .27000, -16.,  15., 241.,   0.,   0.
0936      *, 250., .28050, 240., 120.,   0.,   0.,   0.
0937      *, 250., .29100, 240., 121.,   0.,   0.,   0.
0938      *, 250., .30150, 241., 120.,   0.,   0.,   0.
0939      *, 250., .31200, 241., 121.,   0.,   0.,   0.
0940      *, 250., .32650, 240.,-340.,   0.,   0.,   0.
0941      *, 250., .34100, 240.,-341.,   0.,   0.,   0.
0942      *, 250., .35550, 241.,-340.,   0.,   0.,   0.
0943      *, 250., .37000, 241.,-341.,   0.,   0.,   0.
0944      *, 250., 0.820  ,   2.,  -4.,   1.,  -2.,   0.
0945      *, 250., 0.920  ,   2.,  -2.,   1.,  -4.,   0.
0946      *, 250., 0.975  ,   2.,  -4.,   4.,  -3.,   0.
0947      *, 250., 0.985  ,   2.,  -3.,   4.,  -4.,   0.
0948      *, 250., 0.995  ,   2.,  -1.,   1.,  -2.,   0.
0949      *, 250., 1.     ,   2.,  -1.,   4.,  -3.,   0./
0950       data ((dectab(i,j),i=1,7),j=143,176)/
0951      *     238*1. /
0952       data ((dectab(i,j),i=1,7),j=177,190)
0953      * /350., .06000,  12., -11., 340.,   0.,   0.
0954      *, 350., .12000,  12., -11., 341.,   0.,   0.
0955      *, 350., .18000,  14., -13., 340.,   0.,   0.
0956      *, 350., .24000,  14., -13., 341.,   0.,   0.
0957      *, 350., .25500,  16., -15., 340.,   0.,   0.
0958      *, 350., .27000,  16., -15., 341.,   0.,   0.
0959      *, 350., .28050, 340., 120.,   0.,   0.,   0.
0960      *, 350., .29100, 340., 121.,   0.,   0.,   0.
0961      *, 350., .30150, 341., 120.,   0.,   0.,   0.
0962      *, 350., .31200, 341., 121.,   0.,   0.,   0.
0963      *, 350., .32650, 340.,-340.,   0.,   0.,   0.
0964      *, 350., .34100, 340.,-341.,   0.,   0.,   0.
0965      *, 350., .35550, 341.,-340.,   0.,   0.,   0.
0966      *, 350., .37000, 341.,-341.,   0.,   0.,   0./
0967       data ((dectab(i,j),i=1,7),j=191,196)/
0968      *  350., 0.820  ,   3.,  -4.,   1.,  -2.,   0.
0969      *, 350., 0.920  ,   3.,  -2.,   1.,  -4.,   0.
0970      *, 350., 0.975  ,   3.,  -4.,   4.,  -3.,   0.
0971      *, 350., 0.985  ,   3.,  -3.,   4.,  -4.,   0.
0972      *, 350., 0.995  ,   3.,  -1.,   1.,  -2.,   0.
0973      *, 350., 1.     ,   3.,  -1.,   4.,  -3.,   0./
0974       data ((dectab(i,j),i=1,7),j=197,244)/
0975      *     336*1. /
0976       data ((dectab(i,j),i=1,7),j=245,262)/
0977      *  160., .33330,  -1.,   2.,  -5.,   0.,   0.
0978      *, 160., .66660,  -4.,   3.,  -5.,   0.,   0.
0979      *, 160., .77770,  11., -12.,  -5.,   0.,   0.
0980      *, 160., .88880,  13., -14.,  -5.,   0.,   0.
0981      *, 160.,1.00000, -15.,  16.,  -5.,   0.,   0.
0982      *, 260., .33330,  -1.,   2.,  -5.,   0.,   0.
0983      *, 260., .66660,  -4.,   3.,  -5.,   0.,   0.
0984      *, 260., .77770, -11.,  12.,  -5.,   0.,   0.
0985      *, 260., .88880, -13.,  14.,  -5.,   0.,   0.
0986      *, 260.,1.00000, -15.,  16.,  -5.,   0.,   0.
0987      *, 360., .33330,  -1.,   2.,  -5.,   0.,   0.
0988      *, 360., .66660,  -4.,   3.,  -5.,   0.,   0.
0989      *, 360., .77770, -11.,  12.,  -5.,   0.,   0.
0990      *, 360., .88880, -13.,  14.,  -5.,   0.,   0.
0991      *, 360.,1.00000, -15.,  16.,  -5.,   0.,   0.
0992      *, 151.,1.00000, 150.,  10.,   0.,   0.,   0.
0993      *, 251.,1.00000, 250.,  10.,   0.,   0.,   0.
0994      *, 351.,1.00000, 350.,  10.,   0.,   0.,   0./
0995       data ((dectab(i,j),i=1,7),j=263,280)/
0996      *  161.,1.00000, 160.,  10.,   0.,   0.,   0.
0997      *, 261.,1.00000, 260.,  10.,   0.,   0.,   0.
0998      *, 361.,1.00000, 360.,  10.,   0.,   0.,   0.
0999      *,1230.,1.00000,2130.,  10.,   0.,   0.,   0.
1000      *,1111.,1.00000,1120., 120.,   0.,   0.,   0.
1001      *,1121., .66670,1120., 110.,   0.,   0.,   0.
1002      *,1121.,1.00000,1220., 120.,   0.,   0.,   0.
1003      *,1221., .66670,1220., 110.,   0.,   0.,   0.
1004      *,1221.,1.00000,1120.,-120.,   0.,   0.,   0.
1005      *,2221.,1.00000,1220.,-120.,   0.,   0.,   0.
1006      *,1131., .88000,2130., 120.,   0.,   0.,   0.
1007      *,1131., .94000,1130., 110.,   0.,   0.,   0.
1008      *,1131.,1.00000,1230., 120.,   0.,   0.,   0.
1009      *,1231., .88000,2130., 110.,   0.,   0.,   0.
1010      *,1231., .94000,1130.,-120.,   0.,   0.,   0.
1011      *,1231.,1.00000,2230., 120.,   0.,   0.,   0.
1012      *,2231., .88000,2130.,-120.,   0.,   0.,   0.
1013      *,2231., .94000,1230.,-120.,   0.,   0.,   0./
1014       data ((dectab(i,j),i=1,7),j=281,298)/
1015      * 2231.,1.00000,2230., 110.,   0.,   0.,   0.
1016      *,1331., .66670,2330., 120.,   0.,   0.,   0.
1017      *,1331.,1.00000,1330., 110.,   0.,   0.,   0.
1018      *,2331., .66670,1330.,-120.,   0.,   0.,   0.
1019      *,2331.,1.00000,2330., 110.,   0.,   0.,   0.
1020      *,  16., .18000,  12., -11.,  15.,   0.,   0.
1021      *,  16., .36000,  14., -13.,  15.,   0.,   0.
1022      *,  16., .45100,-120.,  15.,   0.,   0.,   0.
1023      *,  16., .66000,-121.,  15.,   0.,   0.,   0.
1024      *,  16., .78000, 110., 110.,-120.,  15.,   0.
1025      *,  16., .83600, 120.,-120.,-120.,  15.,   0.
1026      *,  16.,1.00000, 120., 110.,-120.,-120.,  15.
1027      *,2140., .03750, -12.,  11.,2130.,   0.,   0.
1028      *,2140., .07500, -12.,  11.,1231.,   0.,   0.
1029      *,2140., .11250, -14.,  13.,2130.,   0.,   0.
1030      *,2140., .15000, -14.,  13.,1231.,   0.,   0.
1031      *,2140., .18200,2130., 120.,   0.,   0.,   0.
1032      *,2140., .21300,1230., 120.,   0.,   0.,   0./
1033       data ((dectab(i,j),i=1,7),j=299,316)/
1034      * 2140., .24400,1120.,-230.,   0.,   0.,   0.
1035      *,2140., .29500,1131., 110.,   0.,   0.,   0.
1036      *,2140., .34600,1231., 120.,   0.,   0.,   0.
1037      *,2140., .39700,1121.,-230.,   0.,   0.,   0.
1038      *,2140., .44800,1111.,-130.,   0.,   0.,   0.
1039      *,2140., .49900,1130., 111.,   0.,   0.,   0.
1040      *,2140., .55000,1230., 121.,   0.,   0.,   0.
1041      *,2140., .60100,1120.,-231.,   0.,   0.,   0.
1042      *,2140., .65800,1120.,-230., 120.,-120.,   0.
1043      *,2140., .71500,1120.,-230., 110., 110.,   0.
1044      *,2140., .77200,1120.,-130., 120., 110.,   0.
1045      *,2140., .82900,1220.,-230., 120., 110.,   0.
1046      *,2140., .88600,1220.,-130., 120., 120.,   0.
1047      *,2140., .94300,2130., 120., 120.,-120.,   0.
1048      *,2140.,1.00000,2130., 120., 110., 110.,   0.
1049      *,1140.,1.00000,2140., 120.,   0.,   0.,   0.
1050      *,1240.,1.00000,2140., 110.,   0.,   0.,   0.
1051      *,2240.,1.00000,2140.,-120.,   0.,   0.,   0./
1052       data ((dectab(i,j),i=1,7),j=317,334)/
1053      * 1340., .03750, -12.,  11.,1330.,   0.,   0.
1054      *,1340., .07500, -12.,  11.,1331.,   0.,   0.
1055      *,1340., .11250, -14.,  13.,1330.,   0.,   0.
1056      *,1340., .15000, -14.,  13.,1331.,   0.,   0.
1057      *,1340., .19900,1330., 120.,   0.,   0.,   0.
1058      *,1340., .24800,1231., 130.,   0.,   0.,   0.
1059      *,1340., .28800,1330., 120.,   0.,   0.,   0.
1060      *,1340., .32800,1131.,-230.,   0.,   0.,   0.
1061      *,1340., .36800,1330., 121.,   0.,   0.,   0.
1062      *,1340., .40800,1130.,-230.,   0.,   0.,   0.
1063      *,1340., .44800,1330., 120., 110.,   0.,   0.
1064      *,1340., .48800,2330., 120., 120.,   0.,   0.
1065      *,1340., .52800,1130.,-130., 120.,   0.,   0.
1066      *,1340., .56800,1130.,-230., 110.,   0.,   0.
1067      *,1340., .60800,1230.,-230., 120.,   0.,   0.
1068      *,1340., .66400,2130.,-230., 120., 110.,   0.
1069      *,1340., .72000,2130.,-130., 120., 120.,   0.
1070      *,1340., .77600,1130.,-230., 120.,-120.,   0./
1071       data ((dectab(i,j),i=1,7),j=335,352)/
1072      * 1340., .83200,1130.,-230., 110., 110.,   0.
1073      *,1340., .88800,1330., 120., 120.,-120.,   0.
1074      *,1340., .94400,1330., 120., 110., 110.,   0.
1075      *,1340.,1.00000,2330., 120., 120., 110.,   0.
1076      *,3140., .03750, -12.,  11.,1330.,   0.,   0.
1077      *,3140., .07500, -12.,  11.,1331.,   0.,   0.
1078      *,3140., .11250, -14.,  13.,1330.,   0.,   0.
1079      *,3140., .15000, -14.,  13.,1331.,   0.,   0.
1080      *,3140., .19900,1330., 120.,   0.,   0.,   0.
1081      *,3140., .24800,1231., 130.,   0.,   0.,   0.
1082      *,3140., .28800,1330., 120.,   0.,   0.,   0.
1083      *,3140., .32800,1131.,-230.,   0.,   0.,   0.
1084      *,3140., .36800,1330., 121.,   0.,   0.,   0.
1085      *,3140., .40800,1130.,-230.,   0.,   0.,   0.
1086      *,3140., .44800,1330., 120., 110.,   0.,   0.
1087      *,3140., .48800,2330., 120., 120.,   0.,   0.
1088      *,3140., .52800,1130.,-130., 120.,   0.,   0.
1089      *,3140., .56800,1130.,-230., 110.,   0.,   0./
1090       data ((dectab(i,j),i=1,7),j=353,370)/
1091      * 3140., .60800,1230.,-230., 120.,   0.,   0.
1092      *,3140., .66400,2130.,-230., 120., 110.,   0.
1093      *,3140., .72000,2130.,-130., 120., 120.,   0.
1094      *,3140., .77600,1130.,-230., 120.,-120.,   0.
1095      *,3140., .83200,1130.,-230., 110., 110.,   0.
1096      *,3140., .88800,1330., 120., 120.,-120.,   0.
1097      *,3140., .94400,1330., 120., 110., 110.,   0.
1098      *,3140.,1.00000,2330., 120., 120., 110.,   0.
1099      *,2340., .03750, -12.,  11.,2330.,   0.,   0.
1100      *,2340., .07500, -12.,  11.,2331.,   0.,   0.
1101      *,2340., .11250, -14.,  13.,2330.,   0.,   0.
1102      *,2340., .15000, -14.,  13.,2331.,   0.,   0.
1103      *,2340., .17500,2330., 120.,   0.,   0.,   0.
1104      *,2340., .20000,1330., 110.,   0.,   0.,   0.
1105      *,2340., .22500,1130.,-130.,   0.,   0.,   0.
1106      *,2340., .25000,1230.,-230.,   0.,   0.,   0.
1107      *,2340., .29500,2331., 120.,   0.,   0.,   0.
1108      *,2340., .34000,1331., 110.,   0.,   0.,   0./
1109       data ((dectab(i,j),i=1,7),j=371,388)/
1110      * 2340., .38500,1131.,-130.,   0.,   0.,   0.
1111      *,2340., .43000,1231.,-230.,   0.,   0.,   0.
1112      *,2340., .47500,2330., 121.,   0.,   0.,   0.
1113      *,2340., .52000,1330., 111.,   0.,   0.,   0.
1114      *,2340., .56500,1130.,-131.,   0.,   0.,   0.
1115      *,2340., .61000,1230.,-231.,   0.,   0.,   0.
1116      *,2340., .64900,2130.,-230., 120.,-120.,   0.
1117      *,2340., .68800,2130.,-230., 110., 110.,   0.
1118      *,2340., .72700,2130.,-130., 120., 110.,   0.
1119      *,2340., .76600,1130.,-230.,-120., 110.,   0.
1120      *,2340., .80500,1130.,-130., 120.,-120.,   0.
1121      *,2340., .84400,1130.,-130., 110., 110.,   0.
1122      *,2340., .88300,1330., 120.,-120., 110.,   0.
1123      *,2340., .92200,1330., 110., 110., 110.,   0.
1124      *,2340., .96100,2330., 120., 120.,-120.,   0.
1125      *,2340.,1.00000,2330., 120., 110., 110.,   0.
1126      *,3240., .03750, -12.,  11.,2330.,   0.,   0.
1127      *,3240., .07500, -12.,  11.,2331.,   0.,   0./
1128       data ((dectab(i,j),i=1,7),j=389,406)/
1129      * 3240., .11250, -14.,  13.,2330.,   0.,   0.
1130      *,3240., .15000, -14.,  13.,2331.,   0.,   0.
1131      *,3240., .17500,2330., 120.,   0.,   0.,   0.
1132      *,3240., .20000,1330., 110.,   0.,   0.,   0.
1133      *,3240., .22500,1130.,-130.,   0.,   0.,   0.
1134      *,3240., .25000,1230.,-230.,   0.,   0.,   0.
1135      *,3240., .29500,2331., 120.,   0.,   0.,   0.
1136      *,3240., .34000,1331., 110.,   0.,   0.,   0.
1137      *,3240., .38500,1131.,-130.,   0.,   0.,   0.
1138      *,3240., .43000,1231.,-230.,   0.,   0.,   0.
1139      *,3240., .47500,2330., 121.,   0.,   0.,   0.
1140      *,3240., .52000,1330., 111.,   0.,   0.,   0.
1141      *,3240., .56500,1130.,-131.,   0.,   0.,   0.
1142      *,3240., .61000,1230.,-231.,   0.,   0.,   0.
1143      *,3240., .64900,2130.,-230., 120.,-120.,   0.
1144      *,3240., .68800,2130.,-230., 110., 110.,   0.
1145      *,3240., .72700,2130.,-130., 120., 110.,   0.
1146      *,3240., .76600,1130.,-230.,-120., 110.,   0./
1147       data ((dectab(i,j),i=1,7),j=407,424)/
1148      * 3240., .80500,1130.,-130., 120.,-120.,   0.
1149      *,3240., .84400,1130.,-130., 110., 110.,   0.
1150      *,3240., .88300,1330., 120.,-120., 110.,   0.
1151      *,3240., .92200,1330., 110., 110., 110.,   0.
1152      *,3240., .96100,2330., 120., 120.,-120.,   0.
1153      *,3240.,1.00000,2330., 120., 110., 110.,   0.
1154      *,3340., .07500, -12.,  11.,3331.,   0.,   0.
1155      *,3340., .15000, -12.,  11.,3331.,   0.,   0.
1156      *,3340., .25000,1330.,-230.,   0.,   0.,   0.
1157      *,3340., .31000,3331., 120.,   0.,   0.,   0.
1158      *,3340., .37000,1331.,-230.,   0.,   0.,   0.
1159      *,3340., .43000,1330.,-231.,   0.,   0.,   0.
1160      *,3340., .49000,2330.,-230., 120.,   0.,   0.
1161      *,3340., .55000,1330.,-230., 110.,   0.,   0.
1162      *,3340., .61000,1330.,-130., 120.,   0.,   0.
1163      *,3340., .67500,3331., 120., 120.,-120.,   0.
1164      *,3340., .74000,3331., 120., 110., 110.,   0.
1165      *,3340., .80500,1330.,-230., 120.,-120.,   0./
1166       data ((dectab(i,j),i=1,7),j=425,442)/
1167      * 3340., .87000,1330.,-230., 110., 110.,   0.
1168      *,3340., .93500,2330.,-230., 120., 110.,   0.
1169      *,3340.,1.00000,2330.,-130., 120., 120.,   0.
1170      *,1141.,1.00000,2140., 120.,   0.,   0.,   0.
1171      *,1241.,1.00000,2140., 110.,   0.,   0.,   0.
1172      *,2241.,1.00000,2140.,-120.,   0.,   0.,   0.
1173      *,1341., .66670,2340., 120.,   0.,   0.,   0.
1174      *,1341.,1.00000,1340., 110.,   0.,   0.,   0.
1175      *,2341., .66670,1340.,-120.,   0.,   0.,   0.
1176      *,2341.,1.00000,2340., 110.,   0.,   0.,   0.
1177      *,3341.,1.00000,3340., 110.,   0.,   0.,   0.
1178      *,1150., .06000,  12., -11.,1140.,   0.,   0.
1179      *,1150., .12000,  12., -11.,1141.,   0.,   0.
1180      *,1150., .18000,  14., -13.,1140.,   0.,   0.
1181      *,1150., .24000,  14., -13.,1141.,   0.,   0.
1182      *,1150., .25500,  16., -15.,1140.,   0.,   0.
1183      *,1150., .27000,  16., -15.,1141.,   0.,   0.
1184      *,1150., .28925,1140.,-120.,   0.,   0.,   0./
1185       data ((dectab(i,j),i=1,7),j=443,460)/
1186      * 1150., .30850,1140.,-121.,   0.,   0.,   0.
1187      *,1150., .32775,1141.,-120.,   0.,   0.,   0.
1188      *,1150., .34700,1141.,-121.,   0.,   0.,   0.
1189      *,1150., .35775,1140., 340.,   0.,   0.,   0.
1190      *,1150., .36850,1140., 341.,   0.,   0.,   0.
1191      *,1150., .37925,1141., 340.,   0.,   0.,   0.
1192      *,1150., .39000,1141., 341.,   0.,   0.,   0.
1193      *,1150., .42050,1140.,-120., 110.,   0.,   0.
1194      *,1150., .45100,1140.,-120., 220.,   0.,   0.
1195      *,1150., .48150,1140.,-120., 111.,   0.,   0.
1196      *,1150., .51200,1140.,-120., 221.,   0.,   0.
1197      *,1150., .54250,1140.,-121., 110.,   0.,   0.
1198      *,1150., .57300,1140.,-121., 220.,   0.,   0.
1199      *,1150., .60350,1140.,-121., 111.,   0.,   0.
1200      *,1150., .63400,1140.,-121., 221.,   0.,   0.
1201      *,1150., .66450,1141.,-120., 110.,   0.,   0.
1202      *,1150., .69500,1141.,-120., 220.,   0.,   0.
1203      *,1150., .72550,1141.,-120., 111.,   0.,   0./
1204       data ((dectab(i,j),i=1,7),j=461,478)/
1205      * 1150., .75600,1141.,-120., 221.,   0.,   0.
1206      *,1150., .78650,1141.,-121., 110.,   0.,   0.
1207      *,1150., .81700,1141.,-121., 220.,   0.,   0.
1208      *,1150., .84750,1141.,-121., 111.,   0.,   0.
1209      *,1150., .87800,1141.,-121., 221.,   0.,   0.
1210      *,1150., .89325,1140.,-130., 230.,   0.,   0.
1211      *,1150., .90850,1140.,-130., 231.,   0.,   0.
1212      *,1150., .92375,1140.,-131., 230.,   0.,   0.
1213      *,1150., .93900,1140.,-131., 231.,   0.,   0.
1214      *,1150., .95425,1141.,-130., 230.,   0.,   0.
1215      *,1150., .96950,1141.,-130., 231.,   0.,   0.
1216      *,1150., .98475,1141.,-131., 230.,   0.,   0.
1217      *,1150.,1.00000,1141.,-131., 231.,   0.,   0.
1218      *,1250., .06000,  12., -11.,1240.,   0.,   0.
1219      *,1250., .12000,  12., -11.,1241.,   0.,   0.
1220      *,1250., .18000,  14., -13.,1240.,   0.,   0.
1221      *,1250., .24000,  14., -13.,1241.,   0.,   0.
1222      *,1250., .25500,  16., -15.,1240.,   0.,   0./
1223       data ((dectab(i,j),i=1,7),j=479,496)/
1224      * 1250., .27000,  16., -15.,1241.,   0.,   0.
1225      *,1250., .28925,1240.,-120.,   0.,   0.,   0.
1226      *,1250., .30850,1240.,-121.,   0.,   0.,   0.
1227      *,1250., .32775,1241.,-120.,   0.,   0.,   0.
1228      *,1250., .34700,1241.,-121.,   0.,   0.,   0.
1229      *,1250., .35775,1240., 340.,   0.,   0.,   0.
1230      *,1250., .36850,1240., 341.,   0.,   0.,   0.
1231      *,1250., .37925,1241., 340.,   0.,   0.,   0.
1232      *,1250., .39000,1241., 341.,   0.,   0.,   0.
1233      *,1250., .42050,1240.,-120., 110.,   0.,   0.
1234      *,1250., .45100,1240.,-120., 220.,   0.,   0.
1235      *,1250., .48150,1240.,-120., 111.,   0.,   0.
1236      *,1250., .51200,1240.,-120., 221.,   0.,   0.
1237      *,1250., .54250,1240.,-121., 110.,   0.,   0.
1238      *,1250., .57300,1240.,-121., 220.,   0.,   0.
1239      *,1250., .60350,1240.,-121., 111.,   0.,   0.
1240      *,1250., .63400,1240.,-121., 221.,   0.,   0.
1241      *,1250., .66450,1241.,-120., 110.,   0.,   0./
1242       data ((dectab(i,j),i=1,7),j=497,514)/
1243      * 1250., .69500,1241.,-120., 220.,   0.,   0.
1244      *,1250., .72550,1241.,-120., 111.,   0.,   0.
1245      *,1250., .75600,1241.,-120., 221.,   0.,   0.
1246      *,1250., .78650,1241.,-121., 110.,   0.,   0.
1247      *,1250., .81700,1241.,-121., 220.,   0.,   0.
1248      *,1250., .84750,1241.,-121., 111.,   0.,   0.
1249      *,1250., .87800,1241.,-121., 221.,   0.,   0.
1250      *,1250., .89325,1240.,-130., 230.,   0.,   0.
1251      *,1250., .90850,1240.,-130., 231.,   0.,   0.
1252      *,1250., .92375,1240.,-131., 230.,   0.,   0.
1253      *,1250., .93900,1240.,-131., 231.,   0.,   0.
1254      *,1250., .95425,1241.,-130., 230.,   0.,   0.
1255      *,1250., .96950,1241.,-130., 231.,   0.,   0.
1256      *,1250., .98475,1241.,-131., 230.,   0.,   0.
1257      *,1250.,1.00000,1241.,-131., 231.,   0.,   0.
1258      *,1350., .06000,  12., -11.,1340.,   0.,   0.
1259      *,1350., .12000,  12., -11.,1341.,   0.,   0.
1260      *,1350., .18000,  14., -13.,1340.,   0.,   0./
1261       data ((dectab(i,j),i=1,7),j=515,532)/
1262      * 1350., .24000,  14., -13.,1341.,   0.,   0.
1263      *,1350., .25500,  16., -15.,1340.,   0.,   0.
1264      *,1350., .27000,  16., -15.,1341.,   0.,   0.
1265      *,1350., .28925,1340.,-120.,   0.,   0.,   0.
1266      *,1350., .30850,1340.,-121.,   0.,   0.,   0.
1267      *,1350., .32775,1341.,-120.,   0.,   0.,   0.
1268      *,1350., .34700,1341.,-121.,   0.,   0.,   0.
1269      *,1350., .35775,1340., 340.,   0.,   0.,   0.
1270      *,1350., .36850,1340., 341.,   0.,   0.,   0.
1271      *,1350., .37925,1341., 340.,   0.,   0.,   0.
1272      *,1350., .39000,1341., 341.,   0.,   0.,   0.
1273      *,1350., .42050,1340.,-120., 110.,   0.,   0.
1274      *,1350., .45100,1340.,-120., 220.,   0.,   0.
1275      *,1350., .48150,1340.,-120., 111.,   0.,   0.
1276      *,1350., .51200,1340.,-120., 221.,   0.,   0.
1277      *,1350., .54250,1340.,-121., 110.,   0.,   0.
1278      *,1350., .57300,1340.,-121., 220.,   0.,   0.
1279      *,1350., .60350,1340.,-121., 111.,   0.,   0./
1280       data ((dectab(i,j),i=1,7),j=533,550)/
1281      * 1350., .63400,1340.,-121., 221.,   0.,   0.
1282      *,1350., .66450,1341.,-120., 110.,   0.,   0.
1283      *,1350., .69500,1341.,-120., 220.,   0.,   0.
1284      *,1350., .72550,1341.,-120., 111.,   0.,   0.
1285      *,1350., .75600,1341.,-120., 221.,   0.,   0.
1286      *,1350., .78650,1341.,-121., 110.,   0.,   0.
1287      *,1350., .81700,1341.,-121., 220.,   0.,   0.
1288      *,1350., .84750,1341.,-121., 111.,   0.,   0.
1289      *,1350., .87800,1341.,-121., 221.,   0.,   0.
1290      *,1350., .89325,1340.,-130., 230.,   0.,   0.
1291      *,1350., .90850,1340.,-130., 231.,   0.,   0.
1292      *,1350., .92375,1340.,-131., 230.,   0.,   0.
1293      *,1350., .93900,1340.,-131., 231.,   0.,   0.
1294      *,1350., .95425,1341.,-130., 230.,   0.,   0.
1295      *,1350., .96950,1341.,-130., 231.,   0.,   0.
1296      *,1350., .98475,1341.,-131., 230.,   0.,   0.
1297      *,1350.,1.00000,1341.,-131., 231.,   0.,   0.
1298      *,2150., .06000,  12., -11.,2140.,   0.,   0./
1299       data ((dectab(i,j),i=1,7),j=551,568)/
1300      * 2150., .12000,  12., -11.,1241.,   0.,   0.
1301      *,2150., .18000,  14., -13.,2140.,   0.,   0.
1302      *,2150., .24000,  14., -13.,1241.,   0.,   0.
1303      *,2150., .25500,  16., -15.,2140.,   0.,   0.
1304      *,2150., .27000,  16., -15.,1241.,   0.,   0.
1305      *,2150., .28925,2140.,-120.,   0.,   0.,   0.
1306      *,2150., .30850,2140.,-121.,   0.,   0.,   0.
1307      *,2150., .32775,1241.,-120.,   0.,   0.,   0.
1308      *,2150., .34700,1241.,-121.,   0.,   0.,   0.
1309      *,2150., .35775,2140., 340.,   0.,   0.,   0.
1310      *,2150., .36850,2140., 341.,   0.,   0.,   0.
1311      *,2150., .37925,1241., 340.,   0.,   0.,   0.
1312      *,2150., .39000,1241., 341.,   0.,   0.,   0.
1313      *,2150., .42050,2140.,-120., 110.,   0.,   0.
1314      *,2150., .45100,2140.,-120., 220.,   0.,   0.
1315      *,2150., .48150,2140.,-120., 111.,   0.,   0.
1316      *,2150., .51200,2140.,-120., 221.,   0.,   0.
1317      *,2150., .54250,2140.,-121., 110.,   0.,   0./
1318       data ((dectab(i,j),i=1,7),j=569,586)/
1319      * 2150., .57300,2140.,-121., 220.,   0.,   0.
1320      *,2150., .60350,2140.,-121., 111.,   0.,   0.
1321      *,2150., .63400,2140.,-121., 221.,   0.,   0.
1322      *,2150., .66450,1241.,-120., 110.,   0.,   0.
1323      *,2150., .69500,1241.,-120., 220.,   0.,   0.
1324      *,2150., .72550,1241.,-120., 111.,   0.,   0.
1325      *,2150., .75600,1241.,-120., 221.,   0.,   0.
1326      *,2150., .78650,1241.,-121., 110.,   0.,   0.
1327      *,2150., .81700,1241.,-121., 220.,   0.,   0.
1328      *,2150., .84750,1241.,-121., 111.,   0.,   0.
1329      *,2150., .87800,1241.,-121., 221.,   0.,   0.
1330      *,2150., .89325,2140.,-130., 230.,   0.,   0.
1331      *,2150., .90850,2140.,-130., 231.,   0.,   0.
1332      *,2150., .92375,2140.,-131., 230.,   0.,   0.
1333      *,2150., .93900,2140.,-131., 231.,   0.,   0.
1334      *,2150., .95425,1241.,-130., 230.,   0.,   0.
1335      *,2150., .96950,1241.,-130., 231.,   0.,   0.
1336      *,2150., .98475,1241.,-131., 230.,   0.,   0./
1337       data ((dectab(i,j),i=1,7),j=587,604)/
1338      * 2150.,1.00000,1241.,-131., 231.,   0.,   0.
1339      *,2250., .06000,  12., -11.,2240.,   0.,   0.
1340      *,2250., .12000,  12., -11.,2241.,   0.,   0.
1341      *,2250., .18000,  14., -13.,2240.,   0.,   0.
1342      *,2250., .24000,  14., -13.,2241.,   0.,   0.
1343      *,2250., .25500,  16., -15.,2240.,   0.,   0.
1344      *,2250., .27000,  16., -15.,2241.,   0.,   0.
1345      *,2250., .28925,2240.,-120.,   0.,   0.,   0.
1346      *,2250., .30850,2240.,-121.,   0.,   0.,   0.
1347      *,2250., .32775,2241.,-120.,   0.,   0.,   0.
1348      *,2250., .34700,2241.,-121.,   0.,   0.,   0.
1349      *,2250., .35775,2240., 340.,   0.,   0.,   0.
1350      *,2250., .36850,2240., 341.,   0.,   0.,   0.
1351      *,2250., .37925,2241., 340.,   0.,   0.,   0.
1352      *,2250., .39000,2241., 341.,   0.,   0.,   0.
1353      *,2250., .42050,2240.,-120., 110.,   0.,   0.
1354      *,2250., .45100,2240.,-120., 220.,   0.,   0.
1355      *,2250., .48150,2240.,-120., 111.,   0.,   0./
1356       data ((dectab(i,j),i=1,7),j=605,622)/
1357      * 2250., .51200,2240.,-120., 221.,   0.,   0.
1358      *,2250., .54250,2240.,-121., 110.,   0.,   0.
1359      *,2250., .57300,2240.,-121., 220.,   0.,   0.
1360      *,2250., .60350,2240.,-121., 111.,   0.,   0.
1361      *,2250., .63400,2240.,-121., 221.,   0.,   0.
1362      *,2250., .66450,2241.,-120., 110.,   0.,   0.
1363      *,2250., .69500,2241.,-120., 220.,   0.,   0.
1364      *,2250., .72550,2241.,-120., 111.,   0.,   0.
1365      *,2250., .75600,2241.,-120., 221.,   0.,   0.
1366      *,2250., .78650,2241.,-121., 110.,   0.,   0.
1367      *,2250., .81700,2241.,-121., 220.,   0.,   0.
1368      *,2250., .84750,2241.,-121., 111.,   0.,   0.
1369      *,2250., .87800,2241.,-121., 221.,   0.,   0.
1370      *,2250., .89325,2240.,-130., 230.,   0.,   0.
1371      *,2250., .90850,2240.,-130., 231.,   0.,   0.
1372      *,2250., .92375,2240.,-131., 230.,   0.,   0.
1373      *,2250., .93900,2240.,-131., 231.,   0.,   0.
1374      *,2250., .95425,2241.,-130., 230.,   0.,   0./
1375       data ((dectab(i,j),i=1,7),j=623,640)/
1376      * 2250., .96950,2241.,-130., 231.,   0.,   0.
1377      *,2250., .98475,2241.,-131., 230.,   0.,   0.
1378      *,2250.,1.00000,2241.,-131., 231.,   0.,   0.
1379      *,2350., .06000,  12., -11.,2340.,   0.,   0.
1380      *,2350., .12000,  12., -11.,2341.,   0.,   0.
1381      *,2350., .18000,  14., -13.,2340.,   0.,   0.
1382      *,2350., .24000,  14., -13.,2341.,   0.,   0.
1383      *,2350., .25500,  16., -15.,2340.,   0.,   0.
1384      *,2350., .27000,  16., -15.,2341.,   0.,   0.
1385      *,2350., .28925,2340.,-120.,   0.,   0.,   0.
1386      *,2350., .30850,2340.,-121.,   0.,   0.,   0.
1387      *,2350., .32775,2341.,-120.,   0.,   0.,   0.
1388      *,2350., .34700,2341.,-121.,   0.,   0.,   0.
1389      *,2350., .35775,2340., 340.,   0.,   0.,   0.
1390      *,2350., .36850,2340., 341.,   0.,   0.,   0.
1391      *,2350., .37925,2341., 340.,   0.,   0.,   0.
1392      *,2350., .39000,2341., 341.,   0.,   0.,   0.
1393      *,2350., .42050,2340.,-120., 110.,   0.,   0./
1394       data ((dectab(i,j),i=1,7),j=641,658)/
1395      * 2350., .45100,2340.,-120., 220.,   0.,   0.
1396      *,2350., .48150,2340.,-120., 111.,   0.,   0.
1397      *,2350., .51200,2340.,-120., 221.,   0.,   0.
1398      *,2350., .54250,2340.,-121., 110.,   0.,   0.
1399      *,2350., .57300,2340.,-121., 220.,   0.,   0.
1400      *,2350., .60350,2340.,-121., 111.,   0.,   0.
1401      *,2350., .63400,2340.,-121., 221.,   0.,   0.
1402      *,2350., .66450,2341.,-120., 110.,   0.,   0.
1403      *,2350., .69500,2341.,-120., 220.,   0.,   0.
1404      *,2350., .72550,2341.,-120., 111.,   0.,   0.
1405      *,2350., .75600,2341.,-120., 221.,   0.,   0.
1406      *,2350., .78650,2341.,-121., 110.,   0.,   0.
1407      *,2350., .81700,2341.,-121., 220.,   0.,   0.
1408      *,2350., .84750,2341.,-121., 111.,   0.,   0.
1409      *,2350., .87800,2341.,-121., 221.,   0.,   0.
1410      *,2350., .89325,2340.,-130., 230.,   0.,   0.
1411      *,2350., .90850,2340.,-130., 231.,   0.,   0.
1412      *,2350., .92375,2340.,-131., 230.,   0.,   0./
1413       data ((dectab(i,j),i=1,7),j=659,720)/
1414      * 434*1./
1415       data ((dectab(i,j),i=1,7),j=721,738)/
1416      * 2350., .93900,2340.,-131., 231.,   0.,   0.
1417      *,2350., .95425,2341.,-130., 230.,   0.,   0.
1418      *,2350., .96950,2341.,-130., 231.,   0.,   0.
1419      *,2350., .98475,2341.,-131., 230.,   0.,   0.
1420      *,2350.,1.00000,2341.,-131., 231.,   0.,   0.
1421      *,3150., .06000,  12., -11.,3140.,   0.,   0.
1422      *,3150., .12000,  12., -11.,1341.,   0.,   0.
1423      *,3150., .18000,  14., -13.,3140.,   0.,   0.
1424      *,3150., .24000,  14., -13.,1341.,   0.,   0.
1425      *,3150., .25500,  16., -15.,3140.,   0.,   0.
1426      *,3150., .27000,  16., -15.,1341.,   0.,   0.
1427      *,3150., .28925,3140.,-120.,   0.,   0.,   0.
1428      *,3150., .30850,3140.,-121.,   0.,   0.,   0.
1429      *,3150., .32775,1341.,-120.,   0.,   0.,   0.
1430      *,3150., .34700,1341.,-121.,   0.,   0.,   0.
1431      *,3150., .35775,3140., 340.,   0.,   0.,   0.
1432      *,3150., .36850,3140., 341.,   0.,   0.,   0.
1433      *,3150., .37925,1341., 340.,   0.,   0.,   0./
1434       data ((dectab(i,j),i=1,7),j=739,756)/
1435      * 3150., .39000,1341., 341.,   0.,   0.,   0.
1436      *,3150., .42050,3140.,-120., 110.,   0.,   0.
1437      *,3150., .45100,3140.,-120., 220.,   0.,   0.
1438      *,3150., .48150,3140.,-120., 111.,   0.,   0.
1439      *,3150., .51200,3140.,-120., 221.,   0.,   0.
1440      *,3150., .54250,3140.,-121., 110.,   0.,   0.
1441      *,3150., .57300,3140.,-121., 220.,   0.,   0.
1442      *,3150., .60350,3140.,-121., 111.,   0.,   0.
1443      *,3150., .63400,3140.,-121., 221.,   0.,   0.
1444      *,3150., .66450,1341.,-120., 110.,   0.,   0.
1445      *,3150., .69500,1341.,-120., 220.,   0.,   0.
1446      *,3150., .72550,1341.,-120., 111.,   0.,   0.
1447      *,3150., .75600,1341.,-120., 221.,   0.,   0.
1448      *,3150., .78650,1341.,-121., 110.,   0.,   0.
1449      *,3150., .81700,1341.,-121., 220.,   0.,   0.
1450      *,3150., .84750,1341.,-121., 111.,   0.,   0.
1451      *,3150., .87800,1341.,-121., 221.,   0.,   0.
1452      *,3150., .89325,3140.,-130., 230.,   0.,   0./
1453       data ((dectab(i,j),i=1,7),j=757,774)/
1454      * 3150., .90850,3140.,-130., 231.,   0.,   0.
1455      *,3150., .92375,3140.,-131., 230.,   0.,   0.
1456      *,3150., .93900,3140.,-131., 231.,   0.,   0.
1457      *,3150., .95425,1341.,-130., 230.,   0.,   0.
1458      *,3150., .96950,1341.,-130., 231.,   0.,   0.
1459      *,3150., .98475,1341.,-131., 230.,   0.,   0.
1460      *,3150.,1.00000,1341.,-131., 231.,   0.,   0.
1461      *,3250., .06000,  12., -11.,3240.,   0.,   0.
1462      *,3250., .12000,  12., -11.,2341.,   0.,   0.
1463      *,3250., .18000,  14., -13.,3240.,   0.,   0.
1464      *,3250., .24000,  14., -13.,2341.,   0.,   0.
1465      *,3250., .25500,  16., -15.,3240.,   0.,   0.
1466      *,3250., .27000,  16., -15.,2341.,   0.,   0.
1467      *,3250., .28925,3240.,-120.,   0.,   0.,   0.
1468      *,3250., .30850,3240.,-121.,   0.,   0.,   0.
1469      *,3250., .32775,2341.,-120.,   0.,   0.,   0.
1470      *,3250., .34700,2341.,-121.,   0.,   0.,   0.
1471      *,3250., .35775,3240., 340.,   0.,   0.,   0./
1472       data ((dectab(i,j),i=1,7),j=775,792)/
1473      * 3250., .36850,3240., 341.,   0.,   0.,   0.
1474      *,3250., .37925,2341., 340.,   0.,   0.,   0.
1475      *,3250., .39000,2341., 341.,   0.,   0.,   0.
1476      *,3250., .42050,3240.,-120., 110.,   0.,   0.
1477      *,3250., .45100,3240.,-120., 220.,   0.,   0.
1478      *,3250., .48150,3240.,-120., 111.,   0.,   0.
1479      *,3250., .51200,3240.,-120., 221.,   0.,   0.
1480      *,3250., .54250,3240.,-121., 110.,   0.,   0.
1481      *,3250., .57300,3240.,-121., 220.,   0.,   0.
1482      *,3250., .60350,3240.,-121., 111.,   0.,   0.
1483      *,3250., .63400,3240.,-121., 221.,   0.,   0.
1484      *,3250., .66450,2341.,-120., 110.,   0.,   0.
1485      *,3250., .69500,2341.,-120., 220.,   0.,   0.
1486      *,3250., .72550,2341.,-120., 111.,   0.,   0.
1487      *,3250., .75600,2341.,-120., 221.,   0.,   0.
1488      *,3250., .78650,2341.,-121., 110.,   0.,   0.
1489      *,3250., .81700,2341.,-121., 220.,   0.,   0.
1490      *,3250., .84750,2341.,-121., 111.,   0.,   0./
1491       data ((dectab(i,j),i=1,7),j=793,810)/
1492      * 3250., .87800,2341.,-121., 221.,   0.,   0.
1493      *,3250., .89325,3240.,-130., 230.,   0.,   0.
1494      *,3250., .90850,3240.,-130., 231.,   0.,   0.
1495      *,3250., .92375,3240.,-131., 230.,   0.,   0.
1496      *,3250., .93900,3240.,-131., 231.,   0.,   0.
1497      *,3250., .95425,2341.,-130., 230.,   0.,   0.
1498      *,3250., .96950,2341.,-130., 231.,   0.,   0.
1499      *,3250., .98475,2341.,-131., 230.,   0.,   0.
1500      *,3250.,1.00000,2341.,-131., 231.,   0.,   0.
1501      *,3350., .06000,  12., -11.,3340.,   0.,   0.
1502      *,3350., .12000,  12., -11.,3341.,   0.,   0.
1503      *,3350., .18000,  14., -13.,3340.,   0.,   0.
1504      *,3350., .24000,  14., -13.,3341.,   0.,   0.
1505      *,3350., .25500,  16., -15.,3340.,   0.,   0.
1506      *,3350., .27000,  16., -15.,3341.,   0.,   0.
1507      *,3350., .28925,3340.,-120.,   0.,   0.,   0.
1508      *,3350., .30850,3340.,-121.,   0.,   0.,   0.
1509      *,3350., .32775,3341.,-120.,   0.,   0.,   0./
1510       data ((dectab(i,j),i=1,7),j=811,828)/
1511      * 3350., .34700,3341.,-121.,   0.,   0.,   0.
1512      *,3350., .35775,3340., 340.,   0.,   0.,   0.
1513      *,3350., .36850,3340., 341.,   0.,   0.,   0.
1514      *,3350., .37925,3341., 340.,   0.,   0.,   0.
1515      *,3350., .39000,3341., 341.,   0.,   0.,   0.
1516      *,3350., .42050,3340.,-120., 110.,   0.,   0.
1517      *,3350., .45100,3340.,-120., 220.,   0.,   0.
1518      *,3350., .48150,3340.,-120., 111.,   0.,   0.
1519      *,3350., .51200,3340.,-120., 221.,   0.,   0.
1520      *,3350., .54250,3340.,-121., 110.,   0.,   0.
1521      *,3350., .57300,3340.,-121., 220.,   0.,   0.
1522      *,3350., .60350,3340.,-121., 111.,   0.,   0.
1523      *,3350., .63400,3340.,-121., 221.,   0.,   0.
1524      *,3350., .66450,3341.,-120., 110.,   0.,   0.
1525      *,3350., .69500,3341.,-120., 220.,   0.,   0.
1526      *,3350., .72550,3341.,-120., 111.,   0.,   0.
1527      *,3350., .75600,3341.,-120., 221.,   0.,   0.
1528      *,3350., .78650,3341.,-121., 110.,   0.,   0./
1529       data ((dectab(i,j),i=1,7),j=829,846)/
1530      * 3350., .81700,3341.,-121., 220.,   0.,   0.
1531      *,3350., .84750,3341.,-121., 111.,   0.,   0.
1532      *,3350., .87800,3341.,-121., 221.,   0.,   0.
1533      *,3350., .89325,3340.,-130., 230.,   0.,   0.
1534      *,3350., .90850,3340.,-130., 231.,   0.,   0.
1535      *,3350., .92375,3340.,-131., 230.,   0.,   0.
1536      *,3350., .93900,3340.,-131., 231.,   0.,   0.
1537      *,3350., .95425,3341.,-130., 230.,   0.,   0.
1538      *,3350., .96950,3341.,-130., 231.,   0.,   0.
1539      *,3350., .98475,3341.,-131., 230.,   0.,   0.
1540      *,3350.,1.00000,3341.,-131., 231.,   0.,   0.
1541      *,1160., .33300,   1.,  -2.,1500.,   0.,   0.
1542      *,1160., .66700,   4.,  -3.,1500.,   0.,   0.
1543      *,1160., .77800, -12.,  11.,1500.,   0.,   0.
1544      *,1160., .88900, -14.,  13.,1500.,   0.,   0.
1545      *,1160.,1.00000, -16.,  15.,1500.,   0.,   0.
1546      *,1260., .33300,   1.,  -2.,2500.,   0.,   0.
1547      *,1260., .66700,   4.,  -3.,2500.,   0.,   0./
1548       data ((dectab(i,j),i=1,7),j=847,864)/
1549      * 1260., .77800, -12.,  11.,2500.,   0.,   0.
1550      *,1260., .88900, -14.,  13.,2500.,   0.,   0.
1551      *,1260.,1.00000, -16.,  15.,2500.,   0.,   0.
1552      *,2260., .33300,   1.,  -2.,2500.,   0.,   0.
1553      *,2260., .66700,   4.,  -3.,2500.,   0.,   0.
1554      *,2260., .77800, -12.,  11.,2500.,   0.,   0.
1555      *,2260., .88900, -14.,  13.,2500.,   0.,   0.
1556      *,2260.,1.00000, -16.,  15.,2500.,   0.,   0.
1557      *,2160., .33300,   1.,  -2.,1500.,   0.,   0.
1558      *,2160., .66700,   4.,  -3.,1500.,   0.,   0.
1559      *,2160., .77800, -12.,  11.,1500.,   0.,   0.
1560      *,2160., .88900, -14.,  13.,1500.,   0.,   0.
1561      *,2160.,1.00000, -16.,  15.,1500.,   0.,   0.
1562      *,1360., .33300,   1.,  -2.,3500.,   0.,   0.
1563      *,1360., .66700,   4.,  -3.,3500.,   0.,   0.
1564      *,1360., .77800, -12.,  11.,3500.,   0.,   0.
1565      *,1360., .88900, -14.,  13.,3500.,   0.,   0.
1566      *,1360.,1.00000, -16.,  15.,3500.,   0.,   0./
1567       data ((dectab(i,j),i=1,7),j=865,882)/
1568      * 2360., .33300,   1.,  -2.,3500.,   0.,   0.
1569      *,2360., .66700,   4.,  -3.,3500.,   0.,   0.
1570      *,2360., .77800, -12.,  11.,3500.,   0.,   0.
1571      *,2360., .88900, -14.,  13.,3500.,   0.,   0.
1572      *,2360.,1.00000, -16.,  15.,3500.,   0.,   0.
1573      *,3360., .33300,   1.,  -2.,3500.,   0.,   0.
1574      *,3360., .66700,   4.,  -3.,3500.,   0.,   0.
1575      *,3360., .77800, -12.,  11.,3500.,   0.,   0.
1576      *,3360., .88900, -14.,  13.,3500.,   0.,   0.
1577      *,3360.,1.00000, -16.,  15.,3500.,   0.,   0.
1578      *,1151.,1.00000,1150.,  10.,   0.,   0.,   0.
1579      *,1251.,1.00000,1250.,  10.,   0.,   0.,   0.
1580      *,2251.,1.00000,2250.,  10.,   0.,   0.,   0.
1581      *,1351.,1.00000,1350.,  10.,   0.,   0.,   0.
1582      *,2351.,1.00000,2350.,  10.,   0.,   0.,   0.
1583      *,3351.,1.00000,3350.,  10.,   0.,   0.,   0.
1584      *,1161.,1.00000,1160.,  10.,   0.,   0.,   0.
1585      *,1261.,1.00000,1260.,  10.,   0.,   0.,   0./
1586       data ((dectab(i,j),i=1,7),j=883,886)/
1587      * 2261.,1.00000,2260.,  10.,   0.,   0.,   0.
1588      *,1361.,1.00000,1360.,  10.,   0.,   0.,   0.
1589      *,2361.,1.00000,2360.,  10.,   0.,   0.,   0.
1590      *,3361.,1.00000,3360.,  10.,   0.,   0.,   0./
1591 c    *---------------------------------------------
1592 c    *    delta++ resonances
1593 c    *---------------------------------------------
1594       data ((dectab(i,j),i=1,7),j=887,900)/
1595 c    *--dl++(1620)---------------------------------
1596      * 1112., .30000,1120., 120.,   0.,   0.,   0.
1597      *,1112., .66000,1111., 110.,   0.,   0.,   0.
1598      *,1112., .90000,1121., 120.,   0.,   0.,   0.
1599      *,1112.,1.00000,1120., 120., 110.,   0.,   0.
1600 c    *--dl++(1700)---------------------------------
1601      *,1113., .15000,1120., 120.,   0.,   0.,   0.
1602      *,1113., .51000,1111., 110.,   0.,   0.,   0.
1603      *,1113., .75000,1121., 120.,   0.,   0.,   0.
1604      *,1113.,1.00000,1120., 120., 110.,   0.,   0.
1605 c    *--dl++(1925)---------------------------------
1606      *,1114., .28000,1120., 120.,   0.,   0.,   0.
1607      *,1114., .40600,1111., 110.,   0.,   0.,   0.
1608      *,1114., .49000,1121., 120.,   0.,   0.,   0.
1609      *,1114., .69000,1120., 121.,   0.,   0.,   0.
1610      *,1114., .70000,1130., 130.,   0.,   0.,   0.
1611      *,1114.,1.00000,1122., 120.,   0.,   0.,   0./
1612 c    *---------------------------------------------
1613 c    *    delta- resonances
1614 c    *---------------------------------------------
1615       data ((dectab(i,j),i=1,7),j=901,914)/
1616 c    *--dl-(1620)----------------------------------
1617      * 2222., .30000,1220.,-120.,   0.,   0.,   0.
1618      *,2222., .66000,2221., 110.,   0.,   0.,   0.
1619      *,2222., .90000,1221.,-120.,   0.,   0.,   0.
1620      *,2222.,1.00000,1220., 110.,-120.,   0.,   0.
1621 c    *--dl-(1700)----------------------------------
1622      *,2223., .15000,1220.,-120.,   0.,   0.,   0.
1623      *,2223., .51000,2221., 110.,   0.,   0.,   0.
1624      *,2223., .75000,1221.,-120.,   0.,   0.,   0.
1625      *,2223.,1.00000,1220., 110.,-120.,   0.,   0.
1626 c    *--dl-(1925)----------------------------------
1627      *,2224., .28000,1220.,-120.,   0.,   0.,   0.
1628      *,2224., .40600,2221., 110.,   0.,   0.,   0.
1629      *,2224., .49000,1221.,-120.,   0.,   0.,   0.
1630      *,2224., .69000,1220.,-121.,   0.,   0.,   0.
1631      *,2224., .70000,2230., 230.,   0.,   0.,   0.
1632      *,2224.,1.00000,1222.,-120.,   0.,   0.,   0./
1633 c    *---------------------------------------------
1634 c    *    n*+ resonances + delta+ resonances
1635 c    *---------------------------------------------
1636       data ((dectab(i,j),i=1,7),j=915,931)/
1637 c    *--n*+(1440)----------------------------------
1638      * 1122., .20000,1120., 110.,   0.,   0.,   0.
1639      *,1122., .60000,1220., 120.,   0.,   0.,   0.
1640      *,1122., .68000,1111.,-120.,   0.,   0.,   0.
1641      *,1122., .73000,1121., 110.,   0.,   0.,   0.
1642      *,1122., .76000,1221., 120.,   0.,   0.,   0.
1643      *,1122., .84000,1120., 120.,-120.,   0.,   0.
1644      *,1122., .87000,1120., 110., 110.,   0.,   0.
1645      *,1122.,1.00000,1220., 120., 110.,   0.,   0.
1646 c    *--n*+(1530)----------------------------------
1647      *,1123., .17000,1120., 110.,   0.,   0.,   0.
1648      *,1123., .51000,1220., 120.,   0.,   0.,   0.
1649      *,1123., .57000,1111.,-120.,   0.,   0.,   0.
1650      *,1123., .61000,1121., 110.,   0.,   0.,   0.
1651      *,1123., .63000,1221., 120.,   0.,   0.,   0.
1652      *,1123., .67000,1120., 120.,-120.,   0.,   0.
1653      *,1123., .68000,1120., 110., 110.,   0.,   0.
1654      *,1123., .75000,1220., 120., 110.,   0.,   0.
1655      *,1123.,1.00000,1120., 220.,   0.,   0.,   0./
1656       data ((dectab(i,j),i=1,7),j=932,948)/
1657 c    *--dl+(1620)----------------------------------
1658      * 1124., .20000,1120., 110.,   0.,   0.,   0.
1659      *,1124., .30000,1220., 120.,   0.,   0.,   0.
1660      *,1124., .54000,1111.,-120.,   0.,   0.,   0.
1661      *,1124., .58000,1121., 110.,   0.,   0.,   0.
1662      *,1124., .90000,1221., 120.,   0.,   0.,   0.
1663      *,1124., .96000,1120., 120.,-120.,   0.,   0.
1664      *,1124.,1.00000,1220., 120., 110.,   0.,   0.
1665 c    *--n*+(1665)----------------------------------
1666      *,1125., .16700,1120., 110.,   0.,   0.,   0.
1667      *,1125., .49970,1220., 120.,   0.,   0.,   0.
1668      *,1125., .62470,1111.,-120.,   0.,   0.,   0.
1669      *,1125., .70800,1121., 110.,   0.,   0.,   0.
1670      *,1125., .74970,1221., 120.,   0.,   0.,   0.
1671      *,1125., .82080,1120., 120.,-120.,   0.,   0.
1672      *,1125., .85190,1120., 110., 110.,   0.,   0.
1673      *,1125., .96300,1220., 120., 110.,   0.,   0.
1674      *,1125., .97300,1120., 220.,   0.,   0.,   0.
1675      *,1125.,1.00000,2130., 130.,   0.,   0.,   0./
1676       data ((dectab(i,j),i=1,7),j=949,955)/
1677 c    *--dl+(1700)----------------------------------
1678      * 1126., .10000,1120., 110.,   0.,   0.,   0.
1679      *,1126., .15000,1220., 120.,   0.,   0.,   0.
1680      *,1126., .39000,1111.,-120.,   0.,   0.,   0.
1681      *,1126., .43000,1121., 110.,   0.,   0.,   0.
1682      *,1126., .75000,1221., 120.,   0.,   0.,   0.
1683      *,1126., .91500,1120., 120.,-120.,   0.,   0.
1684      *,1126.,1.00000,1220., 120., 110.,   0.,   0./
1685       data ((dectab(i,j),i=1,7),j=956,969)/
1686 c    *--n*+(1710)----------------------------------
1687      * 1127., .04430,1120., 110.,   0.,   0.,   0.
1688      *,1127., .13290,1220., 120.,   0.,   0.,   0.
1689      *,1127., .23790,1111.,-120.,   0.,   0.,   0.
1690      *,1127., .30790,1121., 110.,   0.,   0.,   0.
1691      *,1127., .34290,1221., 120.,   0.,   0.,   0.
1692      *,1127., .41190,1120., 120.,-120.,   0.,   0.
1693      *,1127., .48090,1120., 110., 110.,   0.,   0.
1694      *,1127., .54990,1220., 120., 110.,   0.,   0.
1695      *,1127., .66070,1120., 220.,   0.,   0.,   0.
1696      *,1127., .72800,2130., 130.,   0.,   0.,   0.
1697      *,1127., .74930,1230., 130.,   0.,   0.,   0.
1698      *,1127., .76000,1130., 230.,   0.,   0.,   0.
1699      *,1127., .84000,1120., 111.,   0.,   0.,   0.
1700      *,1127.,1.00000,1220., 121.,   0.,   0.,   0./
1701       data ((dectab(i,j),i=1,7),j=970,980)/
1702 c    *--dl+(1925)----------------------------------
1703      * 1128., .18700,1120., 110.,   0.,   0.,   0.
1704      *,1128., .28000,1220., 120.,   0.,   0.,   0.
1705      *,1128., .36400,1111.,-120.,   0.,   0.,   0.
1706      *,1128., .37800,1121., 110.,   0.,   0.,   0.
1707      *,1128., .49000,1221., 120.,   0.,   0.,   0.
1708      *,1128., .62300,1120., 111.,   0.,   0.,   0.
1709      *,1128., .69000,1220., 121.,   0.,   0.,   0.
1710      *,1128., .69350,1130., 230.,   0.,   0.,   0.
1711      *,1128., .69900,1230., 130.,   0.,   0.,   0.
1712      *,1128., .89900,1122., 110.,   0.,   0.,   0.
1713      *,1128.,1.00000,1222., 120.,   0.,   0.,   0./
1714 c    *---------------------------------------------
1715 c    *    n*0  resonances + delta0 resonances
1716 c    *---------------------------------------------
1717       data ((dectab(i,j),i=1,7),j=981,997)/
1718 c    *----------n*0(1440)--------------------------
1719      * 1222., .20000,1220., 110.,   0.,   0.,   0.
1720      *,1222., .60000,1120.,-120.,   0.,   0.,   0.
1721      *,1222., .68000,2221., 120.,   0.,   0.,   0.
1722      *,1222., .73000,1221., 110.,   0.,   0.,   0.
1723      *,1222., .76000,1121.,-120.,   0.,   0.,   0.
1724      *,1222., .84000,1220., 120.,-120.,   0.,   0.
1725      *,1222., .87000,1220., 110., 110.,   0.,   0.
1726      *,1222.,1.00000,1120.,-120., 110.,   0.,   0.
1727 c    *----------n*0(1530)--------------------------
1728      *,1223., .17000,1220., 110.,   0.,   0.,   0.
1729      *,1223., .51000,1120.,-120.,   0.,   0.,   0.
1730      *,1223., .57000,2221., 120.,   0.,   0.,   0.
1731      *,1223., .61000,1221., 110.,   0.,   0.,   0.
1732      *,1223., .63000,1121.,-120.,   0.,   0.,   0.
1733      *,1223., .67000,1220., 120.,-120.,   0.,   0.
1734      *,1223., .68000,1220., 110., 110.,   0.,   0.
1735      *,1223., .75000,1120.,-120., 110.,   0.,   0.
1736      *,1223.,1.00000,1220., 220.,   0.,   0.,   0./
1737       data ((dectab(i,j),i=1,7),j=998,1014)/
1738 c    *----------dl0(1620)--------------------------
1739      * 1224., .20000,1220., 110.,   0.,   0.,   0.
1740      *,1224., .30000,1120.,-120.,   0.,   0.,   0.
1741      *,1224., .54000,2221., 120.,   0.,   0.,   0.
1742      *,1224., .58000,1221., 110.,   0.,   0.,   0.
1743      *,1224., .90000,1121.,-120.,   0.,   0.,   0.
1744      *,1224., .96500,1220., 120.,-120.,   0.,   0.
1745      *,1224.,1.00000,1120.,-120., 110.,   0.,   0.
1746 c    *----------n*0(1665)--------------------------
1747      *,1225., .16700,1220., 110.,   0.,   0.,   0.
1748      *,1225., .49970,1120.,-120.,   0.,   0.,   0.
1749      *,1225., .62470,2221., 120.,   0.,   0.,   0.
1750      *,1225., .70800,1221., 110.,   0.,   0.,   0.
1751      *,1225., .74970,1121.,-120.,   0.,   0.,   0.
1752      *,1225., .82080,1220., 120.,-120.,   0.,   0.
1753      *,1225., .85190,1220., 110., 110.,   0.,   0.
1754      *,1225., .96300,1120.,-120., 110.,   0.,   0.
1755      *,1225., .97300,1220., 220.,   0.,   0.,   0.
1756      *,1225.,1.00000,2130., 230.,   0.,   0.,   0./
1757       data ((dectab(i,j),i=1,7),j=1015,1021)/
1758 c    *----------dl0(1700)--------------------------
1759      * 1226., .10000,1220., 110.,   0.,   0.,   0.
1760      *,1226., .15000,1120.,-120.,   0.,   0.,   0.
1761      *,1226., .39000,2221., 120.,   0.,   0.,   0.
1762      *,1226., .43000,1221., 110.,   0.,   0.,   0.
1763      *,1226., .75000,1121.,-120.,   0.,   0.,   0.
1764      *,1226., .91500,1220., 120.,-120.,   0.,   0.
1765      *,1226.,1.00000,1120.,-120., 110.,   0.,   0./
1766       data ((dectab(i,j),i=1,7),j=1022,1035)/
1767 c    *----------n*0(1710)--------------------------
1768      * 1227., .04430,1220., 110.,   0.,   0.,   0.
1769      *,1227., .13290,1120.,-120.,   0.,   0.,   0.
1770      *,1227., .23790,2221., 120.,   0.,   0.,   0.
1771      *,1227., .30790,1221., 110.,   0.,   0.,   0.
1772      *,1227., .34290,1121.,-120.,   0.,   0.,   0.
1773      *,1227., .41190,1220., 120.,-120.,   0.,   0.
1774      *,1227., .48090,1220., 110., 110.,   0.,   0.
1775      *,1227., .54990,1120.,-120., 110.,   0.,   0.
1776      *,1227., .66070,1220., 220.,   0.,   0.,   0.
1777      *,1227., .72800,2130., 230.,   0.,   0.,   0.
1778      *,1227., .73870,1230., 230.,   0.,   0.,   0.
1779      *,1227., .76000,2230., 130.,   0.,   0.,   0.
1780      *,1227., .92000,1120.,-121.,   0.,   0.,   0.
1781      *,1227.,1.00000,1220., 111.,   0.,   0.,   0./
1782       data ((dectab(i,j),i=1,7),j=1036,1046)/
1783 c    *----------dl0(1925)--------------------------
1784      * 1228., .18700,1220., 110.,   0.,   0.,   0.
1785      *,1228., .28000,1120.,-120.,   0.,   0.,   0.
1786      *,1228., .36400,2221., 120.,   0.,   0.,   0.
1787      *,1228., .37800,1221., 110.,   0.,   0.,   0.
1788      *,1228., .49000,1121.,-120.,   0.,   0.,   0.
1789      *,1228., .55700,1220., 111.,   0.,   0.,   0.
1790      *,1228., .69000,1120.,-121.,   0.,   0.,   0.
1791      *,1228., .69350,2230., 130.,   0.,   0.,   0.
1792      *,1228., .70000,1230., 230.,   0.,   0.,   0.
1793      *,1228., .80000,1122.,-120.,   0.,   0.,   0.
1794      *,1228.,1.00000,1222., 110.,   0.,   0.,   0./
1795 c    *---------------------------------------------
1796 c    *   lambda resonances + sigma0 resonances
1797 c    *---------------------------------------------
1798       data ((dectab(i,j),i=1,7),j=1047,1059)/
1799 c    *----------lambda(1405)-----------------------
1800      * 1233., .33000,1230., 110.,   0.,   0.,   0.
1801      *,1233., .66000,2230., 120.,   0.,   0.,   0.
1802      *,1233.,1.00000,1130.,-120.,   0.,   0.,   0.
1803 c    *----------lambda(1520)-----------------------
1804      *,1234., .22500,1120.,-130.,   0.,   0.,   0.
1805      *,1234., .48000,1220.,-230.,   0.,   0.,   0.
1806      *,1234., .62000,1230., 110.,   0.,   0.,   0.
1807      *,1234., .76000,2230., 120.,   0.,   0.,   0.
1808      *,1234., .90000,1130.,-120.,   0.,   0.,   0.
1809      *,1234., .96000,2130., 120.,-120.,   0.,   0.
1810      *,1234., .99000,2130., 110., 110.,   0.,   0.
1811      *,1234., .99330,1130.,-120., 110.,   0.,   0.
1812      *,1234., .99660,2230., 120., 110.,   0.,   0.
1813      *,1234.,1.00000,1230., 120.,-120.,   0.,   0./
1814       data ((dectab(i,j),i=1,7),j=1060,1075)/
1815 c    *----------lambda(1645)-----------------------
1816      * 1235., .10000,1120.,-130.,   0.,   0.,   0.
1817      *,1235., .20000,1220.,-230.,   0.,   0.,   0.
1818      *,1235., .35000,1230., 110.,   0.,   0.,   0.
1819      *,1235., .50000,2230., 120.,   0.,   0.,   0.
1820      *,1235., .65000,1130.,-120.,   0.,   0.,   0.
1821      *,1235., .75000,2130., 120.,-120.,   0.,   0.
1822      *,1235., .80000,2130., 110., 110.,   0.,   0.
1823      *,1235., .84500,1130.,-120., 110.,   0.,   0.
1824      *,1235., .89000,2230., 120., 110.,   0.,   0.
1825      *,1235., .93500,1230., 120.,-120.,   0.,   0.
1826      *,1235.,1.00000,2130., 220.,   0.,   0.,   0.
1827 c    *----------sigma0(1665)-----------------------
1828      *,1236., .10000,1120.,-130.,   0.,   0.,   0.
1829      *,1236., .20000,1220.,-230.,   0.,   0.,   0.
1830      *,1236., .40000,2230., 120.,   0.,   0.,   0.
1831      *,1236., .60000,1130.,-120.,   0.,   0.,   0.
1832      *,1236.,1.00000,2130., 110.,   0.,   0.,   0./
1833       data ((dectab(i,j),i=1,7),j=1076,1084)/
1834 c    *----------sigma0(1776)-----------------------
1835      * 1237., .17500,1120.,-130.,   0.,   0.,   0.
1836      *,1237., .35000,1220.,-230.,   0.,   0.,   0.
1837      *,1237., .38750,2230., 120.,   0.,   0.,   0.
1838      *,1237., .42500,1130.,-120.,   0.,   0.,   0.
1839      *,1237., .57500,2130., 110.,   0.,   0.,   0.
1840      *,1237., .60000,2231., 120.,   0.,   0.,   0.
1841      *,1237., .62500,1131.,-120.,   0.,   0.,   0.
1842      *,1237., .75000,1234., 110.,   0.,   0.,   0.
1843      *,1237.,1.00000,1230., 220.,   0.,   0.,   0./
1844       data ((dectab(i,j),i=1,7),j=1085,1094)/
1845 c    *----------lambda(1845)-----------------------
1846      * 1238., .17000,1120.,-130.,   0.,   0.,   0.
1847      *,1238., .34000,1220.,-230.,   0.,   0.,   0.
1848      *,1238., .44000,1230., 110.,   0.,   0.,   0.
1849      *,1238., .54000,2230., 120.,   0.,   0.,   0.
1850      *,1238., .64000,1130.,-120.,   0.,   0.,   0.
1851      *,1238., .70000,1231., 110.,   0.,   0.,   0.
1852      *,1238., .76000,2231., 120.,   0.,   0.,   0.
1853      *,1238., .82000,1131.,-120.,   0.,   0.,   0.
1854      *,1238., .91000,1120.,-131.,   0.,   0.,   0.
1855      *,1238.,1.00000,1220.,-231.,   0.,   0.,   0./
1856       data ((dectab(i,j),i=1,7),j=1095,1106)/
1857 c    *----------sigma0(1930)-----------------------
1858      * 1239., .07500,1120.,-130.,   0.,   0.,   0.
1859      *,1239., .15000,1220.,-230.,   0.,   0.,   0.
1860      *,1239., .20000,1121.,-130.,   0.,   0.,   0.
1861      *,1239., .25000,1221.,-230.,   0.,   0.,   0.
1862      *,1239., .32500,1120.,-131.,   0.,   0.,   0.
1863      *,1239., .40000,1220.,-231.,   0.,   0.,   0.
1864      *,1239., .47500,2230., 120.,   0.,   0.,   0.
1865      *,1239., .55000,1130.,-120.,   0.,   0.,   0.
1866      *,1239., .70000,2130., 110.,   0.,   0.,   0.
1867      *,1239., .77500,2231., 120.,   0.,   0.,   0.
1868      *,1239., .85000,1131.,-120.,   0.,   0.,   0.
1869      *,1239.,1.00000,1234., 110.,   0.,   0.,   0./
1870 c    *---------------------------------------------
1871 c    *            sigma+ resonances
1872 c    *---------------------------------------------
1873       data ((dectab(i,j),i=1,7),j=1107,1118)/
1874 c    *----------sigma+(1665)-----------------------
1875      * 1132., .20000,1120.,-230.,   0.,   0.,   0.
1876      *,1132., .40000,1130., 110.,   0.,   0.,   0.
1877      *,1132., .60000,1230., 120.,   0.,   0.,   0.
1878      *,1132.,1.00000,2130., 120.,   0.,   0.,   0.
1879 c    *----------sigma+(1776)-----------------------
1880      *,1133., .35000,1120.,-230.,   0.,   0.,   0.
1881      *,1133., .38750,1130., 110.,   0.,   0.,   0.
1882      *,1133., .42500,1230., 120.,   0.,   0.,   0.
1883      *,1133., .57500,2130., 120.,   0.,   0.,   0.
1884      *,1133., .60000,1131., 110.,   0.,   0.,   0.
1885      *,1133., .62500,1231., 120.,   0.,   0.,   0.
1886      *,1133., .75000,1234., 120.,   0.,   0.,   0.
1887      *,1133.,1.00000,1130., 220.,   0.,   0.,   0./
1888       data ((dectab(i,j),i=1,7),j=1119,1128)/
1889 c    *----------sigma+(1930)-----------------------
1890      * 1134., .15000,1120.,-230.,   0.,   0.,   0.
1891      *,1134., .22500,1111.,-130.,   0.,   0.,   0.
1892      *,1134., .25000,1121.,-230.,   0.,   0.,   0.
1893      *,1134., .40000,1120.,-231.,   0.,   0.,   0.
1894      *,1134., .47500,1130., 110.,   0.,   0.,   0.
1895      *,1134., .55000,1230., 120.,   0.,   0.,   0.
1896      *,1134., .70000,2130., 120.,   0.,   0.,   0.
1897      *,1134., .77500,1131., 110.,   0.,   0.,   0.
1898      *,1134., .85000,1231., 120.,   0.,   0.,   0.
1899      *,1134.,1.00000,1234., 120.,   0.,   0.,   0./
1900 c    *---------------------------------------------
1901 c    *            sigma- resonances
1902 c    *---------------------------------------------
1903       data ((dectab(i,j),i=1,7),j=1129,1140)/
1904 c    *----------sigma-(1665)-----------------------
1905      * 2232., .20000,1220.,-130.,   0.,   0.,   0.
1906      *,2232., .40000,2230., 110.,   0.,   0.,   0.
1907      *,2232., .60000,1230.,-120.,   0.,   0.,   0.
1908      *,2232.,1.00000,2130.,-120.,   0.,   0.,   0.
1909 c    *----------sigma-(1776)-----------------------
1910      *,2233., .35000,1220.,-130.,   0.,   0.,   0.
1911      *,2233., .38750,2230., 110.,   0.,   0.,   0.
1912      *,2233., .42500,1230.,-120.,   0.,   0.,   0.
1913      *,2233., .57500,2130.,-120.,   0.,   0.,   0.
1914      *,2233., .60000,2231., 110.,   0.,   0.,   0.
1915      *,2233., .62500,1231.,-120.,   0.,   0.,   0.
1916      *,2233., .75000,1234.,-120.,   0.,   0.,   0.
1917      *,2233.,1.00000,2230., 220.,   0.,   0.,   0./
1918       data ((dectab(i,j),i=1,7),j=1141,1150)/
1919 c    *----------sigma-(1930)-----------------------
1920      * 2234., .15000,1220.,-130.,   0.,   0.,   0.
1921      *,2234., .17500,1221.,-130.,   0.,   0.,   0.
1922      *,2234., .25000,2221.,-230.,   0.,   0.,   0.
1923      *,2234., .40000,1220.,-131.,   0.,   0.,   0.
1924      *,2234., .47500,2230., 110.,   0.,   0.,   0.
1925      *,2234., .55000,1230.,-120.,   0.,   0.,   0.
1926      *,2234., .70000,2130.,-120.,   0.,   0.,   0.
1927      *,2234., .77500,2231., 110.,   0.,   0.,   0.
1928      *,2234., .85000,1231.,-120.,   0.,   0.,   0.
1929      *,2234.,1.00000,1234.,-120.,   0.,   0.,   0./
1930 c    *---------------------------------------------
1931 c    *      additional mesonresonances
1932 c    *---------------------------------------------
1933       data ((dectab(i,j),i=1,7),j=1151,1159)/
1934 c    *-----------f0(975)---------------------------
1935      *  332., .50000, 120.,-120.,   0.,   0.,   0.
1936      *, 332., .75000, 110., 110.,   0.,   0.,   0.
1937      *, 332., .87500, 130.,-130.,   0.,   0.,   0.
1938      *, 332.,1.00000, 230.,-230.,   0.,   0.,   0.
1939 c    *-----------a0(980)---------------------------
1940      *, 112., .56000, 110., 220.,   0.,   0.,   0.
1941      *, 112., .78000, 130.,-130.,   0.,   0.,   0.
1942      *, 112.,1.00000, 230.,-230.,   0.,   0.,   0.
1943 c    *-----------a+(980)---------------------------
1944      *, 122., .60000, 120., 220.,   0.,   0.,   0.
1945      *, 122.,1.00000, 130.,-230.,   0.,   0.,   0./
1946 c    *---------------------------------------------
1947 c    *      weak baryon decays
1948 c    *---------------------------------------------
1949       data ((dectab(i,j),i=1,7),j=1160,1169)/
1950 c    *-----------lambda(1116)----------------------
1951      * 2130.,0.64200,1120.,-120.,   0.,   0.,   0.
1952      *,2130.,1.00000,1220., 110.,   0.,   0.,   0.
1953 c    *-----------sigma+(1180)----------------------
1954      *,1130.,0.51580,1120., 110.,   0.,   0.,   0.
1955      *,1130.,1.00000,1220., 120.,   0.,   0.,   0.
1956 c    *-----------sigma-(1180)----------------------
1957      *,2230.,1.00000,1220.,-120.,   0.,   0.,   0.
1958 c    *---------kaskade-(1360)----------------------
1959      *,2330.,1.00000,2130.,-120.,   0.,   0.,   0.
1960 c    *---------kaskade0(1360)----------------------
1961      *,1330.,1.00000,2130., 110.,   0.,   0.,   0.
1962 c    *---------omega-(1680)------------------------
1963      *,3331.,0.68000,2130.,-130.,   0.,   0.,   0.
1964      *,3331.,0.82000,1330.,-120.,   0.,   0.,   0.
1965      *,3331.,1.00000,2330., 110.,   0.,   0.,   0./
1966 c    *---------------------------------------------
1967 c    *      weak meson decays
1968 c    *---------------------------------------------
1969       data ((dectab(i,j),i=1,7),j=1170,1171)/
1970 c    *-----------k0s()--------------------------
1971      *   20., .68610, 120.,-120.,   0.,   0.,   0.
1972      *,  20.,1.00000, 110., 110.,   0.,   0.,   0./
1973       data ((dectab(i,j),i=1,7),j=1172,ndectb)/
1974 c    *-----------k0l-------------------------------
1975      *  320., .2113, 110., 110., 110.,   0.,   0.
1976      *, 320., .2113, 110., 110., 110.,   0.,   0.
1977      *, 320., .2120, 110., 110., 110.,   0.,   0.
1978      *, 320., .3380, 120.,-120., 110.,   0.,   0.
1979      *, 320., .4744, 120.,  14., -13.,   0.,   0.
1980      *, 320., .6108,-120., -14.,  13.,   0.,   0.
1981      *, 320., .8054, 120.,  12., -11.,   0.,   0.
1982      *, 320.,1.0000,-120., -12.,  11.,   0.,   0.
1983 c    *-----------k+-------------------------------
1984      *, 130., .6352 , -14.,  13.,   0.,   0.,   0.
1985      *, 130., .8468 , 120., 110.,   0.,   0.,   0.
1986      *, 130., .9027 , 120., 120.,-120.,   0.,   0.
1987      *, 130., .92   , 120., 110., 110.,   0.,   0.
1988      *, 130., .9518 , 110., -14.,  13.,   0.,   0.
1989      *, 130.,1.     , 110., -12.,  11.,   0.,   0.
1990 c    *-----------pi+------------------------------
1991      *, 120., 1.    , -14.,  13.,   0.,   0.,   0.
1992 c    *-----------mu-------------------------------
1993      *,  14., 1.    ,  12., -11.,  13.,   0.,   0.
1994 c    *-----------etac-------------------------------
1995      *, 440.,  .32  , 230.,-230., 110.,   0.,   0.
1996      *, 440.,  .64  , 220., 110., 110.,   0.,   0.
1997      *, 440.,  .76  , 120.,-120., 130.,-130.,   0.
1998      *, 440.,  .88  , 120.,-120., 120.,-120.,   0.
1999      *, 440., 1.    , 130.,-130., 130.,-130.,   0.
2000 c    *-----------etac-------------------------------
2001      *,1220., 1.    ,1120.,  12., -11.,   0.,   0./
2002 
2003       call idresi
2004 
2005 c     determine wmass2,wgam2
2006 c     ----------------------
2007       alfa=1./137.036
2008       gf=1.16570e-5
2009       sin2w=.215
2010       sinw=sqrt(sin2w)
2011 c      cosw=sqrt(1.-sin2w)           !?????????????????unused
2012       amw=sqrt(pi*alfa/(.9304*sqrt(2.)*gf))/sinw
2013       wmass2=amw
2014       call idmass(5,amlep5)
2015       call idmass(6,amlep6)
2016       ngam=12
2017       if(amlep5+amlep6.gt.amw) ngam=9
2018       wgam2=gf*amw**3/(6.*pi*sqrt(2.))*ngam
2019 
2020       data iblank/' '/
2021       ird=0
2022       do 1 i=1,mxlook
2023 1     look(i)=0
2024       do 2 i=1,mxdky
2025       do 3 j=1,5
2026 3     mode(j,i)=0
2027 2     cbr(i)=0.
2028       nodcay=.false.
2029       noeta=.false.
2030       nopi0=.false.
2031       nonunu=.false.
2032       noevol=.false.
2033       nohadr=.false.
2034       if(lprint) write(ifch,10)
2035 10    format('1',30('*')/' *',28x,'*'/
2036      1' *',5x,'isajet decay table',5x,'*'/
2037      2' *',28x,'*'/' ',30('*')//
2038      36x,'part',18x,'decay mode',19x,'cum br',15x,'ident',17x,
2039      4'decay ident')
2040       loop=0
2041       iold=0
2042       if(nodcay) return
2043 
2044 200   loop=loop+1
2045       if(loop.gt.mxdky) goto9999
2046 220   do 210 i=1,5
2047       imode(i)=0
2048       lmode(i)=iblank
2049 210   continue
2050       ird=ird+1
2051       if(ird.gt.ndectb)return
2052 c      if(ird.gt.1171)return   ! ??????????????????????????
2053       ires=nint(dectab(1,ird))
2054       br=dectab(2,ird)
2055       do 215 i=1,5
2056 215   imode(i)=nint(dectab(2+i,ird))
2057       if(nopi0.and.ires.eq.110) goto220
2058       if(noeta.and.ires.eq.220) goto220
2059       if(ires.eq.iold) goto230
2060       if(ires.lt.0.or.ires.gt.mxlook)
2061      *call utstop('hdecin: ires out of range&')
2062       look(ires)=loop
2063 230   iold=ires
2064       cbr(loop)=br
2065       do 240 i=1,5
2066       mode(i,loop)=imode(i)
2067       if(imode(i).ne.0) lmode(i)=idlabl(imode(i))
2068 240   continue
2069       lres=idlabl(ires)
2070       if(lprint) write(ifch,20) lres,(lmode(k),k=1,5),
2071      1br,ires,(imode(k),k=1,5)
2072 20    format(6x,a5,6x,5(a5,2x),3x,f8.5,15x,i5,4x,5(i5,2x))
2073       goto200
2074 
2075 9999  write(ifch,*)'loop=', loop
2076       call utstop('hdecin: loop > mxdky&')
2077 
2078       end
2079 
2080 C -----------------------------------------------
2081       FUNCTION FM(NQ,S0,S1,S2,S3)
2082 C -----------------------------------------------
2083 C Normalized TRANSITION MATRIX FOR THE DALIZT PLOT DISTRI.
2084 C OF K -> 3 PIONS. PARAMETRIZATION OF WEINBERG
2085 C AS DESCRIBE IN PARTICLE DATA BOOK.
2086 C G IS THE LINEAR COEFFICIENT (SLOPE g)
2087 C H IS THE QUADRATIC COEFFICIENT h
2088 C D IS THE QUADRATIC COEFFICIENT k
2089 C Amax is the maximum of this amplitude (taken from Corsika by D. Heck)
2090 C NQ is the decay channel :
2091 C   1 - K -> 3 Pi
2092 C   2 - K -> Pi + 2 Pi0
2093 C   3 - K0 -> 3 Pi0
2094 C   4 - K0 -> 2 Pi + Pi0
2095 C -----------------------------------------------
2096       DIMENSION G(4),H(4),D(4),Amax(4)
2097       PARAMETER (PIM=139.57E-3)
2098       DATA G/-0.2154,0.594,0.,0.67/
2099       DATA H/0.01,0.035,0.,0.079/
2100       DATA D/-0.01,0.,0.,0.0098/
2101       DATA Amax/1.27,1.84,1.,2.22/
2102 
2103       FM=1.+G(NQ)*(S3-S0)/(PIM*PIM)+H(NQ)*((S3-S0)/(PIM*PIM))**2
2104      *+D(NQ)*((S2-S1)/(PIM*PIM))**2
2105       FM=FM/Amax(NQ)
2106 
2107       RETURN
2108       END
2109 C -----------------------------------------------
2110       FUNCTION FML(N,AM,RM1,RM2,E1S,E2S,E3S)
2111 C -----------------------------------------------
2112 C Normalized DALITZ PLOT DENSITY (RHO)
2113 C OF K -> 1 PION + 2 LEPTONS
2114 C AS DESCRIBE IN PARTICLE DATA BOOK.
2115 C CLP IS THE LAMBDA + FORM FACTOR COEFFICIENT
2116 C CLN IS THE LAMBDA 0 FORM FACTOR COEFFICIENT
2117 C EEP IS E'pion
2118 C GP IS THE F+(t) FORM FACTOR (t=AM*AM+SM1-2.D0*AM*E1S)
2119 C H IS EPS(t)=F-(t)/F+(t) WHERE F- IS CALCULATED FROM F0
2120 C Amax is the maximum of this density (taken from Corsika by D. Heck)
2121 C N is the decay channel :
2122 C   1 - K -> Pi0 + e + Nu
2123 C   2 - K -> Pi0 + Mu + Nu
2124 C   3 - K0 -> Pi + e + Nu
2125 C   4 - K0 -> Pi + Mu + Nu
2126 C -----------------------------------------------
2127       DIMENSION CLP(4),CLN(4),Amax(4)
2128       DATA CLP/0.0276,0.031,0.0288,0.034/
2129       DATA CLN/0.0,0.006,0.,0.025/
2130       DATA Amax/1.28e-2,1.194e-2,1.31e-2,1.241e-2/
2131 
2132       SM1=RM1*RM1
2133       SM2=RM2*RM2
2134       EEP=0.5D0*(AM*AM+SM1-SM2)/AM-E1S
2135       GP=1.+CLP(N)*(AM*AM+SM1-2.*AM*E1S)/SM1
2136       H=(AM*AM-SM1)/SM1*(CLN(N)-CLP(N))/GP
2137       FML=GP*GP*(AM*(2.*E2S*E3S-AM*EEP)+
2138      *SM2*(0.25*EEP-E3S)+H*SM2*(E3S-0.5*EEP)+
2139      *0.25*H*H*SM2*EEP)
2140       FML=FML/Amax(N)
2141       RETURN
2142       END
2143 C -----------------------------------------------
2144       FUNCTION FMU(X)
2145 C -----------------------------------------------
2146 C PROBABILITY DISTRI. FOR ELECTRON ENERGY FROM MUON DECAY :
2147 C MU -> 2NU + E. DESCRIBE IN PARTICLE DATA BOOK.
2148 C (SIMPLIFY DIFFERENTIAL DECAY RATE INTEGRATED)
2149 C X REDUCED ENERGY OF PARTICLE
2150 C -----------------------------------------------
2151 
2152       FMU=2.*(3.-2.*X)*X*X
2153 
2154       RETURN
2155       END