All Classes Namespaces Files Functions Variables Typedefs Enumerations Enumerator Macros Groups
sycone.f
Go to the documentation of this file.
1 CDECK ID>, SYCONE.
2 **************************************************************************
3  SUBROUTINE sycone(NJREQ,NTRAK,ITKMAX,PTRAK,R,EPS,NJMAX,NJET,PJET,
4  + ipass,ijmul,ierr)
5 *.
6 *...SYCONE Like PXCONE, but forcing NJET=NJREQ.
7 * Fixes Epsilon and looks for largest value of R that gives NJREQ.
8 *.
9 *. INPUT :
10 *. OUTPUT :
11 *.
12 *. COMMON :
13 *. SEQUENCE :
14 *. CALLS : PXCONE VZERO
15 *. CALLED :
16 *.
17 *. REPORT CONDITIONS
18 *.
19 *. AUTHOR : D.R.Ward
20 *. VERSION : 1.02
21 *. CREATED : 5-Aug-94
22 *. LAST MOD : 09-Feb-1996
23 *.
24 *. Modification Log.
25 *. 09-Feb-96 S.Yamashita get from WWCONE in WWpackage WW106
26 *.**********************************************************************
27  implicit none
28  INTEGER ntrak,itkmax,njmax,njet,ipass(*),ijmul(*),ierr,nit,i,njreq
29  REAL ptrak(itkmax,*),r,eps,pjet(itkmax,*),r0,r1,r2,esum
30  esum=0.
31  DO 10 i=1,ntrak
32  esum=esum+ptrak(4,i)
33  10 CONTINUE
34  r0=0.
35  r1=0.8
36  r2=1.6
37  nit=0
38  r=r1
39  eps=esum/17.4
40  20 CALL pxcone(ntrak,itkmax,ptrak,r,eps,njmax,njet,pjet,
41  + ipass,ijmul,ierr)
42 * Print *,'NIT=',nit,' R=',R,' NJET=',njet
43  IF(njet.GT.njreq-1) THEN
44  r0=r1
45  r1=(r1+r2)/2.
46  ELSE
47  r2=r1
48  r1=(r1+r0)/2.
49  ENDIF
50  nit=nit+1
51  r=r1
52  IF(nit.LE.5 .OR. (nit.LE.10 .AND. njet.NE.njreq)) go to 20
53  r=r0
54  CALL vzero(ipass,ntrak)
55  CALL pxcone(ntrak,itkmax,ptrak,r,eps,njmax,njet,pjet,
56  + ipass,ijmul,ierr)
57  ierr=0
58  IF(njet.NE.njreq) ierr=1
59 * Print *,'Finally: R=',R,' Njet=',Njet, ' Ierr=',ierr
60  END
61 
62 *********************** E N D O F C O D E ********************************
63 *
64 *+PATCH,SYJDOC.
65 *INTRODUCTION:
66 *
67 * SYJJET
68 * is a set of routine which is desined to get better association of
69 * jet and particles especially for high mass Higgs and WW/ZZ SM processes.
70 *
71 * It needs to link with PX-lib, CKERN-lib (Stan's code for Cambridge)
72 *
73 * 1. SOURCE CODE : /u/ws/satoru/SYJJET/syjjet.car (SnOPAL)
74 * /u/ws/satoru/SYJJET/syjjet.car (shift)
75 * 2. Cradle File : /u/ws/satoru/SYJJET/SYJJET.CRA (SnOPAL)
76 * /u/ws/satoru/SYJJET/SYJJET.CRA (shift)
77 * 3. Library : /u/ws/satoru/syjjet.a (SnOPAL)
78 * /u/ws/satoru/syjjet.a (shift)
79 * ** This library already includes CKERN. So you just need to link with
80 * PX library as usual.
81 *
82 *
83 * This program can handle so-called traditional jet-finders and also
84 * newly developed "jet-associator".
85 *
86 * The idea of the improvement of jet-particle association is as follows.
87 * 1. Make core jet
88 * 2. using core-jet direction etc... re-association is done for all
89 * particles choosing the closest jet in terms of angle, Jade-parameter
90 * etc...
91 * Hence there are variety of combination can be made for
92 * possible core formation, jet-association, jet-merge etc...
93 *
94 * I've chosen a sort of good association and can be done simplly with
95 * call one routine
96 * SYJJET4 for 4 jet formation.
97 *
98 * This package includes a kernel program
99 * SYJKRN
100 *
101 * This routine can handle various jet finders and re-association scheme.
102 *
103 * Currently available traditional jet-finders are
104 * 1. JADE E0,E,P,P0
105 * 2. Geneva
106 * 3. Durham
107 * 4. Cambridge
108 * 5. Lund
109 * 6. Cone
110 *
111 * All can be used for
112 * A) fixed Ycut(Xcut/R/Eps)
113 * B) fixed number of jets
114 *
115 * Reassociation can be done with various "distance-parameters" such as
116 * 1. angle
117 * 2. JADE-type
118 * 3. Invariant mass
119 * 4. Durham-type
120 * etc...
121 *
122 * Also Jet Merge can be done with similar paramter for jet-jet "distance".
123 *
124 * 5jet, variable n-jet, etc... almost all things can be done with this
125 * program.
126 *
127 * ============================================================================
128 *USAGE:
129 *
130 * **** 4 J E T *****
131 * Just for 4-Jet, I describe here how to call it.
132 *
133 * O. link:
134 * your program and this library (syjjet.a) and px-library.
135 *
136 * A. CALL SYJJET4(NPAR,PPAR,JAS,PJET,Y34,Y45,IERR)
137 *
138 ** Inputs:
139 ** NPAR : I : Number of "MT-particles"
140 ** PPAR(5,*) R : 5-momentum for each "MT-particles"
141 ** Outputs:
142 ** JAS(*) I : Jet association like YASSO
143 ** PJET(5,*) R : Jet 5-momentum
144 ** Y34 Y45 R : Durham Y34/Y45
145 ** IERR I : 0 for O.K.
146 *
147 * If all calculations are O.K. (normal) IERR is 0.
148 * Y34 and Y45 with normal Durham are automatically back as Y34 and Y45.
149 * JAS(i) (i=1 to NPAR) should be between 1 and 4.
150 * This JAS is the results of re-association.
151 * PJET is the jet energy with energy ordering.
152 *
153 * The internal procedure for the jet-finding are as follows.
154 * 1. The program starts from 4-core-jets formation just with "particle" with
155 * more than 1.2 GeV threshold.
156 * 2. The event is forced to be 4-jets.
157 * 3. Then re-association starts.
158 * The "distance" used in this version is
159 * JADE-E0 type parameter between "particle" and "core-jet".
160 * All "particles" including that not used in core-formation (having lower
161 * energy than 1.2 GeV) are re-assigned to jet having smallest
subroutine sycone(NJREQ, NTRAK, ITKMAX, PTRAK, R, EPS, NJMAX, NJET, PJET, IPASS, IJMUL, IERR)
Definition: sycone.f:3
subroutine pxcone(NTRAK, ITKDM, PTRAK, CONER, EPSLON, MXJET, NJET, PJET, IPASS, IJMUL, IERR)
Definition: pxcone.f:2
gsl_rng * r
Definition: VTXNoiseHits.h:86