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__ = """
8 Sebastien Binet (binet@cern.ch)
9 """
10 
11 
12 from functools import cache
13 from AthenaCommon.Logging import logging
14 
15 @cache
16 def _load_dict(lib):
17  """Helper function to remember which libraries have been already loaded
18  """
19  import cppyy
20  if not lib.startswith(lib):
21  lib="lib"+lib
22  return cppyy.load_library(lib)
23 
24 @cache
26  import ROOT
27  ROOT.gROOT.SetBatch(True)
28  return ROOT
29 
30 
31 
32 
34 _clid_typename_aliases = {
35 
36  'vector<int>' : 'std::vector<int>',
37  'vector<unsigned int>' : 'std::vector<unsigned int>',
38  'vector<float>' : 'std::vector<float>',
39  'vector<double>' : 'std::vector<double>',
40  'string' : 'std::string',
41 
43  'INavigable4MomentumCollection' : 'DataVector<INavigable4Momentum>',
44  'DataVector<IParticle>' : 'IParticleContainer',
45  'ParticleBaseContainer' : 'DataVector<ParticleBase>',
46  'TrackCollection' : 'DataVector<Trk::Track>',
47  'Trk::TrackCollection' : 'DataVector<Trk::Track>',
48  'DataVector<Track>' : 'TrackCollection',
49  'AthenaHitsVector<TrackRecord>' : 'TrackRecordCollection',
50  'Trk::SegmentCollection' : 'DataVector<Trk::Segment>',
51  }
52 
53 
54 
56  """Placeholder class to register callbacks for 'pythonizations' of C++
57  classes.
58  FIXME: find a better mechanism ?
59  """
60  msg = logging.getLogger('AthenaBindingsCatalog')
61  instances = {}
62 
63  @staticmethod
64  def register(klass, cb=None):
65  """Register a class name `klass` with an initialization method.
66  If no callback method has been given, the default is to call:
67  _py_init_<klass>()
68  """
69  try:
70  if cb is None: eval( 'cb = _py_init_%s'%klass )
71  except Exception as err:
72  _msg = _PyAthenaBindingsCatalog.msg
73  _msg.error("Problem registering callback for [%s]", klass)
74  _msg.error("Exception: %s", err)
75  cb = lambda : None # noqa: E731
76  _PyAthenaBindingsCatalog.instances[klass] = cb
77  return
78 
79  @staticmethod
80  @cache
81  def init(name):
82  """Initialize the python binding with the callback previously registered
83  If no callback was registered, swallow the warning...
84  """
85  klass = None
86  try: klass = _PyAthenaBindingsCatalog.instances[name]()
87  except KeyError:
88  ROOT = _import_ROOT() # noqa: F841
89  from AthenaServices.Dso import registry
90  registry.load_type (name)
91  try:
92  import cppyy
93  #klass = getattr(ROOT, name)
94  #klass = cppyy.makeClass(name)
95  klass=getattr(cppyy.gbl,name)
96  except AttributeError:
97  raise AttributeError("no reflex-dict for type [%s]"%name)
98  return klass
99 
100 
101 @cache
102 def py_svc(svcName, createIf=True, iface=None):
103  """
104  Helper function to retrieve a service by name, using Gaudi python bindings.
105  @param svcName: the name of the service one wants to retrieve (possibly a
106  fully qualified name as in: 'MySvcClass/TheSvcName')
107  @param createIf: If True, the service will be created if it hasn't been yet
108  instantiated.
109  @param iface: type one wants to cast the service to (can be a string or the
110  cppyy type)
111  """
112  fullName = svcName
113  s = svcName.split('/')
114  svcType = s[0]
115  if len(s)==2: svcName=s[1]
116 
117  # handle pycomponents...
118  from .Configurables import PyComponents
119  if svcType in _PyAthenaBindingsCatalog.instances:
120  pytype = _PyAthenaBindingsCatalog.init( svcType )
121  # for types which have been pythonized, help the user
122  # find the good interface...
123  if iface is None: iface = pytype
124 
125  from GaudiPython.Bindings import gbl,InterfaceCast
126  svcLocator = gbl.Gaudi.svcLocator()
127  svc = gbl.GaudiPython.Helper.service(svcLocator, fullName, createIf)
128  if svc and not(iface is None):
129  svc = InterfaceCast(iface).cast(svc)
130 
131  # if the component is actually a py-component,
132  # retrieve the python object from the registry
133  if svcName in PyComponents.instances:
134  svc = PyComponents.instances[svcName]
135 
136  if svc:
137  from AthenaPython import PyAthena
138  setattr(PyAthena.services, svcName, svc)
139  return svc
140 
141 
142 @cache
143 def py_tool(toolName, createIf=True, iface=None):
144  """
145  Helper function to retrieve a tool (owned by the ToolSvc) by name, using
146  Gaudi python bindings.
147  @param toolName: the name of the tool one wants to retrieve (possibly a
148  fully qualified name as in: 'MyToolClass/TheToolName')
149  @param createIf: If True, the tool will be created if it hasn't been yet
150  instantiated.
151  @param iface: type one wants to cast the tool to (can be a string or the
152  cppyy type)
153 
154  Ex:
155  ## retrieve default interface (ie: GaudiKernel/IAlgTool)
156  tool = py_tool('LArOnlDbPrepTool')
157  assert(type(tool) == cppyy.gbl.IAlgTool)
158 
159  ## retrieve with specified interface
160  tool = py_tool('LArOnlDbPrepTool', iface='ILArOnlDbPrepTool')
161  assert(type(tool) == cppyy.gbl.ILArOnlDbPrepTool)
162 
163  """
164  t = toolName.split('/')
165  toolType = t[0]
166  if len(t)==2: toolName=t[1]
167 
168  # handle pycomponents...
169  from .Configurables import PyComponents
170  if toolType in _PyAthenaBindingsCatalog.instances:
171  pytype = _PyAthenaBindingsCatalog.init( toolType )
172  # for types which have been pythonized, help the user
173  # find the good interface...
174  if iface is None: iface = pytype
175 
176  from GaudiPython.Bindings import gbl,InterfaceCast
177  _py_tool = gbl.GaudiPython.Helper.tool
178  toolSvc = py_svc('ToolSvc', iface='IToolSvc')
179  tool = _py_tool(toolSvc, toolType, toolName, 0, createIf)
180  if tool and not(iface is None):
181  tool = InterfaceCast(iface).cast(tool)
182 
183  # if the component is actually a py-component,
184  # retrieve the python object from the registry
185  if toolName in PyComponents.instances:
186  tool = PyComponents.instances[toolName]
187 
188  if tool:
189  from AthenaPython import PyAthena
190  setattr(PyAthena.services.ToolSvc, toolName, tool)
191  return tool
192 
193 
194 def py_alg(algName, iface='IAlgorithm'):
195  """
196  Helper function to retrieve an IAlgorithm (managed by the IAlgManager_) by
197  name, using Gaudi python bindings.
198  @param algName: the name of the algorithm's instance one wants to retrieve
199  ex: 'McAodBuilder'
200  @param iface: type one wants to cast the tool to (can be a string or the
201  cppyy type)
202 
203  Ex:
204  ## retrieve default interface (ie: GaudiKernel/IAlgorithm)
205  alg = py_alg('McAodBuilder')
206  assert(type(alg) == cppyy.gbl.IAlgorithm)
207 
208  ## retrieve with specified interface
209  alg = py_alg('McAodBuilder', iface='Algorithm')
210  assert(type(alg) == cppyy.gbl.Algorithm)
211 
212  """
213  algmgr = py_svc('ApplicationMgr',iface='IAlgManager')
214  if not algmgr:
215  msg = logging.getLogger('PyAthena.py_alg')
216  error = 'could not retrieve IAlgManager/ApplicationMgr'
217  msg.error (error)
218  raise RuntimeError (error)
219 
220  # handle pycomponents...
221  from .Configurables import PyComponents
222  import ROOT
223  alg = ROOT.MakeNullPointer(iface)
224  if not algmgr.getAlgorithm(algName, alg).isSuccess():
225  return
226 
227  # if the component is actually a py-component,
228  # retrieve the python object from the registry
229  if algName in PyComponents.instances:
230  alg = PyComponents.instances[algName]
231 
232  if alg:
233  from AthenaPython import PyAthena
234  setattr(PyAthena.algs, algName, alg)
235  return alg
236 
237 
238 @cache
240 
242  import RootUtils.PyROOTFixes
243 
244  try: RootUtils.PyROOTFixes.enable_pickling()
245  except Exception: pass # fwd compatibility
246  from StoreGateBindings.Bindings import StoreGateSvc
247 
248  return StoreGateSvc
249 
250 
251 @cache
253  import cppyy
254  # IIncidentSvc bindings from dictionary
255  _load_dict( "libGaudiKernelDict" )
256 
257  # retrieve the IIncidentSvc class
258  global IIncidentSvc
259  IIncidentSvc = cppyy.gbl.IIncidentSvc
260 
261  IIncidentSvc._cpp_addListener = IIncidentSvc.addListener
262  def addListener (self, *args):
263  listener = args[0]
264  if hasattr (listener, '_cppHandle'):
265  args = (listener._cppHandle,) + args[1:] # noqa: B009 (private property)
266  return self._cpp_addListener (*args)
267  addListener.__doc__ = IIncidentSvc._cpp_addListener.__doc__
268  IIncidentSvc.addListener = addListener
269  del addListener
270 
271  IIncidentSvc._cpp_removeListener = IIncidentSvc.removeListener
272  def removeListener (self, *args):
273  listener = args[0]
274  if hasattr (listener, '_cppHandle'):
275  args = (listener._cppHandle,) + args[1:]
276  return self._cpp_removeListener (*args)
277  removeListener.__doc__ = IIncidentSvc._cpp_removeListener.__doc__
278  IIncidentSvc.removeListener = removeListener
279  del removeListener
280  return IIncidentSvc
281 
282 
283 @cache
285  import cppyy
286  # IClassIDSvc bindings from dictionary
287  _load_dict( "libAthenaPythonDict" )
288 
289  # retrieve the IClassIDSvc class
290  global IClassIDSvc
291  IClassIDSvc = cppyy.gbl.IClassIDSvc
292 
293  _missing_clids = {
294  'DataHistory' : 83814411,
295  83814411 : 'DataHistory',
296  }
297 
298  # re-use the python-based clid generator
299  # (faster than calling back into C++ via Reflex bindings)
300  from CLIDComps.clidGenerator import clidGenerator
301  IClassIDSvc._clidgen = clidGenerator(db=None)
302 
303  # add pythonized methods
304  @cache
305  def _clid (self, name):
306  # handle special cases where CLID has been registered with a typedef
307  try: name = _clid_typename_aliases[name]
308  except KeyError: pass
309  try:
310  return _missing_clids[name]
311  except KeyError: pass
312  return self._clidgen.getClidFromName(name)
313  IClassIDSvc.clid = _clid
314  del _clid
315 
316  @cache
317  def _typename (self, clid):
318  # handle special cases of missing clids
319  try:
320  return _missing_clids[clid]
321  except KeyError:
322  pass
323  return self._clidgen.getNameFromClid(clid)
324  IClassIDSvc.typename = _typename
325  del _typename
326 
327  return IClassIDSvc
328 
329 
330 @cache
332  import cppyy
333  # ITHistSvc bindings from dictionary
334  _load_dict( "libGaudiKernelDict" )
335 
336 
337  # retrieve the ITHistSvc class
338  global ITHistSvc
339  ITHistSvc = cppyy.gbl.ITHistSvc
340 
341  ROOT = _import_ROOT()
342  @property
343  def _py_cache(self):
344  try:
345  return self.__py_cache
346  except AttributeError:
347  self.__py_cache = dict()
348  return self.__py_cache
349  ITHistSvc._py_cache = _py_cache
350 
351  # save original regXYZ methods: we'll use some modified ones
352  # to improve look-up time from python
353  for n in ('Hist', 'Graph', 'Efficiency', 'Tree'):
354  code = "ITHistSvc._cpp_reg%s = ITHistSvc.reg%s" % (n,n)
355  exec (code, globals(),locals())
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 = '_cpp_regHist'
393  elif isinstance(obj, (ROOT.TGraph,)):
394  meth = '_cpp_regGraph'
395  elif isinstance(obj, (ROOT.TEfficiency,)):
396  meth = '_cpp_regEfficiency'
397  elif isinstance(obj, (ROOT.TTree,)):
398  meth = '_cpp_regTree'
399  else:
400  raise TypeError("invalid type '%r'"%type(obj))
401  if getattr(self,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 
507  for n in ('Hist', 'Graph', 'Efficiency', 'Tree'):
508  code = """\
509 def reg%s(self, oid, oid_type=None):
510  if not (oid_type is None):
511  return self.book(oid,obj=oid_type)
512  if ITHistSvc._cpp_reg%s(self,oid).isSuccess():
513  # update py_cache
514  return self.get(oid)
515  err = ''.join(['invalid arguments oid=',repr(oid),' oid_type=',
516  repr(oid_type)])
517  raise ValueError(err)
518 ITHistSvc.reg%s = reg%s
519 del reg%s""" % (n,n,n,n,n)
520  exec (code, globals(),locals())
521  pass
522  def load(self, oid, oid_type):
523  """Helper method to load a given object `oid' from a stream, knowing
524  its type. `oid_type' is a string whose value is either:
525  - 'hist', to load any THx and TProfiles
526  - 'tree', to load TTrees
527  - 'efficiency', to load TEfficiency
528  - 'graph', to load TGraph and TGraphErrors
529  """
530  _allowed_values = ('hist','tree','efficiency','graph')
531  if oid_type not in _allowed_values:
532  raise ValueError(
533  'oid_type (=%r) MUST be one of %r'%(oid_type,
534  _allowed_values)
535  )
536  return getattr(self, 'reg%s'%oid_type.capitalize())(oid)
537  ITHistSvc.load = load
538  del load
539 
540 
541 
542  for n in ('__contains__',
543  '__iter__',
544  '__len__',
545  'has_key',
546  'items', 'iteritems',
547  'iterkeys', 'itervalues',
548  'keys',
549  'values'):
550  code = """\
551 def %s(self, *args, **kw):
552  return self._py_cache.%s(*args,**kw)
553 ITHistSvc.%s = %s
554 del %s""" % (n,n,n,n,n)
555  exec (code, globals(),locals())
556  def pop(self, k):
557  obj = self.get(k)
558  assert self.deReg(obj).isSuccess(), \
559  "could not remove object [%r]"%k
560  return obj
561  ITHistSvc.pop = pop
562  del pop
563 
564  def popitem(self):
565  k = self.iterkeys().next()
566  return (k, self.pop(k))
567  ITHistSvc.popitem = popitem
568  del popitem
569 
570 
571 
577 
578 
582 
583 
585  return ITHistSvc
586 
587 
588 @cache
590  import cppyy
591  # EventStreamInfo bindings from dictionary
592  _load_dict( "libEventInfoDict" )
593 
594  # retrieve the EventStreamInfo class
595  ESI = cppyy.gbl.EventStreamInfo
596  # retrieve the PyEventStreamInfo helper class
597  PyESI= cppyy.gbl.PyEventStreamInfo
598  def run_numbers(self):
599  self._run_numbers = PyESI.runNumbers(self)
600  return list(self._run_numbers)
601  def evt_types(self):
602  self._evt_types = PyESI.eventTypes(self)
603  return list(self._evt_types)
604  def item_list(self):
605  self._item_list = PyESI.itemList(self)
606  return list(tuple(i) for i in self._item_list)
607  def lumi_blocks(self):
608  self._lumi_blocks = PyESI.lumiBlockNumbers(self)
609  return list(self._lumi_blocks)
610  def processing_tags(self):
611  self._processing_tags = PyESI.processingTags(self)
612  return list(self._processing_tags)
613  for fct in ('run_numbers', 'evt_types', 'item_list',
614  'lumi_blocks', 'processing_tags'):
615  setattr(ESI, fct, locals()[fct])
616 
617  return ESI
618 
619 
620 @cache
622  import cppyy
623  # EventStreamInfo bindings from dictionary
624  _load_dict( "libEventInfoDict" )
625 
626  # retrieve the EventType class
627  cls = cppyy.gbl.EventType
628  cls.bit_mask_typecodes = [
629  ('IS_DATA','IS_SIMULATION'), #0
630  ('IS_ATLAS', 'IS_TESTBEAM'), #1
631  ('IS_PHYSICS','IS_CALIBRATION'),#2
632  ]
633  # retrieve the PyEventType class
634  py_cls = cppyy.gbl.PyEventType
635  def raw_bit_mask(self):
636  self._raw_bit_mask = py_cls.bit_mask(self)
637  return self._raw_bit_mask
638  cls.raw_bit_mask = property(raw_bit_mask)
639  def bit_mask(self):
640  def decode_bitmask(idx):
641  if len(self.raw_bit_mask) <= idx:
642  return self.bit_mask_typecodes[idx][0]
643  isa_idx = self.raw_bit_mask[idx]
644  return self.bit_mask_typecodes[idx][isa_idx]
645  bm = map(decode_bitmask,
646  range(len(self.bit_mask_typecodes)))
647  return tuple(bm)
648  cls.bit_mask = property(bit_mask)
649  return cls
650 
651 
652 @cache
654  return _gen_data_link
655 
656 
657 @cache
659  return _gen_element_link
660 
661 
662 @cache
664  return _gen_elv
665 
666 
667 @cache
669  return _gen_navtok
670 
671 
672 @cache
673 def _gen_data_link(klass, storage_policy=None):
674  """helper method to easily instantiate a DataLink class.
675  Sensible default for the storage policy is chosen if none given (it usually
676  boils down to DataProxyStorage)
677 
678  @example:
679  >>> DLink = PyAthena.DataLink('CompositeParticleContainer')
680  >>> cp = DLink()
681  >>> cp = DLink('MyStoreGateKey')
682  """
683  ROOT = _import_ROOT ()
684  if isinstance(klass, str):
685  klass = getattr(ROOT, klass)
686  if storage_policy is None:
687  storage_policy = ROOT.DataProxyStorage(klass)
688  return ROOT.DataLink(klass, storage_policy)
689 
690 
691 @cache
692 def _gen_element_link(klass, storage_policy=None, indexing_policy=None):
693  """helper method to easily instantiate an ElementLink class.
694  Sensible defaults for the storage and indexing policies are chosen if none
695  given (it usually boils down to DataProxyStorage and ForwardIndexingPolicy)
696 
697  @example:
698  >>> CPLink = PyAthena.ElementLink('CompositeParticleContainer')
699  >>> cp = CPLink()
700  >>> EleLink = PyAthena.ElementLink(PyAthena.ElectronContainer)
701  >>> ele = EleLink()
702  """
703  ROOT = _import_ROOT ()
704  if isinstance(klass, str):
705  klass = getattr(ROOT, klass)
706  #if storage_policy is None:
707  # storage_policy = ROOT.DataProxyStorage(klass)
708  #if indexing_policy is None:
709  # indexing_policy = ROOT.ForwardIndexingPolicy(klass)
710  #return ROOT.ElementLink(klass, storage_policy, indexing_policy)
711  return ROOT.ElementLink(klass)
712 
713 
714 @cache
715 def _gen_elv(klass, storage_policy=None, indexing_policy=None):
716  """helper method to easily instantiate an ElementLinkVector class.
717  Sensible defaults for the storage and indexing policies are chosen if none
718  given (it usually boils down to DataProxyStorage and ForwardIndexingPolicy)
719 
720  @example:
721  >>> IELV = PyAthena.ElementLinkVector('INavigable4MomentumCollection')
722  >>> ielv = IELV()
723  """
724  ROOT = _import_ROOT ()
725  if isinstance(klass, str):
726  klass = getattr(ROOT, klass)
727  if storage_policy is None:
728  storage_policy = ROOT.DataProxyStorage(klass)
729  if indexing_policy is None:
730  indexing_policy = ROOT.ForwardIndexingPolicy(klass)
731  return ROOT.ElementLinkVector(klass, storage_policy, indexing_policy)
732 
733 
734 @cache
735 def _gen_navtok(klass, weight_cls=None, hash_cls=None):
736  """helper method to easily instantiate a NavigationToken class.
737  Sensible default for the weight and hash parameters are chosen if none are
738  given
739 
740  @example:
741  >>> cls = PyAthena.NavigationToken('CaloCell')
742  >>> token = cls()
743  """
744  ROOT = _import_ROOT ()
745  if isinstance(klass, str):
746  klass = getattr(ROOT, klass)
747  if weight_cls is None:
748  weight_cls = getattr(ROOT, 'NavigationDefaults::DefaultWeight')
749  if hash_cls is None:
750  hash_cls = getattr(ROOT, 'SG::hash<const %s *>' % (klass.__name__,))
751  return ROOT.NavigationToken(klass, weight_cls, hash_cls)
752 
753 
754 def _std_map_pythonize(cls, key_type, value_type):
755  def __contains__(self, k):
756  return self.find(k) != self.end()
757  cls.__contains__ = __contains__
758 
759  def __setitem__(self, k, v):
760  itr = self.find(k)
761  self.insert(itr, self.__class__.value_type(k,v))
762  return v
763  cls.__setitem__ = __setitem__
764 
765  cls.__cxx_getitem__ = cls.__getitem__
766  def __getitem__(self, k):
767  # python's dict semantics
768  if k not in self:
769  raise KeyError(k)
770  return self.__cxx_getitem__(k)
771  cls.__getitem__ = __getitem__
772 
773  if not hasattr(cls, '__iter__'):
774  def toiter(beg, end):
775  while beg != end:
776  yield beg.__deref__()
777  beg.__preinc__()
778  return
779 
780  def __iter__(self):
781  for i in toiter(self.begin(), self.end()):
782  yield i
783  cls.__iter__ = __iter__
784 
785  def keys(self):
786  keys = []
787  for i in self:
788  keys.append(i.first)
789  return keys
790  cls.keys = keys
791 
792  def values(self):
793  vals = []
794  for i in self:
795  vals.append(i.first)
796  return vals
797  cls.values = values
798 
799  def iterkeys(self):
800  for i in self:
801  yield i.first
802  cls.iterkeys = iterkeys
803 
804  def itervalues(self):
805  for i in self:
806  yield i.second
807  cls.itervalues = itervalues
808 
809  def iteritems(self):
810  for i in self:
811  yield (i.first, i.second)
812  cls.iteritems = iteritems
813 
814  return cls
815 
816 # -----------------------------------------------------------------------------
817 
818 def _setup():
819  _register = _PyAthenaBindingsCatalog.register
820  _register('StoreGateSvc', _py_init_StoreGateSvc)
821 
822  _register( 'IncidentSvc', _py_init_IIncidentSvc)
823  _register('IIncidentSvc', _py_init_IIncidentSvc)
824 
825  _register( 'ClassIDSvc', _py_init_ClassIDSvc)
826  _register('IClassIDSvc', _py_init_ClassIDSvc)
827 
828  _register( 'THistSvc', _py_init_THistSvc)
829  _register('ITHistSvc', _py_init_THistSvc)
830 
831  _register('EventStreamInfo', _py_init_EventStreamInfo)
832  _register('EventType', _py_init_EventType)
833 
834  _register('DataLink', _py_init_DataLink)
835  _register('ElementLink', _py_init_ElementLink)
836  _register('ElementLinkVector', _py_init_ElementLinkVector)
837  pass
838 
839 
840 _setup()
841 
842 
843 del _setup
844 
python.Bindings.iteritems
iteritems
Definition: Control/AthenaPython/python/Bindings.py:812
Logging
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:735
python.Bindings._PyAthenaBindingsCatalog
Definition: Control/AthenaPython/python/Bindings.py:55
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:754
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:143
python.Bindings.__iter__
__iter__
Definition: Control/AthenaPython/python/Bindings.py:783
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:692
python.Bindings._py_init_IIncidentSvc
def _py_init_IIncidentSvc()
pythonizations for IIncidentSvc
Definition: Control/AthenaPython/python/Bindings.py:252
xAODRootTest._typename
def _typename(t)
Definition: xAODRootTest.py:34
python.Bindings._load_dict
def _load_dict(lib)
Definition: Control/AthenaPython/python/Bindings.py:16
python.Bindings._setup
def _setup()
initialize the bindings' registration
Definition: Control/AthenaPython/python/Bindings.py:818
python.Bindings.values
values
Definition: Control/AthenaPython/python/Bindings.py:797
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:715
python.FilePeekerLib.toiter
def toiter(beg, end)
Definition: FilePeekerLib.py:28
python.Bindings._py_init_EventType
def _py_init_EventType()
pythonizations for EventType
Definition: Control/AthenaPython/python/Bindings.py:621
python.Bindings.py_svc
def py_svc(svcName, createIf=True, iface=None)
Definition: Control/AthenaPython/python/Bindings.py:102
python.Bindings._py_init_DataLink
def _py_init_DataLink()
pythonizations for DataLink
Definition: Control/AthenaPython/python/Bindings.py:653
fillPileUpNoiseLumi.next
next
Definition: fillPileUpNoiseLumi.py:53
book
T * book(const std::string &n, const std::string &t, unsigned nbins)
Definition: main_benchmark.cxx:138
python.KeyStore.dict
def dict(self)
Definition: KeyStore.py:321
python.Bindings.iterkeys
iterkeys
Definition: Control/AthenaPython/python/Bindings.py:802
plotBeamSpotVxVal.range
range
Definition: plotBeamSpotVxVal.py:195
python.Bindings._py_init_THistSvc
def _py_init_THistSvc()
pythonizations for ITHistSvc
Definition: Control/AthenaPython/python/Bindings.py:331
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:239
python.Bindings.raw_bit_mask
raw_bit_mask
Definition: Control/AthenaPython/python/Bindings.py:638
python.Bindings._PyAthenaBindingsCatalog.init
def init(name)
Definition: Control/AthenaPython/python/Bindings.py:81
python.Bindings._py_init_NavigationToken
def _py_init_NavigationToken()
pythonizations for NavigationToken
Definition: Control/AthenaPython/python/Bindings.py:668
python.CaloScaleNoiseConfig.type
type
Definition: CaloScaleNoiseConfig.py:78
python.KeyStore.list
def list(self, key=None)
Definition: KeyStore.py:318
python.Bindings.bit_mask
bit_mask
Definition: Control/AthenaPython/python/Bindings.py:648
python.Bindings.__setitem__
__setitem__
Definition: Control/AthenaPython/python/Bindings.py:763
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:807
python.Bindings._import_ROOT
def _import_ROOT()
Definition: Control/AthenaPython/python/Bindings.py:25
python.Bindings._py_init_ClassIDSvc
def _py_init_ClassIDSvc()
pythonizations for ClassIDSvc
Definition: Control/AthenaPython/python/Bindings.py:284
python.Bindings.keys
keys
Definition: Control/AthenaPython/python/Bindings.py:790
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:771
python.Bindings._py_init_ElementLink
def _py_init_ElementLink()
pythonizations for ElementLink
Definition: Control/AthenaPython/python/Bindings.py:658
python.Bindings._PyAthenaBindingsCatalog.register
def register(klass, cb=None)
Definition: Control/AthenaPython/python/Bindings.py:64
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:663
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:589
python.Bindings.__contains__
__contains__
Definition: Control/AthenaPython/python/Bindings.py:757
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:673
python.Bindings.py_alg
def py_alg(algName, iface='IAlgorithm')
helper method to easily retrieve algorithms by name --------------------—
Definition: Control/AthenaPython/python/Bindings.py:194