ATLAS Offline Software
Control/AthenaPython/python/Bindings.py
Go to the documentation of this file.
1 # Copyright (C) 2002-2025 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=None):
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 algorithm 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  alg = algmgr.algorithm(algName)
219  if not alg:
220  return
221 
222  if iface is not None:
223  from GaudiPython.Bindings import InterfaceCast
224  alg = InterfaceCast(iface).cast(alg)
225 
226  # if the component is actually a py-component,
227  # retrieve the python object from the registry
228  if algName in PyComponents.instances:
229  alg = PyComponents.instances[algName]
230 
231  if alg:
232  from AthenaPython import PyAthena
233  setattr(PyAthena.algs, algName, alg)
234  return alg
235 
236 
237 @cache
239 
241  import RootUtils.PyROOTFixes
242 
243  try: RootUtils.PyROOTFixes.enable_pickling()
244  except Exception: pass # fwd compatibility
245  from StoreGateBindings.Bindings import StoreGateSvc
246 
247  return StoreGateSvc
248 
249 
250 @cache
252  import cppyy
253  # IIncidentSvc bindings from dictionary
254  _load_dict( "libGaudiKernelDict" )
255 
256  # retrieve the IIncidentSvc class
257  global IIncidentSvc
258  IIncidentSvc = cppyy.gbl.IIncidentSvc
259 
260  IIncidentSvc._cpp_addListener = IIncidentSvc.addListener
261  def addListener (self, *args):
262  listener = args[0]
263  if hasattr (listener, '_cppHandle'):
264  args = (listener._cppHandle,) + args[1:] # noqa: B009 (private property)
265  return self._cpp_addListener (*args)
266  addListener.__doc__ = IIncidentSvc._cpp_addListener.__doc__
267  IIncidentSvc.addListener = addListener
268  del addListener
269 
270  IIncidentSvc._cpp_removeListener = IIncidentSvc.removeListener
271  def removeListener (self, *args):
272  listener = args[0]
273  if hasattr (listener, '_cppHandle'):
274  args = (listener._cppHandle,) + args[1:]
275  return self._cpp_removeListener (*args)
276  removeListener.__doc__ = IIncidentSvc._cpp_removeListener.__doc__
277  IIncidentSvc.removeListener = removeListener
278  del removeListener
279  return IIncidentSvc
280 
281 
282 @cache
284  import cppyy
285  # IClassIDSvc bindings from dictionary
286  _load_dict( "libAthenaPythonDict" )
287 
288  # retrieve the IClassIDSvc class
289  global IClassIDSvc
290  IClassIDSvc = cppyy.gbl.IClassIDSvc
291 
292  _missing_clids = {
293  'DataHistory' : 83814411,
294  83814411 : 'DataHistory',
295  }
296 
297  # re-use the python-based clid generator
298  # (faster than calling back into C++ via Reflex bindings)
299  from CLIDComps.clidGenerator import clidGenerator
300  IClassIDSvc._clidgen = clidGenerator(db=None)
301 
302  # add pythonized methods
303  @cache
304  def _clid (self, name):
305  # handle special cases where CLID has been registered with a typedef
306  try: name = _clid_typename_aliases[name]
307  except KeyError: pass
308  try:
309  return _missing_clids[name]
310  except KeyError: pass
311  return self._clidgen.getClidFromName(name)
312  IClassIDSvc.clid = _clid
313  del _clid
314 
315  @cache
316  def _typename (self, clid):
317  # handle special cases of missing clids
318  try:
319  return _missing_clids[clid]
320  except KeyError:
321  pass
322  return self._clidgen.getNameFromClid(clid)
323  IClassIDSvc.typename = _typename
324  del _typename
325 
326  return IClassIDSvc
327 
328 
329 @cache
331  import cppyy
332  # ITHistSvc bindings from dictionary
333  _load_dict( "libGaudiKernelDict" )
334 
335 
336  # retrieve the ITHistSvc class
337  global ITHistSvc
338  ITHistSvc = cppyy.gbl.ITHistSvc
339 
340  ROOT = _import_ROOT()
341  @property
342  def _py_cache(self):
343  try:
344  return self.__py_cache
345  except AttributeError:
346  self.__py_cache = dict()
347  return self.__py_cache
348  ITHistSvc._py_cache = _py_cache
349 
350  # save original regXYZ methods: we'll use some modified ones
351  # to improve look-up time from python
352  ITHistSvc._cpp_regHist = ITHistSvc.regHist
353  ITHistSvc._cpp_regGraph = ITHistSvc.regGraph
354  ITHistSvc._cpp_regEfficiency = ITHistSvc.regEfficiency
355  ITHistSvc._cpp_regTree = ITHistSvc.regTree
356 
357  def book(self, oid, obj=None, *args, **kw):
358  """book a histogram, profile or tree
359  @param oid is the unique object identifier even across streams,
360  ie: 'stream'+'id'
361  @param obj either an already full-fledge constructed ROOT object
362  or None (then `*args` or `**kw` need to be correctly setup)
363  @param *args list of arguments to give to the constructor of the
364  ROOT object one wants to book
365  @param **kw a dictionary containing a key 'args' being the list of
366  arguments to the constructor of the ROOT objects one wants to
367  book
368  examples:
369  >>> th.book('/temp/1d/h1', 'TH1D', args=('h1','h1',100,0.,100.))
370  >>> th.book('/temp/1d/h2', ROOT.TH1D, args=('h2','h2',100,0.,100.))
371  >>> th.book('/temp/1d/h3', ROOT.TH1D, 'h3','h3',100,0.,100.)
372  >>> th.book('/temp/1d/h4', ROOT.TH1D('h4','h4',100,0.,100.))
373  >>> th.book('/temp/1d/h5', obj=ROOT.TH1D('h5','h5',100,0.,100.))
374  >>> th.book('/temp/1d/h6', klass='TH1D', args=('h6','h6',100,0.,100.))
375 
376  >>> th.book('/temp/tree/t1', ROOT.TTree('t1','t1'))
377  >>> th.book('/temp/tree/t2', obj=ROOT.TTree('t2','t2'))
378  >>> th.book('/temp/tree/t3', klass='TTree', args=('t3','t3'))
379  """
380  _err = "please provide _either_ an already constructed ROOT object or"\
381  "a class name/class type (with appropriate arguments)"
382  klass = kw.get('klass', None)
383  assert not (obj is None and klass is None), _err
384  assert not (obj is not None and klass is not None), _err
385 
386  if isinstance(obj, (str,type)):
387  klass=obj
388  obj=None
389  if obj:
390  if isinstance(obj, ROOT.TH1):
391  # capture all of TH1x,TH2x,TH3x,TProfileXY
392  meth = self._cpp_regHist
393  elif isinstance(obj, (ROOT.TGraph,)):
394  meth = self._cpp_regGraph
395  elif isinstance(obj, (ROOT.TEfficiency,)):
396  meth = self._cpp_regEfficiency
397  elif isinstance(obj, (ROOT.TTree,)):
398  meth = self._cpp_regTree
399  else:
400  raise TypeError("invalid type '%r'"%type(obj))
401  if meth(oid, obj).isSuccess():
402  self._py_cache[oid]=obj
403  return obj
404  raise RuntimeError('could not book object [%r]'%obj)
405 
406  if klass:
407  if isinstance(klass, str):
408  klass = getattr(ROOT, klass)
409  if args:
410  return self.book(oid, obj=klass(*args))
411  if kw and 'args' in kw:
412  return self.book(oid, obj=klass(*kw['args']))
413  err = "invalid arguments: either provide a valid `*args` or "\
414  "a `**kw` containing a 'args' key"
415  raise RuntimeError(err)
416  raise RuntimeError("unforseen case: oid='%r' obj='%r' args='%r' "
417  "kw='%r'"%(oid,obj,args,kw))
418 
419  ITHistSvc.book = book
420 
421  def get(self, oid, klass=None):
422  """retrieve an already booked ROOT object.
423  If the object was booked on the C++ side, try to use the `klass` hint
424  (the usual string or type) to find the object in the correct 'folder'
425  (histograms, graphs or trees).
426  If `klass` is None, then go through all the folders iteratively (slow)
427  """
428  try:
429  return self._py_cache[oid]
430  except KeyError:
431  pass
432  def _get_helper(klass, hsvc, meth, oid, update_cache=True):
433  makeNullPtr = ROOT.MakeNullPointer
434  o = makeNullPtr(klass)
435  if meth(oid, o).isSuccess():
436  if update_cache:
437  hsvc._py_cache[oid] = o
438  return o
439  return
440  if klass:
441  if isinstance(klass, str):
442  klass = getattr(ROOT, klass)
443  if issubclass(klass, (ROOT.TH1,)):
444  return _get_helper(klass, self, self.getHist, oid)
445  if issubclass(klass, (ROOT.TGraph,)):
446  return _get_helper(klass, self, self.getGraph, oid)
447  if issubclass(klass, (ROOT.TEfficiency,)):
448  return _get_helper(klass, self, self.getEfficiency, oid)
449  if issubclass(klass, (ROOT.TTree,)):
450  return _get_helper(klass, self, self.getTree, oid)
451  raise RuntimeError('unsupported type [%r]'%klass)
452 
453  # as we are sentenced to crawl through all these std::vector<str>
454  # we might as well update our local cache...
455 
456  # first update histos
457  oids = [n for n in self.getHists() if n not in self._py_cache.keys()]
458  for name in oids:
459  obj = _get_helper(ROOT.TH1, self, self.getHist, name,
460  update_cache=False)
461  if obj:
462  # now try with real class
463  klass = getattr(ROOT, obj.ClassName())
464  obj = _get_helper(klass, self, self.getHist, name)
465 
466  # then graphs
467  oids = [n for n in self.getGraphs() if n not in self._py_cache.keys()]
468  for name in oids:
469  _get_helper(ROOT.TGraph, self, self.getGraph, name)
470 
471  # then efficiencies
472  oids = [n for n in self.getEfficiencies() if n not in self._py_cache.keys()]
473  for name in oids:
474  _get_helper(ROOT.TEfficiency, self, self.getEfficiency, name)
475 
476  # finally try ttrees
477  oids = [n for n in self.getTrees() if n not in self._py_cache.keys()]
478  for name in oids:
479  _get_helper(ROOT.TTree, self, self.getTree, name)
480 
481 
482  return self._py_cache[oid]
483 
484  ITHistSvc.get = get
485  del get
486 
487  def getitem(self, oid):
488  return self.get(oid)
489  ITHistSvc.__getitem__ = getitem
490  del getitem
491 
492  def delitem(self, oid):
493  if isinstance(oid, str):
494  self.get(oid)
495  del self._py_cache[oid]
496  assert self.deReg(oid).isSuccess(), \
497  "could not remove object [%r]"%oid
498  return
499  ITHistSvc.__delitem__ = delitem
500 
501  def setitem(self, k, v):
502  return self.book(k, obj=v)
503  ITHistSvc.__setitem__ = setitem
504  del setitem
505 
506  def regObject(self, regFcn, oid, oid_type=None):
507  """Helper method to register object 'oid' using 'regFcn'."""
508  if oid_type is not None:
509  return self.book(oid,obj=oid_type)
510  if regFcn(self,oid).isSuccess():
511  # update py_cache
512  return self.get(oid)
513  err = ''.join(['invalid arguments oid=',repr(oid),' oid_type=',
514  repr(oid_type)])
515  raise ValueError(err)
516 
517  ITHistSvc.regHist = partialmethod(regObject, ITHistSvc._cpp_regHist)
518  ITHistSvc.regTree = partialmethod(regObject, ITHistSvc._cpp_regTree)
519  ITHistSvc.regEfficiency = partialmethod(regObject, ITHistSvc._cpp_regEfficiency)
520  ITHistSvc.regGraph = partialmethod(regObject, ITHistSvc._cpp_regGraph)
521  del regObject
522 
523  def load(self, oid, oid_type):
524  """Helper method to load a given object `oid' from a stream, knowing
525  its type. `oid_type' is a string whose value is either:
526  - 'hist', to load any THx and TProfiles
527  - 'tree', to load TTrees
528  - 'efficiency', to load TEfficiency
529  - 'graph', to load TGraph and TGraphErrors
530  """
531  if oid_type == 'hist':
532  return self.regHist(oid)
533  elif oid_type == 'tree':
534  return self.regTree(oid)
535  elif oid_type == 'efficiency':
536  return self.regEfficiency(oid)
537  elif oid_type == 'graph':
538  return self.regGraph(oid)
539  else:
540  raise ValueError(f'oid_type (={oid_type}) MUST be one of hist, tree, efficiency, graph')
541 
542  ITHistSvc.load = load
543  del load
544 
545 
546 
547  for n in ('__contains__',
548  '__iter__',
549  '__len__',
550  'has_key',
551  'items', 'iteritems',
552  'iterkeys', 'itervalues',
553  'keys', 'values'):
554  code = """\
555 def %s(self, *args, **kw):
556  return self._py_cache.%s(*args,**kw)
557 ITHistSvc.%s = %s
558 del %s""" % (n,n,n,n,n)
559  exec (code, globals(),locals())
560 
561 
562  def __bool__(self):
563  return self is not None
564  ITHistSvc.__bool__ = __bool__
565  del __bool__
566 
567  def pop(self, k):
568  obj = self.get(k)
569  assert self.deReg(obj).isSuccess(), \
570  "could not remove object [%r]"%k
571  return obj
572  ITHistSvc.pop = pop
573  del pop
574 
575  def popitem(self):
576  k = self.iterkeys().next()
577  return (k, self.pop(k))
578  ITHistSvc.popitem = popitem
579  del popitem
580 
581 
582 
588 
589 
593 
594 
596  return ITHistSvc
597 
598 
599 @cache
601  import cppyy
602  # EventStreamInfo bindings from dictionary
603  _load_dict( "libEventInfoDict" )
604 
605  # retrieve the EventStreamInfo class
606  ESI = cppyy.gbl.EventStreamInfo
607  # retrieve the PyEventStreamInfo helper class
608  PyESI= cppyy.gbl.PyEventStreamInfo
609  def run_numbers(self):
610  self._run_numbers = PyESI.runNumbers(self)
611  return list(self._run_numbers)
612  def evt_types(self):
613  self._evt_types = PyESI.eventTypes(self)
614  return list(self._evt_types)
615  def item_list(self):
616  self._item_list = PyESI.itemList(self)
617  return list(tuple(i) for i in self._item_list)
618  def lumi_blocks(self):
619  self._lumi_blocks = PyESI.lumiBlockNumbers(self)
620  return list(self._lumi_blocks)
621  def processing_tags(self):
622  self._processing_tags = PyESI.processingTags(self)
623  return list(self._processing_tags)
624  for fct in ('run_numbers', 'evt_types', 'item_list',
625  'lumi_blocks', 'processing_tags'):
626  setattr(ESI, fct, locals()[fct])
627 
628  return ESI
629 
630 
631 @cache
633  import cppyy
634  # EventStreamInfo bindings from dictionary
635  _load_dict( "libEventInfoDict" )
636 
637  # retrieve the EventType class
638  cls = cppyy.gbl.EventType
639  cls.bit_mask_typecodes = [
640  ('IS_DATA','IS_SIMULATION'), #0
641  ('IS_ATLAS', 'IS_TESTBEAM'), #1
642  ('IS_PHYSICS','IS_CALIBRATION'),#2
643  ]
644  # retrieve the PyEventType class
645  py_cls = cppyy.gbl.PyEventType
646  def raw_bit_mask(self):
647  self._raw_bit_mask = py_cls.bit_mask(self)
648  return self._raw_bit_mask
649  cls.raw_bit_mask = property(raw_bit_mask)
650  def bit_mask(self):
651  def decode_bitmask(idx):
652  if len(self.raw_bit_mask) <= idx:
653  return self.bit_mask_typecodes[idx][0]
654  isa_idx = self.raw_bit_mask[idx]
655  return self.bit_mask_typecodes[idx][isa_idx]
656  bm = map(decode_bitmask,
657  range(len(self.bit_mask_typecodes)))
658  return tuple(bm)
659  cls.bit_mask = property(bit_mask)
660  return cls
661 
662 
663 @cache
665  return _gen_data_link
666 
667 
668 @cache
670  return _gen_element_link
671 
672 
673 @cache
675  return _gen_elv
676 
677 
678 @cache
680  return _gen_navtok
681 
682 
683 @cache
684 def _gen_data_link(klass, storage_policy=None):
685  """helper method to easily instantiate a DataLink class.
686  Sensible default for the storage policy is chosen if none given (it usually
687  boils down to DataProxyStorage)
688 
689  @example:
690  >>> DLink = PyAthena.DataLink('CompositeParticleContainer')
691  >>> cp = DLink()
692  >>> cp = DLink('MyStoreGateKey')
693  """
694  ROOT = _import_ROOT ()
695  if isinstance(klass, str):
696  klass = getattr(ROOT, klass)
697  if storage_policy is None:
698  storage_policy = ROOT.DataProxyStorage(klass)
699  return ROOT.DataLink(klass, storage_policy)
700 
701 
702 @cache
703 def _gen_element_link(klass, storage_policy=None, indexing_policy=None):
704  """helper method to easily instantiate an ElementLink class.
705  Sensible defaults for the storage and indexing policies are chosen if none
706  given (it usually boils down to DataProxyStorage and ForwardIndexingPolicy)
707 
708  @example:
709  >>> CPLink = PyAthena.ElementLink('CompositeParticleContainer')
710  >>> cp = CPLink()
711  >>> EleLink = PyAthena.ElementLink(PyAthena.ElectronContainer)
712  >>> ele = EleLink()
713  """
714  ROOT = _import_ROOT ()
715  if isinstance(klass, str):
716  klass = getattr(ROOT, klass)
717  #if storage_policy is None:
718  # storage_policy = ROOT.DataProxyStorage(klass)
719  #if indexing_policy is None:
720  # indexing_policy = ROOT.ForwardIndexingPolicy(klass)
721  #return ROOT.ElementLink(klass, storage_policy, indexing_policy)
722  return ROOT.ElementLink(klass)
723 
724 
725 @cache
726 def _gen_elv(klass, storage_policy=None, indexing_policy=None):
727  """helper method to easily instantiate an ElementLinkVector class.
728  Sensible defaults for the storage and indexing policies are chosen if none
729  given (it usually boils down to DataProxyStorage and ForwardIndexingPolicy)
730 
731  @example:
732  >>> IELV = PyAthena.ElementLinkVector('INavigable4MomentumCollection')
733  >>> ielv = IELV()
734  """
735  ROOT = _import_ROOT ()
736  if isinstance(klass, str):
737  klass = getattr(ROOT, klass)
738  if storage_policy is None:
739  storage_policy = ROOT.DataProxyStorage(klass)
740  if indexing_policy is None:
741  indexing_policy = ROOT.ForwardIndexingPolicy(klass)
742  return ROOT.ElementLinkVector(klass, storage_policy, indexing_policy)
743 
744 
745 @cache
746 def _gen_navtok(klass, weight_cls=None, hash_cls=None):
747  """helper method to easily instantiate a NavigationToken class.
748  Sensible default for the weight and hash parameters are chosen if none are
749  given
750 
751  @example:
752  >>> cls = PyAthena.NavigationToken('CaloCell')
753  >>> token = cls()
754  """
755  ROOT = _import_ROOT ()
756  if isinstance(klass, str):
757  klass = getattr(ROOT, klass)
758  if weight_cls is None:
759  weight_cls = getattr(ROOT, 'NavigationDefaults::DefaultWeight')
760  if hash_cls is None:
761  hash_cls = getattr(ROOT, 'SG::hash<const %s *>' % (klass.__name__,))
762  return ROOT.NavigationToken(klass, weight_cls, hash_cls)
763 
764 
765 def _std_map_pythonize(cls, key_type, value_type):
766  def __contains__(self, k):
767  return self.find(k) != self.end()
768  cls.__contains__ = __contains__
769 
770  def __setitem__(self, k, v):
771  itr = self.find(k)
772  self.insert(itr, self.__class__.value_type(k,v))
773  return v
774  cls.__setitem__ = __setitem__
775 
776  cls.__cxx_getitem__ = cls.__getitem__
777  def __getitem__(self, k):
778  # python's dict semantics
779  if k not in self:
780  raise KeyError(k)
781  return self.__cxx_getitem__(k)
782  cls.__getitem__ = __getitem__
783 
784  if not hasattr(cls, '__iter__'):
785  def toiter(beg, end):
786  while beg != end:
787  yield beg.__deref__()
788  beg.__preinc__()
789  return
790 
791  def __iter__(self):
792  for i in toiter(self.begin(), self.end()):
793  yield i
794  cls.__iter__ = __iter__
795 
796  def keys(self):
797  keys = []
798  for i in self:
799  keys.append(i.first)
800  return keys
801  cls.keys = keys
802 
803  def values(self):
804  vals = []
805  for i in self:
806  vals.append(i.first)
807  return vals
808  cls.values = values
809 
810  def iterkeys(self):
811  for i in self:
812  yield i.first
813  cls.iterkeys = iterkeys
814 
815  def itervalues(self):
816  for i in self:
817  yield i.second
818  cls.itervalues = itervalues
819 
820  def iteritems(self):
821  for i in self:
822  yield (i.first, i.second)
823  cls.iteritems = iteritems
824 
825  return cls
826 
827 # -----------------------------------------------------------------------------
828 
829 def _setup():
830  _register = _PyAthenaBindingsCatalog.register
831  _register('StoreGateSvc', _py_init_StoreGateSvc)
832 
833  _register( 'IncidentSvc', _py_init_IIncidentSvc)
834  _register('IIncidentSvc', _py_init_IIncidentSvc)
835 
836  _register( 'ClassIDSvc', _py_init_ClassIDSvc)
837  _register('IClassIDSvc', _py_init_ClassIDSvc)
838 
839  _register( 'THistSvc', _py_init_THistSvc)
840  _register('ITHistSvc', _py_init_THistSvc)
841 
842  _register('EventStreamInfo', _py_init_EventStreamInfo)
843  _register('EventType', _py_init_EventType)
844 
845  _register('DataLink', _py_init_DataLink)
846  _register('ElementLink', _py_init_ElementLink)
847  _register('ElementLinkVector', _py_init_ElementLinkVector)
848  pass
849 
850 
851 _setup()
852 
853 
854 del _setup
855 
python.Bindings.iteritems
iteritems
Definition: Control/AthenaPython/python/Bindings.py:823
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:746
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:765
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:794
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:703
python.Bindings._py_init_IIncidentSvc
def _py_init_IIncidentSvc()
pythonizations for IIncidentSvc
Definition: Control/AthenaPython/python/Bindings.py:251
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.CaloAddPedShiftConfig.type
type
Definition: CaloAddPedShiftConfig.py:42
python.Bindings._setup
def _setup()
initialize the bindings' registration
Definition: Control/AthenaPython/python/Bindings.py:829
python.Bindings.values
values
Definition: Control/AthenaPython/python/Bindings.py:808
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:726
python.FilePeekerLib.toiter
def toiter(beg, end)
Definition: FilePeekerLib.py:23
python.Bindings._py_init_EventType
def _py_init_EventType()
pythonizations for EventType
Definition: Control/AthenaPython/python/Bindings.py:632
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:664
fillPileUpNoiseLumi.next
next
Definition: fillPileUpNoiseLumi.py:52
python.Bindings.iterkeys
iterkeys
Definition: Control/AthenaPython/python/Bindings.py:813
plotBeamSpotVxVal.range
range
Definition: plotBeamSpotVxVal.py:194
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:330
CalibCoolCompareRT.run_numbers
list run_numbers
Definition: CalibCoolCompareRT.py:10
python.Bindings._py_init_StoreGateSvc
def _py_init_StoreGateSvc()
pythonizations for StoreGateSvc
Definition: Control/AthenaPython/python/Bindings.py:238
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:649
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:679
python.Bindings.bit_mask
bit_mask
Definition: Control/AthenaPython/python/Bindings.py:659
python.Bindings.__setitem__
__setitem__
Definition: Control/AthenaPython/python/Bindings.py:774
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:29
python.Bindings.itervalues
itervalues
Definition: Control/AthenaPython/python/Bindings.py:818
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:283
python.Bindings.keys
keys
Definition: Control/AthenaPython/python/Bindings.py:801
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:782
python.Bindings.py_alg
def py_alg(algName, iface=None)
helper method to easily retrieve algorithms by name --------------------—
Definition: Control/AthenaPython/python/Bindings.py:190
python.Bindings._py_init_ElementLink
def _py_init_ElementLink()
pythonizations for ElementLink
Definition: Control/AthenaPython/python/Bindings.py:669
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:674
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:600
python.Bindings.__contains__
__contains__
Definition: Control/AthenaPython/python/Bindings.py:768
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:684