ATLAS Offline Software
Control/AthenaPython/python/Bindings.py
Go to the documentation of this file.
1 # Copyright (C) 2002-2024 CERN for the benefit of the ATLAS collaboration
2 
3 # @file: AthenaPython/python/Bindings.py
4 # @author: Sebastien Binet <binet@cern.ch>
5 
6 
7 __author__ = "Sebastien Binet (binet@cern.ch)"
8 
9 
10 from functools import cache, partialmethod
11 from AthenaCommon.Logging import logging
12 
13 @cache
14 def _load_dict(lib):
15  """Helper function to remember which libraries have been already loaded
16  """
17  import cppyy
18  if not lib.startswith(lib):
19  lib="lib"+lib
20  return cppyy.load_library(lib)
21 
22 @cache
24  import ROOT
25  ROOT.gROOT.SetBatch(True)
26  return ROOT
27 
28 
29 
30 
32 _clid_typename_aliases = {
33 
34  'vector<int>' : 'std::vector<int>',
35  'vector<unsigned int>' : 'std::vector<unsigned int>',
36  'vector<float>' : 'std::vector<float>',
37  'vector<double>' : 'std::vector<double>',
38  'string' : 'std::string',
39 
41  'INavigable4MomentumCollection' : 'DataVector<INavigable4Momentum>',
42  'DataVector<IParticle>' : 'IParticleContainer',
43  'ParticleBaseContainer' : 'DataVector<ParticleBase>',
44  'TrackCollection' : 'DataVector<Trk::Track>',
45  'Trk::TrackCollection' : 'DataVector<Trk::Track>',
46  'DataVector<Track>' : 'TrackCollection',
47  'AthenaHitsVector<TrackRecord>' : 'TrackRecordCollection',
48  'Trk::SegmentCollection' : 'DataVector<Trk::Segment>',
49  }
50 
51 
52 
54  """Placeholder class to register callbacks for 'pythonizations' of C++
55  classes.
56  FIXME: find a better mechanism ?
57  """
58  msg = logging.getLogger('AthenaBindingsCatalog')
59  instances = {}
60 
61  @staticmethod
62  def register(klass, cb=None):
63  """Register a class name `klass` with an initialization method.
64  If no callback method has been given, the default is to call:
65  _py_init_<klass>()
66  """
67  try:
68  if cb is None: eval( 'cb = _py_init_%s'%klass )
69  except Exception as err:
70  _msg = _PyAthenaBindingsCatalog.msg
71  _msg.error("Problem registering callback for [%s]", klass)
72  _msg.error("Exception: %s", err)
73  cb = lambda : None # noqa: E731
74  _PyAthenaBindingsCatalog.instances[klass] = cb
75  return
76 
77  @staticmethod
78  @cache
79  def init(name):
80  """Initialize the python binding with the callback previously registered
81  If no callback was registered, swallow the warning...
82  """
83  klass = None
84  try: klass = _PyAthenaBindingsCatalog.instances[name]()
85  except KeyError:
86  ROOT = _import_ROOT() # noqa: F841
87  from AthenaServices.Dso import registry
88  registry.load_type (name)
89  try:
90  import cppyy
91  klass=getattr(cppyy.gbl,name)
92  except AttributeError:
93  raise AttributeError("no reflex-dict for type [%s]"%name)
94  return klass
95 
96 
97 @cache
98 def py_svc(svcName, createIf=True, iface=None):
99  """
100  Helper function to retrieve a service by name, using Gaudi python bindings.
101  @param svcName: the name of the service one wants to retrieve (possibly a
102  fully qualified name as in: 'MySvcClass/TheSvcName')
103  @param createIf: If True, the service will be created if it hasn't been yet
104  instantiated.
105  @param iface: type one wants to cast the service to (can be a string or the
106  cppyy type)
107  """
108  fullName = svcName
109  s = svcName.split('/')
110  svcType = s[0]
111  if len(s)==2: svcName=s[1]
112 
113  # handle pycomponents...
114  from .Configurables import PyComponents
115  if svcType in _PyAthenaBindingsCatalog.instances:
116  pytype = _PyAthenaBindingsCatalog.init( svcType )
117  # for types which have been pythonized, help the user
118  # find the good interface...
119  if iface is None: iface = pytype
120 
121  from GaudiPython.Bindings import gbl,InterfaceCast
122  svcLocator = gbl.Gaudi.svcLocator()
123  svc = gbl.GaudiPython.Helper.service(svcLocator, fullName, createIf)
124  if svc and not(iface is None):
125  svc = InterfaceCast(iface).cast(svc)
126 
127  # if the component is actually a py-component,
128  # retrieve the python object from the registry
129  if svcName in PyComponents.instances:
130  svc = PyComponents.instances[svcName]
131 
132  if svc:
133  from AthenaPython import PyAthena
134  setattr(PyAthena.services, svcName, svc)
135  return svc
136 
137 
138 @cache
139 def py_tool(toolName, createIf=True, iface=None):
140  """
141  Helper function to retrieve a tool (owned by the ToolSvc) by name, using
142  Gaudi python bindings.
143  @param toolName: the name of the tool one wants to retrieve (possibly a
144  fully qualified name as in: 'MyToolClass/TheToolName')
145  @param createIf: If True, the tool will be created if it hasn't been yet
146  instantiated.
147  @param iface: type one wants to cast the tool to (can be a string or the
148  cppyy type)
149 
150  Ex:
151  ## retrieve default interface (ie: GaudiKernel/IAlgTool)
152  tool = py_tool('LArOnlDbPrepTool')
153  assert(type(tool) == cppyy.gbl.IAlgTool)
154 
155  ## retrieve with specified interface
156  tool = py_tool('LArOnlDbPrepTool', iface='ILArOnlDbPrepTool')
157  assert(type(tool) == cppyy.gbl.ILArOnlDbPrepTool)
158 
159  """
160  t = toolName.split('/')
161  toolType = t[0]
162  if len(t)==2: toolName=t[1]
163 
164  # handle pycomponents...
165  from .Configurables import PyComponents
166  if toolType in _PyAthenaBindingsCatalog.instances:
167  pytype = _PyAthenaBindingsCatalog.init( toolType )
168  # for types which have been pythonized, help the user
169  # find the good interface...
170  if iface is None: iface = pytype
171 
172  from GaudiPython.Bindings import gbl,InterfaceCast
173  _py_tool = gbl.GaudiPython.Helper.tool
174  toolSvc = py_svc('ToolSvc', iface='IToolSvc')
175  tool = _py_tool(toolSvc, toolType, toolName, 0, createIf)
176  if tool and not(iface is None):
177  tool = InterfaceCast(iface).cast(tool)
178 
179  # if the component is actually a py-component,
180  # retrieve the python object from the registry
181  if toolName in PyComponents.instances:
182  tool = PyComponents.instances[toolName]
183 
184  if tool:
185  from AthenaPython import PyAthena
186  setattr(PyAthena.services.ToolSvc, toolName, tool)
187  return tool
188 
189 
190 def py_alg(algName, iface='IAlgorithm'):
191  """
192  Helper function to retrieve an IAlgorithm (managed by the IAlgManager_) by
193  name, using Gaudi python bindings.
194  @param algName: the name of the algorithm's instance one wants to retrieve
195  ex: 'McAodBuilder'
196  @param iface: type one wants to cast the tool to (can be a string or the
197  cppyy type)
198 
199  Ex:
200  ## retrieve default interface (ie: GaudiKernel/IAlgorithm)
201  alg = py_alg('McAodBuilder')
202  assert(type(alg) == cppyy.gbl.IAlgorithm)
203 
204  ## retrieve with specified interface
205  alg = py_alg('McAodBuilder', iface='Algorithm')
206  assert(type(alg) == cppyy.gbl.Algorithm)
207 
208  """
209  algmgr = py_svc('ApplicationMgr',iface='IAlgManager')
210  if not algmgr:
211  msg = logging.getLogger('PyAthena.py_alg')
212  error = 'could not retrieve IAlgManager/ApplicationMgr'
213  msg.error (error)
214  raise RuntimeError (error)
215 
216  # handle pycomponents...
217  from .Configurables import PyComponents
218  import ROOT
219  alg = ROOT.MakeNullPointer(iface)
220  if not algmgr.getAlgorithm(algName, alg).isSuccess():
221  return
222 
223  # if the component is actually a py-component,
224  # retrieve the python object from the registry
225  if algName in PyComponents.instances:
226  alg = PyComponents.instances[algName]
227 
228  if alg:
229  from AthenaPython import PyAthena
230  setattr(PyAthena.algs, algName, alg)
231  return alg
232 
233 
234 @cache
236 
238  import RootUtils.PyROOTFixes
239 
240  try: RootUtils.PyROOTFixes.enable_pickling()
241  except Exception: pass # fwd compatibility
242  from StoreGateBindings.Bindings import StoreGateSvc
243 
244  return StoreGateSvc
245 
246 
247 @cache
249  import cppyy
250  # IIncidentSvc bindings from dictionary
251  _load_dict( "libGaudiKernelDict" )
252 
253  # retrieve the IIncidentSvc class
254  global IIncidentSvc
255  IIncidentSvc = cppyy.gbl.IIncidentSvc
256 
257  IIncidentSvc._cpp_addListener = IIncidentSvc.addListener
258  def addListener (self, *args):
259  listener = args[0]
260  if hasattr (listener, '_cppHandle'):
261  args = (listener._cppHandle,) + args[1:] # noqa: B009 (private property)
262  return self._cpp_addListener (*args)
263  addListener.__doc__ = IIncidentSvc._cpp_addListener.__doc__
264  IIncidentSvc.addListener = addListener
265  del addListener
266 
267  IIncidentSvc._cpp_removeListener = IIncidentSvc.removeListener
268  def removeListener (self, *args):
269  listener = args[0]
270  if hasattr (listener, '_cppHandle'):
271  args = (listener._cppHandle,) + args[1:]
272  return self._cpp_removeListener (*args)
273  removeListener.__doc__ = IIncidentSvc._cpp_removeListener.__doc__
274  IIncidentSvc.removeListener = removeListener
275  del removeListener
276  return IIncidentSvc
277 
278 
279 @cache
281  import cppyy
282  # IClassIDSvc bindings from dictionary
283  _load_dict( "libAthenaPythonDict" )
284 
285  # retrieve the IClassIDSvc class
286  global IClassIDSvc
287  IClassIDSvc = cppyy.gbl.IClassIDSvc
288 
289  _missing_clids = {
290  'DataHistory' : 83814411,
291  83814411 : 'DataHistory',
292  }
293 
294  # re-use the python-based clid generator
295  # (faster than calling back into C++ via Reflex bindings)
296  from CLIDComps.clidGenerator import clidGenerator
297  IClassIDSvc._clidgen = clidGenerator(db=None)
298 
299  # add pythonized methods
300  @cache
301  def _clid (self, name):
302  # handle special cases where CLID has been registered with a typedef
303  try: name = _clid_typename_aliases[name]
304  except KeyError: pass
305  try:
306  return _missing_clids[name]
307  except KeyError: pass
308  return self._clidgen.getClidFromName(name)
309  IClassIDSvc.clid = _clid
310  del _clid
311 
312  @cache
313  def _typename (self, clid):
314  # handle special cases of missing clids
315  try:
316  return _missing_clids[clid]
317  except KeyError:
318  pass
319  return self._clidgen.getNameFromClid(clid)
320  IClassIDSvc.typename = _typename
321  del _typename
322 
323  return IClassIDSvc
324 
325 
326 @cache
328  import cppyy
329  # ITHistSvc bindings from dictionary
330  _load_dict( "libGaudiKernelDict" )
331 
332 
333  # retrieve the ITHistSvc class
334  global ITHistSvc
335  ITHistSvc = cppyy.gbl.ITHistSvc
336 
337  ROOT = _import_ROOT()
338  @property
339  def _py_cache(self):
340  try:
341  return self.__py_cache
342  except AttributeError:
343  self.__py_cache = dict()
344  return self.__py_cache
345  ITHistSvc._py_cache = _py_cache
346 
347  # save original regXYZ methods: we'll use some modified ones
348  # to improve look-up time from python
349  ITHistSvc._cpp_regHist = ITHistSvc.regHist
350  ITHistSvc._cpp_regGraph = ITHistSvc.regGraph
351  ITHistSvc._cpp_regEfficiency = ITHistSvc.regEfficiency
352  ITHistSvc._cpp_regTree = ITHistSvc.regTree
353 
354  def book(self, oid, obj=None, *args, **kw):
355  """book a histogram, profile or tree
356  @param oid is the unique object identifier even across streams,
357  ie: 'stream'+'id'
358  @param obj either an already full-fledge constructed ROOT object
359  or None (then `*args` or `**kw` need to be correctly setup)
360  @param *args list of arguments to give to the constructor of the
361  ROOT object one wants to book
362  @param **kw a dictionary containing a key 'args' being the list of
363  arguments to the constructor of the ROOT objects one wants to
364  book
365  examples:
366  >>> th.book('/temp/1d/h1', 'TH1D', args=('h1','h1',100,0.,100.))
367  >>> th.book('/temp/1d/h2', ROOT.TH1D, args=('h2','h2',100,0.,100.))
368  >>> th.book('/temp/1d/h3', ROOT.TH1D, 'h3','h3',100,0.,100.)
369  >>> th.book('/temp/1d/h4', ROOT.TH1D('h4','h4',100,0.,100.))
370  >>> th.book('/temp/1d/h5', obj=ROOT.TH1D('h5','h5',100,0.,100.))
371  >>> th.book('/temp/1d/h6', klass='TH1D', args=('h6','h6',100,0.,100.))
372 
373  >>> th.book('/temp/tree/t1', ROOT.TTree('t1','t1'))
374  >>> th.book('/temp/tree/t2', obj=ROOT.TTree('t2','t2'))
375  >>> th.book('/temp/tree/t3', klass='TTree', args=('t3','t3'))
376  """
377  _err = "please provide _either_ an already constructed ROOT object or"\
378  "a class name/class type (with appropriate arguments)"
379  klass = kw.get('klass', None)
380  assert not (obj is None and klass is None), _err
381  assert not (obj is not None and klass is not None), _err
382 
383  if isinstance(obj, (str,type)):
384  klass=obj
385  obj=None
386  if obj:
387  if isinstance(obj, ROOT.TH1):
388  # capture all of TH1x,TH2x,TH3x,TProfileXY
389  meth = self._cpp_regHist
390  elif isinstance(obj, (ROOT.TGraph,)):
391  meth = self._cpp_regGraph
392  elif isinstance(obj, (ROOT.TEfficiency,)):
393  meth = self._cpp_regEfficiency
394  elif isinstance(obj, (ROOT.TTree,)):
395  meth = self._cpp_regTree
396  else:
397  raise TypeError("invalid type '%r'"%type(obj))
398  if meth(oid, obj).isSuccess():
399  self._py_cache[oid]=obj
400  return obj
401  raise RuntimeError('could not book object [%r]'%obj)
402 
403  if klass:
404  if isinstance(klass, str):
405  klass = getattr(ROOT, klass)
406  if args:
407  return self.book(oid, obj=klass(*args))
408  if kw and 'args' in kw:
409  return self.book(oid, obj=klass(*kw['args']))
410  err = "invalid arguments: either provide a valid `*args` or "\
411  "a `**kw` containing a 'args' key"
412  raise RuntimeError(err)
413  raise RuntimeError("unforseen case: oid='%r' obj='%r' args='%r' "
414  "kw='%r'"%(oid,obj,args,kw))
415 
416  ITHistSvc.book = book
417 
418  def get(self, oid, klass=None):
419  """retrieve an already booked ROOT object.
420  If the object was booked on the C++ side, try to use the `klass` hint
421  (the usual string or type) to find the object in the correct 'folder'
422  (histograms, graphs or trees).
423  If `klass` is None, then go through all the folders iteratively (slow)
424  """
425  try:
426  return self._py_cache[oid]
427  except KeyError:
428  pass
429  def _get_helper(klass, hsvc, meth, oid, update_cache=True):
430  makeNullPtr = ROOT.MakeNullPointer
431  o = makeNullPtr(klass)
432  if meth(oid, o).isSuccess():
433  if update_cache:
434  hsvc._py_cache[oid] = o
435  return o
436  return
437  if klass:
438  if isinstance(klass, str):
439  klass = getattr(ROOT, klass)
440  if issubclass(klass, (ROOT.TH1,)):
441  return _get_helper(klass, self, self.getHist, oid)
442  if issubclass(klass, (ROOT.TGraph,)):
443  return _get_helper(klass, self, self.getGraph, oid)
444  if issubclass(klass, (ROOT.TEfficiency,)):
445  return _get_helper(klass, self, self.getEfficiency, oid)
446  if issubclass(klass, (ROOT.TTree,)):
447  return _get_helper(klass, self, self.getTree, oid)
448  raise RuntimeError('unsupported type [%r]'%klass)
449 
450  # as we are sentenced to crawl through all these std::vector<str>
451  # we might as well update our local cache...
452 
453  # first update histos
454  oids = [n for n in self.getHists() if n not in self._py_cache.keys()]
455  for name in oids:
456  obj = _get_helper(ROOT.TH1, self, self.getHist, name,
457  update_cache=False)
458  if obj:
459  # now try with real class
460  klass = getattr(ROOT, obj.ClassName())
461  obj = _get_helper(klass, self, self.getHist, name)
462 
463  # then graphs
464  oids = [n for n in self.getGraphs() if n not in self._py_cache.keys()]
465  for name in oids:
466  _get_helper(ROOT.TGraph, self, self.getGraph, name)
467 
468  # then efficiencies
469  oids = [n for n in self.getEfficiencies() if n not in self._py_cache.keys()]
470  for name in oids:
471  _get_helper(ROOT.TEfficiency, self, self.getEfficiency, name)
472 
473  # finally try ttrees
474  oids = [n for n in self.getTrees() if n not in self._py_cache.keys()]
475  for name in oids:
476  _get_helper(ROOT.TTree, self, self.getTree, name)
477 
478 
479  return self._py_cache[oid]
480 
481  ITHistSvc.get = get
482  del get
483 
484  def getitem(self, oid):
485  return self.get(oid)
486  ITHistSvc.__getitem__ = getitem
487  del getitem
488 
489  def delitem(self, oid):
490  if isinstance(oid, str):
491  self.get(oid)
492  del self._py_cache[oid]
493  assert self.deReg(oid).isSuccess(), \
494  "could not remove object [%r]"%oid
495  return
496  ITHistSvc.__delitem__ = delitem
497 
498  def setitem(self, k, v):
499  return self.book(k, obj=v)
500  ITHistSvc.__setitem__ = setitem
501  del setitem
502 
503  def regObject(self, regFcn, oid, oid_type=None):
504  """Helper method to register object 'oid' using 'regFcn'."""
505  if oid_type is not None:
506  return self.book(oid,obj=oid_type)
507  if regFcn(self,oid).isSuccess():
508  # update py_cache
509  return self.get(oid)
510  err = ''.join(['invalid arguments oid=',repr(oid),' oid_type=',
511  repr(oid_type)])
512  raise ValueError(err)
513 
514  ITHistSvc.regHist = partialmethod(regObject, ITHistSvc._cpp_regHist)
515  ITHistSvc.regTree = partialmethod(regObject, ITHistSvc._cpp_regTree)
516  ITHistSvc.regEfficiency = partialmethod(regObject, ITHistSvc._cpp_regEfficiency)
517  ITHistSvc.regGraph = partialmethod(regObject, ITHistSvc._cpp_regGraph)
518  del regObject
519 
520  def load(self, oid, oid_type):
521  """Helper method to load a given object `oid' from a stream, knowing
522  its type. `oid_type' is a string whose value is either:
523  - 'hist', to load any THx and TProfiles
524  - 'tree', to load TTrees
525  - 'efficiency', to load TEfficiency
526  - 'graph', to load TGraph and TGraphErrors
527  """
528  if oid_type == 'hist':
529  return self.regHist(oid)
530  elif oid_type == 'tree':
531  return self.regTree(oid)
532  elif oid_type == 'efficiency':
533  return self.regEfficiency(oid)
534  elif oid_type == 'graph':
535  return self.regGraph(oid)
536  else:
537  raise ValueError(f'oid_type (={oid_type}) MUST be one of hist, tree, efficiency, graph')
538 
539  ITHistSvc.load = load
540  del load
541 
542 
543 
544  for n in ('__contains__',
545  '__iter__',
546  '__len__',
547  'has_key',
548  'items', 'iteritems',
549  'iterkeys', 'itervalues',
550  'keys', 'values'):
551  code = """\
552 def %s(self, *args, **kw):
553  return self._py_cache.%s(*args,**kw)
554 ITHistSvc.%s = %s
555 del %s""" % (n,n,n,n,n)
556  exec (code, globals(),locals())
557 
558 
559  def __bool__(self):
560  return self is not None
561  ITHistSvc.__bool__ = __bool__
562  del __bool__
563 
564  def pop(self, k):
565  obj = self.get(k)
566  assert self.deReg(obj).isSuccess(), \
567  "could not remove object [%r]"%k
568  return obj
569  ITHistSvc.pop = pop
570  del pop
571 
572  def popitem(self):
573  k = self.iterkeys().next()
574  return (k, self.pop(k))
575  ITHistSvc.popitem = popitem
576  del popitem
577 
578 
579 
585 
586 
590 
591 
593  return ITHistSvc
594 
595 
596 @cache
598  import cppyy
599  # EventStreamInfo bindings from dictionary
600  _load_dict( "libEventInfoDict" )
601 
602  # retrieve the EventStreamInfo class
603  ESI = cppyy.gbl.EventStreamInfo
604  # retrieve the PyEventStreamInfo helper class
605  PyESI= cppyy.gbl.PyEventStreamInfo
606  def run_numbers(self):
607  self._run_numbers = PyESI.runNumbers(self)
608  return list(self._run_numbers)
609  def evt_types(self):
610  self._evt_types = PyESI.eventTypes(self)
611  return list(self._evt_types)
612  def item_list(self):
613  self._item_list = PyESI.itemList(self)
614  return list(tuple(i) for i in self._item_list)
615  def lumi_blocks(self):
616  self._lumi_blocks = PyESI.lumiBlockNumbers(self)
617  return list(self._lumi_blocks)
618  def processing_tags(self):
619  self._processing_tags = PyESI.processingTags(self)
620  return list(self._processing_tags)
621  for fct in ('run_numbers', 'evt_types', 'item_list',
622  'lumi_blocks', 'processing_tags'):
623  setattr(ESI, fct, locals()[fct])
624 
625  return ESI
626 
627 
628 @cache
630  import cppyy
631  # EventStreamInfo bindings from dictionary
632  _load_dict( "libEventInfoDict" )
633 
634  # retrieve the EventType class
635  cls = cppyy.gbl.EventType
636  cls.bit_mask_typecodes = [
637  ('IS_DATA','IS_SIMULATION'), #0
638  ('IS_ATLAS', 'IS_TESTBEAM'), #1
639  ('IS_PHYSICS','IS_CALIBRATION'),#2
640  ]
641  # retrieve the PyEventType class
642  py_cls = cppyy.gbl.PyEventType
643  def raw_bit_mask(self):
644  self._raw_bit_mask = py_cls.bit_mask(self)
645  return self._raw_bit_mask
646  cls.raw_bit_mask = property(raw_bit_mask)
647  def bit_mask(self):
648  def decode_bitmask(idx):
649  if len(self.raw_bit_mask) <= idx:
650  return self.bit_mask_typecodes[idx][0]
651  isa_idx = self.raw_bit_mask[idx]
652  return self.bit_mask_typecodes[idx][isa_idx]
653  bm = map(decode_bitmask,
654  range(len(self.bit_mask_typecodes)))
655  return tuple(bm)
656  cls.bit_mask = property(bit_mask)
657  return cls
658 
659 
660 @cache
662  return _gen_data_link
663 
664 
665 @cache
667  return _gen_element_link
668 
669 
670 @cache
672  return _gen_elv
673 
674 
675 @cache
677  return _gen_navtok
678 
679 
680 @cache
681 def _gen_data_link(klass, storage_policy=None):
682  """helper method to easily instantiate a DataLink class.
683  Sensible default for the storage policy is chosen if none given (it usually
684  boils down to DataProxyStorage)
685 
686  @example:
687  >>> DLink = PyAthena.DataLink('CompositeParticleContainer')
688  >>> cp = DLink()
689  >>> cp = DLink('MyStoreGateKey')
690  """
691  ROOT = _import_ROOT ()
692  if isinstance(klass, str):
693  klass = getattr(ROOT, klass)
694  if storage_policy is None:
695  storage_policy = ROOT.DataProxyStorage(klass)
696  return ROOT.DataLink(klass, storage_policy)
697 
698 
699 @cache
700 def _gen_element_link(klass, storage_policy=None, indexing_policy=None):
701  """helper method to easily instantiate an ElementLink class.
702  Sensible defaults for the storage and indexing policies are chosen if none
703  given (it usually boils down to DataProxyStorage and ForwardIndexingPolicy)
704 
705  @example:
706  >>> CPLink = PyAthena.ElementLink('CompositeParticleContainer')
707  >>> cp = CPLink()
708  >>> EleLink = PyAthena.ElementLink(PyAthena.ElectronContainer)
709  >>> ele = EleLink()
710  """
711  ROOT = _import_ROOT ()
712  if isinstance(klass, str):
713  klass = getattr(ROOT, klass)
714  #if storage_policy is None:
715  # storage_policy = ROOT.DataProxyStorage(klass)
716  #if indexing_policy is None:
717  # indexing_policy = ROOT.ForwardIndexingPolicy(klass)
718  #return ROOT.ElementLink(klass, storage_policy, indexing_policy)
719  return ROOT.ElementLink(klass)
720 
721 
722 @cache
723 def _gen_elv(klass, storage_policy=None, indexing_policy=None):
724  """helper method to easily instantiate an ElementLinkVector class.
725  Sensible defaults for the storage and indexing policies are chosen if none
726  given (it usually boils down to DataProxyStorage and ForwardIndexingPolicy)
727 
728  @example:
729  >>> IELV = PyAthena.ElementLinkVector('INavigable4MomentumCollection')
730  >>> ielv = IELV()
731  """
732  ROOT = _import_ROOT ()
733  if isinstance(klass, str):
734  klass = getattr(ROOT, klass)
735  if storage_policy is None:
736  storage_policy = ROOT.DataProxyStorage(klass)
737  if indexing_policy is None:
738  indexing_policy = ROOT.ForwardIndexingPolicy(klass)
739  return ROOT.ElementLinkVector(klass, storage_policy, indexing_policy)
740 
741 
742 @cache
743 def _gen_navtok(klass, weight_cls=None, hash_cls=None):
744  """helper method to easily instantiate a NavigationToken class.
745  Sensible default for the weight and hash parameters are chosen if none are
746  given
747 
748  @example:
749  >>> cls = PyAthena.NavigationToken('CaloCell')
750  >>> token = cls()
751  """
752  ROOT = _import_ROOT ()
753  if isinstance(klass, str):
754  klass = getattr(ROOT, klass)
755  if weight_cls is None:
756  weight_cls = getattr(ROOT, 'NavigationDefaults::DefaultWeight')
757  if hash_cls is None:
758  hash_cls = getattr(ROOT, 'SG::hash<const %s *>' % (klass.__name__,))
759  return ROOT.NavigationToken(klass, weight_cls, hash_cls)
760 
761 
762 def _std_map_pythonize(cls, key_type, value_type):
763  def __contains__(self, k):
764  return self.find(k) != self.end()
765  cls.__contains__ = __contains__
766 
767  def __setitem__(self, k, v):
768  itr = self.find(k)
769  self.insert(itr, self.__class__.value_type(k,v))
770  return v
771  cls.__setitem__ = __setitem__
772 
773  cls.__cxx_getitem__ = cls.__getitem__
774  def __getitem__(self, k):
775  # python's dict semantics
776  if k not in self:
777  raise KeyError(k)
778  return self.__cxx_getitem__(k)
779  cls.__getitem__ = __getitem__
780 
781  if not hasattr(cls, '__iter__'):
782  def toiter(beg, end):
783  while beg != end:
784  yield beg.__deref__()
785  beg.__preinc__()
786  return
787 
788  def __iter__(self):
789  for i in toiter(self.begin(), self.end()):
790  yield i
791  cls.__iter__ = __iter__
792 
793  def keys(self):
794  keys = []
795  for i in self:
796  keys.append(i.first)
797  return keys
798  cls.keys = keys
799 
800  def values(self):
801  vals = []
802  for i in self:
803  vals.append(i.first)
804  return vals
805  cls.values = values
806 
807  def iterkeys(self):
808  for i in self:
809  yield i.first
810  cls.iterkeys = iterkeys
811 
812  def itervalues(self):
813  for i in self:
814  yield i.second
815  cls.itervalues = itervalues
816 
817  def iteritems(self):
818  for i in self:
819  yield (i.first, i.second)
820  cls.iteritems = iteritems
821 
822  return cls
823 
824 # -----------------------------------------------------------------------------
825 
826 def _setup():
827  _register = _PyAthenaBindingsCatalog.register
828  _register('StoreGateSvc', _py_init_StoreGateSvc)
829 
830  _register( 'IncidentSvc', _py_init_IIncidentSvc)
831  _register('IIncidentSvc', _py_init_IIncidentSvc)
832 
833  _register( 'ClassIDSvc', _py_init_ClassIDSvc)
834  _register('IClassIDSvc', _py_init_ClassIDSvc)
835 
836  _register( 'THistSvc', _py_init_THistSvc)
837  _register('ITHistSvc', _py_init_THistSvc)
838 
839  _register('EventStreamInfo', _py_init_EventStreamInfo)
840  _register('EventType', _py_init_EventType)
841 
842  _register('DataLink', _py_init_DataLink)
843  _register('ElementLink', _py_init_ElementLink)
844  _register('ElementLinkVector', _py_init_ElementLinkVector)
845  pass
846 
847 
848 _setup()
849 
850 
851 del _setup
852 
python.Bindings.iteritems
iteritems
Definition: Control/AthenaPython/python/Bindings.py:820
python.Bindings._gen_navtok
def _gen_navtok(klass, weight_cls=None, hash_cls=None)
helper method to easily instantiate NavigationToken --------------------—
Definition: Control/AthenaPython/python/Bindings.py:743
python.Bindings._PyAthenaBindingsCatalog
Definition: Control/AthenaPython/python/Bindings.py:53
python.Bindings._std_map_pythonize
def _std_map_pythonize(cls, key_type, value_type)
helper method to pythonize further std::map
Definition: Control/AthenaPython/python/Bindings.py:762
python.Bindings.py_tool
def py_tool(toolName, createIf=True, iface=None)
helper method to easily retrieve tools from ToolSvc by name ------------—
Definition: Control/AthenaPython/python/Bindings.py:139
python.Bindings.__iter__
__iter__
Definition: Control/AthenaPython/python/Bindings.py:791
python.Bindings._gen_element_link
def _gen_element_link(klass, storage_policy=None, indexing_policy=None)
helper method to easily instantiate ElementLink ------------------------—
Definition: Control/AthenaPython/python/Bindings.py:700
python.Bindings._py_init_IIncidentSvc
def _py_init_IIncidentSvc()
pythonizations for IIncidentSvc
Definition: Control/AthenaPython/python/Bindings.py:248
xAODRootTest._typename
def _typename(t)
Definition: xAODRootTest.py:34
python.Bindings._load_dict
def _load_dict(lib)
Definition: Control/AthenaPython/python/Bindings.py:14
python.Bindings._setup
def _setup()
initialize the bindings' registration
Definition: Control/AthenaPython/python/Bindings.py:826
python.Bindings.values
values
Definition: Control/AthenaPython/python/Bindings.py:805
klass
This class describe the base functionalities of a HypoTool used by the ComboAlg.
python.Bindings._gen_elv
def _gen_elv(klass, storage_policy=None, indexing_policy=None)
helper method to easily instantiate ElementLinkVector ------------------—
Definition: Control/AthenaPython/python/Bindings.py:723
python.FilePeekerLib.toiter
def toiter(beg, end)
Definition: FilePeekerLib.py:25
python.Bindings._py_init_EventType
def _py_init_EventType()
pythonizations for EventType
Definition: Control/AthenaPython/python/Bindings.py:629
python.Bindings.py_svc
def py_svc(svcName, createIf=True, iface=None)
Definition: Control/AthenaPython/python/Bindings.py:98
python.Bindings._py_init_DataLink
def _py_init_DataLink()
pythonizations for DataLink
Definition: Control/AthenaPython/python/Bindings.py:661
fillPileUpNoiseLumi.next
next
Definition: fillPileUpNoiseLumi.py:52
python.Bindings.iterkeys
iterkeys
Definition: Control/AthenaPython/python/Bindings.py:810
plotBeamSpotVxVal.range
range
Definition: plotBeamSpotVxVal.py:195
PyAthena::repr
std::string repr(PyObject *o)
returns the string representation of a python object equivalent of calling repr(o) in python
Definition: PyAthenaUtils.cxx:106
histSizes.list
def list(name, path='/')
Definition: histSizes.py:38
python.Bindings._py_init_THistSvc
def _py_init_THistSvc()
pythonizations for ITHistSvc
Definition: Control/AthenaPython/python/Bindings.py:327
CalibCoolCompareRT.run_numbers
list run_numbers
Definition: CalibCoolCompareRT.py:11
python.Bindings._py_init_StoreGateSvc
def _py_init_StoreGateSvc()
pythonizations for StoreGateSvc
Definition: Control/AthenaPython/python/Bindings.py:235
TCS::join
std::string join(const std::vector< std::string > &v, const char c=',')
Definition: Trigger/TrigT1/L1Topo/L1TopoCommon/Root/StringUtils.cxx:10
python.Bindings.raw_bit_mask
raw_bit_mask
Definition: Control/AthenaPython/python/Bindings.py:646
python.Bindings._PyAthenaBindingsCatalog.init
def init(name)
Definition: Control/AthenaPython/python/Bindings.py:79
python.Bindings._py_init_NavigationToken
def _py_init_NavigationToken()
pythonizations for NavigationToken
Definition: Control/AthenaPython/python/Bindings.py:676
python.CaloScaleNoiseConfig.type
type
Definition: CaloScaleNoiseConfig.py:78
python.Bindings.bit_mask
bit_mask
Definition: Control/AthenaPython/python/Bindings.py:656
python.Bindings.__setitem__
__setitem__
Definition: Control/AthenaPython/python/Bindings.py:771
get
T * get(TKey *tobj)
get a TObject* from a TKey* (why can't a TObject be a TKey?)
Definition: hcg.cxx:127
pickleTool.object
object
Definition: pickleTool.py:30
python.Bindings.itervalues
itervalues
Definition: Control/AthenaPython/python/Bindings.py:815
python.Bindings._import_ROOT
def _import_ROOT()
Definition: Control/AthenaPython/python/Bindings.py:23
python.Bindings._py_init_ClassIDSvc
def _py_init_ClassIDSvc()
pythonizations for ClassIDSvc
Definition: Control/AthenaPython/python/Bindings.py:280
python.Bindings.keys
keys
Definition: Control/AthenaPython/python/Bindings.py:798
python.root_pickle.load
def load(f, use_proxy=1, key=None)
Definition: root_pickle.py:476
python.Bindings.__getitem__
__getitem__
Definition: Control/AthenaPython/python/Bindings.py:779
python.Bindings._py_init_ElementLink
def _py_init_ElementLink()
pythonizations for ElementLink
Definition: Control/AthenaPython/python/Bindings.py:666
python.Bindings._PyAthenaBindingsCatalog.register
def register(klass, cb=None)
Definition: Control/AthenaPython/python/Bindings.py:62
value_type
Definition: EDM_MasterSearch.h:11
python.Bindings._py_init_ElementLinkVector
def _py_init_ElementLinkVector()
pythonizations for ElementLinkVector
Definition: Control/AthenaPython/python/Bindings.py:671
python.Bindings._py_init_EventStreamInfo
def _py_init_EventStreamInfo()
def setattr( self, attr, value ): try: from GaudiPython.Bindings import iProperty except ImportError:...
Definition: Control/AthenaPython/python/Bindings.py:597
python.Bindings.__contains__
__contains__
Definition: Control/AthenaPython/python/Bindings.py:765
python.Bindings._gen_data_link
def _gen_data_link(klass, storage_policy=None)
helper method to easily instantiate DataLink ---------------------------—
Definition: Control/AthenaPython/python/Bindings.py:681
python.Bindings.py_alg
def py_alg(algName, iface='IAlgorithm')
helper method to easily retrieve algorithms by name --------------------—
Definition: Control/AthenaPython/python/Bindings.py:190