Merge lp:~maddevelopers/mg5amcnlo/simple_cut_via_pdgcode into lp:~mg5core2/mg5amcnlo/2.6.1

Proposed by Olivier Mattelaer
Status: Merged
Merged at revision: 308
Proposed branch: lp:~maddevelopers/mg5amcnlo/simple_cut_via_pdgcode
Merge into: lp:~mg5core2/mg5amcnlo/2.6.1
Diff against target: 843 lines (+467/-62)
9 files modified
Template/LO/Cards/run_card.dat (+9/-0)
Template/LO/Source/run.inc (+14/-1)
Template/LO/SubProcesses/setcuts.f (+67/-5)
Template/NLO/Cards/run_card.dat (+10/-1)
Template/NLO/Source/run.inc (+10/-1)
Template/NLO/SubProcesses/cuts.f (+33/-0)
Template/NLO/SubProcesses/setcuts.f (+143/-44)
madgraph/interface/common_run_interface.py (+14/-1)
madgraph/various/banner.py (+167/-9)
To merge this branch: bzr merge lp:~maddevelopers/mg5amcnlo/simple_cut_via_pdgcode
Reviewer Review Type Date Requested Status
Rikkert Frederix (community) Approve
Valentin Hirschi Pending
Stefano Frixione Pending
Review via email: mp+331864@code.launchpad.net

Description of the change

Add some basic cut (pt and invariant mass) specified by PDG code.
This is introduced both at NLO and LO.
(pseudo rapidity cut are also available at LO)

Some restriction apply to the particle that can be specified.
- No particle that can be already constraint by standard cut.
- No massless particle for NLO run

The cut is not just added in cuts.f but the phase-space integrator is also aware of such cut to improve the efficiency of the phase-space integration.
Some bug have been fix in that regards in the NLO part.

To post a comment you must log in.
Revision history for this message
Olivier Mattelaer (olivier-mattelaer) wrote :

Any comment on this?

I would like to release 2.6.1 quite quickly and would like to have this include.
Any objection?

If nobody speak, I will do one run of auto-review and merge it then.

Cheers,

Olivier

298. By Rikkert Frederix

small typos (mainly spelling) in the (N)LO/run_card.dat

299. By Rikkert Frederix

some very mild cleaning of the NLO cuts.f and setcuts.f

300. By Rikkert Frederix

small fixes (again mostly typos)

Revision history for this message
Rikkert Frederix (frederix) wrote :

Hi Olivier,

I started looking more carefully through this implementation (and fixing some of the English along the way).

About this in banner.py:

        if any(pdg in pdg_to_cut for pdg in [1,2,3,4,5,21,22,11,13,15]):
            # Note that this will double check in the fortran code
            raise Exception, "Can not use PDG related cuts for massless SM particles"

Can't we directly check if they are massless? Or is this not possible at this place in the code. In particular, in the 4FS the b's are massless (and in the 3FS even the charms are massless) and it should be perfectly fine for the code to work with those.

Cheers,
Rik

301. By Olivier Mattelaer

use maxjetflavor to test if light jet are massive or not --for validity check for pdgcut--. Plus secure the mxx_only_part_antipart against not valid input

Revision history for this message
Olivier Mattelaer (olivier-mattelaer) wrote :

Hi Rikkert,

Thanks to look at this.

> Can't we directly check if they are massless? Or is this not possible at this place in the code.

Since that routine encapsulated only the run_card information, the only information that we can (easily) use is the “maxjetflavor”
to check if you want put cut on b/c quark.

So I have changed the line to:
if any(pdg in pdg_to_cut for pdg in [21,22,11,13,15]+ range(self['maxjetflavor']+1)):

“maxjetflavor” is not a 100% save variable (the user can change it) but
1) This is an hidden parameter (so only expert are going to change it)
2) The massive check is also done at fortran level (so not really critical if someone bypass the crash here)
3) the code also check at fortran level that the flag is_a_j, is_a_lp, is_a_lm, is_a_ph are all on false)

Note that I do not want to allow to have c/b cut at LO since dedicated cut are already existing for such situation.

Cheers,

Olivier

PS: The associate test of such changes make me discover some cases where the code was not nicely protected against invalid input. So I have fix those as well.

> On Nov 17, 2017, at 17:10, Rikkert Frederix <email address hidden> wrote:
>
> Hi Olivier,
>
> I started looking more carefully through this implementation (and fixing some of the English along the way).
>
> About this in banner.py:
>
> if any(pdg in pdg_to_cut for pdg in [1,2,3,4,5,21,22,11,13,15]):
> # Note that this will double check in the fortran code
> raise Exception, "Can not use PDG related cuts for massless SM particles"
>
> Can't we directly check if they are massless? Or is this not possible at this place in the code. In particular, in the 4FS the b's are massless (and in the 3FS even the charms are massless) and it should be perfectly fine for the code to work with those.
>
> Cheers,
> Rik
>
> --
> https://code.launchpad.net/~maddevelopers/mg5amcnlo/simple_cut_via_pdgcode/+merge/331864
> Your team MadDevelopers is subscribed to branch lp:~maddevelopers/mg5amcnlo/simple_cut_via_pdgcode.

Revision history for this message
Rikkert Frederix (frederix) wrote :

Hi Olivier,

Thanks for implementing this. It's ready to go in my opinion.

Cheers,
Rik

review: Approve

Preview Diff

[H/L] Next/Prev Comment, [J/K] Next/Prev File, [N/P] Next/Prev Hunk
1=== modified file 'Template/LO/Cards/run_card.dat'
2--- Template/LO/Cards/run_card.dat 2017-07-28 13:11:54 +0000
3+++ Template/LO/Cards/run_card.dat 2017-11-18 00:45:50 +0000
4@@ -119,6 +119,8 @@
5 %(ptamax)s = ptamax ! maximum pt for the photons
6 %(ptlmax)s = ptlmax ! maximum pt for the charged leptons
7 %(missetmax)s = missetmax ! maximum missing Et (sum of neutrino's momenta)
8+ %(pt_min_pdg)s = pt_min_pdg ! pt cut for other particles (use pdg code). Applied on particle and anti-particle
9+ %(pt_max_pdg)s = pt_max_pdg ! pt cut for other particles (syntax e.g. {6: 100, 25: 50})
10 #*********************************************************************
11 # Minimum and maximum E's (in the center of mass frame) *
12 #*********************************************************************
13@@ -130,6 +132,8 @@
14 %(ebmax)s = ebmax ! maximum E for the b
15 %(eamax)s = eamax ! maximum E for the photons
16 %(elmax)s = elmax ! maximum E for the charged leptons
17+ %(e_min_pdg)s = e_min_pdg ! E cut for other particles (use pdg code). Applied on particle and anti-particle
18+ %(e_max_pdg)s = e_max_pdg ! E cut for other particles (syntax e.g. {6: 100, 25: 50})
19 #*********************************************************************
20 # Maximum and minimum absolute rapidity (for max, -1 means no cut) *
21 #*********************************************************************
22@@ -141,6 +145,8 @@
23 %(etabmin)s = etabmin ! min rap for the b
24 %(etaamin)s = etaamin ! min rap for the photons
25 %(etalmin)s = etalmin ! main rap for the charged leptons
26+ %(eta_min_pdg)s = eta_min_pdg ! rap cut for other particles (use pdg code). Applied on particle and anti-particle
27+ %(eta_max_pdg)s = eta_max_pdg ! rap cut for other particles (syntax e.g. {6: 2.5, 23: 5})
28 #*********************************************************************
29 # Minimum and maximum DeltaR distance *
30 #*********************************************************************
31@@ -177,6 +183,9 @@
32 %(mmbbmax)s = mmbbmax ! max invariant mass of a b pair
33 %(mmaamax)s = mmaamax ! max invariant mass of gamma gamma pair
34 %(mmllmax)s = mmllmax ! max invariant mass of l+l- (same flavour) lepton pair
35+ %(mxx_min_pdg)s = mxx_min_pdg ! min invariant mass of a pair of particles X/X~ (e.g. {6:250})
36+ %(mxx_only_part_antipart)s = mxx_only_part_antipart ! if True the invariant mass is applied only
37+ ! to pairs of particle/antiparticle and not to pairs of the same pdg codes.
38 #*********************************************************************
39 # Minimum and maximum invariant mass for all letpons *
40 #*********************************************************************
41
42=== modified file 'Template/LO/Source/run.inc'
43--- Template/LO/Source/run.inc 2016-08-20 06:27:26 +0000
44+++ Template/LO/Source/run.inc 2017-11-18 00:45:50 +0000
45@@ -70,4 +70,17 @@
46 C
47 integer pdgs_for_merging_cut(0:1000)
48 common/TO_MERGE/pdgs_for_merging_cut
49-
50+c
51+c
52+c
53+ integer pdg_cut(0:25)
54+ double precision ptmin4pdg(0:25)
55+ double precision ptmax4pdg(0:25)
56+ double precision Emin4pdg(0:25)
57+ double precision Emax4pdg(0:25)
58+ double precision etamin4pdg(0:25)
59+ double precision etamax4pdg(0:25)
60+ double precision mxxmin4pdg(0:25)
61+ logical mxxpart_antipart(1:25)
62+ common/TO_PDG_SPECIFIC_CUT/pdg_cut, ptmin4pdg,ptmax4pdg, Emin4pdg, Emax4pdg, etamin4pdg,
63+ &etamax4pdg, mxxmin4pdg,mxxpart_antipart
64\ No newline at end of file
65
66=== modified file 'Template/LO/SubProcesses/setcuts.f'
67--- Template/LO/SubProcesses/setcuts.f 2016-08-30 23:56:34 +0000
68+++ Template/LO/SubProcesses/setcuts.f 2017-11-18 00:45:50 +0000
69@@ -23,7 +23,7 @@
70 c
71 c LOCAL
72 c
73- integer i,j
74+ integer i,j,k
75 integer icollider,detail_level
76 integer ncheck
77 logical done,fopened
78@@ -114,7 +114,7 @@
79 c
80 c count the number of j/bjet/photon/lepton
81 c
82- integer nb_j, nb_b, nb_a, nb_l, nb_nocut
83+ integer nb_j, nb_b, nb_a, nb_l, nb_nocut,nb_pdg
84 double precision smin_p, smin_m ! local variable to compute smin
85 c
86 c setup masses for the final-state particles
87@@ -204,7 +204,7 @@
88 is_a_nu(i)=.false.
89
90
91-c-do not apply cuts to these
92+c-do not apply cuts to these. CAREFULL: PDG_CUT do not consider do_cuts (they simply check the cut_decays)
93 if (pmass(i).gt.20d0) do_cuts(i)=.false. ! no cuts on top,W,Z,H
94 if (abs(idup(i,1,iproc)).eq.12) do_cuts(i)=.false. ! no cuts on ve ve~
95 if (abs(idup(i,1,iproc)).eq.14) do_cuts(i)=.false. ! no cuts on vm vm~
96@@ -308,8 +308,27 @@
97 c endif
98 endif
99 enddo
100-
101-
102+c
103+c check for pdg specific cut
104+c
105+ if (pdg_cut(1).ne.0)then
106+
107+ do j=1,pdg_cut(0)
108+ do i=nincoming+1, nexternal
109+ if(.not.cut_decays.and.from_decay(i))then
110+ cycle
111+ endif
112+ if (abs(idup(i, 1, iproc)).eq.pdg_cut(j))then
113+ etmin(i) = ptmin4pdg(j)
114+ etmax(i)= ptmax4pdg(j)
115+ emin(i)= Emin4pdg(j)
116+ emax(i)= Emax4pdg(j)
117+ etamin(i)= etamin4pdg(j)
118+ etamax(i)= etamax4pdg(j)
119+ endif
120+ enddo
121+ enddo
122+ endif
123
124 c
125 c delta r cut
126@@ -385,6 +404,35 @@
127 endif
128 enddo
129 enddo
130+c
131+c smin cut from PDG cut
132+c
133+ if (pdg_cut(1).ne.0)then
134+ do k=1,pdg_cut(0)
135+ do i=nincoming+1, nexternal
136+ if(.not.cut_decays.and.from_decay(i))then
137+ cycle
138+ endif
139+ if (abs(idup(i, 1, iproc)).ne.pdg_cut(k))then
140+ cycle
141+ endif
142+ do j = i+1,nexternal
143+ if(.not.cut_decays.and.from_decay(j))then
144+ cycle
145+ endif
146+ if (mxxpart_antipart(k))then
147+ if (idup(j, 1, iproc).eq.-1*idup(i, 1, iproc))then
148+ s_min(j,i) = mxxmin4pdg(k)**2
149+ endif
150+ else
151+ if (abs(idup(j, 1, iproc)).eq.pdg_cut(k))then
152+ s_min(j,i) = mxxmin4pdg(k)**2
153+ endif
154+ endif
155+ enddo
156+ enddo
157+ enddo
158+ endif
159
160 c
161 c ptll cut (min and max)
162@@ -598,6 +646,20 @@
163 endif
164 smin = smin + max(smin_p**2, smin_m, mmnl**2, ptllmin**2, misset**2)
165 endif
166+c check for other PDG particle
167+ do i = 1,pdg_cut(0)
168+ nb_pdg=0
169+ do j=nincoming, nexternal
170+ if (abs(idup(i,1,iproc)).eq.pdg_cut(i))then
171+ k = j ! use to get the mass
172+ if(do_cuts(i)) nb_pdg = nb_pdg + 1
173+ endif
174+ enddo
175+ smin_p = nb_pdg *(pmass(k)**2 + ptmin4pdg(i)**2)
176+ smin_m = nb_pdg*((2-nb_pdg)*pmass(k)**2 + (nb_pdg-1)/2.*mxxmin4pdg(i)**2)
177+ smin = smin + max(smin_p, smin_m)
178+ enddo
179+
180 c ensure symmetry of s_min(i,j)
181 do i=nincoming+1,nexternal-1
182 do j=nincoming+1,nexternal-1
183
184=== modified file 'Template/NLO/Cards/run_card.dat'
185--- Template/NLO/Cards/run_card.dat 2017-07-28 07:44:57 +0000
186+++ Template/NLO/Cards/run_card.dat 2017-11-18 00:45:50 +0000
187@@ -71,7 +71,7 @@
188 # WARNING: PYTHIA6PT works only for processes without FSR!!!! *
189 #***********************************************************************
190 %(parton_shower)s = parton_shower
191- %(shower_scale_factor)s = shower_scale_factor ! multiply default shower starting
192+ %(shower_scale_factor)s = shower_scale_factor ! multiply default shower starting
193 ! scale by this factor
194 #***********************************************************************
195 # Renormalization and factorization scales *
196@@ -156,6 +156,15 @@
197 %(epsgamma)s = epsgamma ! epsilon_gamma parameter of eq.(3.4) in hep-ph/9801442
198 %(isoem)s = isoEM ! isolate photons from EM energy (photons and leptons)
199 #***********************************************************************
200+# Cuts associated to MASSIVE particles identified by their PDG codes. *
201+# All cuts are applied to both particles and anti-particles, so use *
202+# POSITIVE PDG CODES only. Example of the syntax is {6 : 100} or *
203+# {6:100, 25:200} for multiple particles *
204+#***********************************************************************
205+ %(pt_min_pdg)s = pt_min_pdg ! Min pT for a massive particle
206+ %(pt_max_pdg)s = pt_max_pdg ! Max pT for a massive particle
207+ %(mxx_min_pdg)s = mxx_min_pdg ! inv. mass for any pair of (anti)particles
208+#***********************************************************************
209 # For aMCfast+APPLGRID use in PDF fitting (http://amcfast.hepforge.org)*
210 #***********************************************************************
211 %(iappl)s = iappl ! aMCfast switch (0=OFF, 1=prepare grids, 2=fill grids)
212
213=== modified file 'Template/NLO/Source/run.inc'
214--- Template/NLO/Source/run.inc 2017-06-19 17:15:00 +0000
215+++ Template/NLO/Source/run.inc 2017-11-18 00:45:50 +0000
216@@ -78,4 +78,13 @@
217 c For FO run (with lhe type of analysis
218 c
219 double precision FO_LHE_weight_ratio
220- common /FO_ANALYSIS_LHW/FO_LHE_weight_ratio
221\ No newline at end of file
222+ common /FO_ANALYSIS_LHW/FO_LHE_weight_ratio
223+c
224+c
225+c
226+ integer pdg_cut(0:25)
227+ double precision ptmin4pdg(0:25)
228+ double precision ptmax4pdg(0:25)
229+ double precision mxxmin4pdg(0:25)
230+ logical mxxpart_antipart(1:25)
231+ common/TO_PDG_SPECIFIC_CUT/pdg_cut, ptmin4pdg,ptmax4pdg, mxxmin4pdg, mxxpart_antipart
232\ No newline at end of file
233
234=== modified file 'Template/NLO/SubProcesses/cuts.f'
235--- Template/NLO/SubProcesses/cuts.f 2017-08-08 11:31:26 +0000
236+++ Template/NLO/SubProcesses/cuts.f 2017-11-18 00:45:50 +0000
237@@ -40,6 +40,8 @@
238 external R2_04,invm2_04,pt_04,eta_04,pt,eta
239 c local integers
240 integer i,j
241+c temporary variable for caching locally computation
242+ double precision tmpvar
243 c jet cluster algorithm
244 integer nQCD,NJET,JET(nexternal)
245 double precision pQCD(0:3,nexternal),PJET(0:3,nexternal)
246@@ -62,6 +64,11 @@
247 double precision p_unlops(0:3,nexternal)
248 include "run.inc" ! includes the ickkw parameter
249 logical passUNLOPScuts
250+c PDG specific cut
251+ double precision etmin(nincoming+1:nexternal-1)
252+ double precision etmax(nincoming+1:nexternal-1)
253+ double precision mxxmin(nincoming+1:nexternal-1,nincoming+1:nexternal-1)
254+ common /to_cuts/etmin,etmax,mxxmin
255 c logicals that define if particles are leptons, jets or photons. These
256 c are filled from the PDG codes (iPDG array) in this function.
257 logical is_a_lp(nexternal),is_a_lm(nexternal),is_a_j(nexternal)
258@@ -372,6 +379,31 @@
259 c End photon isolation
260 endif
261
262+C
263+C PDG SPECIFIC CUTS (PT/M_IJ)
264+C
265+ do i=nincoming+1,nexternal-1
266+ if(etmin(i).gt.0d0 .or. etmax(i).gt.0d0)then
267+ tmpvar = pt_04(p(0,i))
268+ if (tmpvar.lt.etmin(i)) then
269+ passcuts_user=.false.
270+ return
271+ elseif (tmpvar.gt.etmax(i) .and. etmax(i).gt.0d0) then
272+ passcuts_user=.false.
273+ return
274+ endif
275+ endif
276+ do j=i+1, nexternal-1
277+ if (mxxmin(i,j).gt.0d0)then
278+ if (invm2_04(p(0,i),p(0,j),1d0).lt.mxxmin(i,j)**2)then
279+ passcuts_user=.false.
280+ return
281+ endif
282+ endif
283+ enddo
284+ enddo
285+
286+
287 C***************************************************************
288 C***************************************************************
289 C PUT HERE YOUR USER-DEFINED CUTS
290@@ -379,6 +411,7 @@
291 C***************************************************************
292 C
293 c$$$C EXAMPLE: cut on top quark pT
294+c$$$C Note that PDG specific cut are more optimised than simple user cut
295 c$$$ do i=1,nexternal ! loop over all external particles
296 c$$$ if (istatus(i).eq.1 ! final state particle
297 c$$$ & .and. abs(ipdg(i)).eq.6) then ! top quark
298
299=== modified file 'Template/NLO/SubProcesses/setcuts.f'
300--- Template/NLO/SubProcesses/setcuts.f 2017-06-16 08:20:04 +0000
301+++ Template/NLO/SubProcesses/setcuts.f 2017-11-18 00:45:50 +0000
302@@ -19,7 +19,7 @@
303 c
304 c LOCAL
305 c
306- integer i,j
307+ integer i,j,k
308 C
309 C GLOBAL
310 C
311@@ -36,6 +36,11 @@
312 LOGICAL IS_A_J(NEXTERNAL),IS_A_LP(NEXTERNAL),IS_A_LM(NEXTERNAL)
313 LOGICAL IS_A_PH(NEXTERNAL)
314 COMMON /TO_SPECISA/IS_A_J,IS_A_LP,IS_A_LM,IS_A_PH
315+c
316+ double precision etmin(nincoming+1:nexternal-1)
317+ double precision etmax(nincoming+1:nexternal-1)
318+ double precision mxxmin(nincoming+1:nexternal-1,nincoming+1:nexternal-1)
319+ common /to_cuts/etmin,etmax, mxxmin
320 c
321 c setup masses for the final-state particles (fills the /to_mass/ common block)
322 c
323@@ -87,6 +92,56 @@
324 c-photons
325 if (idup(i,1).eq.22) is_a_ph(i)=.true. ! photon
326 enddo
327+c
328+c check for pdg specific cut (pt/eta)
329+c
330+ do i=nincoming+1, nexternal-1 ! never include last particle
331+ etmin(i) = 0d0
332+ etmax(i) = -1d0
333+ do j = i, nexternal-1
334+ mxxmin(i,j) = 0d0
335+ enddo
336+ enddo
337+
338+ if (pdg_cut(1).ne.0)then
339+ do j=1,pdg_cut(0)
340+ do i=nincoming+1, nexternal-1 ! never include last particle
341+ if (abs(idup(i,1)).ne.pdg_cut(j)) cycle
342+c fully ensure that only massive particles are allowed at NLO
343+ if(pmass(i).eq.0d0) then
344+ write(*,*) 'Illegal use of pdg specific cut.'
345+ write(*,*) 'For NLO process, '/
346+ $ /'only massive particle can be included'
347+ stop 1
348+ endif
349+c fully ensure that this is not a jet/lepton/photon
350+ if(is_a_lp(i) .or. is_a_lm(i) .or. is_a_j(i) .or.
351+ $ is_a_ph(i)) then
352+ write(*,*) 'Illegal use of pdg specific cut.'
353+ write(*,*) 'This can not be used for '/
354+ $ /'jet/lepton/photon/gluon'
355+ stop 1
356+ endif
357+ etmin(i) = ptmin4pdg(j)
358+ etmax(i) = ptmax4pdg(j)
359+! add the invariant mass cut
360+ if(mxxmin4pdg(j).ne.0d0)then
361+ do k=i+1, nexternal-1
362+ if (mxxpart_antipart(j))then
363+ if (idup(k, 1).eq.-1*idup(i,1))then
364+ mxxmin(i,k) = mxxmin4pdg(j)
365+ endif
366+ else
367+ if (abs(idup(k, 1)).eq.pdg_cut(j))then
368+ mxxmin(i,k) = mxxmin4pdg(j)
369+ endif
370+ endif
371+ enddo
372+ endif
373+ enddo
374+ enddo
375+ endif
376+
377
378 RETURN
379 END
380@@ -157,6 +212,14 @@
381 common /c_leshouche_inc/idup,mothup,icolup,niprocs
382 real*8 emass(nexternal)
383 common/to_mass/emass
384+c block for the (simple) cut bsed on the pdg
385+ double precision etmin(nincoming+1:nexternal-1)
386+ double precision etmax(nincoming+1:nexternal-1)
387+ double precision mxxmin(nincoming+1:nexternal-1,nincoming+1:nexternal-1)
388+ common /to_cuts/etmin,etmax,mxxmin
389+ double precision smin_update , mxx
390+ integer nb_iden_pdg
391+c
392 logical firsttime,firsttime_chans(maxchannels)
393 data firsttime /.true./
394 data firsttime_chans/maxchannels*.true./
395@@ -201,13 +264,13 @@
396 c Add the minimal jet pTs to tau
397 if(IS_A_J(i) .and. i.ne.nexternal)then
398 if (j_fks.gt.nincoming .and. j_fks.lt.nexternal) then
399- taumin(iFKS,ichan)=taumin(iFKS,ichan)+max(ptj,emass(i))
400- taumin_s(iFKS,ichan)=taumin_s(iFKS,ichan)+max(ptj,emass(i))
401- taumin_j(iFKS,ichan)=taumin_j(iFKS,ichan)+max(ptj,emass(i))
402+ taumin(iFKS,ichan)=taumin(iFKS,ichan)+dsqrt(ptj**2 +emass(i)**2)
403+ taumin_s(iFKS,ichan)=taumin_s(iFKS,ichan)+dsqrt(ptj**2 +emass(i)**2)
404+ taumin_j(iFKS,ichan)=taumin_j(iFKS,ichan)+dsqrt(ptj**2 +emass(i)**2)
405 elseif (j_fks.ge.1 .and. j_fks.le.nincoming) then
406 taumin(iFKS,ichan)=taumin(iFKS,ichan)+emass(i)
407- taumin_s(iFKS,ichan)=taumin_s(iFKS,ichan)+max(ptj,emass(i))
408- taumin_j(iFKS,ichan)=taumin_j(iFKS,ichan)+max(ptj,emass(i))
409+ taumin_s(iFKS,ichan)=taumin_s(iFKS,ichan)+dsqrt(ptj**2 +emass(i)**2)
410+ taumin_j(iFKS,ichan)=taumin_j(iFKS,ichan)+dsqrt(ptj**2 +emass(i)**2)
411 elseif (j_fks.eq.nexternal) then
412 write (*,*)
413 & 'ERROR, j_fks cannot be the final parton'
414@@ -234,11 +297,13 @@
415 xm(i)=emass(i)+ptgmin
416 elseif (is_a_lp(i)) then
417 c Add the postively charged lepton pTs to tau
418- taumin(iFKS,ichan)=taumin(iFKS,ichan)+emass(i)
419- if (j_fks.gt.nincoming)
420- & taumin(iFKS,ichan)=taumin(iFKS,ichan)+ptl
421- taumin_s(iFKS,ichan)=taumin_s(iFKS,ichan)+emass(i)+ptl
422- taumin_j(iFKS,ichan)=taumin_j(iFKS,ichan)+emass(i)+ptl
423+ if (j_fks.gt.nincoming) then
424+ taumin(iFKS,ichan)=taumin(iFKS,ichan)+dsqrt(ptl**2+emass(i)**2)
425+ else
426+ taumin(iFKS,ichan)=taumin(iFKS,ichan)+emass(i)
427+ endif
428+ taumin_s(iFKS,ichan)=taumin_s(iFKS,ichan)+dsqrt(emass(i)**2+ptl**2)
429+ taumin_j(iFKS,ichan)=taumin_j(iFKS,ichan)+dsqrt(emass(i)**2+ptl**2)
430 xm(i)=emass(i)+ptl
431 c Add the lepton invariant mass to tau if there is at least another
432 c lepton of opposite charge. (Only add half of it, i.e. 'the part
433@@ -248,23 +313,23 @@
434 if (is_a_lm(j) .and. idup(i,1).eq.-idup(j,1) .and.
435 $ (mll_sf.ne.0d0 .or. mll.ne.0d0) ) then
436 if (j_fks.gt.nincoming)
437- & taumin(iFKS,ichan) = taumin(iFKS,ichan)-ptl-emass(i) +
438- & max(mll/2d0,mll_sf/2d0,ptl+emass(i))
439- taumin_s(iFKS,ichan) = taumin_s(iFKS,ichan)-ptl-emass(i)
440- $ + max(mll/2d0,mll_sf/2d0,ptl+emass(i))
441- taumin_j(iFKS,ichan) = taumin_j(iFKS,ichan)-ptl-emass(i)
442- $ + max(mll/2d0,mll_sf/2d0,ptl+emass(i))
443+ & taumin(iFKS,ichan) = taumin(iFKS,ichan)-dsqrt(ptl**2+emass(i)**2) +
444+ & max(mll/2d0,mll_sf/2d0,dsqrt(ptl**2+emass(i)**2))
445+ taumin_s(iFKS,ichan) = taumin_s(iFKS,ichan)-dsqrt(ptl**2+emass(i)**2)
446+ $ + max(mll/2d0,mll_sf/2d0,dsqrt(ptl**2+emass(i)**2))
447+ taumin_j(iFKS,ichan) = taumin_j(iFKS,ichan)-dsqrt(ptl**2+emass(i)**2)
448+ $ + max(mll/2d0,mll_sf/2d0,dsqrt(ptl**2+emass(i)**2))
449 xm(i)=xm(i)-ptl-emass(i)+max(mll/2d0,mll_sf/2d0
450 $ ,ptl+emass(i))
451 exit
452 elseif (is_a_lm(j) .and. mll.ne.0d0) then
453 if (j_fks.gt.nincoming)
454- & taumin(iFKS,ichan)= taumin(iFKS,ichan)-ptl-emass(i) +
455- & max(mll/2d0,ptl+emass(i))
456- taumin_s(iFKS,ichan) = taumin_s(iFKS,ichan)-ptl-emass(i)
457- $ + max(mll/2d0,ptl+emass(i))
458- taumin_j(iFKS,ichan) = taumin_j(iFKS,ichan)-ptl-emass(i)
459- $ + max(mll/2d0,ptl+emass(i))
460+ & taumin(iFKS,ichan)= taumin(iFKS,ichan)-dsqrt(ptl**2+emass(i)**2) +
461+ & max(mll/2d0,dsqrt(ptl**2+emass(i)**2))
462+ taumin_s(iFKS,ichan) = taumin_s(iFKS,ichan)-dsqrt(ptl**2+emass(i)**2)
463+ $ + max(mll/2d0, dsqrt(ptl**2+emass(i)**2))
464+ taumin_j(iFKS,ichan) = taumin_j(iFKS,ichan)-dsqrt(ptl**2+emass(i)**2)
465+ $ + max(mll/2d0,dsqrt(ptl**2+emass(i)**2))
466 xm(i)=xm(i)-ptl-emass(i)+max(mll/2d0,ptl
467 $ +emass(i))
468 exit
469@@ -272,11 +337,13 @@
470 enddo
471 elseif (is_a_lm(i)) then
472 c Add the negatively charged lepton pTs to tau
473- taumin(iFKS,ichan)=taumin(iFKS,ichan)+emass(i)
474- if (j_fks.gt.nincoming)
475- & taumin(iFKS,ichan)=taumin(iFKS,ichan)+ptl
476- taumin_s(iFKS,ichan)=taumin_s(iFKS,ichan)+emass(i)+ptl
477- taumin_j(iFKS,ichan)=taumin_j(iFKS,ichan)+emass(i)+ptl
478+ if (j_fks.gt.nincoming) then
479+ taumin(iFKS,ichan)=taumin(iFKS,ichan)+dsqrt(ptl**2+emass(i)**2)
480+ else
481+ taumin(iFKS,ichan)=taumin(iFKS,ichan)+emass(i)
482+ endif
483+ taumin_s(iFKS,ichan)=taumin_s(iFKS,ichan)+dsqrt(ptl**2+emass(i)**2)
484+ taumin_j(iFKS,ichan)=taumin_j(iFKS,ichan)+dsqrt(ptl**2+emass(i)**2)
485 xm(i)=emass(i)+ptl
486 c Add the lepton invariant mass to tau if there is at least another
487 c lepton of opposite charge. (Only add half of it, i.e. 'the part
488@@ -286,33 +353,65 @@
489 if (is_a_lp(j) .and. idup(i,1).eq.-idup(j,1) .and.
490 $ (mll_sf.ne.0d0 .or. mll.ne.0d0) ) then
491 if (j_fks.gt.nincoming)
492- & taumin(iFKS,ichan) = taumin(iFKS,ichan)-ptl-emass(i) +
493- & max(mll/2d0,mll_sf/2d0,ptl+emass(i))
494- taumin_s(iFKS,ichan) = taumin_s(iFKS,ichan)-ptl-emass(i)
495- $ + max(mll/2d0,mll_sf/2d0,ptl+emass(i))
496- taumin_j(iFKS,ichan) = taumin_j(iFKS,ichan)-ptl-emass(i)
497- $ + max(mll/2d0,mll_sf/2d0,ptl+emass(i))
498+ & taumin(iFKS,ichan) = taumin(iFKS,ichan)-dsqrt(ptl**2+emass(i)**2) +
499+ & max(mll/2d0,mll_sf/2d0,dsqrt(ptl**2+emass(i)**2))
500+ taumin_s(iFKS,ichan) = taumin_s(iFKS,ichan)-dsqrt(ptl**2+emass(i)**2)
501+ $ + max(mll/2d0,mll_sf/2d0,dsqrt(ptl**2+emass(i)**2))
502+ taumin_j(iFKS,ichan) = taumin_j(iFKS,ichan)-dsqrt(ptl**2+emass(i)**2)
503+ $ + max(mll/2d0,mll_sf/2d0,dsqrt(ptl**2+emass(i)**2))
504 xm(i)=xm(i)-ptl-emass(i)+max(mll/2d0,mll_sf/2d0
505 $ ,ptl+emass(i))
506 exit
507 elseif (is_a_lp(j) .and. mll.ne.0d0) then
508 if (j_fks.gt.nincoming)
509- & taumin(iFKS,ichan) = taumin(iFKS,ichan)-ptl-emass(i) +
510- & max(mll/2d0,ptl+emass(i))
511- taumin_s(iFKS,ichan) = taumin_s(iFKS,ichan)-ptl-emass(i)
512- $ + max(mll/2d0,ptl+emass(i))
513- taumin_j(iFKS,ichan) = taumin_j(iFKS,ichan)-ptl-emass(i)
514- $ + max(mll/2d0,ptl+emass(i))
515+ & taumin(iFKS,ichan) = taumin(iFKS,ichan)-dsqrt(ptl**2+emass(i)**2) +
516+ & max(mll/2d0,dsqrt(ptl**2+emass(i)**2))
517+ taumin_s(iFKS,ichan) = taumin_s(iFKS,ichan)-dsqrt(ptl**2+emass(i)**2)
518+ $ + max(mll/2d0,dsqrt(ptl**2+emass(i)**2))
519+ taumin_j(iFKS,ichan) = taumin_j(iFKS,ichan)-dsqrt(ptl**2+emass(i)**2)
520+ $ + max(mll/2d0,dsqrt(ptl**2+emass(i)**2))
521 xm(i)=xm(i)-ptl-emass(i)+max(mll/2d0,ptl
522 $ +emass(i))
523 exit
524 endif
525 enddo
526 else
527- taumin(iFKS,ichan)=taumin(iFKS,ichan)+emass(i)
528- taumin_s(iFKS,ichan)=taumin_s(iFKS,ichan)+emass(i)
529- taumin_j(iFKS,ichan)=taumin_j(iFKS,ichan)+emass(i)
530- xm(i)=emass(i)
531+ if (i.eq.nexternal)then
532+ taumin(iFKS,ichan)=taumin(iFKS,ichan) + emass(i)
533+ taumin_s(iFKS,ichan)=taumin_s(iFKS,ichan) + emass(i)
534+ taumin_j(iFKS,ichan)=taumin_j(iFKS,ichan) + emass(i)
535+ xm(i) = emass(i)
536+ else
537+ smin_update = 0
538+ nb_iden_pdg = 1
539+ mxx = 0d0
540+c assume smin apply always on the same set of particle
541+ do j=nincoming+1,nexternal-1
542+ if (mxxmin(i,j).ne.0d0.or.mxxmin(j,i).ne.0d0) then
543+ nb_iden_pdg = nb_iden_pdg +1
544+ if (mxx.eq.0d0) mxx = max(mxxmin(i,j), mxxmin(j,i))
545+ endif
546+ enddo
547+ ! S >= (2*N-N^2)*M1^2 + (N^2-N)/2 * Mxx^2
548+ smin_update = nb_iden_pdg*((2-nb_iden_pdg)*emass(i)**2 + (nb_iden_pdg-1)/2.*mxx**2)
549+ ! compare with the update from pt cut
550+ if (smin_update.lt.nb_iden_pdg**2*(etmin(i)**2 + emass(i)**2))then
551+ ! the pt is more restrictive
552+ smin_update = dsqrt(etmin(i)**2 + emass(i)**2)
553+ else
554+ smin_update = dsqrt(smin_update)/nb_iden_pdg ! share over N particle, and change dimension
555+ endif
556+ smin_update = emass(i)
557+ ! update in sqrt(s) so take the
558+ if (j_fks.gt.nincoming) then
559+ taumin(iFKS,ichan)=taumin(iFKS,ichan) + smin_update
560+ else
561+ taumin(iFKS,ichan)=taumin(iFKS,ichan) + emass(i)
562+ endif
563+ taumin_s(iFKS,ichan)=taumin_s(iFKS,ichan) + smin_update
564+ taumin_j(iFKS,ichan)=taumin_j(iFKS,ichan) + smin_update
565+ xm(i) = smin_update
566+ endif
567 endif
568 xw(i)=0d0
569 enddo
570
571=== modified file 'madgraph/interface/common_run_interface.py'
572--- madgraph/interface/common_run_interface.py 2017-11-17 12:35:40 +0000
573+++ madgraph/interface/common_run_interface.py 2017-11-18 00:45:50 +0000
574@@ -5169,8 +5169,11 @@
575 self.mw_card[block][name] = value
576
577 def setR(self, name, value):
578- logger.info('modify parameter %s of the run_card.dat to %s' % (name, value),'$MG:color:BLACK')
579+
580 self.run_card.set(name, value, user=True)
581+ new_value = self.run_card.get(name)
582+ logger.info('modify parameter %s of the run_card.dat to %s' % (name, new_value),'$MG:color:BLACK')
583+
584
585 def setML(self, name, value, default=False):
586
587@@ -5234,6 +5237,16 @@
588 """This is run on quitting the class. Apply here all the self-consistency
589 rule that you want. Do the modification via the set command."""
590
591+ # For NLO run forbid any pdg specific cut on massless particle
592+ if isinstance(self.run_card,banner_mod.RunCardNLO):
593+ for pdg in set(self.run_card['pt_min_pdg'].keys()+self.run_card['pt_max_pdg'].keys()+
594+ self.run_card['mxx_min_pdg'].keys()):
595+
596+ if int(pdg)<0:
597+ raise Exception, "For PDG specific cuts, always use positive PDG codes: the cuts are applied to both particles and anti-particles"
598+ if self.param_card.get_value('mass', int(pdg), default=0) ==0:
599+ raise Exception, "For NLO runs, you can use PDG specific cuts only for massive particles: (failed for %s)" % pdg
600+
601 # if NLO reweighting is ON: ensure that we keep the rwgt information
602 if 'reweight' in self.allow_arg and 'run' in self.allow_arg and \
603 isinstance(self.run_card,banner_mod.RunCardNLO) and \
604
605=== modified file 'madgraph/various/banner.py'
606--- madgraph/various/banner.py 2017-10-24 19:40:17 +0000
607+++ madgraph/various/banner.py 2017-11-18 00:45:50 +0000
608@@ -2328,8 +2328,17 @@
609 for name, value in self.system_default.items():
610 self.set(name, value, changeifuserset=False)
611
612+ for name in self.legacy_parameter:
613+ if self[name] != self.legacy_parameter[name]:
614+ logger.warning("The parameter %s is not supported anymore this parameter will be ignored." % name)
615+
616 default_include_file = 'run_card.inc'
617
618+ def update_system_parameter_for_include(self):
619+ """update hidden system only parameter for the correct writtin in the
620+ include"""
621+ return
622+
623 def write_include_file(self, output_dir):
624 """Write the various include file in output_dir.
625 The entry True of self.includepath will be written in run_card.inc
626@@ -2338,6 +2347,9 @@
627 # ensure that all parameter are coherent and fix those if needed
628 self.check_validity()
629
630+ #ensusre that system only parameter are correctly set
631+ self.update_system_parameter_for_include()
632+
633 for incname in self.includepath:
634 if incname is True:
635 pathinc = self.default_include_file
636@@ -2632,8 +2644,35 @@
637 self.add_param('survey_nchannel_per_job', 2, hidden=True, include=False)
638 self.add_param('refine_evt_by_job', -1, hidden=True, include=False)
639
640- # Specify what particle IDs to use for the CKKWL merging cut ktdurham
641+ # parameter allowing to define simple cut via the pdg
642+ # Special syntax are related to those. (can not be edit directly)
643+ self.add_param('pt_min_pdg',{'__type__':0.}, include=False)
644+ self.add_param('pt_max_pdg',{'__type__':0.}, include=False)
645+ self.add_param('E_min_pdg',{'__type__':0.}, include=False)
646+ self.add_param('E_max_pdg',{'__type__':0.}, include=False)
647+ self.add_param('eta_min_pdg',{'__type__':0.}, include=False)
648+ self.add_param('eta_max_pdg',{'__type__':0.}, include=False)
649+ self.add_param('mxx_min_pdg',{'__type__':0.}, include=False)
650+ self.add_param('mxx_only_part_antipart', {'default':False}, include=False, hidden=True)
651
652+ self.add_param('pdg_cut',[0], hidden=True, system=True) # store which PDG are tracked
653+ self.add_param('ptmin4pdg',[0.], hidden=True, system=True) # store pt min
654+ self.add_param('ptmax4pdg',[-1.], hidden=True, system=True)
655+ self.add_param('Emin4pdg',[0.], hidden=True, system=True) # store pt min
656+ self.add_param('Emax4pdg',[-1.], hidden=True, system=True)
657+ self.add_param('etamin4pdg',[0.], hidden=True, system=True) # store pt min
658+ self.add_param('etamax4pdg',[-1.], hidden=True, system=True)
659+ self.add_param('mxxmin4pdg',[-1.], hidden=True, system=True)
660+ self.add_param('mxxpart_antipart', [False], hidden=True, system=True)
661+ # Not implemetented right now (double particle cut)
662+ #self.add_param('pdg_cut_2',[0], hidden=True, system=True)
663+ # self.add_param('M_min_pdg',[0.], hidden=True, system=True) # store pt min
664+ #self.add_param('M_max_pdg',[0.], hidden=True, system=True)
665+ # self.add_param('DR_min_pdg',[0.], hidden=True, system=True) # store pt min
666+ #self.add_param('DR_max_pdg',[0.], hidden=True, system=True)
667+
668+
669+
670 def check_validity(self):
671 """ """
672
673@@ -2709,7 +2748,7 @@
674 self['mmjj'] = 0.0
675
676
677-
678+
679 # check validity of the pdf set
680 possible_set = ['lhapdf', 'mrs02nl','mrs02nn',
681 'cteq4_m', 'cteq4_l','cteq4_d',
682@@ -2724,13 +2763,68 @@
683 #add warning if lhaid not define
684 self.get_default('lhaid', log_level=20)
685
686- for name in self.legacy_parameter:
687- if self[name] != self.legacy_parameter[name]:
688- logger.warning("The parameter %s is not supported anymore this parameter will be ignored." % name)
689-
690-
691+ def update_system_parameter_for_include(self):
692+
693+ # set the pdg_for_cut fortran parameter
694+ pdg_to_cut = set(self['pt_min_pdg'].keys() +self['pt_max_pdg'].keys() +
695+ self['e_min_pdg'].keys() +self['e_max_pdg'].keys() +
696+ self['eta_min_pdg'].keys() +self['eta_max_pdg'].keys()+
697+ self['mxx_min_pdg'].keys() + self['mxx_only_part_antipart'].keys())
698+ pdg_to_cut.discard('__type__')
699+ pdg_to_cut.discard('default')
700+ if len(pdg_to_cut)>25:
701+ raise Exception, "Maximum 25 different pdgs are allowed for pdg specific cut"
702+
703+ if any(int(pdg)<0 for pdg in pdg_to_cut):
704+ logger.warning('PDG specific cuts are always applied symmetrically on particle/anti-particle. Always use positve PDG codes')
705+ raise MadGraph5Error, 'Some PDG specific cuts are defined with negative pdg code'
706+
707+
708+ if any(pdg in pdg_to_cut for pdg in [1,2,3,4,5,21,22,11,13,15]):
709+ raise Exception, "Can not use PDG related cut for light quark/b quark/lepton/gluon/photon"
710+
711+ if pdg_to_cut:
712+ self['pdg_cut'] = list(pdg_to_cut)
713+ self['ptmin4pdg'] = []
714+ self['Emin4pdg'] = []
715+ self['etamin4pdg'] =[]
716+ self['ptmax4pdg'] = []
717+ self['Emax4pdg'] = []
718+ self['etamax4pdg'] =[]
719+ self['mxxmin4pdg'] =[]
720+ self['mxxpart_antipart'] = []
721+ for pdg in self['pdg_cut']:
722+ for var in ['pt','e','eta', 'Mxx']:
723+ for minmax in ['min', 'max']:
724+ if var in ['Mxx'] and minmax =='max':
725+ continue
726+ new_var = '%s%s4pdg' % (var, minmax)
727+ old_var = '%s_%s_pdg' % (var, minmax)
728+ default = 0. if minmax=='min' else -1.
729+ self[new_var].append(self[old_var][str(pdg)] if str(pdg) in self[old_var] else default)
730+ #special for mxx_part_antipart
731+ old_var = 'mxx_only_part_antipart'
732+ new_var = 'mxxpart_antipart'
733+ if 'default' in self[old_var]:
734+ default = self[old_var]['default']
735+ self[new_var].append(self[old_var][str(pdg)] if str(pdg) in self[old_var] else default)
736+ else:
737+ if str(pdg) not in self[old_var]:
738+ raise Exception("no default value defined for %s and no value defined for pdg %s" % (old_var, pdg))
739+ self[new_var].append(self[old_var][str(pdg)])
740+ else:
741+ self['pdg_cut'] = [0]
742+ self['ptmin4pdg'] = [0.]
743+ self['Emin4pdg'] = [0.]
744+ self['etamin4pdg'] =[0.]
745+ self['ptmax4pdg'] = [-1.]
746+ self['Emax4pdg'] = [-1.]
747+ self['etamax4pdg'] =[-1.]
748+ self['mxxmin4pdg'] =[0.]
749+ self['mxx_part_antipart'] = [False]
750
751-
752+
753+
754 def create_default_for_process(self, proc_characteristic, history, proc_def):
755 """Rules
756 process 1->N all cut set on off.
757@@ -3277,7 +3371,7 @@
758
759 class RunCardNLO(RunCard):
760 """A class object for the run_card for a (aMC@)NLO pocess"""
761-
762+
763 def default_setup(self):
764 """define the default value"""
765
766@@ -3361,6 +3455,20 @@
767 self.add_param('FO_LHE_postprocessing',['grouping','random'],
768 hidden=True, system=True, include=False)
769
770+ # parameter allowing to define simple cut via the pdg
771+ self.add_param('g',{'__type__':0.}, include=False)
772+ self.add_param('pt_min_pdg',{'__type__':0.}, include=False)
773+ self.add_param('pt_max_pdg',{'__type__':0.}, include=False)
774+ self.add_param('mxx_min_pdg',{'__type__':0.}, include=False)
775+ self.add_param('mxx_only_part_antipart', {'default':False}, include=False, hidden=True)
776+
777+ #hidden parameter that are transfer to the fortran code
778+ self.add_param('pdg_cut',[0], hidden=True, system=True) # store which PDG are tracked
779+ self.add_param('ptmin4pdg',[0.], hidden=True, system=True) # store pt min
780+ self.add_param('ptmax4pdg',[-1.], hidden=True, system=True)
781+ self.add_param('mxxmin4pdg',[0.], hidden=True, system=True)
782+ self.add_param('mxxpart_antipart', [False], hidden=True, system=True)
783+
784 def check_validity(self):
785 """check the validity of the various input"""
786
787@@ -3505,6 +3613,56 @@
788 raise InvalidRunCard, "'rw_fscale' has two or more identical entries. They have to be all different for the code to work correctly."
789
790
791+ def update_system_parameter_for_include(self):
792+
793+ # set the pdg_for_cut fortran parameter
794+ pdg_to_cut = set(self['pt_min_pdg'].keys() +self['pt_max_pdg'].keys()+
795+ self['mxx_min_pdg'].keys()+ self['mxx_only_part_antipart'].keys())
796+ pdg_to_cut.discard('__type__')
797+ pdg_to_cut.discard('default')
798+ if len(pdg_to_cut)>25:
799+ raise Exception, "Maximum 25 different PDGs are allowed for PDG specific cut"
800+
801+ if any(int(pdg)<0 for pdg in pdg_to_cut):
802+ logger.warning('PDG specific cuts are always applied symmetrically on particle/anti-particle. Always use positve PDG codes')
803+ raise MadGraph5Error, 'Some PDG specific cuts are defined with negative PDG codes'
804+
805+
806+ if any(pdg in pdg_to_cut for pdg in [21,22,11,13,15]+ range(self['maxjetflavor']+1)):
807+ # Note that this will double check in the fortran code
808+ raise Exception, "Can not use PDG related cuts for massless SM particles/leptons"
809+ if pdg_to_cut:
810+ self['pdg_cut'] = list(pdg_to_cut)
811+ self['ptmin4pdg'] = []
812+ self['ptmax4pdg'] = []
813+ self['mxxmin4pdg'] = []
814+ self['mxxpart_antipart'] = []
815+ for pdg in self['pdg_cut']:
816+ for var in ['pt','mxx']:
817+ for minmax in ['min', 'max']:
818+ if var == 'mxx' and minmax == 'max':
819+ continue
820+ new_var = '%s%s4pdg' % (var, minmax)
821+ old_var = '%s_%s_pdg' % (var, minmax)
822+ default = 0. if minmax=='min' else -1.
823+ self[new_var].append(self[old_var][str(pdg)] if str(pdg) in self[old_var] else default)
824+ #special for mxx_part_antipart
825+ old_var = 'mxx_only_part_antipart'
826+ new_var = 'mxxpart_antipart'
827+ if 'default' in self[old_var]:
828+ default = self[old_var]['default']
829+ self[new_var].append(self[old_var][str(pdg)] if str(pdg) in self[old_var] else default)
830+ else:
831+ if str(pdg) not in self[old_var]:
832+ raise Exception("no default value defined for %s and no value defined for pdg %s" % (old_var, pdg))
833+ self[new_var].append(self[old_var][str(pdg)])
834+ else:
835+ self['pdg_cut'] = [0]
836+ self['ptmin4pdg'] = [0.]
837+ self['ptmax4pdg'] = [-1.]
838+ self['mxxmin4pdg'] = [0.]
839+ self['mxx_part_antipart'] = [False]
840+
841 def write(self, output_file, template=None, python_template=False):
842 """Write the run_card in output_file according to template
843 (a path to a valid run_card)"""

Subscribers

People subscribed via source and target branches

to all changes: