merge
[cython.git] / Cython / Compiler / ExprNodes.py
1 #
2 #   Pyrex - Parse tree nodes for expressions
3 #
4
5 import operator
6
7 from Errors import error, warning, warn_once, InternalError
8 from Errors import hold_errors, release_errors, held_errors, report_error
9 from Code import UtilityCode
10 import StringEncoding
11 import Naming
12 import Nodes
13 from Nodes import Node
14 import PyrexTypes
15 from PyrexTypes import py_object_type, c_long_type, typecast, error_type, \
16      unspecified_type
17 from Builtin import list_type, tuple_type, set_type, dict_type, \
18      unicode_type, str_type, bytes_type, type_type
19 import Builtin
20 import Symtab
21 import Options
22 from Cython import Utils
23 from Annotate import AnnotationItem
24 from Cython import Utils
25
26 from Cython.Debugging import print_call_chain
27 from DebugFlags import debug_disposal_code, debug_temp_alloc, \
28     debug_coercion
29
30 try:
31     set
32 except NameError:
33     from sets import Set as set
34
35 class NotConstant(object):
36     def __repr__(self):
37         return "<NOT CONSTANT>"
38
39 not_a_constant = NotConstant()
40 constant_value_not_set = object()
41
42 # error messages when coercing from key[0] to key[1]
43 find_coercion_error = {
44     # string related errors
45     (Builtin.unicode_type, Builtin.bytes_type) : "Cannot convert Unicode string to 'bytes' implicitly, encoding required.",
46     (Builtin.unicode_type, Builtin.str_type)   : "Cannot convert Unicode string to 'str' implicitly. This is not portable and requires explicit encoding.",
47     (Builtin.unicode_type, PyrexTypes.c_char_ptr_type) : "Unicode objects do not support coercion to C types.",
48     (Builtin.bytes_type, Builtin.unicode_type) : "Cannot convert 'bytes' object to unicode implicitly, decoding required",
49     (Builtin.bytes_type, Builtin.str_type) : "Cannot convert 'bytes' object to str implicitly. This is not portable to Py3.",
50     (Builtin.str_type, Builtin.unicode_type) : "str objects do not support coercion to unicode, use a unicode string literal instead (u'')",
51     (Builtin.str_type, Builtin.bytes_type) : "Cannot convert 'str' to 'bytes' implicitly. This is not portable.",
52     (Builtin.str_type, PyrexTypes.c_char_ptr_type) : "'str' objects do not support coercion to C types (use 'bytes'?).",
53     (PyrexTypes.c_char_ptr_type, Builtin.unicode_type) : "Cannot convert 'char*' to unicode implicitly, decoding required",
54     (PyrexTypes.c_uchar_ptr_type, Builtin.unicode_type) : "Cannot convert 'char*' to unicode implicitly, decoding required",
55     }.get
56
57
58 class ExprNode(Node):
59     #  subexprs     [string]     Class var holding names of subexpr node attrs
60     #  type         PyrexType    Type of the result
61     #  result_code  string       Code fragment
62     #  result_ctype string       C type of result_code if different from type
63     #  is_temp      boolean      Result is in a temporary variable
64     #  is_sequence_constructor  
65     #               boolean      Is a list or tuple constructor expression
66     #  is_starred   boolean      Is a starred expression (e.g. '*a')
67     #  saved_subexpr_nodes
68     #               [ExprNode or [ExprNode or None] or None]
69     #                            Cached result of subexpr_nodes()
70     #  use_managed_ref boolean   use ref-counted temps/assignments/etc.
71     
72     result_ctype = None
73     type = None
74     temp_code = None
75     old_temp = None # error checker for multiple frees etc.
76     use_managed_ref = True # can be set by optimisation transforms
77
78     #  The Analyse Expressions phase for expressions is split
79     #  into two sub-phases:
80     #
81     #    Analyse Types
82     #      Determines the result type of the expression based
83     #      on the types of its sub-expressions, and inserts
84     #      coercion nodes into the expression tree where needed.
85     #      Marks nodes which will need to have temporary variables
86     #      allocated.
87     #
88     #    Allocate Temps
89     #      Allocates temporary variables where needed, and fills
90     #      in the result_code field of each node.
91     #
92     #  ExprNode provides some convenience routines which
93     #  perform both of the above phases. These should only
94     #  be called from statement nodes, and only when no
95     #  coercion nodes need to be added around the expression
96     #  being analysed. In that case, the above two phases
97     #  should be invoked separately.
98     #
99     #  Framework code in ExprNode provides much of the common
100     #  processing for the various phases. It makes use of the
101     #  'subexprs' class attribute of ExprNodes, which should
102     #  contain a list of the names of attributes which can
103     #  hold sub-nodes or sequences of sub-nodes.
104     #  
105     #  The framework makes use of a number of abstract methods. 
106     #  Their responsibilities are as follows.
107     #
108     #    Declaration Analysis phase
109     #
110     #      analyse_target_declaration
111     #        Called during the Analyse Declarations phase to analyse
112     #        the LHS of an assignment or argument of a del statement.
113     #        Nodes which cannot be the LHS of an assignment need not
114     #        implement it.
115     #
116     #    Expression Analysis phase
117     #
118     #      analyse_types
119     #        - Call analyse_types on all sub-expressions.
120     #        - Check operand types, and wrap coercion nodes around
121     #          sub-expressions where needed.
122     #        - Set the type of this node.
123     #        - If a temporary variable will be required for the
124     #          result, set the is_temp flag of this node.
125     #
126     #      analyse_target_types
127     #        Called during the Analyse Types phase to analyse
128     #        the LHS of an assignment or argument of a del 
129     #        statement. Similar responsibilities to analyse_types.
130     #
131     #      target_code
132     #        Called by the default implementation of allocate_target_temps.
133     #        Should return a C lvalue for assigning to the node. The default
134     #        implementation calls calculate_result_code.
135     #
136     #      check_const
137     #        - Check that this node and its subnodes form a
138     #          legal constant expression. If so, do nothing,
139     #          otherwise call not_const. 
140     #
141     #        The default implementation of check_const 
142     #        assumes that the expression is not constant.
143     #
144     #      check_const_addr
145     #        - Same as check_const, except check that the
146     #          expression is a C lvalue whose address is
147     #          constant. Otherwise, call addr_not_const.
148     #
149     #        The default implementation of calc_const_addr
150     #        assumes that the expression is not a constant 
151     #        lvalue.
152     #
153     #   Code Generation phase
154     #
155     #      generate_evaluation_code
156     #        - Call generate_evaluation_code for sub-expressions.
157     #        - Perform the functions of generate_result_code
158     #          (see below).
159     #        - If result is temporary, call generate_disposal_code
160     #          on all sub-expressions.
161     #
162     #        A default implementation of generate_evaluation_code
163     #        is provided which uses the following abstract methods:
164     #
165     #          generate_result_code
166     #            - Generate any C statements necessary to calculate
167     #              the result of this node from the results of its
168     #              sub-expressions.
169     #
170     #          calculate_result_code
171     #            - Should return a C code fragment evaluating to the 
172     #              result. This is only called when the result is not 
173     #              a temporary.
174     #
175     #      generate_assignment_code
176     #        Called on the LHS of an assignment.
177     #        - Call generate_evaluation_code for sub-expressions.
178     #        - Generate code to perform the assignment.
179     #        - If the assignment absorbed a reference, call
180     #          generate_post_assignment_code on the RHS,
181     #          otherwise call generate_disposal_code on it.
182     #
183     #      generate_deletion_code
184     #        Called on an argument of a del statement.
185     #        - Call generate_evaluation_code for sub-expressions.
186     #        - Generate code to perform the deletion.
187     #        - Call generate_disposal_code on all sub-expressions.
188     #
189     #
190     
191     is_sequence_constructor = 0
192     is_attribute = 0
193     
194     saved_subexpr_nodes = None
195     is_temp = 0
196     is_target = 0
197     is_starred = 0
198
199     constant_result = constant_value_not_set
200
201     try:
202         _get_child_attrs = operator.attrgetter('subexprs')
203     except AttributeError:
204         # Python 2.3
205         def _get_child_attrs(self):
206             return self.subexprs
207     child_attrs = property(fget=_get_child_attrs)
208         
209     def not_implemented(self, method_name):
210         print_call_chain(method_name, "not implemented") ###
211         raise InternalError(
212             "%s.%s not implemented" %
213                 (self.__class__.__name__, method_name))
214                 
215     def is_lvalue(self):
216         return 0
217     
218     def is_ephemeral(self):
219         #  An ephemeral node is one whose result is in
220         #  a Python temporary and we suspect there are no
221         #  other references to it. Certain operations are
222         #  disallowed on such values, since they are
223         #  likely to result in a dangling pointer.
224         return self.type.is_pyobject and self.is_temp
225
226     def subexpr_nodes(self):
227         #  Extract a list of subexpression nodes based
228         #  on the contents of the subexprs class attribute.
229         nodes = []
230         for name in self.subexprs:
231             item = getattr(self, name)
232             if item is not None:
233                 if type(item) is list:
234                     nodes.extend(item)
235                 else:
236                     nodes.append(item)
237         return nodes
238         
239     def result(self):
240         if self.is_temp:
241             return self.temp_code
242         else:
243             return self.calculate_result_code()
244     
245     def result_as(self, type = None):
246         #  Return the result code cast to the specified C type.
247         return typecast(type, self.ctype(), self.result())
248     
249     def py_result(self):
250         #  Return the result code cast to PyObject *.
251         return self.result_as(py_object_type)
252     
253     def ctype(self):
254         #  Return the native C type of the result (i.e. the
255         #  C type of the result_code expression).
256         return self.result_ctype or self.type
257
258     def get_constant_c_result_code(self):
259         # Return the constant value of this node as a result code
260         # string, or None if the node is not constant.  This method
261         # can be called when the constant result code is required
262         # before the code generation phase.
263         #
264         # The return value is a string that can represent a simple C
265         # value, a constant C name or a constant C expression.  If the
266         # node type depends on Python code, this must return None.
267         return None
268
269     def calculate_constant_result(self):
270         # Calculate the constant compile time result value of this
271         # expression and store it in ``self.constant_result``.  Does
272         # nothing by default, thus leaving ``self.constant_result``
273         # unknown.  If valid, the result can be an arbitrary Python
274         # value.
275         #
276         # This must only be called when it is assured that all
277         # sub-expressions have a valid constant_result value.  The
278         # ConstantFolding transform will do this.
279         pass
280
281     def has_constant_result(self):
282         return self.constant_result is not constant_value_not_set and \
283                self.constant_result is not not_a_constant
284
285     def compile_time_value(self, denv):
286         #  Return value of compile-time expression, or report error.
287         error(self.pos, "Invalid compile-time expression")
288     
289     def compile_time_value_error(self, e):
290         error(self.pos, "Error in compile-time expression: %s: %s" % (
291             e.__class__.__name__, e))
292     
293     # ------------- Declaration Analysis ----------------
294     
295     def analyse_target_declaration(self, env):
296         error(self.pos, "Cannot assign to or delete this")
297     
298     # ------------- Expression Analysis ----------------
299     
300     def analyse_const_expression(self, env):
301         #  Called during the analyse_declarations phase of a
302         #  constant expression. Analyses the expression's type,
303         #  checks whether it is a legal const expression,
304         #  and determines its value.
305         self.analyse_types(env)
306         return self.check_const()
307     
308     def analyse_expressions(self, env):
309         #  Convenience routine performing both the Type
310         #  Analysis and Temp Allocation phases for a whole 
311         #  expression.
312         self.analyse_types(env)
313     
314     def analyse_target_expression(self, env, rhs):
315         #  Convenience routine performing both the Type
316         #  Analysis and Temp Allocation phases for the LHS of
317         #  an assignment.
318         self.analyse_target_types(env)
319     
320     def analyse_boolean_expression(self, env):
321         #  Analyse expression and coerce to a boolean.
322         self.analyse_types(env)
323         bool = self.coerce_to_boolean(env)
324         return bool
325     
326     def analyse_temp_boolean_expression(self, env):
327         #  Analyse boolean expression and coerce result into
328         #  a temporary. This is used when a branch is to be
329         #  performed on the result and we won't have an
330         #  opportunity to ensure disposal code is executed
331         #  afterwards. By forcing the result into a temporary,
332         #  we ensure that all disposal has been done by the
333         #  time we get the result.
334         self.analyse_types(env)
335         return self.coerce_to_boolean(env).coerce_to_simple(env)
336
337     # --------------- Type Inference -----------------
338     
339     def type_dependencies(self, env):
340         # Returns the list of entries whose types must be determined
341         # before the type of self can be infered.
342         if hasattr(self, 'type') and self.type is not None:
343             return ()
344         return sum([node.type_dependencies(env) for node in self.subexpr_nodes()], ())
345     
346     def infer_type(self, env):
347         # Attempt to deduce the type of self. 
348         # Differs from analyse_types as it avoids unnecessary 
349         # analysis of subexpressions, but can assume everything
350         # in self.type_dependencies() has been resolved.
351         if hasattr(self, 'type') and self.type is not None:
352             return self.type
353         elif hasattr(self, 'entry') and self.entry is not None:
354             return self.entry.type
355         else:
356             self.not_implemented("infer_type")
357     
358     # --------------- Type Analysis ------------------
359     
360     def analyse_as_module(self, env):
361         # If this node can be interpreted as a reference to a
362         # cimported module, return its scope, else None.
363         return None
364         
365     def analyse_as_type(self, env):
366         # If this node can be interpreted as a reference to a
367         # type, return that type, else None.
368         return None
369     
370     def analyse_as_extension_type(self, env):
371         # If this node can be interpreted as a reference to an
372         # extension type, return its type, else None.
373         return None
374     
375     def analyse_types(self, env):
376         self.not_implemented("analyse_types")
377     
378     def analyse_target_types(self, env):
379         self.analyse_types(env)
380
381     def nogil_check(self, env):
382         # By default, any expression based on Python objects is
383         # prevented in nogil environments.  Subtypes must override
384         # this if they can work without the GIL.
385         if self.type.is_pyobject:
386             self.gil_error()
387
388     def gil_assignment_check(self, env):
389         if env.nogil and self.type.is_pyobject:
390             error(self.pos, "Assignment of Python object not allowed without gil")
391
392     def check_const(self):
393         self.not_const()
394         return False
395     
396     def not_const(self):
397         error(self.pos, "Not allowed in a constant expression")
398     
399     def check_const_addr(self):
400         self.addr_not_const()
401         return False
402     
403     def addr_not_const(self):
404         error(self.pos, "Address is not constant")
405
406     # ----------------- Result Allocation -----------------
407     
408     def result_in_temp(self):
409         #  Return true if result is in a temporary owned by
410         #  this node or one of its subexpressions. Overridden
411         #  by certain nodes which can share the result of
412         #  a subnode.
413         return self.is_temp
414             
415     def target_code(self):
416         #  Return code fragment for use as LHS of a C assignment.
417         return self.calculate_result_code()
418     
419     def calculate_result_code(self):
420         self.not_implemented("calculate_result_code")
421     
422 #    def release_target_temp(self, env):
423 #        #  Release temporaries used by LHS of an assignment.
424 #        self.release_subexpr_temps(env)
425
426     def allocate_temp_result(self, code):
427         if self.temp_code:
428             raise RuntimeError("Temp allocated multiple times in %r: %r" % (self.__class__.__name__, self.pos))
429         type = self.type
430         if not type.is_void:
431             if type.is_pyobject:
432                 type = PyrexTypes.py_object_type
433             self.temp_code = code.funcstate.allocate_temp(
434                 type, manage_ref=self.use_managed_ref)
435         else:
436             self.temp_code = None
437
438     def release_temp_result(self, code):
439         if not self.temp_code:
440             if self.old_temp:
441                 raise RuntimeError("temp %s released multiple times in %s" % (
442                         self.old_temp, self.__class__.__name__))
443             else:
444                 raise RuntimeError("no temp, but release requested in %s" % (
445                         self.__class__.__name__))
446         code.funcstate.release_temp(self.temp_code)
447         self.old_temp = self.temp_code
448         self.temp_code = None
449
450     # ---------------- Code Generation -----------------
451     
452     def make_owned_reference(self, code):
453         #  If result is a pyobject, make sure we own
454         #  a reference to it.
455         if self.type.is_pyobject and not self.result_in_temp():
456             code.put_incref(self.result(), self.ctype())
457     
458     def generate_evaluation_code(self, code):
459         code.mark_pos(self.pos)
460         
461         #  Generate code to evaluate this node and
462         #  its sub-expressions, and dispose of any
463         #  temporary results of its sub-expressions.
464         self.generate_subexpr_evaluation_code(code)
465
466         if self.is_temp:
467             self.allocate_temp_result(code)
468
469         self.generate_result_code(code)
470         if self.is_temp:
471             # If we are temp we do not need to wait until this node is disposed
472             # before disposing children.
473             self.generate_subexpr_disposal_code(code)
474             self.free_subexpr_temps(code)
475
476     def generate_subexpr_evaluation_code(self, code):
477         for node in self.subexpr_nodes():
478             node.generate_evaluation_code(code)
479     
480     def generate_result_code(self, code):
481         self.not_implemented("generate_result_code")
482     
483     def generate_disposal_code(self, code):
484         if self.is_temp:
485             if self.type.is_pyobject:
486                 code.put_decref_clear(self.result(), self.ctype())
487         else:
488             # Already done if self.is_temp
489             self.generate_subexpr_disposal_code(code)
490
491     def generate_subexpr_disposal_code(self, code):
492         #  Generate code to dispose of temporary results
493         #  of all sub-expressions.
494         for node in self.subexpr_nodes():
495             node.generate_disposal_code(code)
496     
497     def generate_post_assignment_code(self, code):
498         if self.is_temp:
499             if self.type.is_pyobject:
500                 code.putln("%s = 0;" % self.result())
501         else:
502             self.generate_subexpr_disposal_code(code)
503
504     def generate_assignment_code(self, rhs, code):
505         #  Stub method for nodes which are not legal as
506         #  the LHS of an assignment. An error will have 
507         #  been reported earlier.
508         pass
509     
510     def generate_deletion_code(self, code):
511         #  Stub method for nodes that are not legal as
512         #  the argument of a del statement. An error
513         #  will have been reported earlier.
514         pass
515
516     def free_temps(self, code):
517         if self.is_temp:
518             if not self.type.is_void:
519                 self.release_temp_result(code)
520         else:
521             self.free_subexpr_temps(code)
522     
523     def free_subexpr_temps(self, code):
524         for sub in self.subexpr_nodes():
525             sub.free_temps(code)
526
527     def generate_function_definitions(self, env, code):
528         pass
529
530     # ---------------- Annotation ---------------------
531     
532     def annotate(self, code):
533         for node in self.subexpr_nodes():
534             node.annotate(code)
535     
536     # ----------------- Coercion ----------------------
537     
538     def coerce_to(self, dst_type, env):
539         #   Coerce the result so that it can be assigned to
540         #   something of type dst_type. If processing is necessary,
541         #   wraps this node in a coercion node and returns that.
542         #   Otherwise, returns this node unchanged.
543         #
544         #   This method is called during the analyse_expressions
545         #   phase of the src_node's processing.
546         #
547         #   Note that subclasses that override this (especially
548         #   ConstNodes) must not (re-)set their own .type attribute
549         #   here.  Since expression nodes may turn up in different
550         #   places in the tree (e.g. inside of CloneNodes in cascaded
551         #   assignments), this method must return a new node instance
552         #   if it changes the type.
553         #
554         src = self
555         src_type = self.type
556         src_is_py_type = src_type.is_pyobject
557         dst_is_py_type = dst_type.is_pyobject
558
559         if self.check_for_coercion_error(dst_type):
560             return self
561
562         if dst_type.is_reference:
563             dst_type = dst_type.ref_base_type
564         
565         if dst_type.is_pyobject:
566             if not src.type.is_pyobject:
567                 if dst_type is bytes_type and src.type.is_int:
568                     src = CoerceIntToBytesNode(src, env)
569                 else:
570                     src = CoerceToPyTypeNode(src, env)
571             if not src.type.subtype_of(dst_type):
572                 if not isinstance(src, NoneNode):
573                     src = PyTypeTestNode(src, dst_type, env)
574         elif src.type.is_pyobject:
575             src = CoerceFromPyTypeNode(dst_type, src, env)
576         elif (dst_type.is_complex 
577               and src_type != dst_type
578               and dst_type.assignable_from(src_type)):
579             src = CoerceToComplexNode(src, dst_type, env)
580         else: # neither src nor dst are py types
581             # Added the string comparison, since for c types that
582             # is enough, but Cython gets confused when the types are
583             # in different pxi files.
584             if not (str(src.type) == str(dst_type) or dst_type.assignable_from(src_type)):
585                 self.fail_assignment(dst_type)
586         return src
587
588     def fail_assignment(self, dst_type):
589         error(self.pos, "Cannot assign type '%s' to '%s'" % (self.type, dst_type))
590
591     def check_for_coercion_error(self, dst_type, fail=False, default=None):
592         if fail and not default:
593             default = "Cannot assign type '%(FROM)s' to '%(TO)s'"
594         message = find_coercion_error((self.type, dst_type), default)
595         if message is not None:
596             error(self.pos, message % {'FROM': self.type, 'TO': dst_type})
597             return True
598         if fail:
599             self.fail_assignment(dst_type)
600             return True
601         return False
602
603     def coerce_to_pyobject(self, env):
604         return self.coerce_to(PyrexTypes.py_object_type, env)
605
606     def coerce_to_boolean(self, env):
607         #  Coerce result to something acceptable as
608         #  a boolean value.
609
610         # if it's constant, calculate the result now
611         if self.has_constant_result():
612             bool_value = bool(self.constant_result)
613             return BoolNode(self.pos, value=bool_value,
614                             constant_result=bool_value)
615
616         type = self.type
617         if type.is_pyobject or type.is_ptr or type.is_float:
618             return CoerceToBooleanNode(self, env)
619         else:
620             if not (type.is_int or type.is_enum or type.is_error):
621                 error(self.pos, 
622                     "Type '%s' not acceptable as a boolean" % type)
623             return self
624     
625     def coerce_to_integer(self, env):
626         # If not already some C integer type, coerce to longint.
627         if self.type.is_int:
628             return self
629         else:
630             return self.coerce_to(PyrexTypes.c_long_type, env)
631     
632     def coerce_to_temp(self, env):
633         #  Ensure that the result is in a temporary.
634         if self.result_in_temp():
635             return self
636         else:
637             return CoerceToTempNode(self, env)
638     
639     def coerce_to_simple(self, env):
640         #  Ensure that the result is simple (see is_simple).
641         if self.is_simple():
642             return self
643         else:
644             return self.coerce_to_temp(env)
645     
646     def is_simple(self):
647         #  A node is simple if its result is something that can
648         #  be referred to without performing any operations, e.g.
649         #  a constant, local var, C global var, struct member
650         #  reference, or temporary.
651         return self.result_in_temp()
652
653     def may_be_none(self):
654         if not self.type.is_pyobject:
655             return False
656         if self.constant_result not in (not_a_constant, constant_value_not_set):
657             return self.constant_result is not None
658         return True
659
660     def as_cython_attribute(self):
661         return None
662
663     def as_none_safe_node(self, message, error="PyExc_TypeError"):
664         # Wraps the node in a NoneCheckNode if it is not known to be
665         # not-None (e.g. because it is a Python literal).
666         if self.may_be_none():
667             return NoneCheckNode(self, error, message)
668         else:
669             return self
670
671
672 class AtomicExprNode(ExprNode):
673     #  Abstract base class for expression nodes which have
674     #  no sub-expressions.
675     
676     subexprs = []
677
678     # Override to optimize -- we know we have no children
679     def generate_subexpr_evaluation_code(self, code):
680         pass
681     def generate_subexpr_disposal_code(self, code):
682         pass
683
684 class PyConstNode(AtomicExprNode):
685     #  Abstract base class for constant Python values.
686     
687     is_literal = 1
688     type = py_object_type
689     
690     def is_simple(self):
691         return 1
692
693     def may_be_none(self):
694         return False
695
696     def analyse_types(self, env):
697         pass
698     
699     def calculate_result_code(self):
700         return self.value
701
702     def generate_result_code(self, code):
703         pass
704
705
706 class NoneNode(PyConstNode):
707     #  The constant value None
708     
709     value = "Py_None"
710
711     constant_result = None
712     
713     nogil_check = None
714
715     def compile_time_value(self, denv):
716         return None
717
718     def may_be_none(self):
719         return True
720
721
722 class EllipsisNode(PyConstNode):
723     #  '...' in a subscript list.
724     
725     value = "Py_Ellipsis"
726
727     constant_result = Ellipsis
728
729     def compile_time_value(self, denv):
730         return Ellipsis
731
732
733 class ConstNode(AtomicExprNode):
734     # Abstract base type for literal constant nodes.
735     #
736     # value     string      C code fragment
737     
738     is_literal = 1
739     nogil_check = None
740
741     def is_simple(self):
742         return 1
743
744     def may_be_none(self):
745         return False
746
747     def analyse_types(self, env):
748         pass # Types are held in class variables
749     
750     def check_const(self):
751         return True
752     
753     def get_constant_c_result_code(self):
754         return self.calculate_result_code()
755
756     def calculate_result_code(self):
757         return str(self.value)
758
759     def generate_result_code(self, code):
760         pass
761
762
763 class BoolNode(ConstNode):
764     type = PyrexTypes.c_bint_type
765     #  The constant value True or False
766
767     def calculate_constant_result(self):
768         self.constant_result = self.value
769
770     def compile_time_value(self, denv):
771         return self.value
772     
773     def calculate_result_code(self):
774         return str(int(self.value))
775
776
777 class NullNode(ConstNode):
778     type = PyrexTypes.c_null_ptr_type
779     value = "NULL"
780     constant_result = 0
781
782     def get_constant_c_result_code(self):
783         return self.value
784
785
786 class CharNode(ConstNode):
787     type = PyrexTypes.c_char_type
788
789     def calculate_constant_result(self):
790         self.constant_result = ord(self.value)
791     
792     def compile_time_value(self, denv):
793         return ord(self.value)
794     
795     def calculate_result_code(self):
796         return "'%s'" % StringEncoding.escape_char(self.value)
797
798
799 class IntNode(ConstNode):
800
801     # unsigned     "" or "U"
802     # longness     "" or "L" or "LL"
803
804     unsigned = ""
805     longness = ""
806
807     def __init__(self, pos, **kwds):
808         ExprNode.__init__(self, pos, **kwds)
809         if 'type' not in kwds:
810             rank = max(1, len(self.longness))
811             sign = not self.unsigned
812             self.type = PyrexTypes.modifiers_and_name_to_type[sign, rank, "int"]
813
814     def coerce_to(self, dst_type, env):
815         if self.type is dst_type:
816             return self
817         elif dst_type.is_float:
818             float_value = float(self.value)
819             return FloatNode(self.pos, value=repr(float_value), constant_result=float_value)
820         node = IntNode(self.pos, value=self.value, constant_result=self.constant_result,
821                        unsigned=self.unsigned, longness=self.longness)
822         if dst_type.is_numeric and not dst_type.is_complex:
823             return node
824         if dst_type.is_pyobject:
825             node.type = PyrexTypes.py_object_type
826         # We still need to perform normal coerce_to processing on the
827         # result, because we might be coercing to an extension type,
828         # in which case a type test node will be needed.
829         return ConstNode.coerce_to(node, dst_type, env)
830
831     def coerce_to_boolean(self, env):
832         return IntNode(
833             self.pos, value=self.value,
834             type = PyrexTypes.c_bint_type,
835             unsigned=self.unsigned, longness=self.longness)
836
837     def generate_evaluation_code(self, code):
838         if self.type.is_pyobject:
839             # pre-allocate a Python version of the number
840             plain_integer_string = self.value_as_c_integer_string(plain_digits=True)
841             self.result_code = code.get_py_num(plain_integer_string, self.longness)
842         else:
843             self.result_code = self.get_constant_c_result_code()
844     
845     def get_constant_c_result_code(self):
846         return self.value_as_c_integer_string() + self.unsigned + self.longness
847
848     def value_as_c_integer_string(self, plain_digits=False):
849         value = self.value
850         if isinstance(value, basestring) and len(value) > 2:
851             # must convert C-incompatible Py3 oct/bin notations
852             if value[1] in 'oO':
853                 if plain_digits:
854                     value = int(value[2:], 8)
855                 else:
856                     value = value[0] + value[2:] # '0o123' => '0123'
857             elif value[1] in 'bB':
858                 value = int(value[2:], 2)
859             elif plain_digits and value[1] in 'xX':
860                 value = int(value[2:], 16)
861         return str(value)
862
863     def calculate_result_code(self):
864         return self.result_code
865
866     def calculate_constant_result(self):
867         self.constant_result = Utils.str_to_number(self.value)
868
869     def compile_time_value(self, denv):
870         return Utils.str_to_number(self.value)
871
872
873 class FloatNode(ConstNode):
874     type = PyrexTypes.c_double_type
875
876     def calculate_constant_result(self):
877         self.constant_result = float(self.value)
878
879     def compile_time_value(self, denv):
880         return float(self.value)
881     
882     def calculate_result_code(self):
883         strval = self.value
884         assert isinstance(strval, (str, unicode))
885         cmpval = repr(float(strval))
886         if cmpval == 'nan':
887             return "(Py_HUGE_VAL * 0)"
888         elif cmpval == 'inf':
889             return "Py_HUGE_VAL"
890         elif cmpval == '-inf':
891             return "(-Py_HUGE_VAL)"
892         else:
893             return strval
894
895
896 class BytesNode(ConstNode):
897     # A char* or bytes literal
898     #
899     # value      BytesLiteral
900
901     type = PyrexTypes.c_char_ptr_type
902
903     def compile_time_value(self, denv):
904         return self.value
905
906     def analyse_as_type(self, env):
907         type = PyrexTypes.parse_basic_type(self.value)
908         if type is not None:    
909             return type
910         from TreeFragment import TreeFragment
911         pos = (self.pos[0], self.pos[1], self.pos[2]-7)
912         declaration = TreeFragment(u"sizeof(%s)" % self.value, name=pos[0].filename, initial_pos=pos)
913         sizeof_node = declaration.root.stats[0].expr
914         sizeof_node.analyse_types(env)
915         if isinstance(sizeof_node, SizeofTypeNode):
916             return sizeof_node.arg_type
917
918     def can_coerce_to_char_literal(self):
919         return len(self.value) == 1
920
921     def coerce_to_boolean(self, env):
922         # This is special because we start off as a C char*.  Testing
923         # that for truth directly would yield the wrong result.
924         return BoolNode(self.pos, value=bool(self.value))
925
926     def coerce_to(self, dst_type, env):
927         if dst_type.is_int:
928             if not self.can_coerce_to_char_literal():
929                 error(self.pos, "Only single-character string literals can be coerced into ints.")
930                 return self
931             if dst_type is PyrexTypes.c_py_unicode_type:
932                 error(self.pos, "Bytes literals cannot coerce to Py_UNICODE, use a unicode literal instead.")
933                 return self
934             return CharNode(self.pos, value=self.value)
935
936         node = BytesNode(self.pos, value=self.value)
937         if dst_type == PyrexTypes.c_char_ptr_type:
938             node.type = PyrexTypes.c_char_ptr_type
939             return node
940         elif dst_type == PyrexTypes.c_uchar_ptr_type:
941             node.type = PyrexTypes.c_char_ptr_type
942             return CastNode(node, PyrexTypes.c_uchar_ptr_type)
943
944         if not self.type.is_pyobject:
945             if dst_type in (py_object_type, Builtin.bytes_type):
946                 node.type = Builtin.bytes_type
947             elif dst_type.is_pyobject:
948                 self.fail_assignment(dst_type)
949                 return self
950         elif dst_type.is_pyobject and dst_type is not py_object_type:
951             self.check_for_coercion_error(dst_type, fail=True)
952             return node
953
954         # We still need to perform normal coerce_to processing on the
955         # result, because we might be coercing to an extension type,
956         # in which case a type test node will be needed.
957         return ConstNode.coerce_to(node, dst_type, env)
958
959     def as_py_string_node(self, env):
960         # Return a new BytesNode with the same value as this node
961         # but whose type is a Python type instead of a C type.
962         return BytesNode(self.pos, value = self.value, type = Builtin.bytes_type)
963
964     def generate_evaluation_code(self, code):
965         if self.type.is_pyobject:
966             self.result_code = code.get_py_string_const(self.value)
967         else:
968             self.result_code = code.get_string_const(self.value)
969
970     def get_constant_c_result_code(self):
971         return None # FIXME
972     
973     def calculate_result_code(self):
974         return self.result_code
975
976
977 class UnicodeNode(PyConstNode):
978     # A Python unicode object
979     #
980     # value        EncodedString
981     # bytes_value  BytesLiteral    the literal parsed as bytes string ('-3' unicode literals only)
982
983     bytes_value = None
984     type = unicode_type
985
986     def coerce_to(self, dst_type, env):
987         if dst_type is self.type:
988             pass
989         elif dst_type is PyrexTypes.c_py_unicode_type:
990             if not self.can_coerce_to_char_literal():
991                 error(self.pos, "Only single-character Unicode string literals can be coerced into Py_UNICODE.")
992                 return self
993             int_value = ord(self.value)
994             return IntNode(self.pos, value=int_value, constant_result=int_value)
995         elif not dst_type.is_pyobject:
996             if dst_type.is_string and self.bytes_value is not None:
997                 # special case: '-3' enforced unicode literal used in a C char* context
998                 return BytesNode(self.pos, value=self.bytes_value).coerce_to(dst_type, env)
999             error(self.pos, "Unicode literals do not support coercion to C types other than Py_UNICODE.")
1000         elif dst_type is not py_object_type:
1001             if not self.check_for_coercion_error(dst_type):
1002                 self.fail_assignment(dst_type)
1003         return self
1004
1005     def can_coerce_to_char_literal(self):
1006         return len(self.value) == 1
1007
1008     def contains_surrogates(self):
1009         # Check if the unicode string contains surrogate code points
1010         # on a CPython platform with wide (UCS-4) or narrow (UTF-16)
1011         # Unicode, i.e. characters that would be spelled as two
1012         # separate code units on a narrow platform.
1013         for c in map(ord, self.value):
1014             if c > 65535: # can only happen on wide platforms
1015                 return True
1016             # We only look for the first code unit (D800-DBFF) of a
1017             # surrogate pair - if we find one, the other one
1018             # (DC00-DFFF) is likely there, too.  If we don't find it,
1019             # any second code unit cannot make for a surrogate pair by
1020             # itself.
1021             if c >= 0xD800 and c <= 0xDBFF:
1022                 return True
1023         return False
1024
1025     def generate_evaluation_code(self, code):
1026         self.result_code = code.get_py_string_const(self.value)
1027
1028     def calculate_result_code(self):
1029         return self.result_code
1030         
1031     def compile_time_value(self, env):
1032         return self.value
1033
1034
1035 class StringNode(PyConstNode):
1036     # A Python str object, i.e. a byte string in Python 2.x and a
1037     # unicode string in Python 3.x
1038     #
1039     # value          BytesLiteral
1040     # unicode_value  EncodedString
1041     # is_identifier  boolean
1042
1043     type = str_type
1044     is_identifier = None
1045     unicode_value = None
1046
1047     def coerce_to(self, dst_type, env):
1048         if dst_type is not py_object_type and not str_type.subtype_of(dst_type):
1049 #            if dst_type is Builtin.bytes_type:
1050 #                # special case: bytes = 'str literal'
1051 #                return BytesNode(self.pos, value=self.value)
1052             if not dst_type.is_pyobject:
1053                 return BytesNode(self.pos, value=self.value).coerce_to(dst_type, env)
1054             self.check_for_coercion_error(dst_type, fail=True)
1055
1056         # this will be a unicode string in Py3, so make sure we can decode it
1057         if self.value.encoding:
1058             encoding = self.value.encoding
1059             try:
1060                 self.value.decode(encoding)
1061             except UnicodeDecodeError:
1062                 error(self.pos, "String decoding as '%s' failed. Consider using a byte string or unicode string explicitly, or adjust the source code encoding." % encoding)
1063
1064         return self
1065
1066     def can_coerce_to_char_literal(self):
1067         return not self.is_identifier and len(self.value) == 1
1068
1069     def generate_evaluation_code(self, code):
1070         self.result_code = code.get_py_string_const(
1071             self.value, identifier=self.is_identifier, is_str=True)
1072
1073     def get_constant_c_result_code(self):
1074         return None
1075
1076     def calculate_result_code(self):
1077         return self.result_code
1078         
1079     def compile_time_value(self, env):
1080         return self.value
1081
1082
1083 class IdentifierStringNode(StringNode):
1084     # A special str value that represents an identifier (bytes in Py2,
1085     # unicode in Py3).
1086     is_identifier = True
1087
1088
1089 class LongNode(AtomicExprNode):
1090     #  Python long integer literal
1091     #
1092     #  value   string
1093
1094     type = py_object_type
1095
1096     def calculate_constant_result(self):
1097         self.constant_result = Utils.str_to_number(self.value)
1098     
1099     def compile_time_value(self, denv):
1100         return Utils.str_to_number(self.value)
1101     
1102     def analyse_types(self, env):
1103         self.is_temp = 1
1104
1105     def may_be_none(self):
1106         return False
1107
1108     gil_message = "Constructing Python long int"
1109
1110     def generate_result_code(self, code):
1111         code.putln(
1112             '%s = PyLong_FromString((char *)"%s", 0, 0); %s' % (
1113                 self.result(),
1114                 self.value,
1115                 code.error_goto_if_null(self.result(), self.pos)))
1116         code.put_gotref(self.py_result())
1117
1118
1119 class ImagNode(AtomicExprNode):
1120     #  Imaginary number literal
1121     #
1122     #  value   float    imaginary part
1123     
1124     type = PyrexTypes.c_double_complex_type
1125
1126     def calculate_constant_result(self):
1127         self.constant_result = complex(0.0, self.value)
1128     
1129     def compile_time_value(self, denv):
1130         return complex(0.0, self.value)
1131     
1132     def analyse_types(self, env):
1133         self.type.create_declaration_utility_code(env)
1134
1135     def may_be_none(self):
1136         return False
1137
1138     def coerce_to(self, dst_type, env):
1139         if self.type is dst_type:
1140             return self
1141         node = ImagNode(self.pos, value=self.value)
1142         if dst_type.is_pyobject:
1143             node.is_temp = 1
1144             node.type = PyrexTypes.py_object_type
1145         # We still need to perform normal coerce_to processing on the
1146         # result, because we might be coercing to an extension type,
1147         # in which case a type test node will be needed.
1148         return AtomicExprNode.coerce_to(node, dst_type, env)
1149
1150     gil_message = "Constructing complex number"
1151
1152     def calculate_result_code(self):
1153         if self.type.is_pyobject:
1154             return self.result()
1155         else:
1156             return "%s(0, %r)" % (self.type.from_parts, float(self.value))
1157
1158     def generate_result_code(self, code):
1159         if self.type.is_pyobject:
1160             code.putln(
1161                 "%s = PyComplex_FromDoubles(0.0, %r); %s" % (
1162                     self.result(),
1163                     float(self.value),
1164                     code.error_goto_if_null(self.result(), self.pos)))
1165             code.put_gotref(self.py_result())
1166         
1167
1168 class NewExprNode(AtomicExprNode):
1169
1170     # C++ new statement
1171     #
1172     # cppclass              node                 c++ class to create
1173     
1174     type = None
1175     
1176     def infer_type(self, env):
1177         type = self.cppclass.analyse_as_type(env)
1178         if type is None or not type.is_cpp_class:
1179             error(self.pos, "new operator can only be applied to a C++ class")
1180             self.type = error_type
1181             return
1182         self.cpp_check(env)
1183         constructor = type.scope.lookup(u'<init>')
1184         if constructor is None:
1185             return_type = PyrexTypes.CFuncType(type, [])
1186             return_type = PyrexTypes.CPtrType(return_type)
1187             type.scope.declare_cfunction(u'<init>', return_type, self.pos)
1188             constructor = type.scope.lookup(u'<init>')
1189         self.class_type = type
1190         self.entry = constructor
1191         self.type = constructor.type
1192         return self.type
1193     
1194     def analyse_types(self, env):
1195         if self.type is None:
1196             self.infer_type(env)
1197
1198     def may_be_none(self):
1199         return False
1200
1201     def generate_result_code(self, code):
1202         pass
1203    
1204     def calculate_result_code(self):
1205         return "new " + self.class_type.declaration_code("")
1206
1207
1208 class NameNode(AtomicExprNode):
1209     #  Reference to a local or global variable name.
1210     #
1211     #  name            string    Python name of the variable
1212     #  entry           Entry     Symbol table entry
1213     #  type_entry      Entry     For extension type names, the original type entry
1214     
1215     is_name = True
1216     is_cython_module = False
1217     cython_attribute = None
1218     lhs_of_first_assignment = False
1219     is_used_as_rvalue = 0
1220     entry = None
1221     type_entry = None
1222
1223     def create_analysed_rvalue(pos, env, entry):
1224         node = NameNode(pos)
1225         node.analyse_types(env, entry=entry)
1226         return node
1227         
1228     def as_cython_attribute(self):
1229         return self.cython_attribute
1230     
1231     create_analysed_rvalue = staticmethod(create_analysed_rvalue)
1232     
1233     def type_dependencies(self, env):
1234         if self.entry is None:
1235             self.entry = env.lookup(self.name)
1236         if self.entry is not None and self.entry.type.is_unspecified:
1237             return (self.entry,)
1238         else:
1239             return ()
1240     
1241     def infer_type(self, env):
1242         if self.entry is None:
1243             self.entry = env.lookup(self.name)
1244         if self.entry is None:
1245             return py_object_type
1246         elif (self.entry.type.is_extension_type or self.entry.type.is_builtin_type) and \
1247                 self.name == self.entry.type.name:
1248             # Unfortunately the type attribute of type objects
1249             # is used for the pointer to the type they represent.
1250             return type_type
1251         else:
1252             return self.entry.type
1253     
1254     def compile_time_value(self, denv):
1255         try:
1256             return denv.lookup(self.name)
1257         except KeyError:
1258             error(self.pos, "Compile-time name '%s' not defined" % self.name)
1259
1260     def get_constant_c_result_code(self):
1261         if not self.entry or self.entry.type.is_pyobject:
1262             return None
1263         return self.entry.cname
1264     
1265     def coerce_to(self, dst_type, env):
1266         #  If coercing to a generic pyobject and this is a builtin
1267         #  C function with a Python equivalent, manufacture a NameNode
1268         #  referring to the Python builtin.
1269         #print "NameNode.coerce_to:", self.name, dst_type ###
1270         if dst_type is py_object_type:
1271             entry = self.entry
1272             if entry and entry.is_cfunction:
1273                 var_entry = entry.as_variable
1274                 if var_entry:
1275                     if var_entry.is_builtin and Options.cache_builtins:
1276                         var_entry = env.declare_builtin(var_entry.name, self.pos)
1277                     node = NameNode(self.pos, name = self.name)
1278                     node.entry = var_entry
1279                     node.analyse_rvalue_entry(env)
1280                     return node
1281         return super(NameNode, self).coerce_to(dst_type, env)
1282     
1283     def analyse_as_module(self, env):
1284         # Try to interpret this as a reference to a cimported module.
1285         # Returns the module scope, or None.
1286         entry = self.entry
1287         if not entry:
1288             entry = env.lookup(self.name)
1289         if entry and entry.as_module:
1290             return entry.as_module
1291         return None
1292         
1293     def analyse_as_type(self, env):
1294         if self.cython_attribute:
1295             type = PyrexTypes.parse_basic_type(self.cython_attribute)
1296         else:
1297             type = PyrexTypes.parse_basic_type(self.name)
1298         if type:
1299             return type
1300         entry = self.entry
1301         if not entry:
1302             entry = env.lookup(self.name)
1303         if entry and entry.is_type:
1304             return entry.type
1305         else:
1306             return None
1307     
1308     def analyse_as_extension_type(self, env):
1309         # Try to interpret this as a reference to an extension type.
1310         # Returns the extension type, or None.
1311         entry = self.entry
1312         if not entry:
1313             entry = env.lookup(self.name)
1314         if entry and entry.is_type and entry.type.is_extension_type:
1315             return entry.type
1316         else:
1317             return None
1318     
1319     def analyse_target_declaration(self, env):
1320         if not self.entry:
1321             self.entry = env.lookup_here(self.name)
1322         if not self.entry:
1323             if env.directives['warn.undeclared']:
1324                 warning(self.pos, "implicit declaration of '%s'" % self.name, 1)
1325             if env.directives['infer_types'] != False:
1326                 type = unspecified_type
1327             else:
1328                 type = py_object_type
1329             self.entry = env.declare_var(self.name, type, self.pos)
1330         env.control_flow.set_state(self.pos, (self.name, 'initialized'), True)
1331         env.control_flow.set_state(self.pos, (self.name, 'source'), 'assignment')
1332         if self.entry.is_declared_generic:
1333             self.result_ctype = py_object_type
1334     
1335     def analyse_types(self, env):
1336         if self.entry is None:
1337             self.entry = env.lookup(self.name)
1338         if not self.entry:
1339             self.entry = env.declare_builtin(self.name, self.pos)
1340         if not self.entry:
1341             self.type = PyrexTypes.error_type
1342             return
1343         entry = self.entry
1344         if entry:
1345             entry.used = 1
1346             if entry.type.is_buffer:
1347                 import Buffer
1348                 Buffer.used_buffer_aux_vars(entry)
1349             if entry.utility_code:
1350                 env.use_utility_code(entry.utility_code)
1351         self.analyse_rvalue_entry(env)
1352         
1353     def analyse_target_types(self, env):
1354         self.analyse_entry(env)
1355         if not self.is_lvalue():
1356             error(self.pos, "Assignment to non-lvalue '%s'"
1357                 % self.name)
1358             self.type = PyrexTypes.error_type
1359         self.entry.used = 1
1360         if self.entry.type.is_buffer:
1361             import Buffer
1362             Buffer.used_buffer_aux_vars(self.entry)
1363                 
1364     def analyse_rvalue_entry(self, env):
1365         #print "NameNode.analyse_rvalue_entry:", self.name ###
1366         #print "Entry:", self.entry.__dict__ ###
1367         self.analyse_entry(env)
1368         entry = self.entry
1369         if entry.is_declared_generic:
1370             self.result_ctype = py_object_type
1371         if entry.is_pyglobal or entry.is_builtin:
1372             if Options.cache_builtins and entry.is_builtin:
1373                 self.is_temp = 0
1374             else:
1375                 self.is_temp = 1
1376                 env.use_utility_code(get_name_interned_utility_code)
1377             self.is_used_as_rvalue = 1
1378
1379     def nogil_check(self, env):
1380         if self.is_used_as_rvalue:
1381             entry = self.entry
1382             if entry.is_builtin:
1383                 # if not Options.cache_builtins: # cached builtins are ok
1384                 self.gil_error()
1385             elif entry.is_pyglobal:
1386                 self.gil_error()
1387
1388     gil_message = "Accessing Python global or builtin"
1389
1390     def analyse_entry(self, env):
1391         #print "NameNode.analyse_entry:", self.name ###
1392         self.check_identifier_kind()
1393         entry = self.entry
1394         type = entry.type
1395         self.type = type
1396
1397     def check_identifier_kind(self):
1398         # Check that this is an appropriate kind of name for use in an
1399         # expression.  Also finds the variable entry associated with
1400         # an extension type.
1401         entry = self.entry
1402         if entry.is_type and entry.type.is_extension_type:
1403             self.type_entry = entry
1404         if not (entry.is_const or entry.is_variable 
1405             or entry.is_builtin or entry.is_cfunction
1406             or entry.is_cpp_class):
1407                 if self.entry.as_variable:
1408                     self.entry = self.entry.as_variable
1409                 else:
1410                     error(self.pos, 
1411                           "'%s' is not a constant, variable or function identifier" % self.name)
1412
1413     def is_simple(self):
1414         #  If it's not a C variable, it'll be in a temp.
1415         return 1
1416     
1417     def calculate_target_results(self, env):
1418         pass
1419     
1420     def check_const(self):
1421         entry = self.entry
1422         if entry is not None and not (entry.is_const or entry.is_cfunction or entry.is_builtin):
1423             self.not_const()
1424             return False
1425         return True
1426     
1427     def check_const_addr(self):
1428         entry = self.entry
1429         if not (entry.is_cglobal or entry.is_cfunction or entry.is_builtin):
1430             self.addr_not_const()
1431             return False
1432         return True
1433
1434     def is_lvalue(self):
1435         return self.entry.is_variable and \
1436             not self.entry.type.is_array and \
1437             not self.entry.is_readonly
1438     
1439     def is_ephemeral(self):
1440         #  Name nodes are never ephemeral, even if the
1441         #  result is in a temporary.
1442         return 0
1443     
1444     def calculate_result_code(self):
1445         entry = self.entry
1446         if not entry:
1447             return "<error>" # There was an error earlier
1448         return entry.cname
1449     
1450     def generate_result_code(self, code):
1451         assert hasattr(self, 'entry')
1452         entry = self.entry
1453         if entry is None:
1454             return # There was an error earlier
1455         if entry.is_builtin and Options.cache_builtins:
1456             return # Lookup already cached
1457         elif entry.is_pyclass_attr:
1458             assert entry.type.is_pyobject, "Python global or builtin not a Python object"
1459             interned_cname = code.intern_identifier(self.entry.name)
1460             if entry.is_builtin:
1461                 namespace = Naming.builtins_cname
1462             else: # entry.is_pyglobal
1463                 namespace = entry.scope.namespace_cname
1464             code.globalstate.use_utility_code(getitem_dict_utility_code)
1465             code.putln(
1466                 '%s = PyObject_GetItem(%s, %s); %s' % (
1467                 self.result(),
1468                 namespace,
1469                 interned_cname,
1470                 code.error_goto_if_null(self.result(), self.pos)))
1471             code.put_gotref(self.py_result())
1472             
1473         elif entry.is_pyglobal or entry.is_builtin:
1474             assert entry.type.is_pyobject, "Python global or builtin not a Python object"
1475             interned_cname = code.intern_identifier(self.entry.name)
1476             if entry.is_builtin:
1477                 namespace = Naming.builtins_cname
1478             else: # entry.is_pyglobal
1479                 namespace = entry.scope.namespace_cname
1480             code.globalstate.use_utility_code(get_name_interned_utility_code)
1481             code.putln(
1482                 '%s = __Pyx_GetName(%s, %s); %s' % (
1483                 self.result(),
1484                 namespace, 
1485                 interned_cname,
1486                 code.error_goto_if_null(self.result(), self.pos)))
1487             code.put_gotref(self.py_result())
1488             
1489         elif entry.is_local and False:
1490             # control flow not good enough yet
1491             assigned = entry.scope.control_flow.get_state((entry.name, 'initialized'), self.pos)
1492             if assigned is False:
1493                 error(self.pos, "local variable '%s' referenced before assignment" % entry.name)
1494             elif not Options.init_local_none and assigned is None:
1495                 code.putln('if (%s == 0) { PyErr_SetString(PyExc_UnboundLocalError, "%s"); %s }' %
1496                            (entry.cname, entry.name, code.error_goto(self.pos)))
1497                 entry.scope.control_flow.set_state(self.pos, (entry.name, 'initialized'), True)
1498
1499     def generate_assignment_code(self, rhs, code):
1500         #print "NameNode.generate_assignment_code:", self.name ###
1501         entry = self.entry
1502         if entry is None:
1503             return # There was an error earlier
1504
1505         if (self.entry.type.is_ptr and isinstance(rhs, ListNode)
1506             and not self.lhs_of_first_assignment):
1507             error(self.pos, "Literal list must be assigned to pointer at time of declaration")
1508         
1509         # is_pyglobal seems to be True for module level-globals only.
1510         # We use this to access class->tp_dict if necessary.
1511         if entry.is_pyglobal:
1512             assert entry.type.is_pyobject, "Python global or builtin not a Python object"
1513             interned_cname = code.intern_identifier(self.entry.name)
1514             namespace = self.entry.scope.namespace_cname
1515             if entry.is_member:
1516                 # if the entry is a member we have to cheat: SetAttr does not work
1517                 # on types, so we create a descriptor which is then added to tp_dict
1518                 code.put_error_if_neg(self.pos,
1519                     'PyDict_SetItem(%s->tp_dict, %s, %s)' % (
1520                         namespace,
1521                         interned_cname,
1522                         rhs.py_result()))
1523                 rhs.generate_disposal_code(code)
1524                 rhs.free_temps(code)
1525                 # in Py2.6+, we need to invalidate the method cache
1526                 code.putln("PyType_Modified(%s);" %
1527                             entry.scope.parent_type.typeptr_cname)
1528             elif entry.is_pyclass_attr:
1529                 code.put_error_if_neg(self.pos,
1530                     'PyObject_SetItem(%s, %s, %s)' % (
1531                         namespace,
1532                         interned_cname,
1533                         rhs.py_result()))
1534                 rhs.generate_disposal_code(code)
1535                 rhs.free_temps(code)
1536             else:
1537                 code.put_error_if_neg(self.pos,
1538                     'PyObject_SetAttr(%s, %s, %s)' % (
1539                         namespace,
1540                         interned_cname,
1541                         rhs.py_result()))
1542                 if debug_disposal_code:
1543                     print("NameNode.generate_assignment_code:")
1544                     print("...generating disposal code for %s" % rhs)
1545                 rhs.generate_disposal_code(code)
1546                 rhs.free_temps(code)
1547         else:
1548             if self.type.is_buffer:
1549                 # Generate code for doing the buffer release/acquisition.
1550                 # This might raise an exception in which case the assignment (done
1551                 # below) will not happen.
1552                 #
1553                 # The reason this is not in a typetest-like node is because the
1554                 # variables that the acquired buffer info is stored to is allocated
1555                 # per entry and coupled with it.
1556                 self.generate_acquire_buffer(rhs, code)
1557
1558             if self.type.is_pyobject:
1559                 #print "NameNode.generate_assignment_code: to", self.name ###
1560                 #print "...from", rhs ###
1561                 #print "...LHS type", self.type, "ctype", self.ctype() ###
1562                 #print "...RHS type", rhs.type, "ctype", rhs.ctype() ###
1563                 if self.use_managed_ref:
1564                     rhs.make_owned_reference(code)
1565                     if entry.is_cglobal:
1566                         code.put_gotref(self.py_result())
1567                     if not self.lhs_of_first_assignment:
1568                         if entry.is_local and not Options.init_local_none:
1569                             initialized = entry.scope.control_flow.get_state((entry.name, 'initialized'), self.pos)
1570                             if initialized is True:
1571                                 code.put_decref(self.result(), self.ctype())
1572                             elif initialized is None:
1573                                 code.put_xdecref(self.result(), self.ctype())
1574                         else:
1575                             code.put_decref(self.result(), self.ctype())
1576                     if entry.is_cglobal:
1577                         code.put_giveref(rhs.py_result())
1578
1579             code.putln('%s = %s;' % (self.result(),
1580                                      rhs.result_as(self.ctype())))
1581             if debug_disposal_code:
1582                 print("NameNode.generate_assignment_code:")
1583                 print("...generating post-assignment code for %s" % rhs)
1584             rhs.generate_post_assignment_code(code)
1585             rhs.free_temps(code)
1586
1587     def generate_acquire_buffer(self, rhs, code):
1588         # rhstmp is only used in case the rhs is a complicated expression leading to
1589         # the object, to avoid repeating the same C expression for every reference
1590         # to the rhs. It does NOT hold a reference.
1591         pretty_rhs = isinstance(rhs, NameNode) or rhs.is_temp
1592         if pretty_rhs:
1593             rhstmp = rhs.result_as(self.ctype())
1594         else:
1595             rhstmp = code.funcstate.allocate_temp(self.entry.type, manage_ref=False)
1596             code.putln('%s = %s;' % (rhstmp, rhs.result_as(self.ctype())))
1597
1598         buffer_aux = self.entry.buffer_aux
1599         bufstruct = buffer_aux.buffer_info_var.cname
1600         import Buffer
1601         Buffer.put_assign_to_buffer(self.result(), rhstmp, buffer_aux, self.entry.type,
1602                                     is_initialized=not self.lhs_of_first_assignment,
1603                                     pos=self.pos, code=code)
1604         
1605         if not pretty_rhs:
1606             code.putln("%s = 0;" % rhstmp)
1607             code.funcstate.release_temp(rhstmp)
1608     
1609     def generate_deletion_code(self, code):
1610         if self.entry is None:
1611             return # There was an error earlier
1612         if not self.entry.is_pyglobal:
1613             error(self.pos, "Deletion of local or C global name not supported")
1614             return
1615         if self.entry.is_pyclass_attr:
1616             namespace = self.entry.scope.namespace_cname
1617             code.put_error_if_neg(self.pos,
1618                 'PyMapping_DelItemString(%s, "%s")' % (
1619                     namespace,
1620                     self.entry.name))
1621         else:
1622             code.put_error_if_neg(self.pos, 
1623                 '__Pyx_DelAttrString(%s, "%s")' % (
1624                     Naming.module_cname,
1625                     self.entry.name))
1626                 
1627     def annotate(self, code):
1628         if hasattr(self, 'is_called') and self.is_called:
1629             pos = (self.pos[0], self.pos[1], self.pos[2] - len(self.name) - 1)
1630             if self.type.is_pyobject:
1631                 code.annotate(pos, AnnotationItem('py_call', 'python function', size=len(self.name)))
1632             else:
1633                 code.annotate(pos, AnnotationItem('c_call', 'c function', size=len(self.name)))
1634             
1635 class BackquoteNode(ExprNode):
1636     #  `expr`
1637     #
1638     #  arg    ExprNode
1639     
1640     type = py_object_type
1641     
1642     subexprs = ['arg']
1643     
1644     def analyse_types(self, env):
1645         self.arg.analyse_types(env)
1646         self.arg = self.arg.coerce_to_pyobject(env)
1647         self.is_temp = 1
1648
1649     gil_message = "Backquote expression"
1650
1651     def calculate_constant_result(self):
1652         self.constant_result = repr(self.arg.constant_result)
1653
1654     def generate_result_code(self, code):
1655         code.putln(
1656             "%s = PyObject_Repr(%s); %s" % (
1657                 self.result(),
1658                 self.arg.py_result(),
1659                 code.error_goto_if_null(self.result(), self.pos)))
1660         code.put_gotref(self.py_result())
1661         
1662
1663
1664 class ImportNode(ExprNode):
1665     #  Used as part of import statement implementation.
1666     #  Implements result = 
1667     #    __import__(module_name, globals(), None, name_list)
1668     #
1669     #  module_name   StringNode            dotted name of module
1670     #  name_list     ListNode or None      list of names to be imported
1671     
1672     type = py_object_type
1673     
1674     subexprs = ['module_name', 'name_list']
1675     
1676     def analyse_types(self, env):
1677         self.module_name.analyse_types(env)
1678         self.module_name = self.module_name.coerce_to_pyobject(env)
1679         if self.name_list:
1680             self.name_list.analyse_types(env)
1681             self.name_list.coerce_to_pyobject(env)
1682         self.is_temp = 1
1683         env.use_utility_code(import_utility_code)
1684
1685     gil_message = "Python import"
1686
1687     def generate_result_code(self, code):
1688         if self.name_list:
1689             name_list_code = self.name_list.py_result()
1690         else:
1691             name_list_code = "0"
1692         code.putln(
1693             "%s = __Pyx_Import(%s, %s); %s" % (
1694                 self.result(),
1695                 self.module_name.py_result(),
1696                 name_list_code,
1697                 code.error_goto_if_null(self.result(), self.pos)))
1698         code.put_gotref(self.py_result())
1699
1700
1701 class IteratorNode(ExprNode):
1702     #  Used as part of for statement implementation.
1703     #
1704     #  allocate_counter_temp/release_counter_temp needs to be called
1705     #  by parent (ForInStatNode)
1706     #
1707     #  Implements result = iter(sequence)
1708     #
1709     #  sequence   ExprNode
1710     
1711     type = py_object_type
1712     
1713     subexprs = ['sequence']
1714     
1715     def analyse_types(self, env):
1716         self.sequence.analyse_types(env)
1717         if (self.sequence.type.is_array or self.sequence.type.is_ptr) and \
1718                 not self.sequence.type.is_string:
1719             # C array iteration will be transformed later on
1720             self.type = self.sequence.type
1721         else:
1722             self.sequence = self.sequence.coerce_to_pyobject(env)
1723         self.is_temp = 1
1724
1725     gil_message = "Iterating over Python object"
1726
1727     def allocate_counter_temp(self, code):
1728         self.counter_cname = code.funcstate.allocate_temp(
1729             PyrexTypes.c_py_ssize_t_type, manage_ref=False)
1730
1731     def release_counter_temp(self, code):
1732         code.funcstate.release_temp(self.counter_cname)
1733
1734     def generate_result_code(self, code):
1735         if self.sequence.type.is_array or self.sequence.type.is_ptr:
1736             raise InternalError("for in carray slice not transformed")
1737         is_builtin_sequence = self.sequence.type is list_type or \
1738                               self.sequence.type is tuple_type
1739         may_be_a_sequence = is_builtin_sequence or not self.sequence.type.is_builtin_type
1740         if is_builtin_sequence:
1741             code.putln(
1742                 "if (likely(%s != Py_None)) {" % self.sequence.py_result())
1743         elif may_be_a_sequence:
1744             code.putln(
1745                 "if (PyList_CheckExact(%s) || PyTuple_CheckExact(%s)) {" % (
1746                     self.sequence.py_result(),
1747                     self.sequence.py_result()))
1748         if may_be_a_sequence:
1749             code.putln(
1750                 "%s = 0; %s = %s; __Pyx_INCREF(%s);" % (
1751                     self.counter_cname,
1752                     self.result(),
1753                     self.sequence.py_result(),
1754                     self.result()))
1755             code.putln("} else {")
1756         if is_builtin_sequence:
1757             code.putln(
1758                 'PyErr_SetString(PyExc_TypeError, "\'NoneType\' object is not iterable"); %s' %
1759                 code.error_goto(self.pos))
1760         else:
1761             code.putln("%s = -1; %s = PyObject_GetIter(%s); %s" % (
1762                     self.counter_cname,
1763                     self.result(),
1764                     self.sequence.py_result(),
1765                     code.error_goto_if_null(self.result(), self.pos)))
1766             code.put_gotref(self.py_result())
1767         if may_be_a_sequence:
1768             code.putln("}")
1769
1770
1771 class NextNode(AtomicExprNode):
1772     #  Used as part of for statement implementation.
1773     #  Implements result = iterator.next()
1774     #  Created during analyse_types phase.
1775     #  The iterator is not owned by this node.
1776     #
1777     #  iterator   ExprNode
1778     
1779     type = py_object_type
1780     
1781     def __init__(self, iterator, env):
1782         self.pos = iterator.pos
1783         self.iterator = iterator
1784         if iterator.type.is_ptr or iterator.type.is_array:
1785             self.type = iterator.type.base_type
1786         self.is_temp = 1
1787     
1788     def generate_result_code(self, code):
1789         sequence_type = self.iterator.sequence.type
1790         if sequence_type is list_type:
1791             type_checks = [(list_type, "List")]
1792         elif sequence_type is tuple_type:
1793             type_checks = [(tuple_type, "Tuple")]
1794         elif not sequence_type.is_builtin_type:
1795             type_checks = [(list_type, "List"), (tuple_type, "Tuple")]
1796         else:
1797             type_checks = []
1798
1799         for py_type, prefix in type_checks:
1800             if len(type_checks) > 1:
1801                 code.putln(
1802                     "if (likely(Py%s_CheckExact(%s))) {" % (
1803                         prefix, self.iterator.py_result()))
1804             code.putln(
1805                 "if (%s >= Py%s_GET_SIZE(%s)) break;" % (
1806                     self.iterator.counter_cname,
1807                     prefix,
1808                     self.iterator.py_result()))
1809             code.putln(
1810                 "%s = Py%s_GET_ITEM(%s, %s); __Pyx_INCREF(%s); %s++;" % (
1811                     self.result(),
1812                     prefix,
1813                     self.iterator.py_result(),
1814                     self.iterator.counter_cname,
1815                     self.result(),
1816                     self.iterator.counter_cname))
1817             if len(type_checks) > 1:
1818                 code.put("} else ")
1819         if len(type_checks) == 1:
1820             return
1821         code.putln("{")
1822         code.putln(
1823             "%s = PyIter_Next(%s);" % (
1824                 self.result(),
1825                 self.iterator.py_result()))
1826         code.putln(
1827             "if (!%s) {" %
1828                 self.result())
1829         code.putln(code.error_goto_if_PyErr(self.pos))
1830         code.putln("break;")
1831         code.putln("}")
1832         code.put_gotref(self.py_result())
1833         code.putln("}")
1834
1835
1836 class ExcValueNode(AtomicExprNode):
1837     #  Node created during analyse_types phase
1838     #  of an ExceptClauseNode to fetch the current
1839     #  exception value.
1840     
1841     type = py_object_type
1842     
1843     def __init__(self, pos, env):
1844         ExprNode.__init__(self, pos)
1845
1846     def set_var(self, var):
1847         self.var = var
1848     
1849     def calculate_result_code(self):
1850         return self.var
1851
1852     def generate_result_code(self, code):
1853         pass
1854
1855     def analyse_types(self, env):
1856         pass
1857
1858
1859 class TempNode(ExprNode):
1860     # Node created during analyse_types phase
1861     # of some nodes to hold a temporary value.
1862     #
1863     # Note: One must call "allocate" and "release" on
1864     # the node during code generation to get/release the temp.
1865     # This is because the temp result is often used outside of
1866     # the regular cycle.
1867
1868     subexprs = []
1869     
1870     def __init__(self, pos, type, env):
1871         ExprNode.__init__(self, pos)
1872         self.type = type
1873         if type.is_pyobject:
1874             self.result_ctype = py_object_type
1875         self.is_temp = 1
1876         
1877     def analyse_types(self, env):
1878         return self.type
1879     
1880     def generate_result_code(self, code):
1881         pass
1882
1883     def allocate(self, code):
1884         self.temp_cname = code.funcstate.allocate_temp(self.type, manage_ref=True)
1885
1886     def release(self, code):
1887         code.funcstate.release_temp(self.temp_cname)
1888         self.temp_cname = None
1889
1890     def result(self):
1891         try:
1892             return self.temp_cname
1893         except:
1894             assert False, "Remember to call allocate/release on TempNode"
1895             raise
1896
1897     # Do not participate in normal temp alloc/dealloc:
1898     def allocate_temp_result(self, code):
1899         pass
1900     
1901     def release_temp_result(self, code):
1902         pass
1903
1904 class PyTempNode(TempNode):
1905     #  TempNode holding a Python value.
1906     
1907     def __init__(self, pos, env):
1908         TempNode.__init__(self, pos, PyrexTypes.py_object_type, env)
1909
1910 class RawCNameExprNode(ExprNode):
1911     subexprs = []
1912     
1913     def __init__(self, pos, type=None):
1914         self.pos = pos
1915         self.type = type
1916
1917     def analyse_types(self, env):
1918         return self.type
1919
1920     def set_cname(self, cname):
1921         self.cname = cname
1922
1923     def result(self):
1924         return self.cname
1925
1926     def generate_result_code(self, code):
1927         pass
1928
1929
1930 #-------------------------------------------------------------------
1931 #
1932 #  Trailer nodes
1933 #
1934 #-------------------------------------------------------------------
1935
1936 class IndexNode(ExprNode):
1937     #  Sequence indexing.
1938     #
1939     #  base     ExprNode
1940     #  index    ExprNode
1941     #  indices  [ExprNode]
1942     #  is_buffer_access boolean Whether this is a buffer access.
1943     #
1944     #  indices is used on buffer access, index on non-buffer access.
1945     #  The former contains a clean list of index parameters, the
1946     #  latter whatever Python object is needed for index access.
1947     
1948     subexprs = ['base', 'index', 'indices']
1949     indices = None
1950
1951     def __init__(self, pos, index, *args, **kw):
1952         ExprNode.__init__(self, pos, index=index, *args, **kw)
1953         self._index = index
1954
1955     def calculate_constant_result(self):
1956         self.constant_result = \
1957             self.base.constant_result[self.index.constant_result]
1958
1959     def compile_time_value(self, denv):
1960         base = self.base.compile_time_value(denv)
1961         index = self.index.compile_time_value(denv)
1962         try:
1963             return base[index]
1964         except Exception, e:
1965             self.compile_time_value_error(e)
1966     
1967     def is_ephemeral(self):
1968         return self.base.is_ephemeral()
1969     
1970     def analyse_target_declaration(self, env):
1971         pass
1972         
1973     def analyse_as_type(self, env):
1974         base_type = self.base.analyse_as_type(env)
1975         if base_type and not base_type.is_pyobject:
1976             if base_type.is_cpp_class:
1977                 if isinstance(self.index, TupleNode):
1978                     template_values = self.index.args
1979                 else:
1980                     template_values = [self.index]
1981                 import Nodes
1982                 type_node = Nodes.TemplatedTypeNode(
1983                     pos = self.pos, 
1984                     positional_args = template_values, 
1985                     keyword_args = None)
1986                 return type_node.analyse(env, base_type = base_type)
1987             else:
1988                 return PyrexTypes.CArrayType(base_type, int(self.index.compile_time_value(env)))
1989         return None
1990     
1991     def type_dependencies(self, env):
1992         return self.base.type_dependencies(env)
1993     
1994     def infer_type(self, env):
1995         base_type = self.base.infer_type(env)
1996         if isinstance(self.index, SliceNode):
1997             # slicing!
1998             if base_type.is_string:
1999                 # sliced C strings must coerce to Python 
2000                 return bytes_type
2001             elif base_type in (unicode_type, bytes_type, str_type, list_type, tuple_type):
2002                 # slicing these returns the same type
2003                 return base_type
2004             else:
2005                 # TODO: Handle buffers (hopefully without too much redundancy).
2006                 return py_object_type
2007
2008         index_type = self.index.infer_type(env)
2009         if index_type and index_type.is_int or isinstance(self.index, (IntNode, LongNode)):
2010             # indexing!
2011             if base_type is unicode_type:
2012                 # Py_UNICODE will automatically coerce to a unicode string
2013                 # if required, so this is safe. We only infer Py_UNICODE
2014                 # when the index is a C integer type. Otherwise, we may
2015                 # need to use normal Python item access, in which case
2016                 # it's faster to return the one-char unicode string than
2017                 # to receive it, throw it away, and potentially rebuild it
2018                 # on a subsequent PyObject coercion.
2019                 return PyrexTypes.c_py_unicode_type
2020             elif isinstance(self.base, BytesNode):
2021                 #if env.global_scope().context.language_level >= 3:
2022                 #    # infering 'char' can be made to work in Python 3 mode
2023                 #    return PyrexTypes.c_char_type
2024                 # Py2/3 return different types on indexing bytes objects
2025                 return py_object_type
2026             elif base_type.is_ptr or base_type.is_array:
2027                 return base_type.base_type
2028
2029         # may be slicing or indexing, we don't know
2030         if base_type is unicode_type:
2031             # this type always returns its own type on Python indexing/slicing
2032             return base_type
2033         else:
2034             # TODO: Handle buffers (hopefully without too much redundancy).
2035             return py_object_type
2036     
2037     def analyse_types(self, env):
2038         self.analyse_base_and_index_types(env, getting = 1)
2039     
2040     def analyse_target_types(self, env):
2041         self.analyse_base_and_index_types(env, setting = 1)
2042
2043     def analyse_base_and_index_types(self, env, getting = 0, setting = 0):
2044         # Note: This might be cleaned up by having IndexNode
2045         # parsed in a saner way and only construct the tuple if
2046         # needed.
2047
2048         # Note that this function must leave IndexNode in a cloneable state.
2049         # For buffers, self.index is packed out on the initial analysis, and
2050         # when cloning self.indices is copied.
2051         self.is_buffer_access = False
2052
2053         self.base.analyse_types(env)
2054         if self.base.type.is_error:
2055             # Do not visit child tree if base is undeclared to avoid confusing
2056             # error messages
2057             self.type = PyrexTypes.error_type
2058             return
2059         
2060         is_slice = isinstance(self.index, SliceNode)
2061         # Potentially overflowing index value.
2062         if not is_slice and isinstance(self.index, IntNode) and Utils.long_literal(self.index.value):
2063             self.index = self.index.coerce_to_pyobject(env)
2064
2065         # Handle the case where base is a literal char* (and we expect a string, not an int)
2066         if isinstance(self.base, BytesNode) or is_slice:
2067             if self.base.type.is_string or not (self.base.type.is_ptr or self.base.type.is_array):
2068                 self.base = self.base.coerce_to_pyobject(env)
2069
2070         skip_child_analysis = False
2071         buffer_access = False
2072         if self.base.type.is_buffer:
2073             if self.indices:
2074                 indices = self.indices
2075             else:
2076                 if isinstance(self.index, TupleNode):
2077                     indices = self.index.args
2078                 else:
2079                     indices = [self.index]
2080             if len(indices) == self.base.type.ndim:
2081                 buffer_access = True
2082                 skip_child_analysis = True
2083                 for x in indices:
2084                     x.analyse_types(env)
2085                     if not x.type.is_int:
2086                         buffer_access = False
2087             if buffer_access:
2088                 assert hasattr(self.base, "entry") # Must be a NameNode-like node
2089
2090         # On cloning, indices is cloned. Otherwise, unpack index into indices
2091         assert not (buffer_access and isinstance(self.index, CloneNode))
2092
2093         if buffer_access:
2094             self.indices = indices
2095             self.index = None
2096             self.type = self.base.type.dtype
2097             self.is_buffer_access = True
2098             self.buffer_type = self.base.entry.type
2099
2100             if getting and self.type.is_pyobject:
2101                 self.is_temp = True
2102             if setting:
2103                 if not self.base.entry.type.writable:
2104                     error(self.pos, "Writing to readonly buffer")
2105                 else:
2106                     self.base.entry.buffer_aux.writable_needed = True
2107         else:
2108             base_type = self.base.type
2109             if isinstance(self.index, TupleNode):
2110                 self.index.analyse_types(env, skip_children=skip_child_analysis)
2111             elif not skip_child_analysis:
2112                 self.index.analyse_types(env)
2113             self.original_index_type = self.index.type
2114             if base_type is PyrexTypes.c_py_unicode_type:
2115                 # we infer Py_UNICODE for unicode strings in some
2116                 # cases, but indexing must still work for them
2117                 if self.index.constant_result in (0, -1):
2118                     # FIXME: we know that this node is redundant -
2119                     # currently, this needs to get handled in Optimize.py
2120                     pass
2121                 self.base = self.base.coerce_to_pyobject(env)
2122                 base_type = self.base.type
2123             if base_type.is_pyobject:
2124                 if self.index.type.is_int:
2125                     if (not setting
2126                         and (base_type in (list_type, tuple_type, unicode_type))
2127                         and (not self.index.type.signed or isinstance(self.index, IntNode) and int(self.index.value) >= 0)
2128                         and not env.directives['boundscheck']):
2129                         self.is_temp = 0
2130                     else:
2131                         self.is_temp = 1
2132                     self.index = self.index.coerce_to(PyrexTypes.c_py_ssize_t_type, env).coerce_to_simple(env)
2133                 else:
2134                     self.index = self.index.coerce_to_pyobject(env)
2135                     self.is_temp = 1
2136                 if self.index.type.is_int and base_type is unicode_type:
2137                     # Py_UNICODE will automatically coerce to a unicode string
2138                     # if required, so this is fast and safe
2139                     self.type = PyrexTypes.c_py_unicode_type
2140                 elif is_slice and base_type in (bytes_type, str_type, unicode_type, list_type, tuple_type):
2141                     self.type = base_type
2142                 else:
2143                     self.type = py_object_type
2144             else:
2145                 if base_type.is_ptr or base_type.is_array:
2146                     self.type = base_type.base_type
2147                     if is_slice:
2148                         self.type = base_type
2149                     elif self.index.type.is_pyobject:
2150                         self.index = self.index.coerce_to(
2151                             PyrexTypes.c_py_ssize_t_type, env)
2152                     elif not self.index.type.is_int:
2153                         error(self.pos,
2154                             "Invalid index type '%s'" %
2155                                 self.index.type)
2156                 elif base_type.is_cpp_class:
2157                     function = env.lookup_operator("[]", [self.base, self.index])
2158                     if function is None:
2159                         error(self.pos, "Indexing '%s' not supported for index type '%s'" % (base_type, self.index.type))
2160                         self.type = PyrexTypes.error_type
2161                         self.result_code = "<error>"
2162                         return
2163                     func_type = function.type
2164                     if func_type.is_ptr:
2165                         func_type = func_type.base_type
2166                     self.index = self.index.coerce_to(func_type.args[0].type, env)
2167                     self.type = func_type.return_type
2168                     if setting and not func_type.return_type.is_reference:
2169                         error(self.pos, "Can't set non-reference result '%s'" % self.type)
2170                 else:
2171                     error(self.pos,
2172                         "Attempting to index non-array type '%s'" %
2173                             base_type)
2174                     self.type = PyrexTypes.error_type
2175
2176     gil_message = "Indexing Python object"
2177
2178     def nogil_check(self, env):
2179         if self.is_buffer_access:
2180             if env.directives['boundscheck']:
2181                 error(self.pos, "Cannot check buffer index bounds without gil; use boundscheck(False) directive")
2182                 return
2183             elif self.type.is_pyobject:
2184                 error(self.pos, "Cannot access buffer with object dtype without gil")
2185                 return
2186         super(IndexNode, self).nogil_check(env)
2187
2188
2189     def check_const_addr(self):
2190         return self.base.check_const_addr() and self.index.check_const()
2191     
2192     def is_lvalue(self):
2193         return 1
2194
2195     def calculate_result_code(self):
2196         if self.is_buffer_access:
2197             return "(*%s)" % self.buffer_ptr_code
2198         elif self.base.type is list_type:
2199             return "PyList_GET_ITEM(%s, %s)" % (self.base.result(), self.index.result())
2200         elif self.base.type is tuple_type:
2201             return "PyTuple_GET_ITEM(%s, %s)" % (self.base.result(), self.index.result())
2202         elif self.base.type is unicode_type and self.type is PyrexTypes.c_py_unicode_type:
2203             return "PyUnicode_AS_UNICODE(%s)[%s]" % (self.base.result(), self.index.result())
2204         elif (self.type.is_ptr or self.type.is_array) and self.type == self.base.type:
2205             error(self.pos, "Invalid use of pointer slice")
2206         else:
2207             return "(%s[%s])" % (
2208                 self.base.result(), self.index.result())
2209             
2210     def extra_index_params(self):
2211         if self.index.type.is_int:
2212             if self.original_index_type.signed:
2213                 size_adjustment = ""
2214             else:
2215                 size_adjustment = "+1"
2216             return ", sizeof(%s)%s, %s" % (self.original_index_type.declaration_code(""), size_adjustment, self.original_index_type.to_py_function)
2217         else:
2218             return ""
2219
2220     def generate_subexpr_evaluation_code(self, code):
2221         self.base.generate_evaluation_code(code)
2222         if not self.indices:
2223             self.index.generate_evaluation_code(code)
2224         else:
2225             for i in self.indices:
2226                 i.generate_evaluation_code(code)
2227         
2228     def generate_subexpr_disposal_code(self, code):
2229         self.base.generate_disposal_code(code)
2230         if not self.indices:
2231             self.index.generate_disposal_code(code)
2232         else:
2233             for i in self.indices:
2234                 i.generate_disposal_code(code)
2235
2236     def free_subexpr_temps(self, code):
2237         self.base.free_temps(code)
2238         if not self.indices:
2239             self.index.free_temps(code)
2240         else:
2241             for i in self.indices:
2242                 i.free_temps(code)
2243
2244     def generate_result_code(self, code):
2245         if self.is_buffer_access:
2246             if code.globalstate.directives['nonecheck']:
2247                 self.put_nonecheck(code)
2248             self.buffer_ptr_code = self.buffer_lookup_code(code)
2249             if self.type.is_pyobject:
2250                 # is_temp is True, so must pull out value and incref it.
2251                 code.putln("%s = *%s;" % (self.result(), self.buffer_ptr_code))
2252                 code.putln("__Pyx_INCREF((PyObject*)%s);" % self.result())
2253         elif self.is_temp:
2254             if self.type.is_pyobject:
2255                 if self.index.type.is_int:
2256                     index_code = self.index.result()
2257                     if self.base.type is list_type:
2258                         function = "__Pyx_GetItemInt_List"
2259                     elif self.base.type is tuple_type:
2260                         function = "__Pyx_GetItemInt_Tuple"
2261                     else:
2262                         function = "__Pyx_GetItemInt"
2263                     code.globalstate.use_utility_code(getitem_int_utility_code)
2264                 else:
2265                     index_code = self.index.py_result()
2266                     if self.base.type is dict_type:
2267                         function = "__Pyx_PyDict_GetItem"
2268                         code.globalstate.use_utility_code(getitem_dict_utility_code)
2269                     else:
2270                         function = "PyObject_GetItem"
2271                 code.putln(
2272                     "%s = %s(%s, %s%s); if (!%s) %s" % (
2273                         self.result(),
2274                         function,
2275                         self.base.py_result(),
2276                         index_code,
2277                         self.extra_index_params(),
2278                         self.result(),
2279                         code.error_goto(self.pos)))
2280                 code.put_gotref(self.py_result())
2281             elif self.type is PyrexTypes.c_py_unicode_type and self.base.type is unicode_type:
2282                 assert self.index.type.is_int
2283                 index_code = self.index.result()
2284                 function = "__Pyx_GetItemInt_Unicode"
2285                 code.globalstate.use_utility_code(getitem_int_pyunicode_utility_code)
2286                 code.putln(
2287                     "%s = %s(%s, %s%s); if (unlikely(%s == (Py_UNICODE)-1)) %s;" % (
2288                         self.result(),
2289                         function,
2290                         self.base.py_result(),
2291                         index_code,
2292                         self.extra_index_params(),
2293                         self.result(),
2294                         code.error_goto(self.pos)))
2295             
2296     def generate_setitem_code(self, value_code, code):
2297         if self.index.type.is_int:
2298             function = "__Pyx_SetItemInt"
2299             index_code = self.index.result()
2300             code.globalstate.use_utility_code(setitem_int_utility_code)
2301         else:
2302             index_code = self.index.py_result()
2303             if self.base.type is dict_type:
2304                 function = "PyDict_SetItem"
2305             # It would seem that we could specialized lists/tuples, but that
2306             # shouldn't happen here. 
2307             # Both PyList_SetItem PyTuple_SetItem and a Py_ssize_t as input, 
2308             # not a PyObject*, and bad conversion here would give the wrong 
2309             # exception. Also, tuples are supposed to be immutable, and raise 
2310             # TypeErrors when trying to set their entries (PyTuple_SetItem 
2311             # is for creating new tuples from). 
2312             else:
2313                 function = "PyObject_SetItem"
2314         code.putln(
2315             "if (%s(%s, %s, %s%s) < 0) %s" % (
2316                 function,
2317                 self.base.py_result(),
2318                 index_code,
2319                 value_code,
2320                 self.extra_index_params(),
2321                 code.error_goto(self.pos)))
2322
2323     def generate_buffer_setitem_code(self, rhs, code, op=""):
2324         # Used from generate_assignment_code and InPlaceAssignmentNode
2325         if code.globalstate.directives['nonecheck']:
2326             self.put_nonecheck(code)
2327         ptrexpr = self.buffer_lookup_code(code)
2328         if self.buffer_type.dtype.is_pyobject:
2329             # Must manage refcounts. Decref what is already there
2330             # and incref what we put in.
2331             ptr = code.funcstate.allocate_temp(self.buffer_type.buffer_ptr_type, manage_ref=False)
2332             rhs_code = rhs.result()
2333             code.putln("%s = %s;" % (ptr, ptrexpr))
2334             code.put_gotref("*%s" % ptr)
2335             code.putln("__Pyx_DECREF(*%s); __Pyx_INCREF(%s);" % (
2336                 ptr, rhs_code
2337                 ))
2338             code.putln("*%s %s= %s;" % (ptr, op, rhs_code))
2339             code.put_giveref("*%s" % ptr)
2340             code.funcstate.release_temp(ptr)
2341         else: 
2342             # Simple case
2343             code.putln("*%s %s= %s;" % (ptrexpr, op, rhs.result()))
2344
2345     def generate_assignment_code(self, rhs, code):
2346         self.generate_subexpr_evaluation_code(code)
2347         if self.is_buffer_access:
2348             self.generate_buffer_setitem_code(rhs, code)
2349         elif self.type.is_pyobject:
2350             self.generate_setitem_code(rhs.py_result(), code)
2351         else:
2352             code.putln(
2353                 "%s = %s;" % (
2354                     self.result(), rhs.result()))
2355         self.generate_subexpr_disposal_code(code)
2356         self.free_subexpr_temps(code)
2357         rhs.generate_disposal_code(code)
2358         rhs.free_temps(code)
2359     
2360     def generate_deletion_code(self, code):
2361         self.generate_subexpr_evaluation_code(code)
2362         #if self.type.is_pyobject:
2363         if self.index.type.is_int:
2364             function = "__Pyx_DelItemInt"
2365             index_code = self.index.result()
2366             code.globalstate.use_utility_code(delitem_int_utility_code)
2367         else:
2368             index_code = self.index.py_result()
2369             if self.base.type is dict_type:
2370                 function = "PyDict_DelItem"
2371             else:
2372                 function = "PyObject_DelItem"
2373         code.putln(
2374             "if (%s(%s, %s%s) < 0) %s" % (
2375                 function,
2376                 self.base.py_result(),
2377                 index_code,
2378                 self.extra_index_params(),
2379                 code.error_goto(self.pos)))
2380         self.generate_subexpr_disposal_code(code)
2381         self.free_subexpr_temps(code)
2382
2383     def buffer_lookup_code(self, code):
2384         # Assign indices to temps
2385         index_temps = [code.funcstate.allocate_temp(i.type, manage_ref=False) for i in self.indices]
2386         for temp, index in zip(index_temps, self.indices):
2387             code.putln("%s = %s;" % (temp, index.result()))
2388         # Generate buffer access code using these temps
2389         import Buffer
2390         # The above could happen because child_attrs is wrong somewhere so that
2391         # options are not propagated.
2392         return Buffer.put_buffer_lookup_code(entry=self.base.entry,
2393                                              index_signeds=[i.type.signed for i in self.indices],
2394                                              index_cnames=index_temps,
2395                                              directives=code.globalstate.directives,
2396                                              pos=self.pos, code=code)
2397
2398     def put_nonecheck(self, code):
2399         code.globalstate.use_utility_code(raise_noneindex_error_utility_code)
2400         code.putln("if (%s) {" % code.unlikely("%s == Py_None") % self.base.result_as(PyrexTypes.py_object_type))
2401         code.putln("__Pyx_RaiseNoneIndexingError();")
2402         code.putln(code.error_goto(self.pos))
2403         code.putln("}")
2404
2405 class SliceIndexNode(ExprNode):
2406     #  2-element slice indexing
2407     #
2408     #  base      ExprNode
2409     #  start     ExprNode or None
2410     #  stop      ExprNode or None
2411     
2412     subexprs = ['base', 'start', 'stop']
2413
2414     def infer_type(self, env):
2415         base_type = self.base.infer_type(env)
2416         if base_type.is_string:
2417             return bytes_type
2418         elif base_type in (bytes_type, str_type, unicode_type,
2419                            list_type, tuple_type):
2420             return base_type
2421         return py_object_type
2422
2423     def calculate_constant_result(self):
2424         self.constant_result = self.base.constant_result[
2425             self.start.constant_result : self.stop.constant_result]
2426
2427     def compile_time_value(self, denv):
2428         base = self.base.compile_time_value(denv)
2429         if self.start is None:
2430             start = 0
2431         else:
2432             start = self.start.compile_time_value(denv)
2433         if self.stop is None:
2434             stop = None
2435         else:
2436             stop = self.stop.compile_time_value(denv)
2437         try:
2438             return base[start:stop]
2439         except Exception, e:
2440             self.compile_time_value_error(e)
2441     
2442     def analyse_target_declaration(self, env):
2443         pass
2444     
2445     def analyse_target_types(self, env):
2446         self.analyse_types(env)
2447         # when assigning, we must accept any Python type
2448         if self.type.is_pyobject:
2449             self.type = py_object_type
2450
2451     def analyse_types(self, env):
2452         self.base.analyse_types(env)
2453         if self.start:
2454             self.start.analyse_types(env)
2455         if self.stop:
2456             self.stop.analyse_types(env)
2457         base_type = self.base.type
2458         if base_type.is_string:
2459             self.type = bytes_type
2460         elif base_type.is_ptr:
2461             self.type = base_type
2462         elif base_type.is_array:
2463             # we need a ptr type here instead of an array type, as
2464             # array types can result in invalid type casts in the C
2465             # code
2466             self.type = PyrexTypes.CPtrType(base_type.base_type)
2467         else:
2468             self.base = self.base.coerce_to_pyobject(env)
2469             self.type = py_object_type
2470         if base_type.is_builtin_type:
2471             # slicing builtin types returns something of the same type
2472             self.type = base_type
2473         c_int = PyrexTypes.c_py_ssize_t_type
2474         if self.start:
2475             self.start = self.start.coerce_to(c_int, env)
2476         if self.stop:
2477             self.stop = self.stop.coerce_to(c_int, env)
2478         self.is_temp = 1
2479
2480     nogil_check = Node.gil_error
2481     gil_message = "Slicing Python object"
2482
2483     def generate_result_code(self, code):
2484         if not self.type.is_pyobject:
2485             error(self.pos,
2486                   "Slicing is not currently supported for '%s'." % self.type)
2487             return
2488         if self.base.type.is_string:
2489             if self.stop is None:
2490                 code.putln(
2491                     "%s = PyBytes_FromString(%s + %s); %s" % (
2492                         self.result(),
2493                         self.base.result(),
2494                         self.start_code(),
2495                         code.error_goto_if_null(self.result(), self.pos)))
2496             else:
2497                 code.putln(
2498                     "%s = PyBytes_FromStringAndSize(%s + %s, %s - %s); %s" % (
2499                         self.result(),
2500                         self.base.result(),
2501                         self.start_code(),
2502                         self.stop_code(),
2503                         self.start_code(),
2504                         code.error_goto_if_null(self.result(), self.pos)))
2505         else:
2506             code.putln(
2507                 "%s = __Pyx_PySequence_GetSlice(%s, %s, %s); %s" % (
2508                     self.result(),
2509                     self.base.py_result(),
2510                     self.start_code(),
2511                     self.stop_code(),
2512                     code.error_goto_if_null(self.result(), self.pos)))
2513         code.put_gotref(self.py_result())
2514     
2515     def generate_assignment_code(self, rhs, code):
2516         self.generate_subexpr_evaluation_code(code)
2517         if self.type.is_pyobject:
2518             code.put_error_if_neg(self.pos, 
2519                 "__Pyx_PySequence_SetSlice(%s, %s, %s, %s)" % (
2520                     self.base.py_result(),
2521                     self.start_code(),
2522                     self.stop_code(),
2523                     rhs.py_result()))
2524         else:
2525             start_offset = ''
2526             if self.start:
2527                 start_offset = self.start_code()
2528                 if start_offset == '0':
2529                     start_offset = ''
2530                 else:
2531                     start_offset += '+'
2532             if rhs.type.is_array:
2533                 array_length = rhs.type.size
2534                 self.generate_slice_guard_code(code, array_length)
2535             else:
2536                 error(self.pos,
2537                       "Slice assignments from pointers are not yet supported.")
2538                 # FIXME: fix the array size according to start/stop
2539                 array_length = self.base.type.size
2540             for i in range(array_length):
2541                 code.putln("%s[%s%s] = %s[%d];" % (
2542                         self.base.result(), start_offset, i,
2543                         rhs.result(), i))
2544         self.generate_subexpr_disposal_code(code)
2545         self.free_subexpr_temps(code)
2546         rhs.generate_disposal_code(code)
2547         rhs.free_temps(code)
2548
2549     def generate_deletion_code(self, code):
2550         if not self.base.type.is_pyobject:
2551             error(self.pos,
2552                   "Deleting slices is only supported for Python types, not '%s'." % self.type)
2553             return
2554         self.generate_subexpr_evaluation_code(code)
2555         code.put_error_if_neg(self.pos,
2556             "__Pyx_PySequence_DelSlice(%s, %s, %s)" % (
2557                 self.base.py_result(),
2558                 self.start_code(),
2559                 self.stop_code()))
2560         self.generate_subexpr_disposal_code(code)
2561
2562     def generate_slice_guard_code(self, code, target_size):
2563         if not self.base.type.is_array:
2564             return
2565         slice_size = self.base.type.size
2566         start = stop = None
2567         if self.stop:
2568             stop = self.stop.result()
2569             try:
2570                 stop = int(stop)
2571                 if stop < 0:
2572                     slice_size = self.base.type.size + stop
2573                 else:
2574                     slice_size = stop
2575                 stop = None
2576             except ValueError:
2577                 pass
2578         if self.start:
2579             start = self.start.result()
2580             try:
2581                 start = int(start)
2582                 if start < 0:
2583                     start = self.base.type.size + start
2584                 slice_size -= start
2585                 start = None
2586             except ValueError:
2587                 pass
2588         check = None
2589         if slice_size < 0:
2590             if target_size > 0:
2591                 error(self.pos, "Assignment to empty slice.")
2592         elif start is None and stop is None:
2593             # we know the exact slice length
2594             if target_size != slice_size:
2595                 error(self.pos, "Assignment to slice of wrong length, expected %d, got %d" % (
2596                         slice_size, target_size))
2597         elif start is not None:
2598             if stop is None:
2599                 stop = slice_size
2600             check = "(%s)-(%s)" % (stop, start)
2601         else: # stop is not None:
2602             check = stop
2603         if check:
2604             code.putln("if (unlikely((%s) != %d)) {" % (check, target_size))
2605             code.putln('PyErr_Format(PyExc_ValueError, "Assignment to slice of wrong length, expected %%"PY_FORMAT_SIZE_T"d, got %%"PY_FORMAT_SIZE_T"d", (Py_ssize_t)%d, (Py_ssize_t)(%s));' % (
2606                         target_size, check))
2607             code.putln(code.error_goto(self.pos))
2608             code.putln("}")
2609     
2610     def start_code(self):
2611         if self.start:
2612             return self.start.result()
2613         else:
2614             return "0"
2615     
2616     def stop_code(self):
2617         if self.stop:
2618             return self.stop.result()
2619         elif self.base.type.is_array:
2620             return self.base.type.size
2621         else:
2622             return "PY_SSIZE_T_MAX"
2623     
2624     def calculate_result_code(self):
2625         # self.result() is not used, but this method must exist
2626         return "<unused>"
2627     
2628
2629 class SliceNode(ExprNode):
2630     #  start:stop:step in subscript list
2631     #
2632     #  start     ExprNode
2633     #  stop      ExprNode
2634     #  step      ExprNode
2635     
2636     type = py_object_type
2637     is_temp = 1
2638
2639     def calculate_constant_result(self):
2640         self.constant_result = self.base.constant_result[
2641             self.start.constant_result : \
2642                 self.stop.constant_result : \
2643                 self.step.constant_result]
2644
2645     def compile_time_value(self, denv):
2646         start = self.start.compile_time_value(denv)
2647         if self.stop is None:
2648             stop = None
2649         else:
2650             stop = self.stop.compile_time_value(denv)
2651         if self.step is None:
2652             step = None
2653         else:
2654             step = self.step.compile_time_value(denv)
2655         try:
2656             return slice(start, stop, step)
2657         except Exception, e:
2658             self.compile_time_value_error(e)
2659
2660     subexprs = ['start', 'stop', 'step']
2661     
2662     def analyse_types(self, env):
2663         self.start.analyse_types(env)
2664         self.stop.analyse_types(env)
2665         self.step.analyse_types(env)
2666         self.start = self.start.coerce_to_pyobject(env)
2667         self.stop = self.stop.coerce_to_pyobject(env)
2668         self.step = self.step.coerce_to_pyobject(env)
2669
2670     gil_message = "Constructing Python slice object"
2671
2672     def generate_result_code(self, code):
2673         code.putln(
2674             "%s = PySlice_New(%s, %s, %s); %s" % (
2675                 self.result(),
2676                 self.start.py_result(), 
2677                 self.stop.py_result(), 
2678                 self.step.py_result(),
2679                 code.error_goto_if_null(self.result(), self.pos)))
2680         code.put_gotref(self.py_result())
2681
2682
2683 class CallNode(ExprNode):
2684
2685     # allow overriding the default 'may_be_none' behaviour
2686     may_return_none = None
2687
2688     def may_be_none(self):
2689         if self.may_return_none is not None:
2690             return self.may_return_none
2691         return ExprNode.may_be_none(self)
2692
2693     def analyse_as_type_constructor(self, env):
2694         type = self.function.analyse_as_type(env)
2695         if type and type.is_struct_or_union:
2696             args, kwds = self.explicit_args_kwds()
2697             items = []
2698             for arg, member in zip(args, type.scope.var_entries):
2699                 items.append(DictItemNode(pos=arg.pos, key=StringNode(pos=arg.pos, value=member.name), value=arg))
2700             if kwds:
2701                 items += kwds.key_value_pairs
2702             self.key_value_pairs = items
2703             self.__class__ = DictNode
2704             self.analyse_types(env)
2705             self.coerce_to(type, env)
2706             return True
2707         elif type and type.is_cpp_class:
2708             for arg in self.args:
2709                 arg.analyse_types(env)
2710             constructor = type.scope.lookup("<init>")
2711             self.function = RawCNameExprNode(self.function.pos, constructor.type)
2712             self.function.entry = constructor
2713             self.function.set_cname(type.declaration_code(""))
2714             self.analyse_c_function_call(env)
2715             return True
2716     
2717     def is_lvalue(self):
2718         return self.type.is_reference
2719
2720     def nogil_check(self, env):
2721         func_type = self.function_type()
2722         if func_type.is_pyobject:
2723             self.gil_error()
2724         elif not getattr(func_type, 'nogil', False):
2725             self.gil_error()
2726
2727     gil_message = "Calling gil-requiring function"
2728
2729
2730 class SimpleCallNode(CallNode):
2731     #  Function call without keyword, * or ** args.
2732     #
2733     #  function       ExprNode
2734     #  args           [ExprNode]
2735     #  arg_tuple      ExprNode or None     used internally
2736     #  self           ExprNode or None     used internally
2737     #  coerced_self   ExprNode or None     used internally
2738     #  wrapper_call   bool                 used internally
2739     #  has_optional_args   bool            used internally
2740     #  nogil          bool                 used internally
2741     
2742     subexprs = ['self', 'coerced_self', 'function', 'args', 'arg_tuple']
2743     
2744     self = None
2745     coerced_self = None
2746     arg_tuple = None
2747     wrapper_call = False
2748     has_optional_args = False
2749     nogil = False
2750     analysed = False
2751     
2752     def compile_time_value(self, denv):
2753         function = self.function.compile_time_value(denv)
2754         args = [arg.compile_time_value(denv) for arg in self.args]
2755         try:
2756             return function(*args)
2757         except Exception, e:
2758             self.compile_time_value_error(e)
2759             
2760     def type_dependencies(self, env):
2761         # TODO: Update when Danilo's C++ code merged in to handle the
2762         # the case of function overloading.
2763         return self.function.type_dependencies(env)
2764     
2765     def infer_type(self, env):
2766         function = self.function
2767         func_type = function.infer_type(env)
2768         if isinstance(self.function, NewExprNode):
2769             return PyrexTypes.CPtrType(self.function.class_type)
2770         if func_type.is_ptr:
2771             func_type = func_type.base_type
2772         if func_type.is_cfunction:
2773             return func_type.return_type
2774         elif func_type is type_type:
2775             if function.is_name and function.entry and function.entry.type:
2776                 result_type = function.entry.type
2777                 if result_type.is_extension_type:
2778                     return result_type
2779                 elif result_type.is_builtin_type:
2780                     if function.entry.name == 'float':
2781                         return PyrexTypes.c_double_type
2782                     elif function.entry.name in Builtin.types_that_construct_their_instance:
2783                         return result_type
2784         return py_object_type
2785
2786     def analyse_as_type(self, env):
2787         attr = self.function.as_cython_attribute()
2788         if attr == 'pointer':
2789             if len(self.args) != 1:
2790                 error(self.args.pos, "only one type allowed.")
2791             else:
2792                 type = self.args[0].analyse_as_type(env)
2793                 if not type:
2794                     error(self.args[0].pos, "Unknown type")
2795                 else:
2796                     return PyrexTypes.CPtrType(type)
2797
2798     def explicit_args_kwds(self):
2799         return self.args, None
2800
2801     def analyse_types(self, env):
2802         if self.analyse_as_type_constructor(env):
2803             return
2804         if self.analysed:
2805             return
2806         self.analysed = True
2807         function = self.function
2808         function.is_called = 1
2809         self.function.analyse_types(env)
2810         if function.is_attribute and function.entry and function.entry.is_cmethod:
2811             # Take ownership of the object from which the attribute
2812             # was obtained, because we need to pass it as 'self'.
2813             self.self = function.obj
2814             function.obj = CloneNode(self.self)
2815         func_type = self.function_type()
2816         if func_type.is_pyobject:
2817             self.arg_tuple = TupleNode(self.pos, args = self.args)
2818             self.arg_tuple.analyse_types(env)
2819             self.args = None
2820             if func_type is Builtin.type_type and function.is_name and \
2821                    function.entry and \
2822                    function.entry.is_builtin and \
2823                    function.entry.name in Builtin.types_that_construct_their_instance:
2824                 # calling a builtin type that returns a specific object type
2825                 if function.entry.name == 'float':
2826                     # the following will come true later on in a transform
2827                     self.type = PyrexTypes.c_double_type
2828                     self.result_ctype = PyrexTypes.c_double_type
2829                 else:
2830                     self.type = Builtin.builtin_types[function.entry.name]
2831                     self.result_ctype = py_object_type
2832                 self.may_return_none = False
2833             elif function.is_name and function.type_entry:
2834                 # We are calling an extension type constructor.  As
2835                 # long as we do not support __new__(), the result type
2836                 # is clear
2837                 self.type = function.type_entry.type
2838                 self.result_ctype = py_object_type
2839                 self.may_return_none = False
2840             else:
2841                 self.type = py_object_type
2842             self.is_temp = 1
2843         else:
2844             for arg in self.args:
2845                 arg.analyse_types(env)
2846             if self.self and func_type.args:
2847                 # Coerce 'self' to the type expected by the method.
2848                 self_arg = func_type.args[0]
2849                 if self_arg.not_none: # C methods must do the None test for self at *call* time
2850                     self.self = self.self.as_none_safe_node(
2851                         "'NoneType' object has no attribute '%s'" % self.function.entry.name,
2852                         'PyExc_AttributeError')
2853                 expected_type = self_arg.type
2854                 self.coerced_self = CloneNode(self.self).coerce_to(
2855                     expected_type, env)
2856                 # Insert coerced 'self' argument into argument list.
2857                 self.args.insert(0, self.coerced_self)
2858             self.analyse_c_function_call(env)
2859     
2860     def function_type(self):
2861         # Return the type of the function being called, coercing a function
2862         # pointer to a function if necessary.
2863         func_type = self.function.type
2864         if func_type.is_ptr:
2865             func_type = func_type.base_type
2866         return func_type
2867     
2868     def analyse_c_function_call(self, env):
2869         if self.function.type is error_type:
2870             self.type = error_type
2871             return
2872         if self.function.type.is_cpp_class:
2873             overloaded_entry = self.function.type.scope.lookup("operator()")
2874             if overloaded_entry is None:
2875                 self.type = PyrexTypes.error_type
2876                 self.result_code = "<error>"
2877                 return
2878         elif hasattr(self.function, 'entry'):
2879             overloaded_entry = self.function.entry
2880         else:
2881             overloaded_entry = None
2882         if overloaded_entry:
2883             entry = PyrexTypes.best_match(self.args, overloaded_entry.all_alternatives(), self.pos)
2884             if not entry:
2885                 self.type = PyrexTypes.error_type
2886                 self.result_code = "<error>"
2887                 return
2888             self.function.entry = entry
2889             self.function.type = entry.type
2890             func_type = self.function_type()
2891         else:
2892             func_type = self.function_type()
2893             if not func_type.is_cfunction:
2894                 error(self.pos, "Calling non-function type '%s'" % func_type)
2895                 self.type = PyrexTypes.error_type
2896                 self.result_code = "<error>"
2897                 return
2898         # Check no. of args
2899         max_nargs = len(func_type.args)
2900         expected_nargs = max_nargs - func_type.optional_arg_count
2901         actual_nargs = len(self.args)
2902         if func_type.optional_arg_count and expected_nargs != actual_nargs:
2903             self.has_optional_args = 1
2904             self.is_temp = 1
2905         # Coerce arguments
2906         for i in range(min(max_nargs, actual_nargs)):
2907             formal_type = func_type.args[i].type
2908             self.args[i] = self.args[i].coerce_to(formal_type, env)
2909         for i in range(max_nargs, actual_nargs):
2910             if self.args[i].type.is_pyobject:
2911                 error(self.args[i].pos, 
2912                     "Python object cannot be passed as a varargs parameter")
2913         # Calc result type and code fragment
2914         if isinstance(self.function, NewExprNode):
2915             self.type = PyrexTypes.CPtrType(self.function.class_type)
2916         else:
2917             self.type = func_type.return_type
2918         if self.type.is_pyobject:
2919             self.result_ctype = py_object_type
2920             self.is_temp = 1
2921         elif func_type.exception_value is not None \
2922                  or func_type.exception_check:
2923             self.is_temp = 1
2924         # Called in 'nogil' context?
2925         self.nogil = env.nogil
2926         if (self.nogil and
2927             func_type.exception_check and
2928             func_type.exception_check != '+'):
2929             env.use_utility_code(pyerr_occurred_withgil_utility_code)
2930         # C++ exception handler
2931         if func_type.exception_check == '+':
2932             if func_type.exception_value is None:
2933                 env.use_utility_code(cpp_exception_utility_code)
2934
2935     def calculate_result_code(self):
2936         return self.c_call_code()
2937     
2938     def c_call_code(self):
2939         func_type = self.function_type()
2940         if self.type is PyrexTypes.error_type or not func_type.is_cfunction:
2941             return "<error>"
2942         formal_args = func_type.args
2943         arg_list_code = []
2944         args = zip(formal_args, self.args)
2945         max_nargs = len(func_type.args)
2946         expected_nargs = max_nargs - func_type.optional_arg_count
2947         actual_nargs = len(self.args)
2948         for formal_arg, actual_arg in args[:expected_nargs]:
2949                 arg_code = actual_arg.result_as(formal_arg.type)
2950                 arg_list_code.append(arg_code)
2951                 
2952         if func_type.is_overridable:
2953             arg_list_code.append(str(int(self.wrapper_call or self.function.entry.is_unbound_cmethod)))
2954                 
2955         if func_type.optional_arg_count:
2956             if expected_nargs == actual_nargs:
2957                 optional_args = 'NULL'
2958             else:
2959                 optional_args = "&%s" % self.opt_arg_struct
2960             arg_list_code.append(optional_args)
2961             
2962         for actual_arg in self.args[len(formal_args):]:
2963             arg_list_code.append(actual_arg.result())
2964         result = "%s(%s)" % (self.function.result(),
2965             ', '.join(arg_list_code))
2966         return result
2967     
2968     def generate_result_code(self, code):
2969         func_type = self.function_type()
2970         if func_type.is_pyobject:
2971             arg_code = self.arg_tuple.py_result()
2972             code.putln(
2973                 "%s = PyObject_Call(%s, %s, NULL); %s" % (
2974                     self.result(),
2975                     self.function.py_result(),
2976                     arg_code,
2977                     code.error_goto_if_null(self.result(), self.pos)))
2978             code.put_gotref(self.py_result())
2979         elif func_type.is_cfunction:
2980             if self.has_optional_args:
2981                 actual_nargs = len(self.args)
2982                 expected_nargs = len(func_type.args) - func_type.optional_arg_count
2983                 self.opt_arg_struct = code.funcstate.allocate_temp(
2984                     func_type.op_arg_struct.base_type, manage_ref=True)
2985                 code.putln("%s.%s = %s;" % (
2986                         self.opt_arg_struct,
2987                         Naming.pyrex_prefix + "n",
2988                         len(self.args) - expected_nargs))
2989                 args = zip(func_type.args, self.args)
2990                 for formal_arg, actual_arg in args[expected_nargs:actual_nargs]:
2991                     code.putln("%s.%s = %s;" % (
2992                             self.opt_arg_struct,
2993                             func_type.opt_arg_cname(formal_arg.name),
2994                             actual_arg.result_as(formal_arg.type)))
2995             exc_checks = []
2996             if self.type.is_pyobject and self.is_temp:
2997                 exc_checks.append("!%s" % self.result())
2998             else:
2999                 exc_val = func_type.exception_value
3000                 exc_check = func_type.exception_check
3001                 if exc_val is not None:
3002                     exc_checks.append("%s == %s" % (self.result(), exc_val))
3003                 if exc_check:
3004                     if self.nogil:
3005                         exc_checks.append("__Pyx_ErrOccurredWithGIL()")
3006                     else:    
3007                         exc_checks.append("PyErr_Occurred()")
3008             if self.is_temp or exc_checks:
3009                 rhs = self.c_call_code()
3010                 if self.result():
3011                     lhs = "%s = " % self.result()
3012                     if self.is_temp and self.type.is_pyobject:
3013                         #return_type = self.type # func_type.return_type
3014                         #print "SimpleCallNode.generate_result_code: casting", rhs, \
3015                         #    "from", return_type, "to pyobject" ###
3016                         rhs = typecast(py_object_type, self.type, rhs)
3017                 else:
3018                     lhs = ""
3019                 if func_type.exception_check == '+':
3020                     if func_type.exception_value is None:
3021                         raise_py_exception = "__Pyx_CppExn2PyErr()"
3022                     elif func_type.exception_value.type.is_pyobject:
3023                         raise_py_exception = ' try { throw; } catch(const std::exception& exn) { PyErr_SetString(%s, exn.what()); } catch(...) { PyErr_SetNone(%s); }' % (
3024                             func_type.exception_value.entry.cname,
3025                             func_type.exception_value.entry.cname)
3026                     else:
3027                         raise_py_exception = '%s(); if (!PyErr_Occurred()) PyErr_SetString(PyExc_RuntimeError , "Error converting c++ exception.")' % func_type.exception_value.entry.cname
3028                     if self.nogil:
3029                         raise_py_exception = 'Py_BLOCK_THREADS; %s; Py_UNBLOCK_THREADS' % raise_py_exception
3030                     code.putln(
3031                     "try {%s%s;} catch(...) {%s; %s}" % (
3032                         lhs,
3033                         rhs,
3034                         raise_py_exception,
3035                         code.error_goto(self.pos)))
3036                 else:
3037                     if exc_checks:
3038                         goto_error = code.error_goto_if(" && ".join(exc_checks), self.pos)
3039                     else:
3040                         goto_error = ""
3041                     code.putln("%s%s; %s" % (lhs, rhs, goto_error))
3042                 if self.type.is_pyobject and self.result():
3043                     code.put_gotref(self.py_result())
3044             if self.has_optional_args:
3045                 code.funcstate.release_temp(self.opt_arg_struct)
3046
3047
3048 class PythonCapiFunctionNode(ExprNode):
3049     subexprs = []
3050     def __init__(self, pos, py_name, cname, func_type, utility_code = None):
3051         self.pos = pos
3052         self.name = py_name
3053         self.cname = cname
3054         self.type = func_type
3055         self.utility_code = utility_code
3056
3057     def analyse_types(self, env):
3058         pass
3059
3060     def generate_result_code(self, code):
3061         if self.utility_code:
3062             code.globalstate.use_utility_code(self.utility_code)
3063
3064     def calculate_result_code(self):
3065         return self.cname
3066
3067 class PythonCapiCallNode(SimpleCallNode):
3068     # Python C-API Function call (only created in transforms)
3069
3070     # By default, we assume that the call never returns None, as this
3071     # is true for most C-API functions in CPython.  If this does not
3072     # apply to a call, set the following to True (or None to inherit
3073     # the default behaviour).
3074     may_return_none = False
3075
3076     def __init__(self, pos, function_name, func_type,
3077                  utility_code = None, py_name=None, **kwargs):
3078         self.type = func_type.return_type
3079         self.result_ctype = self.type
3080         self.function = PythonCapiFunctionNode(
3081             pos, py_name, function_name, func_type,
3082             utility_code = utility_code)
3083         # call this last so that we can override the constructed
3084         # attributes above with explicit keyword arguments if required
3085         SimpleCallNode.__init__(self, pos, **kwargs)
3086
3087
3088 class GeneralCallNode(CallNode):
3089     #  General Python function call, including keyword,
3090     #  * and ** arguments.
3091     #
3092     #  function         ExprNode
3093     #  positional_args  ExprNode          Tuple of positional arguments
3094     #  keyword_args     ExprNode or None  Dict of keyword arguments
3095     #  starstar_arg     ExprNode or None  Dict of extra keyword args
3096     
3097     type = py_object_type
3098     
3099     subexprs = ['function', 'positional_args', 'keyword_args', 'starstar_arg']
3100
3101     nogil_check = Node.gil_error
3102
3103     def compile_time_value(self, denv):
3104         function = self.function.compile_time_value(denv)
3105         positional_args = self.positional_args.compile_time_value(denv)
3106         keyword_args = self.keyword_args.compile_time_value(denv)
3107         starstar_arg = self.starstar_arg.compile_time_value(denv)
3108         try:
3109             keyword_args.update(starstar_arg)
3110             return function(*positional_args, **keyword_args)
3111         except Exception, e:
3112             self.compile_time_value_error(e)
3113             
3114     def explicit_args_kwds(self):
3115         if self.starstar_arg or not isinstance(self.positional_args, TupleNode):
3116             raise PostParseError(self.pos,
3117                 'Compile-time keyword arguments must be explicit.')
3118         return self.positional_args.args, self.keyword_args
3119
3120     def analyse_types(self, env):
3121         if self.analyse_as_type_constructor(env):
3122             return
3123         self.function.analyse_types(env)
3124         self.positional_args.analyse_types(env)
3125         if self.keyword_args:
3126             self.keyword_args.analyse_types(env)
3127         if self.starstar_arg:
3128             self.starstar_arg.analyse_types(env)
3129         if not self.function.type.is_pyobject:
3130             if self.function.type.is_error:
3131                 self.type = error_type
3132                 return
3133             if hasattr(self.function, 'entry') and not self.function.entry.as_variable:
3134                 error(self.pos, "Keyword and starred arguments not allowed in cdef functions.")
3135             else:
3136                 self.function = self.function.coerce_to_pyobject(env)
3137         self.positional_args = \
3138             self.positional_args.coerce_to_pyobject(env)
3139         if self.starstar_arg:
3140             self.starstar_arg = \
3141                 self.starstar_arg.coerce_to_pyobject(env)
3142         function = self.function
3143         if function.is_name and function.type_entry:
3144             # We are calling an extension type constructor.  As long
3145             # as we do not support __new__(), the result type is clear
3146             self.type = function.type_entry.type
3147             self.result_ctype = py_object_type
3148             self.may_return_none = False
3149         else:
3150             self.type = py_object_type
3151         self.is_temp = 1
3152         
3153     def generate_result_code(self, code):
3154         if self.type.is_error: return
3155         kwargs_call_function = "PyEval_CallObjectWithKeywords"
3156         if self.keyword_args and self.starstar_arg:
3157             code.put_error_if_neg(self.pos, 
3158                 "PyDict_Update(%s, %s)" % (
3159                     self.keyword_args.py_result(), 
3160                     self.starstar_arg.py_result()))
3161             keyword_code = self.keyword_args.py_result()
3162         elif self.keyword_args:
3163             keyword_code = self.keyword_args.py_result()
3164         elif self.starstar_arg:
3165             keyword_code = self.starstar_arg.py_result()
3166             if self.starstar_arg.type is not Builtin.dict_type:
3167                 # CPython supports calling functions with non-dicts, so do we
3168                 code.globalstate.use_utility_code(kwargs_call_utility_code)
3169                 kwargs_call_function = "__Pyx_PyEval_CallObjectWithKeywords"
3170         else:
3171             keyword_code = None
3172         if not keyword_code:
3173             call_code = "PyObject_Call(%s, %s, NULL)" % (
3174                 self.function.py_result(),
3175                 self.positional_args.py_result())
3176         else:
3177             call_code = "%s(%s, %s, %s)" % (
3178                 kwargs_call_function,
3179                 self.function.py_result(),
3180                 self.positional_args.py_result(),
3181                 keyword_code)
3182         code.putln(
3183             "%s = %s; %s" % (
3184                 self.result(),
3185                 call_code,
3186                 code.error_goto_if_null(self.result(), self.pos)))
3187         code.put_gotref(self.py_result())
3188
3189
3190 class AsTupleNode(ExprNode):
3191     #  Convert argument to tuple. Used for normalising
3192     #  the * argument of a function call.
3193     #
3194     #  arg    ExprNode
3195     
3196     subexprs = ['arg']
3197
3198     def calculate_constant_result(self):
3199         self.constant_result = tuple(self.base.constant_result)
3200     
3201     def compile_time_value(self, denv):
3202         arg = self.arg.compile_time_value(denv)
3203         try:
3204             return tuple(arg)
3205         except Exception, e:
3206             self.compile_time_value_error(e)
3207
3208     def analyse_types(self, env):
3209         self.arg.analyse_types(env)
3210         self.arg = self.arg.coerce_to_pyobject(env)
3211         self.type = tuple_type
3212         self.is_temp = 1
3213
3214     def may_be_none(self):
3215         return False
3216
3217     nogil_check = Node.gil_error
3218     gil_message = "Constructing Python tuple"
3219
3220     def generate_result_code(self, code):
3221         code.putln(
3222             "%s = PySequence_Tuple(%s); %s" % (
3223                 self.result(),
3224                 self.arg.py_result(),
3225                 code.error_goto_if_null(self.result(), self.pos)))
3226         code.put_gotref(self.py_result())
3227     
3228
3229 class AttributeNode(ExprNode):
3230     #  obj.attribute
3231     #
3232     #  obj          ExprNode
3233     #  attribute    string
3234     #  needs_none_check boolean        Used if obj is an extension type.
3235     #                                  If set to True, it is known that the type is not None.
3236     #
3237     #  Used internally:
3238     #
3239     #  is_py_attr           boolean   Is a Python getattr operation
3240     #  member               string    C name of struct member
3241     #  is_called            boolean   Function call is being done on result
3242     #  entry                Entry     Symbol table entry of attribute
3243     
3244     is_attribute = 1
3245     subexprs = ['obj']
3246     
3247     type = PyrexTypes.error_type
3248     entry = None
3249     is_called = 0
3250     needs_none_check = True
3251
3252     def as_cython_attribute(self):
3253         if isinstance(self.obj, NameNode) and self.obj.is_cython_module:
3254             return self.attribute
3255         cy = self.obj.as_cython_attribute()
3256         if cy:
3257             return "%s.%s" % (cy, self.attribute)
3258
3259     def coerce_to(self, dst_type, env):
3260         #  If coercing to a generic pyobject and this is a cpdef function
3261         #  we can create the corresponding attribute
3262         if dst_type is py_object_type:
3263             entry = self.entry
3264             if entry and entry.is_cfunction and entry.as_variable:
3265                 # must be a cpdef function
3266                 self.is_temp = 1
3267                 self.entry = entry.as_variable
3268                 self.analyse_as_python_attribute(env) 
3269                 return self
3270         return ExprNode.coerce_to(self, dst_type, env)
3271
3272     def calculate_constant_result(self):
3273         attr = self.attribute
3274         if attr.startswith("__") and attr.endswith("__"):
3275             return
3276         self.constant_result = getattr(self.obj.constant_result, attr)
3277
3278     def compile_time_value(self, denv):
3279         attr = self.attribute
3280         if attr.startswith("__") and attr.endswith("__"):
3281             error(self.pos,
3282                   "Invalid attribute name '%s' in compile-time expression" % attr)
3283             return None
3284         obj = self.obj.compile_time_value(denv)
3285         try:
3286             return getattr(obj, attr)
3287         except Exception, e:
3288             self.compile_time_value_error(e)
3289     
3290     def type_dependencies(self, env):
3291         return self.obj.type_dependencies(env)
3292     
3293     def infer_type(self, env):
3294         if self.analyse_as_cimported_attribute(env, 0):
3295             return self.entry.type
3296         elif self.analyse_as_unbound_cmethod(env):
3297             return self.entry.type
3298         else:
3299             self.analyse_attribute(env, obj_type = self.obj.infer_type(env))
3300             return self.type
3301
3302     def analyse_target_declaration(self, env):
3303         pass
3304     
3305     def analyse_target_types(self, env):
3306         self.analyse_types(env, target = 1)
3307     
3308     def analyse_types(self, env, target = 0):
3309         if self.analyse_as_cimported_attribute(env, target):
3310             return
3311         if not target and self.analyse_as_unbound_cmethod(env):
3312             return
3313         self.analyse_as_ordinary_attribute(env, target)
3314     
3315     def analyse_as_cimported_attribute(self, env, target):
3316         # Try to interpret this as a reference to an imported
3317         # C const, type, var or function. If successful, mutates
3318         # this node into a NameNode and returns 1, otherwise
3319         # returns 0.
3320         module_scope = self.obj.analyse_as_module(env)
3321         if module_scope:
3322             entry = module_scope.lookup_here(self.attribute)
3323             if entry and (
3324                 entry.is_cglobal or entry.is_cfunction
3325                 or entry.is_type or entry.is_const):
3326                     self.mutate_into_name_node(env, entry, target)
3327                     return 1
3328         return 0
3329     
3330     def analyse_as_unbound_cmethod(self, env):
3331         # Try to interpret this as a reference to an unbound
3332         # C method of an extension type. If successful, mutates
3333         # this node into a NameNode and returns 1, otherwise
3334         # returns 0.
3335         type = self.obj.analyse_as_extension_type(env)
3336         if type:
3337             entry = type.scope.lookup_here(self.attribute)
3338             if entry and entry.is_cmethod:
3339                 # Create a temporary entry describing the C method
3340                 # as an ordinary function.
3341                 ubcm_entry = Symtab.Entry(entry.name,
3342                     "%s->%s" % (type.vtabptr_cname, entry.cname),
3343                     entry.type)
3344                 ubcm_entry.is_cfunction = 1
3345                 ubcm_entry.func_cname = entry.func_cname
3346                 ubcm_entry.is_unbound_cmethod = 1
3347                 self.mutate_into_name_node(env, ubcm_entry, None)
3348                 return 1
3349         return 0
3350         
3351     def analyse_as_type(self, env):
3352         module_scope = self.obj.analyse_as_module(env)
3353         if module_scope:
3354             return module_scope.lookup_type(self.attribute)
3355         if not isinstance(self.obj, (UnicodeNode, StringNode, BytesNode)):
3356             base_type = self.obj.analyse_as_type(env)
3357             if base_type and hasattr(base_type, 'scope'):
3358                 return base_type.scope.lookup_type(self.attribute)
3359         return None
3360     
3361     def analyse_as_extension_type(self, env):
3362         # Try to interpret this as a reference to an extension type
3363         # in a cimported module. Returns the extension type, or None.
3364         module_scope = self.obj.analyse_as_module(env)
3365         if module_scope:
3366             entry = module_scope.lookup_here(self.attribute)
3367             if entry and entry.is_type and entry.type.is_extension_type:
3368                 return entry.type
3369         return None
3370     
3371     def analyse_as_module(self, env):
3372         # Try to interpret this as a reference to a cimported module
3373         # in another cimported module. Returns the module scope, or None.
3374         module_scope = self.obj.analyse_as_module(env)
3375         if module_scope:
3376             entry = module_scope.lookup_here(self.attribute)
3377             if entry and entry.as_module:
3378                 return entry.as_module
3379         return None
3380                 
3381     def mutate_into_name_node(self, env, entry, target):
3382         # Mutate this node into a NameNode and complete the
3383         # analyse_types phase.
3384         self.__class__ = NameNode
3385         self.name = self.attribute
3386         self.entry = entry
3387         del self.obj
3388         del self.attribute
3389         if target:
3390             NameNode.analyse_target_types(self, env)
3391         else:
3392             NameNode.analyse_rvalue_entry(self, env)
3393     
3394     def analyse_as_ordinary_attribute(self, env, target):
3395         self.obj.analyse_types(env)
3396         self.analyse_attribute(env)
3397         if self.entry and self.entry.is_cmethod and not self.is_called:
3398 #            error(self.pos, "C method can only be called")
3399             pass
3400         ## Reference to C array turns into pointer to first element.
3401         #while self.type.is_array:
3402         #    self.type = self.type.element_ptr_type()
3403         if self.is_py_attr:
3404             if not target:
3405                 self.is_temp = 1
3406                 self.result_ctype = py_object_type
3407     
3408     def analyse_attribute(self, env, obj_type = None):
3409         # Look up attribute and set self.type and self.member.
3410         self.is_py_attr = 0
3411         self.member = self.attribute
3412         if obj_type is None:
3413             if self.obj.type.is_string:
3414                 self.obj = self.obj.coerce_to_pyobject(env)
3415             obj_type = self.obj.type
3416         else:
3417             if obj_type.is_string:
3418                 obj_type = py_object_type
3419         if obj_type.is_ptr or obj_type.is_array:
3420             obj_type = obj_type.base_type
3421             self.op = "->"
3422         elif obj_type.is_extension_type:
3423             self.op = "->"
3424         else:
3425             self.op = "."
3426         if obj_type.has_attributes:
3427             entry = None
3428             if obj_type.attributes_known():
3429                 entry = obj_type.scope.lookup_here(self.attribute)
3430                 if entry and entry.is_member:
3431                     entry = None
3432             else:
3433                 error(self.pos, 
3434                     "Cannot select attribute of incomplete type '%s'" 
3435                     % obj_type)
3436                 self.type = PyrexTypes.error_type
3437                 return
3438             self.entry = entry
3439             if entry:
3440                 if obj_type.is_extension_type and entry.name == "__weakref__":
3441                     error(self.pos, "Illegal use of special attribute __weakref__")
3442                 # methods need the normal attribute lookup
3443                 # because they do not have struct entries
3444                 if entry.is_variable or entry.is_cmethod:
3445                     self.type = entry.type
3446                     self.member = entry.cname
3447                     return
3448                 else:
3449                     # If it's not a variable or C method, it must be a Python
3450                     # method of an extension type, so we treat it like a Python
3451                     # attribute.
3452                     pass
3453         # If we get here, the base object is not a struct/union/extension 
3454         # type, or it is an extension type and the attribute is either not
3455         # declared or is declared as a Python method. Treat it as a Python
3456         # attribute reference.
3457         self.analyse_as_python_attribute(env, obj_type)
3458
3459     def analyse_as_python_attribute(self, env, obj_type = None):
3460         if obj_type is None:
3461             obj_type = self.obj.type
3462         self.member = self.attribute
3463         self.type = py_object_type
3464         self.is_py_attr = 1
3465         if not obj_type.is_pyobject and not obj_type.is_error:
3466             if obj_type.can_coerce_to_pyobject(env):
3467                 self.obj = self.obj.coerce_to_pyobject(env)
3468             else:
3469                 error(self.pos,
3470                       "Object of type '%s' has no attribute '%s'" %
3471                       (obj_type, self.attribute))
3472
3473     def nogil_check(self, env):
3474         if self.is_py_attr:
3475             self.gil_error()
3476
3477     gil_message = "Accessing Python attribute"
3478
3479     def is_simple(self):
3480         if self.obj:
3481             return self.result_in_temp() or self.obj.is_simple()
3482         else:
3483             return NameNode.is_simple(self)
3484
3485     def is_lvalue(self):
3486         if self.obj:
3487             return 1
3488         else:
3489             return NameNode.is_lvalue(self)
3490     
3491     def is_ephemeral(self):
3492         if self.obj:
3493             return self.obj.is_ephemeral()
3494         else:
3495             return NameNode.is_ephemeral(self)
3496     
3497     def calculate_result_code(self):
3498         #print "AttributeNode.calculate_result_code:", self.member ###
3499         #print "...obj node =", self.obj, "code", self.obj.result() ###
3500         #print "...obj type", self.obj.type, "ctype", self.obj.ctype() ###
3501         obj = self.obj
3502         obj_code = obj.result_as(obj.type)
3503         #print "...obj_code =", obj_code ###
3504         if self.entry and self.entry.is_cmethod:
3505             if obj.type.is_extension_type:
3506                 return "((struct %s *)%s%s%s)->%s" % (
3507                     obj.type.vtabstruct_cname, obj_code, self.op, 
3508                     obj.type.vtabslot_cname, self.member)
3509             else:
3510                 return self.member
3511         elif obj.type.is_complex:
3512             return "__Pyx_C%s(%s)" % (self.member.upper(), obj_code)
3513         else:
3514             return "%s%s%s" % (obj_code, self.op, self.member)
3515     
3516     def generate_result_code(self, code):
3517         interned_attr_cname = code.intern_identifier(self.attribute)
3518         if self.is_py_attr:
3519             code.putln(
3520                 '%s = PyObject_GetAttr(%s, %s); %s' % (
3521                     self.result(),
3522                     self.obj.py_result(),
3523                     interned_attr_cname,
3524                     code.error_goto_if_null(self.result(), self.pos)))
3525             code.put_gotref(self.py_result())
3526         else:
3527             # result_code contains what is needed, but we may need to insert
3528             # a check and raise an exception
3529             if (self.obj.type.is_extension_type
3530                   and self.needs_none_check
3531                   and code.globalstate.directives['nonecheck']):
3532                 self.put_nonecheck(code)
3533     
3534     def generate_assignment_code(self, rhs, code):
3535         interned_attr_cname = code.intern_identifier(self.attribute)
3536         self.obj.generate_evaluation_code(code)
3537         if self.is_py_attr:
3538             code.put_error_if_neg(self.pos, 
3539                 'PyObject_SetAttr(%s, %s, %s)' % (
3540                     self.obj.py_result(),
3541                     interned_attr_cname,
3542                     rhs.py_result()))
3543             rhs.generate_disposal_code(code)
3544             rhs.free_temps(code)
3545         elif self.obj.type.is_complex:
3546             code.putln("__Pyx_SET_C%s(%s, %s);" % (
3547                 self.member.upper(),
3548                 self.obj.result_as(self.obj.type),
3549                 rhs.result_as(self.ctype())))
3550         else:
3551             if (self.obj.type.is_extension_type
3552                   and self.needs_none_check
3553                   and code.globalstate.directives['nonecheck']):
3554                 self.put_nonecheck(code)
3555
3556             select_code = self.result()
3557             if self.type.is_pyobject and self.use_managed_ref:
3558                 rhs.make_owned_reference(code)
3559                 code.put_giveref(rhs.py_result())
3560                 code.put_gotref(select_code)
3561                 code.put_decref(select_code, self.ctype())
3562             code.putln(
3563                 "%s = %s;" % (
3564                     select_code,
3565                     rhs.result_as(self.ctype())))
3566                     #rhs.result()))
3567             rhs.generate_post_assignment_code(code)
3568             rhs.free_temps(code)
3569         self.obj.generate_disposal_code(code)
3570         self.obj.free_temps(code)
3571     
3572     def generate_deletion_code(self, code):
3573         interned_attr_cname = code.intern_identifier(self.attribute)
3574         self.obj.generate_evaluation_code(code)
3575         if self.is_py_attr or (isinstance(self.entry.scope, Symtab.PropertyScope)
3576                                and self.entry.scope.entries.has_key(u'__del__')):
3577             code.put_error_if_neg(self.pos,
3578                 'PyObject_DelAttr(%s, %s)' % (
3579                     self.obj.py_result(),
3580                     interned_attr_cname))
3581         else:
3582             error(self.pos, "Cannot delete C attribute of extension type")
3583         self.obj.generate_disposal_code(code)
3584         self.obj.free_temps(code)
3585         
3586     def annotate(self, code):
3587         if self.is_py_attr:
3588             code.annotate(self.pos, AnnotationItem('py_attr', 'python attribute', size=len(self.attribute)))
3589         else:
3590             code.annotate(self.pos, AnnotationItem('c_attr', 'c attribute', size=len(self.attribute)))
3591
3592     def put_nonecheck(self, code):
3593         code.globalstate.use_utility_code(raise_noneattr_error_utility_code)
3594         code.putln("if (%s) {" % code.unlikely("%s == Py_None") % self.obj.result_as(PyrexTypes.py_object_type))
3595         code.putln("__Pyx_RaiseNoneAttributeError(\"%s\");" % self.attribute)
3596         code.putln(code.error_goto(self.pos))
3597         code.putln("}")
3598
3599
3600 #-------------------------------------------------------------------
3601 #
3602 #  Constructor nodes
3603 #
3604 #-------------------------------------------------------------------
3605
3606 class StarredTargetNode(ExprNode):
3607     #  A starred expression like "*a"
3608     #
3609     #  This is only allowed in sequence assignment targets such as
3610     #
3611     #      a, *b = (1,2,3,4)    =>     a = 1 ; b = [2,3,4]
3612     #
3613     #  and will be removed during type analysis (or generate an error
3614     #  if it's found at unexpected places).
3615     #
3616     #  target          ExprNode
3617
3618     subexprs = ['target']
3619     is_starred = 1
3620     type = py_object_type
3621     is_temp = 1
3622
3623     def __init__(self, pos, target):
3624         self.pos = pos
3625         self.target = target
3626
3627     def analyse_declarations(self, env):
3628         error(self.pos, "can use starred expression only as assignment target")
3629         self.target.analyse_declarations(env)
3630
3631     def analyse_types(self, env):
3632         error(self.pos, "can use starred expression only as assignment target")
3633         self.target.analyse_types(env)
3634         self.type = self.target.type
3635
3636     def analyse_target_declaration(self, env):
3637         self.target.analyse_target_declaration(env)
3638
3639     def analyse_target_types(self, env):
3640         self.target.analyse_target_types(env)
3641         self.type = self.target.type
3642
3643     def calculate_result_code(self):
3644         return ""
3645
3646     def generate_result_code(self, code):
3647         pass
3648
3649
3650 class SequenceNode(ExprNode):
3651     #  Base class for list and tuple constructor nodes.
3652     #  Contains common code for performing sequence unpacking.
3653     #
3654     #  args                    [ExprNode]
3655     #  iterator                ExprNode
3656     #  unpacked_items          [ExprNode] or None
3657     #  coerced_unpacked_items  [ExprNode] or None
3658     
3659     subexprs = ['args']
3660     
3661     is_sequence_constructor = 1
3662     unpacked_items = None
3663
3664     def compile_time_value_list(self, denv):
3665         return [arg.compile_time_value(denv) for arg in self.args]
3666
3667     def replace_starred_target_node(self):
3668         # replace a starred node in the targets by the contained expression
3669         self.starred_assignment = False
3670         args = []
3671         for arg in self.args:
3672             if arg.is_starred:
3673                 if self.starred_assignment:
3674                     error(arg.pos, "more than 1 starred expression in assignment")
3675                 self.starred_assignment = True
3676                 arg = arg.target
3677                 arg.is_starred = True
3678             args.append(arg)
3679         self.args = args
3680
3681     def analyse_target_declaration(self, env):
3682         self.replace_starred_target_node()
3683         for arg in self.args:
3684             arg.analyse_target_declaration(env)
3685
3686     def analyse_types(self, env, skip_children=False):
3687         for i in range(len(self.args)):
3688             arg = self.args[i]
3689             if not skip_children: arg.analyse_types(env)
3690             self.args[i] = arg.coerce_to_pyobject(env)
3691         self.is_temp = 1
3692         # not setting self.type here, subtypes do this
3693
3694     def may_be_none(self):
3695         return False
3696
3697     def analyse_target_types(self, env):
3698         self.iterator = PyTempNode(self.pos, env)
3699         self.unpacked_items = []
3700         self.coerced_unpacked_items = []
3701         for arg in self.args:
3702             arg.analyse_target_types(env)
3703             if arg.is_starred:
3704                 if not arg.type.assignable_from(Builtin.list_type):
3705                     error(arg.pos,
3706                           "starred target must have Python object (list) type")
3707                 if arg.type is py_object_type:
3708                     arg.type = Builtin.list_type
3709             unpacked_item = PyTempNode(self.pos, env)
3710             coerced_unpacked_item = unpacked_item.coerce_to(arg.type, env)
3711             self.unpacked_items.append(unpacked_item)
3712             self.coerced_unpacked_items.append(coerced_unpacked_item)
3713         self.type = py_object_type
3714
3715     def generate_result_code(self, code):
3716         self.generate_operation_code(code)
3717     
3718     def generate_assignment_code(self, rhs, code):
3719         if self.starred_assignment:
3720             self.generate_starred_assignment_code(rhs, code)
3721         else:
3722             self.generate_parallel_assignment_code(rhs, code)
3723
3724         for item in self.unpacked_items:
3725             item.release(code)
3726         rhs.free_temps(code)
3727
3728     def generate_parallel_assignment_code(self, rhs, code):
3729         # Need to work around the fact that generate_evaluation_code
3730         # allocates the temps in a rather hacky way -- the assignment
3731         # is evaluated twice, within each if-block.
3732
3733         if rhs.type is tuple_type:
3734             tuple_check = "likely(%s != Py_None)"
3735         else:
3736             tuple_check = "PyTuple_CheckExact(%s)"
3737         code.putln(
3738             "if (%s && likely(PyTuple_GET_SIZE(%s) == %s)) {" % (
3739                 tuple_check % rhs.py_result(), 
3740                 rhs.py_result(), 
3741                 len(self.args)))
3742         code.putln("PyObject* tuple = %s;" % rhs.py_result())
3743         for item in self.unpacked_items:
3744             item.allocate(code)
3745         for i in range(len(self.args)):
3746             item = self.unpacked_items[i]
3747             code.put(
3748                 "%s = PyTuple_GET_ITEM(tuple, %s); " % (
3749                     item.result(),
3750                     i))
3751             code.put_incref(item.result(), item.ctype())
3752             value_node = self.coerced_unpacked_items[i]
3753             value_node.generate_evaluation_code(code)
3754         rhs.generate_disposal_code(code)
3755
3756         for i in range(len(self.args)):
3757             self.args[i].generate_assignment_code(
3758                 self.coerced_unpacked_items[i], code)
3759                  
3760         code.putln("} else {")
3761
3762         if rhs.type is tuple_type:
3763             code.globalstate.use_utility_code(tuple_unpacking_error_code)
3764             code.putln("__Pyx_UnpackTupleError(%s, %s);" % (
3765                         rhs.py_result(), len(self.args)))
3766             code.putln(code.error_goto(self.pos))
3767         else:
3768             code.globalstate.use_utility_code(unpacking_utility_code)
3769
3770             self.iterator.allocate(code)
3771             code.putln(
3772                 "%s = PyObject_GetIter(%s); %s" % (
3773                     self.iterator.result(),
3774                     rhs.py_result(),
3775                     code.error_goto_if_null(self.iterator.result(), self.pos)))
3776             code.put_gotref(self.iterator.py_result())
3777             rhs.generate_disposal_code(code)
3778             for i in range(len(self.args)):
3779                 item = self.unpacked_items[i]
3780                 unpack_code = "__Pyx_UnpackItem(%s, %d)" % (
3781                     self.iterator.py_result(), i)
3782                 code.putln(
3783                     "%s = %s; %s" % (
3784                         item.result(),
3785                         typecast(item.ctype(), py_object_type, unpack_code),
3786                         code.error_goto_if_null(item.result(), self.pos)))
3787                 code.put_gotref(item.py_result())
3788                 value_node = self.coerced_unpacked_items[i]
3789                 value_node.generate_evaluation_code(code)
3790             code.put_error_if_neg(self.pos, "__Pyx_EndUnpack(%s, %d)" % (
3791                 self.iterator.py_result(),
3792                 len(self.args)))
3793             if debug_disposal_code:
3794                 print("UnpackNode.generate_assignment_code:")
3795                 print("...generating disposal code for %s" % self.iterator)
3796             self.iterator.generate_disposal_code(code)
3797             self.iterator.free_temps(code)
3798             self.iterator.release(code)
3799
3800             for i in range(len(self.args)):
3801                 self.args[i].generate_assignment_code(
3802                     self.coerced_unpacked_items[i], code)
3803
3804         code.putln("}")
3805
3806     def generate_starred_assignment_code(self, rhs, code):
3807         code.globalstate.use_utility_code(unpacking_utility_code)
3808
3809         for i, arg in enumerate(self.args):
3810             if arg.is_starred:
3811                 starred_target = self.unpacked_items[i]
3812                 fixed_args_left  = self.args[:i]
3813                 fixed_args_right = self.args[i+1:]
3814                 break
3815
3816         self.iterator.allocate(code)
3817         code.putln(
3818             "%s = PyObject_GetIter(%s); %s" % (
3819                 self.iterator.result(),
3820                 rhs.py_result(),
3821                 code.error_goto_if_null(self.iterator.result(), self.pos)))
3822         code.put_gotref(self.iterator.py_result())
3823         rhs.generate_disposal_code(code)
3824
3825         for item in self.unpacked_items:
3826             item.allocate(code)
3827         for i in range(len(fixed_args_left)):
3828             item = self.unpacked_items[i]
3829             unpack_code = "__Pyx_UnpackItem(%s, %d)" % (
3830                 self.iterator.py_result(), i)
3831             code.putln(
3832                 "%s = %s; %s" % (
3833                     item.result(),
3834                     typecast(item.ctype(), py_object_type, unpack_code),
3835                     code.error_goto_if_null(item.result(), self.pos)))
3836             code.put_gotref(item.py_result())
3837             value_node = self.coerced_unpacked_items[i]
3838             value_node.generate_evaluation_code(code)
3839
3840         target_list = starred_target.result()
3841         code.putln("%s = PySequence_List(%s); %s" % (
3842             target_list, self.iterator.py_result(),
3843             code.error_goto_if_null(target_list, self.pos)))
3844         code.put_gotref(target_list)
3845         if fixed_args_right:
3846             code.globalstate.use_utility_code(raise_need_more_values_to_unpack)
3847             unpacked_right_args = self.unpacked_items[-len(fixed_args_right):]
3848             code.putln("if (unlikely(PyList_GET_SIZE(%s) < %d)) {" % (
3849                 (target_list, len(unpacked_right_args))))
3850             code.put("__Pyx_RaiseNeedMoreValuesError(%d+PyList_GET_SIZE(%s)); %s" % (
3851                      len(fixed_args_left), target_list,
3852                      code.error_goto(self.pos)))
3853             code.putln('}')
3854             for i, (arg, coerced_arg) in enumerate(zip(unpacked_right_args[::-1],
3855                                                        self.coerced_unpacked_items[::-1])):
3856                 code.putln(
3857                     "%s = PyList_GET_ITEM(%s, PyList_GET_SIZE(%s)-1); " % (
3858                         arg.py_result(),
3859                         target_list, target_list))
3860                 # resize the list the hard way
3861                 code.putln("((PyVarObject*)%s)->ob_size--;" % target_list)
3862                 code.put_gotref(arg.py_result())
3863                 coerced_arg.generate_evaluation_code(code)
3864
3865         self.iterator.generate_disposal_code(code)
3866         self.iterator.free_temps(code)
3867         self.iterator.release(code)
3868
3869         for i in range(len(self.args)):
3870             self.args[i].generate_assignment_code(
3871                 self.coerced_unpacked_items[i], code)
3872
3873     def annotate(self, code):
3874         for arg in self.args:
3875             arg.annotate(code)
3876         if self.unpacked_items:
3877             for arg in self.unpacked_items:
3878                 arg.annotate(code)
3879             for arg in self.coerced_unpacked_items:
3880                 arg.annotate(code)
3881
3882
3883 class TupleNode(SequenceNode):
3884     #  Tuple constructor.
3885     
3886     type = tuple_type
3887
3888     gil_message = "Constructing Python tuple"
3889
3890     def analyse_types(self, env, skip_children=False):
3891         if len(self.args) == 0:
3892             self.is_temp = 0
3893             self.is_literal = 1
3894         else:
3895             SequenceNode.analyse_types(self, env, skip_children)
3896
3897     def calculate_result_code(self):
3898         if len(self.args) > 0:
3899             error(self.pos, "Positive length tuples must be constructed.")
3900         else:
3901             return Naming.empty_tuple
3902
3903     def calculate_constant_result(self):
3904         self.constant_result = tuple([
3905                 arg.constant_result for arg in self.args])
3906
3907     def compile_time_value(self, denv):
3908         values = self.compile_time_value_list(denv)
3909         try:
3910             return tuple(values)
3911         except Exception, e:
3912             self.compile_time_value_error(e)
3913     
3914     def generate_operation_code(self, code):
3915         if len(self.args) == 0:
3916             # result_code is Naming.empty_tuple
3917             return
3918         code.putln(
3919             "%s = PyTuple_New(%s); %s" % (
3920                 self.result(),
3921                 len(self.args),
3922                 code.error_goto_if_null(self.result(), self.pos)))
3923         code.put_gotref(self.py_result())
3924         for i in range(len(self.args)):
3925             arg = self.args[i]
3926             if not arg.result_in_temp():
3927                 code.put_incref(arg.result(), arg.ctype())
3928             code.putln(
3929                 "PyTuple_SET_ITEM(%s, %s, %s);" % (
3930                     self.result(),
3931                     i,
3932                     arg.py_result()))
3933             code.put_giveref(arg.py_result())
3934     
3935     def generate_subexpr_disposal_code(self, code):
3936         # We call generate_post_assignment_code here instead
3937         # of generate_disposal_code, because values were stored
3938         # in the tuple using a reference-stealing operation.
3939         for arg in self.args:
3940             arg.generate_post_assignment_code(code)
3941             # Should NOT call free_temps -- this is invoked by the default
3942             # generate_evaluation_code which will do that.
3943
3944
3945 class ListNode(SequenceNode):
3946     #  List constructor.
3947     
3948     # obj_conversion_errors    [PyrexError]   used internally
3949     # orignial_args            [ExprNode]     used internally
3950
3951     obj_conversion_errors = []
3952     type = list_type
3953
3954     gil_message = "Constructing Python list"
3955     
3956     def type_dependencies(self, env):
3957         return ()
3958     
3959     def infer_type(self, env):
3960         # TOOD: Infer non-object list arrays.
3961         return list_type
3962
3963     def analyse_expressions(self, env):
3964         SequenceNode.analyse_expressions(self, env)
3965         self.coerce_to_pyobject(env)
3966
3967     def analyse_types(self, env):
3968         hold_errors()
3969         self.original_args = list(self.args)
3970         SequenceNode.analyse_types(self, env)
3971         self.obj_conversion_errors = held_errors()
3972         release_errors(ignore=True)
3973         
3974     def coerce_to(self, dst_type, env):
3975         if dst_type.is_pyobject:
3976             for err in self.obj_conversion_errors:
3977                 report_error(err)
3978             self.obj_conversion_errors = []
3979             if not self.type.subtype_of(dst_type):
3980                 error(self.pos, "Cannot coerce list to type '%s'" % dst_type)
3981         elif dst_type.is_ptr:
3982             base_type = dst_type.base_type
3983             self.type = PyrexTypes.CArrayType(base_type, len(self.args))
3984             for i in range(len(self.original_args)):
3985                 arg = self.args[i]
3986                 if isinstance(arg, CoerceToPyTypeNode):
3987                     arg = arg.arg
3988                 self.args[i] = arg.coerce_to(base_type, env)
3989         elif dst_type.is_struct:
3990             if len(self.args) > len(dst_type.scope.var_entries):
3991                 error(self.pos, "Too may members for '%s'" % dst_type)
3992             else:
3993                 if len(self.args) < len(dst_type.scope.var_entries):
3994                     warning(self.pos, "Too few members for '%s'" % dst_type, 1)
3995                 for i, (arg, member) in enumerate(zip(self.original_args, dst_type.scope.var_entries)):
3996                     if isinstance(arg, CoerceToPyTypeNode):
3997                         arg = arg.arg
3998                     self.args[i] = arg.coerce_to(member.type, env)
3999             self.type = dst_type
4000         else:
4001             self.type = error_type
4002             error(self.pos, "Cannot coerce list to type '%s'" % dst_type)
4003         return self
4004         
4005     def release_temp(self, env):
4006         if self.type.is_array:
4007             # To be valid C++, we must allocate the memory on the stack 
4008             # manually and be sure not to reuse it for something else. 
4009             pass
4010         else:
4011             SequenceNode.release_temp(self, env)
4012
4013     def calculate_constant_result(self):
4014         self.constant_result = [
4015             arg.constant_result for arg in self.args]
4016
4017     def compile_time_value(self, denv):
4018         return self.compile_time_value_list(denv)
4019
4020     def generate_operation_code(self, code):
4021         if self.type.is_pyobject:
4022             for err in self.obj_conversion_errors:
4023                 report_error(err)
4024             code.putln("%s = PyList_New(%s); %s" %
4025                 (self.result(),
4026                 len(self.args),
4027                 code.error_goto_if_null(self.result(), self.pos)))
4028             code.put_gotref(self.py_result())
4029             for i in range(len(self.args)):
4030                 arg = self.args[i]
4031                 #if not arg.is_temp:
4032                 if not arg.result_in_temp():
4033                     code.put_incref(arg.result(), arg.ctype())
4034                 code.putln("PyList_SET_ITEM(%s, %s, %s);" %
4035                     (self.result(),
4036                     i,
4037                     arg.py_result()))
4038                 code.put_giveref(arg.py_result())
4039         elif self.type.is_array:
4040             for i, arg in enumerate(self.args):
4041                 code.putln("%s[%s] = %s;" % (
4042                                 self.result(),
4043                                 i,
4044                                 arg.result()))
4045         elif self.type.is_struct:
4046             for arg, member in zip(self.args, self.type.scope.var_entries):
4047                 code.putln("%s.%s = %s;" % (
4048                         self.result(),
4049                         member.cname,
4050                         arg.result()))
4051         else:
4052             raise InternalError("List type never specified")
4053
4054     def generate_subexpr_disposal_code(self, code):
4055         # We call generate_post_assignment_code here instead
4056         # of generate_disposal_code, because values were stored
4057         # in the list using a reference-stealing operation.
4058         for arg in self.args:
4059             arg.generate_post_assignment_code(code)
4060             # Should NOT call free_temps -- this is invoked by the default
4061             # generate_evaluation_code which will do that.
4062
4063
4064 class ScopedExprNode(ExprNode):
4065     # Abstract base class for ExprNodes that have their own local
4066     # scope, such as generator expressions.
4067     #
4068     # expr_scope    Scope  the inner scope of the expression
4069
4070     subexprs = []
4071     expr_scope = None
4072
4073     def analyse_types(self, env):
4074         # nothing to do here, the children will be analysed separately
4075         pass
4076
4077     def analyse_expressions(self, env):
4078         # nothing to do here, the children will be analysed separately
4079         pass
4080
4081     def analyse_scoped_expressions(self, env):
4082         # this is called with the expr_scope as env
4083         pass
4084
4085     def init_scope(self, outer_scope, expr_scope=None):
4086         self.expr_scope = expr_scope
4087
4088
4089 class ComprehensionNode(ScopedExprNode):
4090     subexprs = ["target"]
4091     child_attrs = ["loop", "append"]
4092
4093     # leak loop variables or not?  non-leaking Py3 behaviour is
4094     # default, except for list comprehensions where the behaviour
4095     # differs in Py2 and Py3 (see Parsing.py)
4096     has_local_scope = True
4097
4098     def infer_type(self, env):
4099         return self.target.infer_type(env)
4100
4101     def analyse_declarations(self, env):
4102         self.append.target = self # this is used in the PyList_Append of the inner loop
4103         self.init_scope(env)
4104         if self.expr_scope is not None:
4105             self.loop.analyse_declarations(self.expr_scope)
4106         else:
4107             self.loop.analyse_declarations(env)
4108
4109     def init_scope(self, outer_scope, expr_scope=None):
4110         if expr_scope is not None:
4111             self.expr_scope = expr_scope
4112         elif self.has_local_scope:
4113             self.expr_scope = Symtab.GeneratorExpressionScope(outer_scope)
4114         else:
4115             self.expr_scope = None
4116
4117     def analyse_types(self, env):
4118         self.target.analyse_expressions(env)
4119         self.type = self.target.type
4120         if not self.has_local_scope:
4121             self.loop.analyse_expressions(env)
4122
4123     def analyse_expressions(self, env):
4124         self.analyse_types(env)
4125
4126     def analyse_scoped_expressions(self, env):
4127         if self.has_local_scope:
4128             self.loop.analyse_expressions(env)
4129
4130     def may_be_none(self):
4131         return False
4132
4133     def calculate_result_code(self):
4134         return self.target.result()
4135     
4136     def generate_result_code(self, code):
4137         self.generate_operation_code(code)
4138
4139     def generate_operation_code(self, code):
4140         self.loop.generate_execution_code(code)
4141
4142     def annotate(self, code):
4143         self.loop.annotate(code)
4144
4145
4146 class ComprehensionAppendNode(Node):
4147     # Need to be careful to avoid infinite recursion:
4148     # target must not be in child_attrs/subexprs
4149
4150     child_attrs = ['expr']
4151
4152     type = PyrexTypes.c_int_type
4153     
4154     def analyse_expressions(self, env):
4155         self.expr.analyse_expressions(env)
4156         if not self.expr.type.is_pyobject:
4157             self.expr = self.expr.coerce_to_pyobject(env)
4158
4159     def generate_execution_code(self, code):
4160         if self.target.type is list_type:
4161             function = "PyList_Append"
4162         elif self.target.type is set_type:
4163             function = "PySet_Add"
4164         else:
4165             raise InternalError(
4166                 "Invalid type for comprehension node: %s" % self.target.type)
4167
4168         self.expr.generate_evaluation_code(code)
4169         code.putln(code.error_goto_if("%s(%s, (PyObject*)%s)" % (
4170             function,
4171             self.target.result(),
4172             self.expr.result()
4173             ), self.pos))
4174         self.expr.generate_disposal_code(code)
4175         self.expr.free_temps(code)
4176
4177     def generate_function_definitions(self, env, code):
4178         self.expr.generate_function_definitions(env, code)
4179
4180     def annotate(self, code):
4181         self.expr.annotate(code)
4182
4183 class DictComprehensionAppendNode(ComprehensionAppendNode):
4184     child_attrs = ['key_expr', 'value_expr']
4185
4186     def analyse_expressions(self, env):
4187         self.key_expr.analyse_expressions(env)
4188         if not self.key_expr.type.is_pyobject:
4189             self.key_expr = self.key_expr.coerce_to_pyobject(env)
4190         self.value_expr.analyse_expressions(env)
4191         if not self.value_expr.type.is_pyobject:
4192             self.value_expr = self.value_expr.coerce_to_pyobject(env)
4193
4194     def generate_execution_code(self, code):
4195         self.key_expr.generate_evaluation_code(code)
4196         self.value_expr.generate_evaluation_code(code)
4197         code.putln(code.error_goto_if("PyDict_SetItem(%s, (PyObject*)%s, (PyObject*)%s)" % (
4198             self.target.result(),
4199             self.key_expr.result(),
4200             self.value_expr.result()
4201             ), self.pos))
4202         self.key_expr.generate_disposal_code(code)
4203         self.key_expr.free_temps(code)
4204         self.value_expr.generate_disposal_code(code)
4205         self.value_expr.free_temps(code)
4206
4207     def generate_function_definitions(self, env, code):
4208         self.key_expr.generate_function_definitions(env, code)
4209         self.value_expr.generate_function_definitions(env, code)
4210
4211     def annotate(self, code):
4212         self.key_expr.annotate(code)
4213         self.value_expr.annotate(code)
4214
4215
4216 class GeneratorExpressionNode(ScopedExprNode):
4217     # A generator expression, e.g.  (i for i in range(10))
4218     #
4219     # Result is a generator.
4220     #
4221     # loop      ForStatNode   the for-loop, containing a YieldExprNode
4222
4223     child_attrs = ["loop"]
4224
4225     type = py_object_type
4226
4227     def analyse_declarations(self, env):
4228         self.init_scope(env)
4229         self.loop.analyse_declarations(self.expr_scope)
4230
4231     def init_scope(self, outer_scope, expr_scope=None):
4232         if expr_scope is not None:
4233             self.expr_scope = expr_scope
4234         else:
4235             self.expr_scope = Symtab.GeneratorExpressionScope(outer_scope)
4236
4237     def analyse_types(self, env):
4238         self.is_temp = True
4239
4240     def analyse_scoped_expressions(self, env):
4241         self.loop.analyse_expressions(env)
4242
4243     def may_be_none(self):
4244         return False
4245
4246     def annotate(self, code):
4247         self.loop.annotate(code)
4248
4249
4250 class InlinedGeneratorExpressionNode(GeneratorExpressionNode):
4251     # An inlined generator expression for which the result is
4252     # calculated inside of the loop.  This will only be created by
4253     # transforms when replacing builtin calls on generator
4254     # expressions.
4255     #
4256     # loop           ForStatNode      the for-loop, not containing any YieldExprNodes
4257     # result_node    ResultRefNode    the reference to the result value temp
4258     # orig_func      String           the name of the builtin function this node replaces
4259
4260     child_attrs = ["loop"]
4261
4262     def analyse_types(self, env):
4263         self.type = self.result_node.type
4264         self.is_temp = True
4265
4266     def coerce_to(self, dst_type, env):
4267         if self.orig_func == 'sum' and dst_type.is_numeric:
4268             # we can optimise by dropping the aggregation variable into C
4269             self.result_node.type = self.type = dst_type
4270             return self
4271         return GeneratorExpressionNode.coerce_to(self, dst_type, env)
4272
4273     def generate_result_code(self, code):
4274         self.result_node.result_code = self.result()
4275         self.loop.generate_execution_code(code)
4276
4277
4278 class SetNode(ExprNode):
4279     #  Set constructor.
4280
4281     type = set_type
4282
4283     subexprs = ['args']
4284
4285     gil_message = "Constructing Python set"
4286     
4287     def analyse_types(self, env):
4288         for i in range(len(self.args)):
4289             arg = self.args[i]
4290             arg.analyse_types(env)
4291             self.args[i] = arg.coerce_to_pyobject(env)
4292         self.type = set_type
4293         self.is_temp = 1
4294
4295     def may_be_none(self):
4296         return False
4297
4298     def calculate_constant_result(self):
4299         self.constant_result = set([
4300                 arg.constant_result for arg in self.args])
4301
4302     def compile_time_value(self, denv):
4303         values = [arg.compile_time_value(denv) for arg in self.args]
4304         try:
4305             return set(values)
4306         except Exception, e:
4307             self.compile_time_value_error(e)
4308
4309     def generate_evaluation_code(self, code):
4310         code.globalstate.use_utility_code(Builtin.py23_set_utility_code)
4311         self.allocate_temp_result(code)
4312         code.putln(
4313             "%s = PySet_New(0); %s" % (
4314                 self.result(),
4315                 code.error_goto_if_null(self.result(), self.pos)))
4316         code.put_gotref(self.py_result())
4317         for arg in self.args:
4318             arg.generate_evaluation_code(code)
4319             code.putln(
4320                 code.error_goto_if_neg(
4321                     "PySet_Add(%s, %s)" % (self.result(), arg.py_result()),
4322                     self.pos))
4323             arg.generate_disposal_code(code)
4324             arg.free_temps(code)
4325
4326
4327 class DictNode(ExprNode):
4328     #  Dictionary constructor.
4329     #
4330     #  key_value_pairs  [DictItemNode]
4331     #
4332     # obj_conversion_errors    [PyrexError]   used internally
4333     
4334     subexprs = ['key_value_pairs']
4335     is_temp = 1
4336     type = dict_type
4337
4338     obj_conversion_errors = []
4339
4340     def calculate_constant_result(self):
4341         self.constant_result = dict([
4342                 item.constant_result for item in self.key_value_pairs])
4343     
4344     def compile_time_value(self, denv):
4345         pairs = [(item.key.compile_time_value(denv), item.value.compile_time_value(denv))
4346             for item in self.key_value_pairs]
4347         try:
4348             return dict(pairs)
4349         except Exception, e:
4350             self.compile_time_value_error(e)
4351     
4352     def type_dependencies(self, env):
4353         return ()
4354     
4355     def infer_type(self, env):
4356         # TOOD: Infer struct constructors.
4357         return dict_type
4358
4359     def analyse_types(self, env):
4360         hold_errors()
4361         for item in self.key_value_pairs:
4362             item.analyse_types(env)
4363         self.obj_conversion_errors = held_errors()
4364         release_errors(ignore=True)
4365
4366     def may_be_none(self):
4367         return False
4368         
4369     def coerce_to(self, dst_type, env):
4370         if dst_type.is_pyobject:
4371             self.release_errors()
4372             if not self.type.subtype_of(dst_type):
4373                 error(self.pos, "Cannot interpret dict as type '%s'" % dst_type)
4374         elif dst_type.is_struct_or_union:
4375             self.type = dst_type
4376             if not dst_type.is_struct and len(self.key_value_pairs) != 1:
4377                 error(self.pos, "Exactly one field must be specified to convert to union '%s'" % dst_type)
4378             elif dst_type.is_struct and len(self.key_value_pairs) < len(dst_type.scope.var_entries):
4379                 warning(self.pos, "Not all members given for struct '%s'" % dst_type, 1)
4380             for item in self.key_value_pairs:
4381                 if isinstance(item.key, CoerceToPyTypeNode):
4382                     item.key = item.key.arg
4383                 if not isinstance(item.key, (UnicodeNode, StringNode, BytesNode)):
4384                     error(item.key.pos, "Invalid struct field identifier")
4385                     item.key = StringNode(item.key.pos, value="<error>")
4386                 else:
4387                     key = str(item.key.value) # converts string literals to unicode in Py3
4388                     member = dst_type.scope.lookup_here(key)
4389                     if not member:
4390                         error(item.key.pos, "struct '%s' has no field '%s'" % (dst_type, key))
4391                     else:
4392                         value = item.value
4393                         if isinstance(value, CoerceToPyTypeNode):
4394                             value = value.arg
4395                         item.value = value.coerce_to(member.type, env)
4396         else:
4397             self.type = error_type
4398             error(self.pos, "Cannot interpret dict as type '%s'" % dst_type)
4399         return self
4400     
4401     def release_errors(self):
4402         for err in self.obj_conversion_errors:
4403             report_error(err)
4404         self.obj_conversion_errors = []
4405
4406     gil_message = "Constructing Python dict"
4407
4408     def generate_evaluation_code(self, code):
4409         #  Custom method used here because key-value
4410         #  pairs are evaluated and used one at a time.
4411         code.mark_pos(self.pos)
4412         self.allocate_temp_result(code)
4413         if self.type.is_pyobject:
4414             self.release_errors()
4415             code.putln(
4416                 "%s = PyDict_New(); %s" % (
4417                     self.result(),
4418                     code.error_goto_if_null(self.result(), self.pos)))
4419             code.put_gotref(self.py_result())
4420         for item in self.key_value_pairs:
4421             item.generate_evaluation_code(code)
4422             if self.type.is_pyobject:
4423                 code.put_error_if_neg(self.pos, 
4424                     "PyDict_SetItem(%s, %s, %s)" % (
4425                         self.result(),
4426                         item.key.py_result(),
4427                         item.value.py_result()))
4428             else:
4429                 code.putln("%s.%s = %s;" % (
4430                         self.result(),
4431                         item.key.value,
4432                         item.value.result()))
4433             item.generate_disposal_code(code)
4434             item.free_temps(code)
4435             
4436     def annotate(self, code):
4437         for item in self.key_value_pairs:
4438             item.annotate(code)
4439             
4440 class DictItemNode(ExprNode):
4441     # Represents a single item in a DictNode
4442     #
4443     # key          ExprNode
4444     # value        ExprNode
4445     subexprs = ['key', 'value']
4446
4447     nogil_check = None # Parent DictNode takes care of it
4448
4449     def calculate_constant_result(self):
4450         self.constant_result = (
4451             self.key.constant_result, self.value.constant_result)
4452             
4453     def analyse_types(self, env):
4454         self.key.analyse_types(env)
4455         self.value.analyse_types(env)
4456         self.key = self.key.coerce_to_pyobject(env)
4457         self.value = self.value.coerce_to_pyobject(env)
4458         
4459     def generate_evaluation_code(self, code):
4460         self.key.generate_evaluation_code(code)
4461         self.value.generate_evaluation_code(code)
4462
4463     def generate_disposal_code(self, code):
4464         self.key.generate_disposal_code(code)
4465         self.value.generate_disposal_code(code)
4466
4467     def free_temps(self, code):
4468         self.key.free_temps(code)
4469         self.value.free_temps(code)
4470         
4471     def __iter__(self):
4472         return iter([self.key, self.value])
4473
4474 class ModuleNameMixin(object):
4475     def set_mod_name(self, env):
4476         self.module_name = env.global_scope().qualified_name
4477
4478     def get_py_mod_name(self, code):
4479         return code.get_py_string_const(
4480                  self.module_name, identifier=True)
4481
4482 class ClassNode(ExprNode, ModuleNameMixin):
4483     #  Helper class used in the implementation of Python
4484     #  class definitions. Constructs a class object given
4485     #  a name, tuple of bases and class dictionary.
4486     #
4487     #  name         EncodedString      Name of the class
4488     #  bases        ExprNode           Base class tuple
4489     #  dict         ExprNode           Class dict (not owned by this node)
4490     #  doc          ExprNode or None   Doc string
4491     #  module_name  EncodedString      Name of defining module
4492     #  keyword_args ExprNode or None   Py3 Dict of keyword arguments, passed to __new__
4493     #  starstar_arg ExprNode or None   Py3 Dict of extra keyword args, same here
4494     
4495     subexprs = ['bases', 'keyword_args', 'starstar_arg', 'doc']
4496
4497     def analyse_types(self, env):
4498         self.bases.analyse_types(env)
4499         if self.doc:
4500             self.doc.analyse_types(env)
4501             self.doc = self.doc.coerce_to_pyobject(env)
4502         if self.keyword_args:
4503             self.keyword_args.analyse_types(env)
4504         if self.starstar_arg:
4505             self.starstar_arg.analyse_types(env)
4506             # make sure we have a Python object as **kwargs mapping
4507             self.starstar_arg = \
4508                 self.starstar_arg.coerce_to_pyobject(env)
4509         self.type = py_object_type
4510         self.is_temp = 1
4511         env.use_utility_code(create_class_utility_code);
4512         #TODO(craig,haoyu) This should be moved to a better place
4513         self.set_mod_name(env)
4514
4515     def may_be_none(self):
4516         return True
4517
4518     gil_message = "Constructing Python class"
4519
4520     def generate_result_code(self, code):
4521         cname = code.intern_identifier(self.name)
4522         if self.keyword_args and self.starstar_arg:
4523             code.put_error_if_neg(self.pos,
4524                 "PyDict_Update(%s, %s)" % (
4525                     self.keyword_args.py_result(),
4526                     self.starstar_arg.py_result()))
4527             keyword_code = self.keyword_args.py_result()
4528         elif self.keyword_args:
4529             keyword_code = self.keyword_args.py_result()
4530         elif self.starstar_arg:
4531             keyword_code = self.starstar_arg.py_result()
4532         else:
4533             keyword_code = 'NULL'
4534
4535         if self.doc:
4536             code.put_error_if_neg(self.pos, 
4537                 'PyDict_SetItemString(%s, "__doc__", %s)' % (
4538                     self.dict.py_result(),
4539                     self.doc.py_result()))
4540         py_mod_name = self.get_py_mod_name(code)
4541         code.putln(
4542             '%s = __Pyx_CreateClass(%s, %s, %s, %s, %s); %s' % (
4543                 self.result(),
4544                 self.bases.py_result(),
4545                 self.dict.py_result(),
4546                 cname,
4547                 py_mod_name,
4548                 keyword_code,
4549                 code.error_goto_if_null(self.result(), self.pos)))
4550         code.put_gotref(self.py_result())
4551
4552
4553 class BoundMethodNode(ExprNode):
4554     #  Helper class used in the implementation of Python
4555     #  class definitions. Constructs an bound method
4556     #  object from a class and a function.
4557     #
4558     #  function      ExprNode   Function object
4559     #  self_object   ExprNode   self object
4560     
4561     subexprs = ['function']
4562     
4563     def analyse_types(self, env):
4564         self.function.analyse_types(env)
4565         self.type = py_object_type
4566         self.is_temp = 1
4567
4568     gil_message = "Constructing an bound method"
4569
4570     def generate_result_code(self, code):
4571         code.putln(
4572             "%s = PyMethod_New(%s, %s, (PyObject*)%s->ob_type); %s" % (
4573                 self.result(),
4574                 self.function.py_result(),
4575                 self.self_object.py_result(),
4576                 self.self_object.py_result(),
4577                 code.error_goto_if_null(self.result(), self.pos)))
4578         code.put_gotref(self.py_result())
4579
4580 class UnboundMethodNode(ExprNode):
4581     #  Helper class used in the implementation of Python
4582     #  class definitions. Constructs an unbound method
4583     #  object from a class and a function.
4584     #
4585     #  function      ExprNode   Function object
4586     
4587     type = py_object_type
4588     is_temp = 1
4589     
4590     subexprs = ['function']
4591     
4592     def analyse_types(self, env):
4593         self.function.analyse_types(env)
4594
4595     def may_be_none(self):
4596         return False
4597
4598     gil_message = "Constructing an unbound method"
4599
4600     def generate_result_code(self, code):
4601         class_cname = code.pyclass_stack[-1].classobj.result()
4602         code.putln(
4603             "%s = PyMethod_New(%s, 0, %s); %s" % (
4604                 self.result(),
4605                 self.function.py_result(),
4606                 class_cname,
4607                 code.error_goto_if_null(self.result(), self.pos)))
4608         code.put_gotref(self.py_result())
4609
4610
4611 class PyCFunctionNode(ExprNode, ModuleNameMixin):
4612     #  Helper class used in the implementation of Python
4613     #  class definitions. Constructs a PyCFunction object
4614     #  from a PyMethodDef struct.
4615     #
4616     #  pymethdef_cname   string             PyMethodDef structure
4617     #  self_object       ExprNode or None
4618     #  binding           bool
4619     #  module_name       EncodedString      Name of defining module
4620
4621     subexprs = []
4622     self_object = None
4623     binding = False
4624     
4625     type = py_object_type
4626     is_temp = 1
4627     
4628     def analyse_types(self, env):
4629         if self.binding:
4630             env.use_utility_code(binding_cfunc_utility_code)
4631
4632         #TODO(craig,haoyu) This should be moved to a better place
4633         self.set_mod_name(env)
4634
4635     def may_be_none(self):
4636         return False
4637     
4638     gil_message = "Constructing Python function"
4639
4640     def self_result_code(self):
4641         if self.self_object is None:
4642             self_result = "NULL"
4643         else:
4644             self_result = self.self_object.py_result()
4645         return self_result
4646
4647     def generate_result_code(self, code):
4648         if self.binding:
4649             constructor = "%s_NewEx" % Naming.binding_cfunc
4650         else:
4651             constructor = "PyCFunction_NewEx"
4652         py_mod_name = self.get_py_mod_name(code)
4653         code.putln(
4654             '%s = %s(&%s, %s, %s); %s' % (
4655                 self.result(),
4656                 constructor,
4657                 self.pymethdef_cname,
4658                 self.self_result_code(),
4659                 py_mod_name,
4660                 code.error_goto_if_null(self.result(), self.pos)))
4661         code.put_gotref(self.py_result())
4662
4663 class InnerFunctionNode(PyCFunctionNode):
4664     # Special PyCFunctionNode that depends on a closure class
4665     #
4666     binding = True
4667     
4668     def self_result_code(self):
4669         return "((PyObject*)%s)" % Naming.cur_scope_cname
4670
4671 class LambdaNode(InnerFunctionNode):
4672     # Lambda expression node (only used as a function reference)
4673     #
4674     # args          [CArgDeclNode]         formal arguments
4675     # star_arg      PyArgDeclNode or None  * argument
4676     # starstar_arg  PyArgDeclNode or None  ** argument
4677     # lambda_name   string                 a module-globally unique lambda name
4678     # result_expr   ExprNode
4679     # def_node      DefNode                the underlying function 'def' node
4680
4681     child_attrs = ['def_node']
4682
4683     def_node = None
4684     name = StringEncoding.EncodedString('<lambda>')
4685
4686     def analyse_declarations(self, env):
4687         #self.def_node.needs_closure = self.needs_closure
4688         self.def_node.analyse_declarations(env)
4689         self.pymethdef_cname = self.def_node.entry.pymethdef_cname
4690         env.add_lambda_def(self.def_node)
4691
4692 class YieldExprNode(ExprNode):
4693     # Yield expression node
4694     #
4695     # arg         ExprNode   the value to return from the generator
4696     # label_name  string     name of the C label used for this yield
4697
4698     subexprs = ['arg']
4699     type = py_object_type
4700
4701     def analyse_types(self, env):
4702         self.is_temp = 1
4703         if self.arg is not None:
4704             self.arg.analyse_types(env)
4705             if not self.arg.type.is_pyobject:
4706                 self.arg = self.arg.coerce_to_pyobject(env)
4707         error(self.pos, "Generators are not supported")
4708
4709     def generate_result_code(self, code):
4710         self.label_name = code.new_label('resume_from_yield')
4711         code.use_label(self.label_name)
4712         code.putln("/* FIXME: save temporary variables */")
4713         code.putln("/* FIXME: return from function, yielding value */")
4714         code.put_label(self.label_name)
4715         code.putln("/* FIXME: restore temporary variables and  */")
4716         code.putln("/* FIXME: extract sent value from closure */")
4717
4718
4719 #-------------------------------------------------------------------
4720 #
4721 #  Unary operator nodes
4722 #
4723 #-------------------------------------------------------------------
4724
4725 compile_time_unary_operators = {
4726     'not': operator.not_,
4727     '~': operator.inv,
4728     '-': operator.neg,
4729     '+': operator.pos,
4730 }
4731
4732 class UnopNode(ExprNode):
4733     #  operator     string
4734     #  operand      ExprNode
4735     #
4736     #  Processing during analyse_expressions phase:
4737     #
4738     #    analyse_c_operation
4739     #      Called when the operand is not a pyobject.
4740     #      - Check operand type and coerce if needed.
4741     #      - Determine result type and result code fragment.
4742     #      - Allocate temporary for result if needed.
4743     
4744     subexprs = ['operand']
4745     infix = True
4746
4747     def calculate_constant_result(self):
4748         func = compile_time_unary_operators[self.operator]
4749         self.constant_result = func(self.operand.constant_result)
4750     
4751     def compile_time_value(self, denv):
4752         func = compile_time_unary_operators.get(self.operator)
4753         if not func:
4754             error(self.pos,
4755                 "Unary '%s' not supported in compile-time expression"
4756                     % self.operator)
4757         operand = self.operand.compile_time_value(denv)
4758         try:
4759             return func(operand)
4760         except Exception, e:
4761             self.compile_time_value_error(e)
4762     
4763     def infer_type(self, env):
4764         operand_type = self.operand.infer_type(env)
4765         if operand_type.is_pyobject:
4766             return py_object_type
4767         else:
4768             return operand_type
4769
4770     def analyse_types(self, env):
4771         self.operand.analyse_types(env)
4772         if self.is_py_operation():
4773             self.coerce_operand_to_pyobject(env)
4774             self.type = py_object_type
4775             self.is_temp = 1
4776         elif self.is_cpp_operation():
4777             self.analyse_cpp_operation(env)
4778         else:
4779             self.analyse_c_operation(env)
4780     
4781     def check_const(self):
4782         return self.operand.check_const()
4783     
4784     def is_py_operation(self):
4785         return self.operand.type.is_pyobject
4786
4787     def nogil_check(self, env):
4788         if self.is_py_operation():
4789             self.gil_error()
4790
4791     def is_cpp_operation(self):
4792         type = self.operand.type
4793         return type.is_cpp_class
4794     
4795     def coerce_operand_to_pyobject(self, env):
4796         self.operand = self.operand.coerce_to_pyobject(env)
4797     
4798     def generate_result_code(self, code):
4799         if self.operand.type.is_pyobject:
4800             self.generate_py_operation_code(code)
4801     
4802     def generate_py_operation_code(self, code):
4803         function = self.py_operation_function()
4804         code.putln(
4805             "%s = %s(%s); %s" % (
4806                 self.result(), 
4807                 function, 
4808                 self.operand.py_result(),
4809                 code.error_goto_if_null(self.result(), self.pos)))
4810         code.put_gotref(self.py_result())
4811         
4812     def type_error(self):
4813         if not self.operand.type.is_error:
4814             error(self.pos, "Invalid operand type for '%s' (%s)" %
4815                 (self.operator, self.operand.type))
4816         self.type = PyrexTypes.error_type
4817
4818     def analyse_cpp_operation(self, env):
4819         type = self.operand.type
4820         if type.is_ptr:
4821             type = type.base_type
4822         function = type.scope.lookup("operator%s" % self.operator)
4823         if not function:
4824             error(self.pos, "'%s' operator not defined for %s"
4825                 % (self.operator, type))
4826             self.type_error()
4827             return
4828         func_type = function.type
4829         if func_type.is_ptr:
4830             func_type = func_type.base_type
4831         self.type = func_type.return_type
4832
4833
4834 class NotNode(ExprNode):
4835     #  'not' operator
4836     #
4837     #  operand   ExprNode
4838     
4839     type = PyrexTypes.c_bint_type
4840
4841     subexprs = ['operand']
4842     
4843     def calculate_constant_result(self):
4844         self.constant_result = not self.operand.constant_result
4845
4846     def compile_time_value(self, denv):
4847         operand = self.operand.compile_time_value(denv)
4848         try:
4849             return not operand
4850         except Exception, e:
4851             self.compile_time_value_error(e)
4852
4853     def infer_type(self, env):
4854         return PyrexTypes.c_bint_type
4855     
4856     def analyse_types(self, env):
4857         self.operand.analyse_types(env)
4858         self.operand = self.operand.coerce_to_boolean(env)
4859     
4860     def calculate_result_code(self):
4861         return "(!%s)" % self.operand.result()
4862     
4863     def generate_result_code(self, code):
4864         pass
4865
4866
4867 class UnaryPlusNode(UnopNode):
4868     #  unary '+' operator
4869     
4870     operator = '+'
4871     
4872     def analyse_c_operation(self, env):
4873         self.type = self.operand.type
4874     
4875     def py_operation_function(self):
4876         return "PyNumber_Positive"
4877     
4878     def calculate_result_code(self):
4879         if self.is_cpp_operation():
4880             return "(+%s)" % self.operand.result()
4881         else:
4882             return self.operand.result()
4883
4884
4885 class UnaryMinusNode(UnopNode):
4886     #  unary '-' operator
4887     
4888     operator = '-'
4889     
4890     def analyse_c_operation(self, env):
4891         if self.operand.type.is_numeric:
4892             self.type = self.operand.type
4893         else:
4894             self.type_error()
4895         if self.type.is_complex:
4896             self.infix = False
4897     
4898     def py_operation_function(self):
4899         return "PyNumber_Negative"
4900     
4901     def calculate_result_code(self):
4902         if self.infix:
4903             return "(-%s)" % self.operand.result()
4904         else:
4905             return "%s(%s)" % (self.operand.type.unary_op('-'), self.operand.result())
4906
4907     def get_constant_c_result_code(self):
4908         value = self.operand.get_constant_c_result_code()
4909         if value:
4910             return "(-%s)" % (value)
4911
4912 class TildeNode(UnopNode):
4913     #  unary '~' operator
4914
4915     def analyse_c_operation(self, env):
4916         if self.operand.type.is_int:
4917             self.type = self.operand.type
4918         else:
4919             self.type_error()
4920
4921     def py_operation_function(self):
4922         return "PyNumber_Invert"
4923     
4924     def calculate_result_code(self):
4925         return "(~%s)" % self.operand.result()
4926
4927
4928 class CUnopNode(UnopNode):
4929
4930     def is_py_operation(self):
4931         return False
4932
4933 class DereferenceNode(CUnopNode):
4934     #  unary * operator
4935
4936     operator = '*'
4937     
4938     def analyse_c_operation(self, env):
4939         if self.operand.type.is_ptr:
4940             self.type = self.operand.type.base_type
4941         else:
4942             self.type_error()
4943
4944     def calculate_result_code(self):
4945         return "(*%s)" % self.operand.result()
4946
4947
4948 class DecrementIncrementNode(CUnopNode):
4949     #  unary ++/-- operator
4950     
4951     def analyse_c_operation(self, env):
4952         if self.operand.type.is_ptr or self.operand.type.is_numeric:
4953             self.type = self.operand.type
4954         else:
4955             self.type_error()
4956
4957     def calculate_result_code(self):
4958         if self.is_prefix:
4959             return "(%s%s)" % (self.operator, self.operand.result())
4960         else:
4961             return "(%s%s)" % (self.operand.result(), self.operator)
4962
4963 def inc_dec_constructor(is_prefix, operator):
4964     return lambda pos, **kwds: DecrementIncrementNode(pos, is_prefix=is_prefix, operator=operator, **kwds)
4965
4966
4967 class AmpersandNode(ExprNode):
4968     #  The C address-of operator.
4969     #
4970     #  operand  ExprNode
4971     
4972     subexprs = ['operand']
4973     
4974     def infer_type(self, env):
4975         return PyrexTypes.c_ptr_type(self.operand.infer_type(env))
4976
4977     def analyse_types(self, env):
4978         self.operand.analyse_types(env)
4979         argtype = self.operand.type
4980         if not (argtype.is_cfunction or self.operand.is_lvalue()):
4981             self.error("Taking address of non-lvalue")
4982             return
4983         if argtype.is_pyobject:
4984             self.error("Cannot take address of Python variable")
4985             return
4986         self.type = PyrexTypes.c_ptr_type(argtype)
4987     
4988     def check_const(self):
4989         return self.operand.check_const_addr()
4990     
4991     def error(self, mess):
4992         error(self.pos, mess)
4993         self.type = PyrexTypes.error_type
4994         self.result_code = "<error>"
4995     
4996     def calculate_result_code(self):
4997         return "(&%s)" % self.operand.result()
4998
4999     def generate_result_code(self, code):
5000         pass
5001     
5002
5003 unop_node_classes = {
5004     "+":  UnaryPlusNode,
5005     "-":  UnaryMinusNode,
5006     "~":  TildeNode,
5007 }
5008
5009 def unop_node(pos, operator, operand):
5010     # Construct unnop node of appropriate class for 
5011     # given operator.
5012     if isinstance(operand, IntNode) and operator == '-':
5013         return IntNode(pos = operand.pos, value = str(-Utils.str_to_number(operand.value)))
5014     elif isinstance(operand, UnopNode) and operand.operator == operator:
5015         warning(pos, "Python has no increment/decrement operator: %s%sx = %s(%sx) = x" % ((operator,)*4), 5)
5016     return unop_node_classes[operator](pos, 
5017         operator = operator, 
5018         operand = operand)
5019
5020
5021 class TypecastNode(ExprNode):
5022     #  C type cast
5023     #
5024     #  operand      ExprNode
5025     #  base_type    CBaseTypeNode
5026     #  declarator   CDeclaratorNode
5027     #
5028     #  If used from a transform, one can if wanted specify the attribute
5029     #  "type" directly and leave base_type and declarator to None
5030     
5031     subexprs = ['operand']
5032     base_type = declarator = type = None
5033     
5034     def type_dependencies(self, env):
5035         return ()
5036     
5037     def infer_type(self, env):
5038         if self.type is None:
5039             base_type = self.base_type.analyse(env)
5040             _, self.type = self.declarator.analyse(base_type, env)
5041         return self.type
5042     
5043     def analyse_types(self, env):
5044         if self.type is None:
5045             base_type = self.base_type.analyse(env)
5046             _, self.type = self.declarator.analyse(base_type, env)
5047         if self.type.is_cfunction:
5048             error(self.pos,
5049                 "Cannot cast to a function type")
5050             self.type = PyrexTypes.error_type
5051         self.operand.analyse_types(env)
5052         to_py = self.type.is_pyobject
5053         from_py = self.operand.type.is_pyobject
5054         if from_py and not to_py and self.operand.is_ephemeral() and not self.type.is_numeric:
5055             error(self.pos, "Casting temporary Python object to non-numeric non-Python type")
5056         if to_py and not from_py:
5057             if self.type is bytes_type and self.operand.type.is_int:
5058                 # FIXME: the type cast node isn't needed in this case
5059                 # and can be dropped once analyse_types() can return a
5060                 # different node
5061                 self.operand = CoerceIntToBytesNode(self.operand, env)
5062             elif self.operand.type.can_coerce_to_pyobject(env):
5063                 self.result_ctype = py_object_type
5064                 self.operand = self.operand.coerce_to_pyobject(env)
5065             else:
5066                 if self.operand.type.is_ptr:
5067                     if not (self.operand.type.base_type.is_void or self.operand.type.base_type.is_struct):
5068                         error(self.pos, "Python objects cannot be cast from pointers of primitive types")
5069                 else:
5070                     # Should this be an error? 
5071                     warning(self.pos, "No conversion from %s to %s, python object pointer used." % (self.operand.type, self.type))
5072                 self.operand = self.operand.coerce_to_simple(env)
5073         elif from_py and not to_py:
5074             if self.type.create_from_py_utility_code(env):
5075                 self.operand = self.operand.coerce_to(self.type, env)
5076             elif self.type.is_ptr:
5077                 if not (self.type.base_type.is_void or self.type.base_type.is_struct):
5078                     error(self.pos, "Python objects cannot be cast to pointers of primitive types")
5079             else:
5080                 warning(self.pos, "No conversion from %s to %s, python object pointer used." % (self.type, self.operand.type))
5081         elif from_py and to_py:
5082             if self.typecheck and self.type.is_extension_type:
5083                 self.operand = PyTypeTestNode(self.operand, self.type, env, notnone=True)
5084         elif self.type.is_complex and self.operand.type.is_complex:
5085             self.operand = self.operand.coerce_to_simple(env)
5086
5087     def nogil_check(self, env):
5088         if self.type and self.type.is_pyobject and self.is_temp:
5089             self.gil_error()
5090
5091     def check_const(self):
5092         return self.operand.check_const()
5093
5094     def calculate_constant_result(self):
5095         # we usually do not know the result of a type cast at code
5096         # generation time
5097         pass
5098     
5099     def calculate_result_code(self):
5100         if self.type.is_complex:
5101             operand_result = self.operand.result()
5102             if self.operand.type.is_complex:
5103                 real_part = self.type.real_type.cast_code("__Pyx_CREAL(%s)" % operand_result)
5104                 imag_part = self.type.real_type.cast_code("__Pyx_CIMAG(%s)" % operand_result)
5105             else:
5106                 real_part = self.type.real_type.cast_code(operand_result)
5107                 imag_part = "0"
5108             return "%s(%s, %s)" % (
5109                     self.type.from_parts,
5110                     real_part,
5111                     imag_part)    
5112         else:
5113             return self.type.cast_code(self.operand.result())
5114     
5115     def get_constant_c_result_code(self):
5116         operand_result = self.operand.get_constant_c_result_code()
5117         if operand_result:
5118             return self.type.cast_code(operand_result)
5119     
5120     def result_as(self, type):
5121         if self.type.is_pyobject and not self.is_temp:
5122             #  Optimise away some unnecessary casting
5123             return self.operand.result_as(type)
5124         else:
5125             return ExprNode.result_as(self, type)
5126
5127     def generate_result_code(self, code):
5128         if self.is_temp:
5129             code.putln(
5130                 "%s = (PyObject *)%s;" % (
5131                     self.result(),
5132                     self.operand.result()))
5133             code.put_incref(self.result(), self.ctype())
5134
5135
5136 class SizeofNode(ExprNode):
5137     #  Abstract base class for sizeof(x) expression nodes.
5138     
5139     type = PyrexTypes.c_size_t_type
5140
5141     def check_const(self):
5142         return True
5143
5144     def generate_result_code(self, code):
5145         pass
5146
5147
5148 class SizeofTypeNode(SizeofNode):
5149     #  C sizeof function applied to a type
5150     #
5151     #  base_type   CBaseTypeNode
5152     #  declarator  CDeclaratorNode
5153     
5154     subexprs = []
5155     arg_type = None
5156     
5157     def analyse_types(self, env):
5158         # we may have incorrectly interpreted a dotted name as a type rather than an attribute
5159         # this could be better handled by more uniformly treating types as runtime-available objects
5160         if 0 and self.base_type.module_path:
5161             path = self.base_type.module_path
5162             obj = env.lookup(path[0])
5163             if obj.as_module is None:
5164                 operand = NameNode(pos=self.pos, name=path[0])
5165                 for attr in path[1:]:
5166                     operand = AttributeNode(pos=self.pos, obj=operand, attribute=attr)
5167                 operand = AttributeNode(pos=self.pos, obj=operand, attribute=self.base_type.name)
5168                 self.operand = operand
5169                 self.__class__ = SizeofVarNode
5170                 self.analyse_types(env)
5171                 return
5172         if self.arg_type is None:
5173             base_type = self.base_type.analyse(env)
5174             _, arg_type = self.declarator.analyse(base_type, env)
5175             self.arg_type = arg_type
5176         self.check_type()
5177         
5178     def check_type(self):
5179         arg_type = self.arg_type
5180         if arg_type.is_pyobject and not arg_type.is_extension_type:
5181             error(self.pos, "Cannot take sizeof Python object")
5182         elif arg_type.is_void:
5183             error(self.pos, "Cannot take sizeof void")
5184         elif not arg_type.is_complete():
5185             error(self.pos, "Cannot take sizeof incomplete type '%s'" % arg_type)
5186         
5187     def calculate_result_code(self):
5188         if self.arg_type.is_extension_type:
5189             # the size of the pointer is boring
5190             # we want the size of the actual struct
5191             arg_code = self.arg_type.declaration_code("", deref=1)
5192         else:
5193             arg_code = self.arg_type.declaration_code("")
5194         return "(sizeof(%s))" % arg_code
5195     
5196
5197 class SizeofVarNode(SizeofNode):
5198     #  C sizeof function applied to a variable
5199     #
5200     #  operand   ExprNode
5201     
5202     subexprs = ['operand']
5203     
5204     def analyse_types(self, env):
5205         # We may actually be looking at a type rather than a variable...
5206         # If we are, traditional analysis would fail...
5207         operand_as_type = self.operand.analyse_as_type(env)
5208         if operand_as_type:
5209             self.arg_type = operand_as_type
5210             self.__class__ = SizeofTypeNode
5211             self.check_type()
5212         else:
5213             self.operand.analyse_types(env)
5214     
5215     def calculate_result_code(self):
5216         return "(sizeof(%s))" % self.operand.result()
5217     
5218     def generate_result_code(self, code):
5219         pass
5220
5221 class TypeofNode(ExprNode):
5222     #  Compile-time type of an expression, as a string.
5223     #
5224     #  operand   ExprNode
5225     #  literal   StringNode # internal
5226     
5227     literal = None
5228     type = py_object_type
5229     
5230     subexprs = ['literal'] # 'operand' will be ignored after type analysis!
5231     
5232     def analyse_types(self, env):
5233         self.operand.analyse_types(env)
5234         self.literal = StringNode(
5235             self.pos, value=StringEncoding.EncodedString(str(self.operand.type)))
5236         self.literal.analyse_types(env)
5237         self.literal = self.literal.coerce_to_pyobject(env)
5238
5239     def may_be_none(self):
5240         return False
5241
5242     def generate_evaluation_code(self, code):
5243         self.literal.generate_evaluation_code(code)
5244     
5245     def calculate_result_code(self):
5246         return self.literal.calculate_result_code()
5247
5248 #-------------------------------------------------------------------
5249 #
5250 #  Binary operator nodes
5251 #
5252 #-------------------------------------------------------------------
5253
5254 def _not_in(x, seq):
5255     return x not in seq
5256
5257 compile_time_binary_operators = {
5258     '<': operator.lt,
5259     '<=': operator.le,
5260     '==': operator.eq,
5261     '!=': operator.ne,
5262     '>=': operator.ge,
5263     '>': operator.gt,
5264     'is': operator.is_,
5265     'is_not': operator.is_not,
5266     '+': operator.add,
5267     '&': operator.and_,
5268     '/': operator.truediv,
5269     '//': operator.floordiv,
5270     '<<': operator.lshift,
5271     '%': operator.mod,
5272     '*': operator.mul,
5273     '|': operator.or_,
5274     '**': operator.pow,
5275     '>>': operator.rshift,
5276     '-': operator.sub,
5277     '^': operator.xor,
5278     'in': operator.contains,
5279     'not_in': _not_in,
5280 }
5281
5282 def get_compile_time_binop(node):
5283     func = compile_time_binary_operators.get(node.operator)
5284     if not func:
5285         error(node.pos,
5286             "Binary '%s' not supported in compile-time expression"
5287                 % node.operator)
5288     return func
5289
5290 class BinopNode(ExprNode):
5291     #  operator     string
5292     #  operand1     ExprNode
5293     #  operand2     ExprNode
5294     #
5295     #  Processing during analyse_expressions phase:
5296     #
5297     #    analyse_c_operation
5298     #      Called when neither operand is a pyobject.
5299     #      - Check operand types and coerce if needed.
5300     #      - Determine result type and result code fragment.
5301     #      - Allocate temporary for result if needed.
5302     
5303     subexprs = ['operand1', 'operand2']
5304
5305     def calculate_constant_result(self):
5306         func = compile_time_binary_operators[self.operator]
5307         self.constant_result = func(
5308             self.operand1.constant_result,
5309             self.operand2.constant_result)
5310
5311     def compile_time_value(self, denv):
5312         func = get_compile_time_binop(self)
5313         operand1 = self.operand1.compile_time_value(denv)
5314         operand2 = self.operand2.compile_time_value(denv)
5315         try:
5316             return func(operand1, operand2)
5317         except Exception, e:
5318             self.compile_time_value_error(e)
5319     
5320     def infer_type(self, env):
5321         return self.result_type(self.operand1.infer_type(env),
5322                                 self.operand2.infer_type(env))
5323     
5324     def analyse_types(self, env):
5325         self.operand1.analyse_types(env)
5326         self.operand2.analyse_types(env)
5327         if self.is_py_operation():
5328             self.coerce_operands_to_pyobjects(env)
5329             self.type = self.result_type(self.operand1.type,
5330                                          self.operand2.type)
5331             assert self.type.is_pyobject
5332             self.is_temp = 1
5333         elif self.is_cpp_operation():
5334             self.analyse_cpp_operation(env)
5335         else:
5336             self.analyse_c_operation(env)
5337     
5338     def is_py_operation(self):
5339         return self.is_py_operation_types(self.operand1.type, self.operand2.type)
5340     
5341     def is_py_operation_types(self, type1, type2):
5342         return type1.is_pyobject or type2.is_pyobject
5343
5344     def is_cpp_operation(self):
5345         return (self.operand1.type.is_cpp_class
5346             or self.operand2.type.is_cpp_class)
5347     
5348     def analyse_cpp_operation(self, env):
5349         type1 = self.operand1.type
5350         type2 = self.operand2.type
5351         entry = env.lookup_operator(self.operator, [self.operand1, self.operand2])
5352         if not entry:
5353             self.type_error()
5354             return
5355         func_type = entry.type
5356         if func_type.is_ptr:
5357             func_type = func_type.base_type
5358         if len(func_type.args) == 1:
5359             self.operand2 = self.operand2.coerce_to(func_type.args[0].type, env)
5360         else:
5361             self.operand1 = self.operand1.coerce_to(func_type.args[0].type, env)
5362             self.operand2 = self.operand2.coerce_to(func_type.args[1].type, env)
5363         self.type = func_type.return_type
5364     
5365     def result_type(self, type1, type2):
5366         if self.is_py_operation_types(type1, type2):
5367             if type2.is_string:
5368                 type2 = Builtin.bytes_type
5369             if type1.is_string:
5370                 type1 = Builtin.bytes_type
5371             elif self.operator == '%' \
5372                      and type1 in (Builtin.str_type, Builtin.unicode_type):
5373                 # note that  b'%s' % b'abc'  doesn't work in Py3
5374                 return type1
5375             if type1.is_builtin_type:
5376                 if type1 is type2:
5377                     if self.operator in '**%+|&^':
5378                         # FIXME: at least these operators should be safe - others?
5379                         return type1
5380                 elif self.operator == '*':
5381                     if type1 in (Builtin.bytes_type, Builtin.str_type, Builtin.unicode_type):
5382                         return type1
5383                     # multiplication of containers/numbers with an
5384                     # integer value always (?) returns the same type
5385                     if type2.is_int:
5386                         return type1
5387             elif type2.is_builtin_type and type1.is_int and self.operator == '*':
5388                 # multiplication of containers/numbers with an
5389                 # integer value always (?) returns the same type
5390                 return type2
5391             return py_object_type
5392         else:
5393             return self.compute_c_result_type(type1, type2)
5394
5395     def nogil_check(self, env):
5396         if self.is_py_operation():
5397             self.gil_error()
5398         
5399     def coerce_operands_to_pyobjects(self, env):
5400         self.operand1 = self.operand1.coerce_to_pyobject(env)
5401         self.operand2 = self.operand2.coerce_to_pyobject(env)
5402     
5403     def check_const(self):
5404         return self.operand1.check_const() and self.operand2.check_const()
5405     
5406     def generate_result_code(self, code):
5407         #print "BinopNode.generate_result_code:", self.operand1, self.operand2 ###
5408         if self.operand1.type.is_pyobject:
5409             function = self.py_operation_function()
5410             if self.operator == '**':
5411                 extra_args = ", Py_None"
5412             else:
5413                 extra_args = ""
5414             code.putln(
5415                 "%s = %s(%s, %s%s); %s" % (
5416                     self.result(), 
5417                     function, 
5418                     self.operand1.py_result(),
5419                     self.operand2.py_result(),
5420                     extra_args,
5421                     code.error_goto_if_null(self.result(), self.pos)))
5422             code.put_gotref(self.py_result())
5423     
5424     def type_error(self):
5425         if not (self.operand1.type.is_error
5426                 or self.operand2.type.is_error):
5427             error(self.pos, "Invalid operand types for '%s' (%s; %s)" %
5428                 (self.operator, self.operand1.type, 
5429                     self.operand2.type))
5430         self.type = PyrexTypes.error_type
5431
5432
5433 class CBinopNode(BinopNode):
5434     
5435     def analyse_types(self, env):
5436         BinopNode.analyse_types(self, env)
5437         if self.is_py_operation():
5438             self.type = PyrexTypes.error_type
5439     
5440     def py_operation_function():
5441         return ""
5442         
5443     def calculate_result_code(self):
5444         return "(%s %s %s)" % (
5445             self.operand1.result(), 
5446             self.operator, 
5447             self.operand2.result())
5448
5449
5450 def c_binop_constructor(operator):
5451     def make_binop_node(pos, **operands):
5452         return CBinopNode(pos, operator=operator, **operands)
5453     return make_binop_node
5454
5455 class NumBinopNode(BinopNode):
5456     #  Binary operation taking numeric arguments.
5457     
5458     infix = True
5459     
5460     def analyse_c_operation(self, env):
5461         type1 = self.operand1.type
5462         type2 = self.operand2.type
5463         self.type = self.compute_c_result_type(type1, type2)
5464         if not self.type:
5465             self.type_error()
5466             return
5467         if self.type.is_complex:
5468             self.infix = False
5469         if not self.infix or (type1.is_numeric and type2.is_numeric):
5470             self.operand1 = self.operand1.coerce_to(self.type, env)
5471             self.operand2 = self.operand2.coerce_to(self.type, env)
5472     
5473     def compute_c_result_type(self, type1, type2):
5474         if self.c_types_okay(type1, type2):
5475             return PyrexTypes.widest_numeric_type(type1, type2)
5476         else:
5477             return None
5478
5479     def get_constant_c_result_code(self):
5480         value1 = self.operand1.get_constant_c_result_code()
5481         value2 = self.operand2.get_constant_c_result_code()
5482         if value1 and value2:
5483             return "(%s %s %s)" % (value1, self.operator, value2)
5484         else:
5485             return None
5486     
5487     def c_types_okay(self, type1, type2):
5488         #print "NumBinopNode.c_types_okay:", type1, type2 ###
5489         return (type1.is_numeric  or type1.is_enum) \
5490             and (type2.is_numeric  or type2.is_enum)
5491
5492     def calculate_result_code(self):
5493         if self.infix:
5494             return "(%s %s %s)" % (
5495                 self.operand1.result(), 
5496                 self.operator, 
5497                 self.operand2.result())
5498         else:
5499             func = self.type.binary_op(self.operator)
5500             if func is None:
5501                 error(self.pos, "binary operator %s not supported for %s" % (self.operator, self.type))
5502             return "%s(%s, %s)" % (
5503                 func,
5504                 self.operand1.result(),
5505                 self.operand2.result())
5506     
5507     def is_py_operation_types(self, type1, type2):
5508         return (type1 is PyrexTypes.c_py_unicode_type or
5509                 type2 is PyrexTypes.c_py_unicode_type or
5510                 BinopNode.is_py_operation_types(self, type1, type2))
5511     
5512     def py_operation_function(self):
5513         fuction = self.py_functions[self.operator]
5514         if self.inplace:
5515             fuction = fuction.replace('PyNumber_', 'PyNumber_InPlace')
5516         return fuction
5517
5518     py_functions = {
5519         "|":        "PyNumber_Or",
5520         "^":        "PyNumber_Xor",
5521         "&":        "PyNumber_And",
5522         "<<":       "PyNumber_Lshift",
5523         ">>":       "PyNumber_Rshift",
5524         "+":        "PyNumber_Add",
5525         "-":        "PyNumber_Subtract",
5526         "*":        "PyNumber_Multiply",
5527         "/":        "__Pyx_PyNumber_Divide",
5528         "//":       "PyNumber_FloorDivide",
5529         "%":        "PyNumber_Remainder",
5530         "**":       "PyNumber_Power"
5531     }
5532
5533 class IntBinopNode(NumBinopNode):
5534     #  Binary operation taking integer arguments.
5535     
5536     def c_types_okay(self, type1, type2):
5537         #print "IntBinopNode.c_types_okay:", type1, type2 ###
5538         return (type1.is_int or type1.is_enum) \
5539             and (type2.is_int or type2.is_enum)
5540
5541     
5542 class AddNode(NumBinopNode):
5543     #  '+' operator.
5544     
5545     def is_py_operation_types(self, type1, type2):
5546         if type1.is_string and type2.is_string:
5547             return 1
5548         else:
5549             return NumBinopNode.is_py_operation_types(self, type1, type2)
5550
5551     def compute_c_result_type(self, type1, type2):
5552         #print "AddNode.compute_c_result_type:", type1, self.operator, type2 ###
5553         if (type1.is_ptr or type1.is_array) and (type2.is_int or type2.is_enum):
5554             return type1
5555         elif (type2.is_ptr or type2.is_array) and (type1.is_int or type1.is_enum):
5556             return type2
5557         else:
5558             return NumBinopNode.compute_c_result_type(
5559                 self, type1, type2)
5560
5561
5562 class SubNode(NumBinopNode):
5563     #  '-' operator.
5564     
5565     def compute_c_result_type(self, type1, type2):
5566         if (type1.is_ptr or type1.is_array) and (type2.is_int or type2.is_enum):
5567             return type1
5568         elif (type1.is_ptr or type1.is_array) and (type2.is_ptr or type2.is_array):
5569             return PyrexTypes.c_int_type
5570         else:
5571             return NumBinopNode.compute_c_result_type(
5572                 self, type1, type2)
5573
5574
5575 class MulNode(NumBinopNode):
5576     #  '*' operator.
5577     
5578     def is_py_operation_types(self, type1, type2):
5579         if (type1.is_string and type2.is_int) \
5580             or (type2.is_string and type1.is_int):
5581                 return 1
5582         else:
5583             return NumBinopNode.is_py_operation_types(self, type1, type2)
5584
5585
5586 class DivNode(NumBinopNode):
5587     #  '/' or '//' operator.
5588     
5589     cdivision = None
5590     truedivision = None   # == "unknown" if operator == '/'
5591     ctruedivision = False
5592     cdivision_warnings = False
5593     zerodivision_check = None
5594
5595     def find_compile_time_binary_operator(self, op1, op2):
5596         func = compile_time_binary_operators[self.operator]
5597         if self.operator == '/' and self.truedivision is None:
5598             # => true div for floats, floor div for integers
5599             if isinstance(op1, (int,long)) and isinstance(op2, (int,long)):
5600                 func = compile_time_binary_operators['//']
5601         return func
5602
5603     def calculate_constant_result(self):
5604         op1 = self.operand1.constant_result
5605         op2 = self.operand2.constant_result
5606         func = self.find_compile_time_binary_operator(op1, op2)
5607         self.constant_result = func(
5608             self.operand1.constant_result,
5609             self.operand2.constant_result)
5610
5611     def compile_time_value(self, denv):
5612         operand1 = self.operand1.compile_time_value(denv)
5613         operand2 = self.operand2.compile_time_value(denv)
5614         try:
5615             func = self.find_compile_time_binary_operator(
5616                 self, operand1, operand2)
5617             return func(operand1, operand2)
5618         except Exception, e:
5619             self.compile_time_value_error(e)
5620
5621     def analyse_types(self, env):
5622         if self.cdivision or env.directives['cdivision']:
5623             self.ctruedivision = False
5624         else:
5625             self.ctruedivision = self.truedivision
5626         NumBinopNode.analyse_types(self, env)
5627         if self.is_cpp_operation():
5628             self.cdivision = True
5629         if not self.type.is_pyobject:
5630             self.zerodivision_check = (
5631                 self.cdivision is None and not env.directives['cdivision']
5632                 and (not self.operand2.has_constant_result() or
5633                      self.operand2.constant_result == 0))
5634             if self.zerodivision_check or env.directives['cdivision_warnings']:
5635                 # Need to check ahead of time to warn or raise zero division error
5636                 self.operand1 = self.operand1.coerce_to_simple(env)
5637                 self.operand2 = self.operand2.coerce_to_simple(env)
5638                 if env.nogil:
5639                     error(self.pos, "Pythonic division not allowed without gil, consider using cython.cdivision(True)")
5640
5641     def compute_c_result_type(self, type1, type2):
5642         if self.operator == '/' and self.ctruedivision:
5643             if not type1.is_float and not type2.is_float:
5644                 widest_type = PyrexTypes.widest_numeric_type(type1, PyrexTypes.c_double_type)
5645                 widest_type = PyrexTypes.widest_numeric_type(type2, widest_type)
5646                 return widest_type
5647         return NumBinopNode.compute_c_result_type(self, type1, type2)
5648
5649     def zero_division_message(self):
5650         if self.type.is_int:
5651             return "integer division or modulo by zero"
5652         else:
5653             return "float division"
5654
5655     def generate_evaluation_code(self, code):
5656         if not self.type.is_pyobject and not self.type.is_complex:
5657             if self.cdivision is None:
5658                 self.cdivision = (code.globalstate.directives['cdivision'] 
5659                                     or not self.type.signed
5660                                     or self.type.is_float)
5661             if not self.cdivision:
5662                 code.globalstate.use_utility_code(div_int_utility_code.specialize(self.type))
5663         NumBinopNode.generate_evaluation_code(self, code)
5664         self.generate_div_warning_code(code)
5665     
5666     def generate_div_warning_code(self, code):
5667         if not self.type.is_pyobject:
5668             if self.zerodivision_check:
5669                 if not self.infix:
5670                     zero_test = "%s(%s)" % (self.type.unary_op('zero'), self.operand2.result())
5671                 else:
5672                     zero_test = "%s == 0" % self.operand2.result()
5673                 code.putln("if (unlikely(%s)) {" % zero_test)
5674                 code.putln('PyErr_Format(PyExc_ZeroDivisionError, "%s");' % self.zero_division_message())
5675                 code.putln(code.error_goto(self.pos))
5676                 code.putln("}")
5677                 if self.type.is_int and self.type.signed and self.operator != '%':
5678                     code.globalstate.use_utility_code(division_overflow_test_code)
5679                     code.putln("else if (sizeof(%s) == sizeof(long) && unlikely(%s == -1) && unlikely(UNARY_NEG_WOULD_OVERFLOW(%s))) {" % (
5680                                     self.type.declaration_code(''), 
5681                                     self.operand2.result(),
5682                                     self.operand1.result()))
5683                     code.putln('PyErr_Format(PyExc_OverflowError, "value too large to perform division");')
5684                     code.putln(code.error_goto(self.pos))
5685                     code.putln("}")
5686             if code.globalstate.directives['cdivision_warnings'] and self.operator != '/':
5687                 code.globalstate.use_utility_code(cdivision_warning_utility_code)
5688                 code.putln("if ((%s < 0) ^ (%s < 0)) {" % (
5689                                 self.operand1.result(),
5690                                 self.operand2.result()))
5691                 code.putln(code.set_error_info(self.pos));
5692                 code.put("if (__Pyx_cdivision_warning()) ")
5693                 code.put_goto(code.error_label)
5694                 code.putln("}")
5695     
5696     def calculate_result_code(self):
5697         if self.type.is_complex:
5698             return NumBinopNode.calculate_result_code(self)
5699         elif self.type.is_float and self.operator == '//':
5700             return "floor(%s / %s)" % (
5701                 self.operand1.result(),
5702                 self.operand2.result())
5703         elif self.truedivision or self.cdivision:
5704             op1 = self.operand1.result()
5705             op2 = self.operand2.result()
5706             if self.truedivision:
5707                 if self.type != self.operand1.type:
5708                     op1 = self.type.cast_code(op1)
5709                 if self.type != self.operand2.type:
5710                     op2 = self.type.cast_code(op2)
5711             return "(%s / %s)" % (op1, op2)
5712         else:
5713             return "__Pyx_div_%s(%s, %s)" % (
5714                     self.type.specialization_name(),
5715                     self.operand1.result(), 
5716                     self.operand2.result())
5717
5718
5719 class ModNode(DivNode):
5720     #  '%' operator.
5721
5722     def is_py_operation_types(self, type1, type2):
5723         return (type1.is_string
5724             or type2.is_string
5725             or NumBinopNode.is_py_operation_types(self, type1, type2))
5726
5727     def zero_division_message(self):
5728         if self.type.is_int:
5729             return "integer division or modulo by zero"
5730         else:
5731             return "float divmod()"
5732     
5733     def generate_evaluation_code(self, code):
5734         if not self.type.is_pyobject:
5735             if self.cdivision is None:
5736                 self.cdivision = code.globalstate.directives['cdivision'] or not self.type.signed
5737             if not self.cdivision:
5738                 if self.type.is_int:
5739                     code.globalstate.use_utility_code(mod_int_utility_code.specialize(self.type))
5740                 else:
5741                     code.globalstate.use_utility_code(
5742                         mod_float_utility_code.specialize(self.type, math_h_modifier=self.type.math_h_modifier))
5743         NumBinopNode.generate_evaluation_code(self, code)
5744         self.generate_div_warning_code(code)
5745     
5746     def calculate_result_code(self):
5747         if self.cdivision:
5748             if self.type.is_float:
5749                 return "fmod%s(%s, %s)" % (
5750                     self.type.math_h_modifier,
5751                     self.operand1.result(), 
5752                     self.operand2.result())
5753             else:
5754                 return "(%s %% %s)" % (
5755                     self.operand1.result(), 
5756                     self.operand2.result())
5757         else:
5758             return "__Pyx_mod_%s(%s, %s)" % (
5759                     self.type.specialization_name(),
5760                     self.operand1.result(), 
5761                     self.operand2.result())
5762
5763 class PowNode(NumBinopNode):
5764     #  '**' operator.
5765     
5766     def analyse_c_operation(self, env):
5767         NumBinopNode.analyse_c_operation(self, env)
5768         if self.type.is_complex:
5769             if self.type.real_type.is_float:
5770                 self.operand1 = self.operand1.coerce_to(self.type, env)
5771                 self.operand2 = self.operand2.coerce_to(self.type, env)
5772                 self.pow_func = "__Pyx_c_pow" + self.type.real_type.math_h_modifier
5773             else:
5774                 error(self.pos, "complex int powers not supported")
5775                 self.pow_func = "<error>"
5776         elif self.type.is_float:
5777             self.pow_func = "pow" + self.type.math_h_modifier
5778         else:
5779             self.pow_func = "__Pyx_pow_%s" % self.type.declaration_code('').replace(' ', '_')
5780             env.use_utility_code(
5781                     int_pow_utility_code.specialize(func_name=self.pow_func, 
5782                                                 type=self.type.declaration_code('')))
5783
5784     def calculate_result_code(self):
5785         # Work around MSVC overloading ambiguity.
5786         def typecast(operand):
5787             if self.type == operand.type:
5788                 return operand.result()
5789             else:
5790                 return self.type.cast_code(operand.result())
5791         return "%s(%s, %s)" % (
5792             self.pow_func, 
5793             typecast(self.operand1), 
5794             typecast(self.operand2))
5795
5796
5797 # Note: This class is temporarily "shut down" into an ineffective temp
5798 # allocation mode.
5799 #
5800 # More sophisticated temp reuse was going on before, one could have a
5801 # look at adding this again after /all/ classes are converted to the
5802 # new temp scheme. (The temp juggling cannot work otherwise).
5803 class BoolBinopNode(ExprNode):
5804     #  Short-circuiting boolean operation.
5805     #
5806     #  operator     string
5807     #  operand1     ExprNode
5808     #  operand2     ExprNode
5809     
5810     subexprs = ['operand1', 'operand2']
5811     
5812     def infer_type(self, env):
5813         type1 = self.operand1.infer_type(env)
5814         type2 = self.operand2.infer_type(env)
5815         return PyrexTypes.independent_spanning_type(type1, type2)
5816
5817     def may_be_none(self):
5818         if self.operator == 'or':
5819             return self.operand2.may_be_none()
5820         else:
5821             return self.operand1.may_be_none() or self.operand2.may_be_none()
5822
5823     def calculate_constant_result(self):
5824         if self.operator == 'and':
5825             self.constant_result = \
5826                 self.operand1.constant_result and \
5827                 self.operand2.constant_result
5828         else:
5829             self.constant_result = \
5830                 self.operand1.constant_result or \
5831                 self.operand2.constant_result
5832     
5833     def compile_time_value(self, denv):
5834         if self.operator == 'and':
5835             return self.operand1.compile_time_value(denv) \
5836                 and self.operand2.compile_time_value(denv)
5837         else:
5838             return self.operand1.compile_time_value(denv) \
5839                 or self.operand2.compile_time_value(denv)
5840     
5841     def coerce_to_boolean(self, env):
5842         return BoolBinopNode(
5843             self.pos,
5844             operator = self.operator,
5845             operand1 = self.operand1.coerce_to_boolean(env),
5846             operand2 = self.operand2.coerce_to_boolean(env),
5847             type = PyrexTypes.c_bint_type,
5848             is_temp = self.is_temp)
5849
5850     def analyse_types(self, env):
5851         self.operand1.analyse_types(env)
5852         self.operand2.analyse_types(env)
5853         self.type = PyrexTypes.independent_spanning_type(self.operand1.type, self.operand2.type)
5854         self.operand1 = self.operand1.coerce_to(self.type, env)
5855         self.operand2 = self.operand2.coerce_to(self.type, env)
5856         
5857         # For what we're about to do, it's vital that
5858         # both operands be temp nodes.
5859         self.operand1 = self.operand1.coerce_to_simple(env)
5860         self.operand2 = self.operand2.coerce_to_simple(env)
5861         self.is_temp = 1
5862
5863     gil_message = "Truth-testing Python object"
5864
5865     def check_const(self):
5866         return self.operand1.check_const() and self.operand2.check_const()
5867     
5868     def generate_evaluation_code(self, code):
5869         code.mark_pos(self.pos)
5870         self.operand1.generate_evaluation_code(code)
5871         test_result, uses_temp = self.generate_operand1_test(code)
5872         if self.operator == 'and':
5873             sense = ""
5874         else:
5875             sense = "!"
5876         code.putln(
5877             "if (%s%s) {" % (
5878                 sense,
5879                 test_result))
5880         if uses_temp:
5881             code.funcstate.release_temp(test_result)
5882         self.operand1.generate_disposal_code(code)
5883         self.operand2.generate_evaluation_code(code)
5884         self.allocate_temp_result(code)
5885         self.operand2.make_owned_reference(code)
5886         code.putln("%s = %s;" % (self.result(), self.operand2.result()))
5887         self.operand2.generate_post_assignment_code(code)
5888         self.operand2.free_temps(code)
5889         code.putln("} else {")
5890         self.operand1.make_owned_reference(code)
5891         code.putln("%s = %s;" % (self.result(), self.operand1.result()))
5892         self.operand1.generate_post_assignment_code(code)
5893         self.operand1.free_temps(code)
5894         code.putln("}")
5895     
5896     def generate_operand1_test(self, code):
5897         #  Generate code to test the truth of the first operand.
5898         if self.type.is_pyobject:
5899             test_result = code.funcstate.allocate_temp(PyrexTypes.c_bint_type,
5900                                                        manage_ref=False)
5901             code.putln(
5902                 "%s = __Pyx_PyObject_IsTrue(%s); %s" % (
5903                     test_result,
5904                     self.operand1.py_result(),
5905                     code.error_goto_if_neg(test_result, self.pos)))
5906         else:
5907             test_result = self.operand1.result()
5908         return (test_result, self.type.is_pyobject)
5909
5910
5911 class CondExprNode(ExprNode):
5912     #  Short-circuiting conditional expression.
5913     #
5914     #  test        ExprNode
5915     #  true_val    ExprNode
5916     #  false_val   ExprNode
5917     
5918     true_val = None
5919     false_val = None
5920     
5921     subexprs = ['test', 'true_val', 'false_val']
5922     
5923     def type_dependencies(self, env):
5924         return self.true_val.type_dependencies(env) + self.false_val.type_dependencies(env)
5925     
5926     def infer_type(self, env):
5927         return PyrexTypes.independent_spanning_type(self.true_val.infer_type(env),
5928                                                     self.false_val.infer_type(env))
5929
5930     def calculate_constant_result(self):
5931         if self.test.constant_result:
5932             self.constant_result = self.true_val.constant_result
5933         else:
5934             self.constant_result = self.false_val.constant_result
5935
5936     def analyse_types(self, env):
5937         self.test.analyse_types(env)
5938         self.test = self.test.coerce_to_boolean(env)
5939         self.true_val.analyse_types(env)
5940         self.false_val.analyse_types(env)
5941         self.type = PyrexTypes.independent_spanning_type(self.true_val.type, self.false_val.type)
5942         if self.true_val.type.is_pyobject or self.false_val.type.is_pyobject:
5943             self.true_val = self.true_val.coerce_to(self.type, env)
5944             self.false_val = self.false_val.coerce_to(self.type, env)
5945         self.is_temp = 1
5946         if self.type == PyrexTypes.error_type:
5947             self.type_error()
5948         
5949     def type_error(self):
5950         if not (self.true_val.type.is_error or self.false_val.type.is_error):
5951             error(self.pos, "Incompatable types in conditional expression (%s; %s)" %
5952                 (self.true_val.type, self.false_val.type))
5953         self.type = PyrexTypes.error_type
5954     
5955     def check_const(self):
5956         return (self.test.check_const() 
5957             and self.true_val.check_const()
5958             and self.false_val.check_const())
5959     
5960     def generate_evaluation_code(self, code):
5961         # Because subexprs may not be evaluated we can use a more optimal
5962         # subexpr allocation strategy than the default, so override evaluation_code.
5963         
5964         code.mark_pos(self.pos)
5965         self.allocate_temp_result(code)
5966         self.test.generate_evaluation_code(code)
5967         code.putln("if (%s) {" % self.test.result() )
5968         self.eval_and_get(code, self.true_val)
5969         code.putln("} else {")
5970         self.eval_and_get(code, self.false_val)
5971         code.putln("}")
5972         self.test.generate_disposal_code(code)
5973         self.test.free_temps(code)
5974
5975     def eval_and_get(self, code, expr):
5976         expr.generate_evaluation_code(code)
5977         expr.make_owned_reference(code)
5978         code.putln("%s = %s;" % (self.result(), expr.result()))
5979         expr.generate_post_assignment_code(code)
5980         expr.free_temps(code)
5981
5982 richcmp_constants = {
5983     "<" : "Py_LT",
5984     "<=": "Py_LE",
5985     "==": "Py_EQ",
5986     "!=": "Py_NE",
5987     "<>": "Py_NE",
5988     ">" : "Py_GT",
5989     ">=": "Py_GE",
5990 }
5991
5992 class CmpNode(object):
5993     #  Mixin class containing code common to PrimaryCmpNodes
5994     #  and CascadedCmpNodes.
5995
5996     special_bool_cmp_function = None
5997
5998     def infer_type(self, env):
5999         # TODO: Actually implement this (after merging with -unstable).
6000         return py_object_type
6001
6002     def calculate_cascaded_constant_result(self, operand1_result):
6003         func = compile_time_binary_operators[self.operator]
6004         operand2_result = self.operand2.constant_result
6005         result = func(operand1_result, operand2_result)
6006         if self.cascade:
6007             self.cascade.calculate_cascaded_constant_result(operand2_result)
6008             if self.cascade.constant_result:
6009                 self.constant_result = result and self.cascade.constant_result
6010         else:
6011             self.constant_result = result
6012
6013     def cascaded_compile_time_value(self, operand1, denv):
6014         func = get_compile_time_binop(self)
6015         operand2 = self.operand2.compile_time_value(denv)
6016         try:
6017             result = func(operand1, operand2)
6018         except Exception, e:
6019             self.compile_time_value_error(e)
6020             result = None
6021         if result:
6022             cascade = self.cascade
6023             if cascade:
6024                 # FIXME: I bet this must call cascaded_compile_time_value()
6025                 result = result and cascade.cascaded_compile_time_value(operand2, denv)
6026         return result
6027
6028     def is_cpp_comparison(self):
6029         return self.operand1.type.is_cpp_class or self.operand2.type.is_cpp_class
6030
6031     def find_common_int_type(self, env, op, operand1, operand2):
6032         # type1 != type2 and at least one of the types is not a C int
6033         type1 = operand1.type
6034         type2 = operand2.type
6035         type1_can_be_int = False
6036         type2_can_be_int = False
6037
6038         if isinstance(operand1, (StringNode, BytesNode, UnicodeNode)) \
6039                and operand1.can_coerce_to_char_literal():
6040             type1_can_be_int = True
6041         if isinstance(operand2, (StringNode, BytesNode, UnicodeNode)) \
6042                  and operand2.can_coerce_to_char_literal():
6043             type2_can_be_int = True
6044
6045         if type1.is_int:
6046             if type2_can_be_int:
6047                 return type1
6048         elif type2.is_int:
6049             if type1_can_be_int:
6050                 return type2
6051         elif type1_can_be_int:
6052             if type2_can_be_int:
6053                 return PyrexTypes.c_uchar_type
6054
6055         return None
6056
6057     def find_common_type(self, env, op, operand1, common_type=None):
6058         operand2 = self.operand2
6059         type1 = operand1.type
6060         type2 = operand2.type
6061
6062         new_common_type = None
6063
6064         # catch general errors
6065         if type1 == str_type and (type2.is_string or type2 in (bytes_type, unicode_type)) or \
6066                type2 == str_type and (type1.is_string or type1 in (bytes_type, unicode_type)):
6067             error(self.pos, "Comparisons between bytes/unicode and str are not portable to Python 3")
6068             new_common_type = error_type
6069
6070         # try to use numeric comparisons where possible
6071         elif type1.is_complex or type2.is_complex:
6072             if op not in ('==', '!='):
6073                 error(self.pos, "complex types are unordered")
6074                 new_common_type = error_type
6075             if type1.is_pyobject:
6076                 new_common_type = type1
6077             elif type2.is_pyobject:
6078                 new_common_type = type2
6079             else:
6080                 new_common_type = PyrexTypes.widest_numeric_type(type1, type2)
6081         elif type1.is_numeric and type2.is_numeric:
6082             new_common_type = PyrexTypes.widest_numeric_type(type1, type2)
6083         elif common_type is None or not common_type.is_pyobject:
6084             new_common_type = self.find_common_int_type(env, op, operand1, operand2)
6085
6086         if new_common_type is None:
6087             # fall back to generic type compatibility tests
6088             if type1 == type2:
6089                 new_common_type = type1
6090             elif type1.is_pyobject or type2.is_pyobject:
6091                 if type2.is_numeric or type2.is_string:
6092                     if operand2.check_for_coercion_error(type1):
6093                         new_common_type = error_type
6094                     else:
6095                         new_common_type = py_object_type
6096                 elif type1.is_numeric or type1.is_string:
6097                     if operand1.check_for_coercion_error(type2):
6098                         new_common_type = error_type
6099                     else:
6100                         new_common_type = py_object_type
6101                 elif py_object_type.assignable_from(type1) and py_object_type.assignable_from(type2):
6102                     new_common_type = py_object_type
6103                 else:
6104                     # one Python type and one non-Python type, not assignable
6105                     self.invalid_types_error(operand1, op, operand2)
6106                     new_common_type = error_type
6107             elif type1.assignable_from(type2):
6108                 new_common_type = type1
6109             elif type2.assignable_from(type1):
6110                 new_common_type = type2
6111             else:
6112                 # C types that we couldn't handle up to here are an error
6113                 self.invalid_types_error(operand1, op, operand2)
6114                 new_common_type = error_type
6115
6116         if new_common_type.is_string and (isinstance(operand1, BytesNode) or
6117                                           isinstance(operand2, BytesNode)):
6118             # special case when comparing char* to bytes literal: must
6119             # compare string values!
6120             new_common_type = bytes_type
6121
6122         # recursively merge types
6123         if common_type is None or new_common_type.is_error:
6124             common_type = new_common_type
6125         else:
6126             # we could do a lot better by splitting the comparison
6127             # into a non-Python part and a Python part, but this is
6128             # safer for now
6129             common_type = PyrexTypes.spanning_type(common_type, new_common_type)
6130
6131         if self.cascade:
6132             common_type = self.cascade.find_common_type(env, self.operator, operand2, common_type)
6133
6134         return common_type
6135
6136     def invalid_types_error(self, operand1, op, operand2):
6137         error(self.pos, "Invalid types for '%s' (%s, %s)" %
6138               (op, operand1.type, operand2.type))
6139
6140     def is_python_comparison(self):
6141         return (not self.is_ptr_contains()
6142             and not self.is_c_string_contains()
6143             and (self.has_python_operands()
6144                  or (self.cascade and self.cascade.is_python_comparison())
6145                  or self.operator in ('in', 'not_in')))
6146
6147     def coerce_operands_to(self, dst_type, env):
6148         operand2 = self.operand2
6149         if operand2.type != dst_type:
6150             self.operand2 = operand2.coerce_to(dst_type, env)
6151         if self.cascade:
6152             self.cascade.coerce_operands_to(dst_type, env)
6153
6154     def is_python_result(self):
6155         return ((self.has_python_operands() and
6156                  self.special_bool_cmp_function is None and
6157                  self.operator not in ('is', 'is_not', 'in', 'not_in') and
6158                  not self.is_c_string_contains() and
6159                  not self.is_ptr_contains())
6160             or (self.cascade and self.cascade.is_python_result()))
6161
6162     def is_c_string_contains(self):
6163         return self.operator in ('in', 'not_in') and \
6164                ((self.operand1.type.is_int
6165                  and (self.operand2.type.is_string or self.operand2.type is bytes_type)) or
6166                 (self.operand1.type is PyrexTypes.c_py_unicode_type
6167                  and self.operand2.type is unicode_type))
6168     
6169     def is_ptr_contains(self):
6170         if self.operator in ('in', 'not_in'):
6171             container_type = self.operand2.type
6172             return (container_type.is_ptr or container_type.is_array) \
6173                 and not container_type.is_string
6174
6175     def find_special_bool_compare_function(self, env):
6176         if self.operator in ('==', '!='):
6177             type1, type2 = self.operand1.type, self.operand2.type
6178             if type1.is_pyobject and type2.is_pyobject:
6179                 if type1 is Builtin.unicode_type or type2 is Builtin.unicode_type:
6180                     env.use_utility_code(pyunicode_equals_utility_code)
6181                     self.special_bool_cmp_function = "__Pyx_PyUnicode_Equals"
6182                     return True
6183         return False
6184
6185     def generate_operation_code(self, code, result_code, 
6186             operand1, op , operand2):
6187         if self.type.is_pyobject:
6188             coerce_result = "__Pyx_PyBool_FromLong"
6189         else:
6190             coerce_result = ""
6191         if 'not' in op: 
6192             negation = "!"
6193         else: 
6194             negation = ""
6195         if self.special_bool_cmp_function:
6196             if operand1.type.is_pyobject:
6197                 result1 = operand1.py_result()
6198             else:
6199                 result1 = operand1.result()
6200             if operand2.type.is_pyobject:
6201                 result2 = operand2.py_result()
6202             else:
6203                 result2 = operand2.result()
6204             code.putln("%s = %s(%s, %s, %s); %s" % (
6205                 result_code,
6206                 self.special_bool_cmp_function,
6207                 result1,
6208                 result2,
6209                 richcmp_constants[op],
6210                 code.error_goto_if_neg(result_code, self.pos)))
6211         elif op == 'in' or op == 'not_in':
6212             code.globalstate.use_utility_code(contains_utility_code)
6213             if self.type.is_pyobject:
6214                 coerce_result = "__Pyx_PyBoolOrNull_FromLong"
6215             if op == 'not_in':
6216                 negation = "__Pyx_NegateNonNeg"
6217             if operand2.type is dict_type:
6218                 method = "PyDict_Contains"
6219             else:
6220                 method = "PySequence_Contains"
6221             if self.type.is_pyobject:
6222                 error_clause = code.error_goto_if_null
6223                 got_ref = "__Pyx_XGOTREF(%s); " % result_code
6224             else:
6225                 error_clause = code.error_goto_if_neg
6226                 got_ref = ""
6227             code.putln(
6228                 "%s = %s(%s(%s(%s, %s))); %s%s" % (
6229                     result_code,
6230                     coerce_result,
6231                     negation,
6232                     method,
6233                     operand2.py_result(), 
6234                     operand1.py_result(), 
6235                     got_ref,
6236                     error_clause(result_code, self.pos)))
6237         elif (operand1.type.is_pyobject
6238             and op not in ('is', 'is_not')):
6239                 code.putln("%s = PyObject_RichCompare(%s, %s, %s); %s" % (
6240                         result_code, 
6241                         operand1.py_result(), 
6242                         operand2.py_result(), 
6243                         richcmp_constants[op],
6244                         code.error_goto_if_null(result_code, self.pos)))
6245                 code.put_gotref(result_code)
6246         elif operand1.type.is_complex:
6247             if op == "!=": 
6248                 negation = "!"
6249             else: 
6250                 negation = ""
6251             code.putln("%s = %s(%s%s(%s, %s));" % (
6252                 result_code, 
6253                 coerce_result,
6254                 negation,
6255                 operand1.type.unary_op('eq'), 
6256                 operand1.result(), 
6257                 operand2.result()))
6258         else:
6259             type1 = operand1.type
6260             type2 = operand2.type
6261             if (type1.is_extension_type or type2.is_extension_type) \
6262                     and not type1.same_as(type2):
6263                 common_type = py_object_type
6264             elif type1.is_numeric:
6265                 common_type = PyrexTypes.widest_numeric_type(type1, type2)
6266             else:
6267                 common_type = type1
6268             code1 = operand1.result_as(common_type)
6269             code2 = operand2.result_as(common_type)
6270             code.putln("%s = %s(%s %s %s);" % (
6271                 result_code, 
6272                 coerce_result, 
6273                 code1, 
6274                 self.c_operator(op), 
6275                 code2))
6276
6277     def c_operator(self, op):
6278         if op == 'is':
6279             return "=="
6280         elif op == 'is_not':
6281             return "!="
6282         else:
6283             return op
6284     
6285 contains_utility_code = UtilityCode(
6286 proto="""
6287 static CYTHON_INLINE long __Pyx_NegateNonNeg(long b) { return unlikely(b < 0) ? b : !b; }
6288 static CYTHON_INLINE PyObject* __Pyx_PyBoolOrNull_FromLong(long b) {
6289     return unlikely(b < 0) ? NULL : __Pyx_PyBool_FromLong(b);
6290 }
6291 """)
6292
6293 char_in_bytes_utility_code = UtilityCode(
6294 proto="""
6295 static CYTHON_INLINE int __Pyx_BytesContains(PyObject* bytes, char character); /*proto*/
6296 """,
6297 impl="""
6298 static CYTHON_INLINE int __Pyx_BytesContains(PyObject* bytes, char character) {
6299     const Py_ssize_t length = PyBytes_GET_SIZE(bytes);
6300     char* char_start = PyBytes_AS_STRING(bytes);
6301     char* pos;
6302     for (pos=char_start; pos < char_start+length; pos++) {
6303         if (character == pos[0]) return 1;
6304     }
6305     return 0;
6306 }
6307 """)
6308
6309 pyunicode_in_unicode_utility_code = UtilityCode(
6310 proto="""
6311 static CYTHON_INLINE int __Pyx_UnicodeContains(PyObject* unicode, Py_UNICODE character); /*proto*/
6312 """,
6313 impl="""
6314 static CYTHON_INLINE int __Pyx_UnicodeContains(PyObject* unicode, Py_UNICODE character) {
6315     const Py_ssize_t length = PyUnicode_GET_SIZE(unicode);
6316     Py_UNICODE* char_start = PyUnicode_AS_UNICODE(unicode);
6317     Py_UNICODE* pos;
6318     for (pos=char_start; pos < char_start+length; pos++) {
6319         if (character == pos[0]) return 1;
6320     }
6321     return 0;
6322 }
6323 """)
6324
6325 pyunicode_equals_utility_code = UtilityCode(
6326 proto="""
6327 static CYTHON_INLINE int __Pyx_PyUnicode_Equals(PyObject* s1, PyObject* s2, int equals); /*proto*/
6328 """,
6329 impl="""
6330 static CYTHON_INLINE int __Pyx_PyUnicode_Equals(PyObject* s1, PyObject* s2, int equals) {
6331     if (s1 == s2) {   /* as done by PyObject_RichCompareBool(); also catches the (interned) empty string */
6332         return (equals == Py_EQ);
6333     } else if (PyUnicode_CheckExact(s1) & PyUnicode_CheckExact(s2)) {
6334         if (PyUnicode_GET_SIZE(s1) != PyUnicode_GET_SIZE(s2)) {
6335             return (equals == Py_NE);
6336         } else if (PyUnicode_GET_SIZE(s1) == 1) {
6337             if (equals == Py_EQ)
6338                 return (PyUnicode_AS_UNICODE(s1)[0] == PyUnicode_AS_UNICODE(s2)[0]);
6339             else
6340                 return (PyUnicode_AS_UNICODE(s1)[0] != PyUnicode_AS_UNICODE(s2)[0]);
6341         } else {
6342             int result = PyUnicode_Compare(s1, s2);
6343             if ((result == -1) && unlikely(PyErr_Occurred()))
6344                 return -1;
6345             return (equals == Py_EQ) ? (result == 0) : (result != 0);
6346         }
6347     } else if ((s1 == Py_None) & (s2 == Py_None)) {
6348         return (equals == Py_EQ);
6349     } else if ((s1 == Py_None) & PyUnicode_CheckExact(s2)) {
6350         return (equals == Py_NE);
6351     } else if ((s2 == Py_None) & PyUnicode_CheckExact(s1)) {
6352         return (equals == Py_NE);
6353     } else {
6354         int result;
6355         PyObject* py_result = PyObject_RichCompare(s1, s2, equals);
6356         if (!py_result)
6357             return -1;
6358         result = __Pyx_PyObject_IsTrue(py_result);
6359         Py_DECREF(py_result);
6360         return result;
6361     }
6362 }
6363 """)
6364
6365
6366 class PrimaryCmpNode(ExprNode, CmpNode):
6367     #  Non-cascaded comparison or first comparison of
6368     #  a cascaded sequence.
6369     #
6370     #  operator      string
6371     #  operand1      ExprNode
6372     #  operand2      ExprNode
6373     #  cascade       CascadedCmpNode
6374     
6375     #  We don't use the subexprs mechanism, because
6376     #  things here are too complicated for it to handle.
6377     #  Instead, we override all the framework methods
6378     #  which use it.
6379     
6380     child_attrs = ['operand1', 'operand2', 'cascade']
6381     
6382     cascade = None
6383
6384     def infer_type(self, env):
6385         # TODO: Actually implement this (after merging with -unstable).
6386         return py_object_type
6387
6388     def type_dependencies(self, env):
6389         return ()
6390
6391     def calculate_constant_result(self):
6392         self.calculate_cascaded_constant_result(self.operand1.constant_result)
6393     
6394     def compile_time_value(self, denv):
6395         operand1 = self.operand1.compile_time_value(denv)
6396         return self.cascaded_compile_time_value(operand1, denv)
6397
6398     def analyse_types(self, env):
6399         self.operand1.analyse_types(env)
6400         self.operand2.analyse_types(env)
6401         if self.is_cpp_comparison():
6402             self.analyse_cpp_comparison(env)
6403             if self.cascade:
6404                 error(self.pos, "Cascading comparison not yet supported for cpp types.")
6405             return
6406         if self.cascade:
6407             self.cascade.analyse_types(env)
6408
6409         if self.operator in ('in', 'not_in'):
6410             if self.is_c_string_contains():
6411                 self.is_pycmp = False
6412                 common_type = None
6413                 if self.cascade:
6414                     error(self.pos, "Cascading comparison not yet supported for 'int_val in string'.")
6415                     return
6416                 if self.operand2.type is unicode_type:
6417                     env.use_utility_code(pyunicode_in_unicode_utility_code)
6418                 else:
6419                     if self.operand1.type is PyrexTypes.c_uchar_type:
6420                         self.operand1 = self.operand1.coerce_to(PyrexTypes.c_char_type, env)
6421                     if self.operand2.type is not bytes_type:
6422                         self.operand2 = self.operand2.coerce_to(bytes_type, env)
6423                     env.use_utility_code(char_in_bytes_utility_code)
6424                 self.operand2 = self.operand2.as_none_safe_node(
6425                     "argument of type 'NoneType' is not iterable")
6426             elif self.is_ptr_contains():
6427                 if self.cascade:
6428                     error(self.pos, "Cascading comparison not yet supported for 'val in sliced pointer'.")
6429                 self.type = PyrexTypes.c_bint_type
6430                 # Will be transformed by IterationTransform
6431                 return
6432             else:
6433                 if self.operand2.type is dict_type:
6434                     self.operand2 = self.operand2.as_none_safe_node("'NoneType' object is not iterable")
6435                 common_type = py_object_type
6436                 self.is_pycmp = True
6437         elif self.find_special_bool_compare_function(env):
6438             common_type = None # if coercion needed, the method call above has already done it
6439             self.is_pycmp = False # result is bint
6440             self.is_temp = True # must check for error return
6441         else:
6442             common_type = self.find_common_type(env, self.operator, self.operand1)
6443             self.is_pycmp = common_type.is_pyobject
6444
6445         if common_type is not None and not common_type.is_error:
6446             if self.operand1.type != common_type:
6447                 self.operand1 = self.operand1.coerce_to(common_type, env)
6448             self.coerce_operands_to(common_type, env)
6449
6450         if self.cascade:
6451             self.operand2 = self.operand2.coerce_to_simple(env)
6452             self.cascade.coerce_cascaded_operands_to_temp(env)
6453         if self.is_python_result():
6454             self.type = PyrexTypes.py_object_type
6455         else:
6456             self.type = PyrexTypes.c_bint_type
6457         cdr = self.cascade
6458         while cdr:
6459             cdr.type = self.type
6460             cdr = cdr.cascade
6461         if self.is_pycmp or self.cascade:
6462             self.is_temp = 1
6463     
6464     def analyse_cpp_comparison(self, env):
6465         type1 = self.operand1.type
6466         type2 = self.operand2.type
6467         entry = env.lookup_operator(self.operator, [self.operand1, self.operand2])
6468         if entry is None:
6469             error(self.pos, "Invalid types for '%s' (%s, %s)" %
6470                 (self.operator, type1, type2))
6471             self.type = PyrexTypes.error_type
6472             self.result_code = "<error>"
6473             return
6474         func_type = entry.type
6475         if func_type.is_ptr:
6476             func_type = func_type.base_type
6477         if len(func_type.args) == 1:
6478             self.operand2 = self.operand2.coerce_to(func_type.args[0].type, env)
6479         else:
6480             self.operand1 = self.operand1.coerce_to(func_type.args[0].type, env)
6481             self.operand2 = self.operand2.coerce_to(func_type.args[1].type, env)
6482         self.type = func_type.return_type
6483     
6484     def has_python_operands(self):
6485         return (self.operand1.type.is_pyobject
6486             or self.operand2.type.is_pyobject)
6487     
6488     def check_const(self):
6489         if self.cascade:
6490             self.not_const()
6491             return False
6492         else:
6493             return self.operand1.check_const() and self.operand2.check_const()
6494
6495     def calculate_result_code(self):
6496         if self.operand1.type.is_complex:
6497             if self.operator == "!=":
6498                 negation = "!"
6499             else:
6500                 negation = ""
6501             return "(%s%s(%s, %s))" % (
6502                 negation,
6503                 self.operand1.type.binary_op('=='), 
6504                 self.operand1.result(), 
6505                 self.operand2.result())
6506         elif self.is_c_string_contains():
6507             if self.operand2.type is bytes_type:
6508                 method = "__Pyx_BytesContains"
6509             else:
6510                 method = "__Pyx_UnicodeContains"
6511             if self.operator == "not_in":
6512                 negation = "!"
6513             else:
6514                 negation = ""
6515             return "(%s%s(%s, %s))" % (
6516                 negation,
6517                 method,
6518                 self.operand2.result(), 
6519                 self.operand1.result())
6520         else:
6521             return "(%s %s %s)" % (
6522                 self.operand1.result(),
6523                 self.c_operator(self.operator),
6524                 self.operand2.result())
6525
6526     def generate_evaluation_code(self, code):
6527         self.operand1.generate_evaluation_code(code)
6528         self.operand2.generate_evaluation_code(code)
6529         if self.is_temp:
6530             self.allocate_temp_result(code)
6531             self.generate_operation_code(code, self.result(), 
6532                 self.operand1, self.operator, self.operand2)
6533             if self.cascade:
6534                 self.cascade.generate_evaluation_code(code,
6535                     self.result(), self.operand2)
6536             self.operand1.generate_disposal_code(code)
6537             self.operand1.free_temps(code)
6538             self.operand2.generate_disposal_code(code)
6539             self.operand2.free_temps(code)
6540
6541     def generate_subexpr_disposal_code(self, code):
6542         #  If this is called, it is a non-cascaded cmp,
6543         #  so only need to dispose of the two main operands.
6544         self.operand1.generate_disposal_code(code)
6545         self.operand2.generate_disposal_code(code)
6546         
6547     def free_subexpr_temps(self, code):
6548         #  If this is called, it is a non-cascaded cmp,
6549         #  so only need to dispose of the two main operands.
6550         self.operand1.free_temps(code)
6551         self.operand2.free_temps(code)
6552         
6553     def annotate(self, code):
6554         self.operand1.annotate(code)
6555         self.operand2.annotate(code)
6556         if self.cascade:
6557             self.cascade.annotate(code)
6558
6559
6560 class CascadedCmpNode(Node, CmpNode):
6561     #  A CascadedCmpNode is not a complete expression node. It 
6562     #  hangs off the side of another comparison node, shares 
6563     #  its left operand with that node, and shares its result 
6564     #  with the PrimaryCmpNode at the head of the chain.
6565     #
6566     #  operator      string
6567     #  operand2      ExprNode
6568     #  cascade       CascadedCmpNode
6569
6570     child_attrs = ['operand2', 'cascade']
6571
6572     cascade = None
6573     constant_result = constant_value_not_set # FIXME: where to calculate this?
6574
6575     def infer_type(self, env):
6576         # TODO: Actually implement this (after merging with -unstable).
6577         return py_object_type
6578
6579     def type_dependencies(self, env):
6580         return ()
6581
6582     def has_constant_result(self):
6583         return self.constant_result is not constant_value_not_set and \
6584                self.constant_result is not not_a_constant
6585
6586     def analyse_types(self, env):
6587         self.operand2.analyse_types(env)
6588         if self.cascade:
6589             self.cascade.analyse_types(env)
6590
6591     def has_python_operands(self):
6592         return self.operand2.type.is_pyobject
6593         
6594     def coerce_operands_to_pyobjects(self, env):
6595         self.operand2 = self.operand2.coerce_to_pyobject(env)
6596         if self.operand2.type is dict_type and self.operator in ('in', 'not_in'):
6597             self.operand2 = self.operand2.as_none_safe_node("'NoneType' object is not iterable")
6598         if self.cascade:
6599             self.cascade.coerce_operands_to_pyobjects(env)
6600
6601     def coerce_cascaded_operands_to_temp(self, env):
6602         if self.cascade:
6603             #self.operand2 = self.operand2.coerce_to_temp(env) #CTT
6604             self.operand2 = self.operand2.coerce_to_simple(env)
6605             self.cascade.coerce_cascaded_operands_to_temp(env)
6606     
6607     def generate_evaluation_code(self, code, result, operand1):
6608         if self.type.is_pyobject:
6609             code.putln("if (__Pyx_PyObject_IsTrue(%s)) {" % result)
6610             code.put_decref(result, self.type)
6611         else:
6612             code.putln("if (%s) {" % result)
6613         self.operand2.generate_evaluation_code(code)
6614         self.generate_operation_code(code, result, 
6615             operand1, self.operator, self.operand2)
6616         if self.cascade:
6617             self.cascade.generate_evaluation_code(
6618                 code, result, self.operand2)
6619         # Cascaded cmp result is always temp
6620         self.operand2.generate_disposal_code(code)
6621         self.operand2.free_temps(code)
6622         code.putln("}")
6623
6624     def annotate(self, code):
6625         self.operand2.annotate(code)
6626         if self.cascade:
6627             self.cascade.annotate(code)
6628
6629
6630 binop_node_classes = {
6631     "or":       BoolBinopNode,
6632     "and":      BoolBinopNode,
6633     "|":        IntBinopNode,
6634     "^":        IntBinopNode,
6635     "&":        IntBinopNode,
6636     "<<":       IntBinopNode,
6637     ">>":       IntBinopNode,
6638     "+":        AddNode,
6639     "-":        SubNode,
6640     "*":        MulNode,
6641     "/":        DivNode,
6642     "//":       DivNode,
6643     "%":        ModNode,
6644     "**":       PowNode
6645 }
6646
6647 def binop_node(pos, operator, operand1, operand2, inplace=False):
6648     # Construct binop node of appropriate class for 
6649     # given operator.
6650     return binop_node_classes[operator](pos, 
6651         operator = operator, 
6652         operand1 = operand1, 
6653         operand2 = operand2,
6654         inplace = inplace)
6655
6656 #-------------------------------------------------------------------
6657 #
6658 #  Coercion nodes
6659 #
6660 #  Coercion nodes are special in that they are created during
6661 #  the analyse_types phase of parse tree processing.
6662 #  Their __init__ methods consequently incorporate some aspects
6663 #  of that phase.
6664 #
6665 #-------------------------------------------------------------------
6666
6667 class CoercionNode(ExprNode):
6668     #  Abstract base class for coercion nodes.
6669     #
6670     #  arg       ExprNode       node being coerced
6671     
6672     subexprs = ['arg']
6673     constant_result = not_a_constant
6674     
6675     def __init__(self, arg):
6676         self.pos = arg.pos
6677         self.arg = arg
6678         if debug_coercion:
6679             print("%s Coercing %s" % (self, self.arg))
6680
6681     def calculate_constant_result(self):
6682         # constant folding can break type coercion, so this is disabled
6683         pass
6684             
6685     def annotate(self, code):
6686         self.arg.annotate(code)
6687         if self.arg.type != self.type:
6688             file, line, col = self.pos
6689             code.annotate((file, line, col-1), AnnotationItem(style='coerce', tag='coerce', text='[%s] to [%s]' % (self.arg.type, self.type)))
6690
6691
6692 class CastNode(CoercionNode):
6693     #  Wrap a node in a C type cast.
6694     
6695     def __init__(self, arg, new_type):
6696         CoercionNode.__init__(self, arg)
6697         self.type = new_type
6698
6699     def may_be_none(self):
6700         return self.arg.may_be_none()
6701     
6702     def calculate_result_code(self):
6703         return self.arg.result_as(self.type)
6704
6705     def generate_result_code(self, code):
6706         self.arg.generate_result_code(code)
6707
6708
6709 class PyTypeTestNode(CoercionNode):
6710     #  This node is used to check that a generic Python
6711     #  object is an instance of a particular extension type.
6712     #  This node borrows the result of its argument node.
6713
6714     def __init__(self, arg, dst_type, env, notnone=False):
6715         #  The arg is know to be a Python object, and
6716         #  the dst_type is known to be an extension type.
6717         assert dst_type.is_extension_type or dst_type.is_builtin_type, "PyTypeTest on non extension type"
6718         CoercionNode.__init__(self, arg)
6719         self.type = dst_type
6720         self.result_ctype = arg.ctype()
6721         self.notnone = notnone
6722
6723     nogil_check = Node.gil_error
6724     gil_message = "Python type test"
6725     
6726     def analyse_types(self, env):
6727         pass
6728
6729     def may_be_none(self):
6730         if self.notnone:
6731             return False
6732         return self.arg.may_be_none()
6733     
6734     def result_in_temp(self):
6735         return self.arg.result_in_temp()
6736     
6737     def is_ephemeral(self):
6738         return self.arg.is_ephemeral()
6739
6740     def calculate_constant_result(self):
6741         # FIXME
6742         pass
6743
6744     def calculate_result_code(self):
6745         return self.arg.result()
6746     
6747     def generate_result_code(self, code):
6748         if self.type.typeobj_is_available():
6749             if not self.type.is_builtin_type:
6750                 code.globalstate.use_utility_code(type_test_utility_code)
6751             code.putln(
6752                 "if (!(%s)) %s" % (
6753                     self.type.type_test_code(self.arg.py_result(), self.notnone),
6754                     code.error_goto(self.pos)))
6755         else:
6756             error(self.pos, "Cannot test type of extern C class "
6757                 "without type object name specification")
6758                 
6759     def generate_post_assignment_code(self, code):
6760         self.arg.generate_post_assignment_code(code)
6761
6762     def free_temps(self, code):
6763         self.arg.free_temps(code)
6764
6765
6766 class NoneCheckNode(CoercionNode):
6767     # This node is used to check that a Python object is not None and
6768     # raises an appropriate exception (as specified by the creating
6769     # transform).
6770
6771     def __init__(self, arg, exception_type_cname, exception_message):
6772         CoercionNode.__init__(self, arg)
6773         self.type = arg.type
6774         self.result_ctype = arg.ctype()
6775         self.exception_type_cname = exception_type_cname
6776         self.exception_message = exception_message
6777
6778     def analyse_types(self, env):
6779         pass
6780
6781     def may_be_none(self):
6782         return False
6783
6784     def result_in_temp(self):
6785         return self.arg.result_in_temp()
6786
6787     def calculate_result_code(self):
6788         return self.arg.result()
6789     
6790     def generate_result_code(self, code):
6791         code.putln(
6792             "if (unlikely(%s == Py_None)) {" % self.arg.result())
6793         code.putln('PyErr_SetString(%s, "%s"); %s ' % (
6794             self.exception_type_cname,
6795             StringEncoding.escape_byte_string(
6796                 self.exception_message.encode('UTF-8')),
6797             code.error_goto(self.pos)))
6798         code.putln("}")
6799
6800     def generate_post_assignment_code(self, code):
6801         self.arg.generate_post_assignment_code(code)
6802
6803     def free_temps(self, code):
6804         self.arg.free_temps(code)
6805
6806
6807 class CoerceToPyTypeNode(CoercionNode):
6808     #  This node is used to convert a C data type
6809     #  to a Python object.
6810     
6811     type = py_object_type
6812     is_temp = 1
6813
6814     def __init__(self, arg, env, type=py_object_type):
6815         CoercionNode.__init__(self, arg)
6816         if not arg.type.create_to_py_utility_code(env):
6817             error(arg.pos,
6818                   "Cannot convert '%s' to Python object" % arg.type)
6819         if type is not py_object_type:
6820             self.type = py_object_type
6821         elif arg.type.is_string:
6822             self.type = bytes_type
6823         elif arg.type is PyrexTypes.c_py_unicode_type:
6824             self.type = unicode_type
6825
6826     gil_message = "Converting to Python object"
6827
6828     def may_be_none(self):
6829         # FIXME: is this always safe?
6830         return False
6831
6832     def coerce_to_boolean(self, env):
6833         arg_type = self.arg.type
6834         if (arg_type == PyrexTypes.c_bint_type or
6835             (arg_type.is_pyobject and arg_type.name == 'bool')):
6836             return self.arg.coerce_to_temp(env)
6837         else:
6838             return CoerceToBooleanNode(self, env)
6839     
6840     def coerce_to_integer(self, env):
6841         # If not already some C integer type, coerce to longint.
6842         if self.arg.type.is_int:
6843             return self.arg
6844         else:
6845             return self.arg.coerce_to(PyrexTypes.c_long_type, env)
6846
6847     def analyse_types(self, env):
6848         # The arg is always already analysed
6849         pass
6850
6851     def generate_result_code(self, code):
6852         function = self.arg.type.to_py_function
6853         code.putln('%s = %s(%s); %s' % (
6854             self.result(), 
6855             function, 
6856             self.arg.result(), 
6857             code.error_goto_if_null(self.result(), self.pos)))
6858         code.put_gotref(self.py_result())
6859
6860
6861 class CoerceIntToBytesNode(CoerceToPyTypeNode):
6862     #  This node is used to convert a C int type to a Python bytes
6863     #  object.
6864
6865     is_temp = 1
6866
6867     def __init__(self, arg, env):
6868         arg = arg.coerce_to_simple(env)
6869         CoercionNode.__init__(self, arg)
6870         self.type = Builtin.bytes_type
6871
6872     def generate_result_code(self, code):
6873         arg = self.arg
6874         arg_result = arg.result()
6875         if arg.type not in (PyrexTypes.c_char_type,
6876                             PyrexTypes.c_uchar_type,
6877                             PyrexTypes.c_schar_type):
6878             if arg.type.signed:
6879                 code.putln("if ((%s < 0) || (%s > 255)) {" % (
6880                     arg_result, arg_result))
6881             else:
6882                 code.putln("if (%s > 255) {" % arg_result)
6883             code.putln('PyErr_Format(PyExc_OverflowError, '
6884                        '"value too large to pack into a byte"); %s' % (
6885                            code.error_goto(self.pos)))
6886             code.putln('}')
6887         temp = None
6888         if arg.type is not PyrexTypes.c_char_type:
6889             temp = code.funcstate.allocate_temp(PyrexTypes.c_char_type, manage_ref=False)
6890             code.putln("%s = (char)%s;" % (temp, arg_result))
6891             arg_result = temp
6892         code.putln('%s = PyBytes_FromStringAndSize(&%s, 1); %s' % (
6893             self.result(),
6894             arg_result,
6895             code.error_goto_if_null(self.result(), self.pos)))
6896         if temp is not None:
6897             code.funcstate.release_temp(temp)
6898         code.put_gotref(self.py_result())
6899
6900
6901 class CoerceFromPyTypeNode(CoercionNode):
6902     #  This node is used to convert a Python object
6903     #  to a C data type.
6904
6905     def __init__(self, result_type, arg, env):
6906         CoercionNode.__init__(self, arg)
6907         self.type = result_type
6908         self.is_temp = 1
6909         if not result_type.create_from_py_utility_code(env):
6910             error(arg.pos,
6911                   "Cannot convert Python object to '%s'" % result_type)
6912         if self.type.is_string and self.arg.is_ephemeral():
6913             error(arg.pos,
6914                   "Obtaining char * from temporary Python value")
6915     
6916     def analyse_types(self, env):
6917         # The arg is always already analysed
6918         pass
6919
6920     def generate_result_code(self, code):
6921         function = self.type.from_py_function
6922         operand = self.arg.py_result()
6923         rhs = "%s(%s)" % (function, operand)
6924         if self.type.is_enum:
6925             rhs = typecast(self.type, c_long_type, rhs)
6926         code.putln('%s = %s; %s' % (
6927             self.result(), 
6928             rhs,
6929             code.error_goto_if(self.type.error_condition(self.result()), self.pos)))
6930         if self.type.is_pyobject:
6931             code.put_gotref(self.py_result())
6932
6933
6934 class CoerceToBooleanNode(CoercionNode):
6935     #  This node is used when a result needs to be used
6936     #  in a boolean context.
6937     
6938     type = PyrexTypes.c_bint_type
6939
6940     _special_builtins = {
6941         Builtin.list_type    : 'PyList_GET_SIZE',
6942         Builtin.tuple_type   : 'PyTuple_GET_SIZE',
6943         Builtin.bytes_type   : 'PyBytes_GET_SIZE',
6944         Builtin.unicode_type : 'PyUnicode_GET_SIZE',
6945         }
6946
6947     def __init__(self, arg, env):
6948         CoercionNode.__init__(self, arg)
6949         if arg.type.is_pyobject:
6950             self.is_temp = 1
6951
6952     def nogil_check(self, env):
6953         if self.arg.type.is_pyobject and self._special_builtins.get(self.arg.type) is None:
6954             self.gil_error()
6955
6956     gil_message = "Truth-testing Python object"
6957     
6958     def check_const(self):
6959         if self.is_temp:
6960             self.not_const()
6961             return False
6962         return self.arg.check_const()
6963     
6964     def calculate_result_code(self):
6965         return "(%s != 0)" % self.arg.result()
6966
6967     def generate_result_code(self, code):
6968         if not self.is_temp:
6969             return
6970         test_func = self._special_builtins.get(self.arg.type)
6971         if test_func is not None:
6972             code.putln("%s = (%s != Py_None) && (%s(%s) != 0);" % (
6973                        self.result(),
6974                        self.arg.py_result(),
6975                        test_func,
6976                        self.arg.py_result()))
6977         else:
6978             code.putln(
6979                 "%s = __Pyx_PyObject_IsTrue(%s); %s" % (
6980                     self.result(), 
6981                     self.arg.py_result(), 
6982                     code.error_goto_if_neg(self.result(), self.pos)))
6983
6984 class CoerceToComplexNode(CoercionNode):
6985
6986     def __init__(self, arg, dst_type, env):
6987         if arg.type.is_complex:
6988             arg = arg.coerce_to_simple(env)
6989         self.type = dst_type
6990         CoercionNode.__init__(self, arg)
6991         dst_type.create_declaration_utility_code(env)
6992
6993     def calculate_result_code(self):
6994         if self.arg.type.is_complex:
6995             real_part = "__Pyx_CREAL(%s)" % self.arg.result()
6996             imag_part = "__Pyx_CIMAG(%s)" % self.arg.result()
6997         else:
6998             real_part = self.arg.result()
6999             imag_part = "0"
7000         return "%s(%s, %s)" % (
7001                 self.type.from_parts,
7002                 real_part,
7003                 imag_part)
7004     
7005     def generate_result_code(self, code):
7006         pass
7007
7008 class CoerceToTempNode(CoercionNode):
7009     #  This node is used to force the result of another node
7010     #  to be stored in a temporary. It is only used if the
7011     #  argument node's result is not already in a temporary.
7012
7013     def __init__(self, arg, env):
7014         CoercionNode.__init__(self, arg)
7015         self.type = self.arg.type
7016         self.constant_result = self.arg.constant_result
7017         self.is_temp = 1
7018         if self.type.is_pyobject:
7019             self.result_ctype = py_object_type
7020
7021     gil_message = "Creating temporary Python reference"
7022
7023     def analyse_types(self, env):
7024         # The arg is always already analysed
7025         pass
7026         
7027     def coerce_to_boolean(self, env):
7028         self.arg = self.arg.coerce_to_boolean(env)
7029         if self.arg.is_simple():
7030             return self.arg
7031         self.type = self.arg.type
7032         self.result_ctype = self.type
7033         return self
7034
7035     def generate_result_code(self, code):
7036         #self.arg.generate_evaluation_code(code) # Already done
7037         # by generic generate_subexpr_evaluation_code!
7038         code.putln("%s = %s;" % (
7039             self.result(), self.arg.result_as(self.ctype())))
7040         if self.type.is_pyobject and self.use_managed_ref:
7041             code.put_incref(self.result(), self.ctype())
7042
7043
7044 class CloneNode(CoercionNode):
7045     #  This node is employed when the result of another node needs
7046     #  to be used multiple times. The argument node's result must
7047     #  be in a temporary. This node "borrows" the result from the
7048     #  argument node, and does not generate any evaluation or
7049     #  disposal code for it. The original owner of the argument 
7050     #  node is responsible for doing those things.
7051     
7052     subexprs = [] # Arg is not considered a subexpr
7053     nogil_check = None
7054     
7055     def __init__(self, arg):
7056         CoercionNode.__init__(self, arg)
7057         if hasattr(arg, 'type'):
7058             self.type = arg.type
7059             self.result_ctype = arg.result_ctype
7060         if hasattr(arg, 'entry'):
7061             self.entry = arg.entry
7062             
7063     def result(self):
7064         return self.arg.result()
7065     
7066     def type_dependencies(self, env):
7067         return self.arg.type_dependencies(env)
7068     
7069     def infer_type(self, env):
7070         return self.arg.infer_type(env)
7071
7072     def analyse_types(self, env):
7073         self.type = self.arg.type
7074         self.result_ctype = self.arg.result_ctype
7075         self.is_temp = 1
7076         if hasattr(self.arg, 'entry'):
7077             self.entry = self.arg.entry
7078     
7079     def generate_evaluation_code(self, code):
7080         pass
7081
7082     def generate_result_code(self, code):
7083         pass
7084         
7085     def generate_disposal_code(self, code):
7086         pass
7087                 
7088     def free_temps(self, code):
7089         pass
7090
7091
7092 class ModuleRefNode(ExprNode):
7093     # Simple returns the module object
7094     
7095     type = py_object_type
7096     is_temp = False
7097     subexprs = []
7098     
7099     def analyse_types(self, env):
7100         pass
7101
7102     def may_be_none(self):
7103         return False
7104
7105     def calculate_result_code(self):
7106         return Naming.module_cname
7107
7108     def generate_result_code(self, code):
7109         pass
7110
7111 class DocstringRefNode(ExprNode):
7112     # Extracts the docstring of the body element
7113     
7114     subexprs = ['body']
7115     type = py_object_type
7116     is_temp = True
7117     
7118     def __init__(self, pos, body):
7119         ExprNode.__init__(self, pos)
7120         assert body.type.is_pyobject
7121         self.body = body
7122
7123     def analyse_types(self, env):
7124         pass
7125
7126     def generate_result_code(self, code):
7127         code.putln('%s = __Pyx_GetAttrString(%s, "__doc__"); %s' % (
7128             self.result(), self.body.result(),
7129             code.error_goto_if_null(self.result(), self.pos)))
7130         code.put_gotref(self.result())
7131
7132
7133
7134 #------------------------------------------------------------------------------------
7135 #
7136 #  Runtime support code
7137 #
7138 #------------------------------------------------------------------------------------
7139
7140 get_name_interned_utility_code = UtilityCode(
7141 proto = """
7142 static PyObject *__Pyx_GetName(PyObject *dict, PyObject *name); /*proto*/
7143 """,
7144 impl = """
7145 static PyObject *__Pyx_GetName(PyObject *dict, PyObject *name) {
7146     PyObject *result;
7147     result = PyObject_GetAttr(dict, name);
7148     if (!result)
7149         PyErr_SetObject(PyExc_NameError, name);
7150     return result;
7151 }
7152 """)
7153
7154 #------------------------------------------------------------------------------------
7155
7156 import_utility_code = UtilityCode(
7157 proto = """
7158 static PyObject *__Pyx_Import(PyObject *name, PyObject *from_list); /*proto*/
7159 """,
7160 impl = """
7161 static PyObject *__Pyx_Import(PyObject *name, PyObject *from_list) {
7162     PyObject *py_import = 0;
7163     PyObject *empty_list = 0;
7164     PyObject *module = 0;
7165     PyObject *global_dict = 0;
7166     PyObject *empty_dict = 0;
7167     PyObject *list;
7168     py_import = __Pyx_GetAttrString(%(BUILTINS)s, "__import__");
7169     if (!py_import)
7170         goto bad;
7171     if (from_list)
7172         list = from_list;
7173     else {
7174         empty_list = PyList_New(0);
7175         if (!empty_list)
7176             goto bad;
7177         list = empty_list;
7178     }
7179     global_dict = PyModule_GetDict(%(GLOBALS)s);
7180     if (!global_dict)
7181         goto bad;
7182     empty_dict = PyDict_New();
7183     if (!empty_dict)
7184         goto bad;
7185     module = PyObject_CallFunctionObjArgs(py_import,
7186         name, global_dict, empty_dict, list, NULL);
7187 bad:
7188     Py_XDECREF(empty_list);
7189     Py_XDECREF(py_import);
7190     Py_XDECREF(empty_dict);
7191     return module;
7192 }
7193 """ % {
7194     "BUILTINS": Naming.builtins_cname,
7195     "GLOBALS":  Naming.module_cname,
7196 })
7197
7198 #------------------------------------------------------------------------------------
7199
7200 get_exception_utility_code = UtilityCode(
7201 proto = """
7202 static PyObject *__Pyx_GetExcValue(void); /*proto*/
7203 """,
7204 impl = """
7205 static PyObject *__Pyx_GetExcValue(void) {
7206     PyObject *type = 0, *value = 0, *tb = 0;
7207     PyObject *tmp_type, *tmp_value, *tmp_tb;
7208     PyObject *result = 0;
7209     PyThreadState *tstate = PyThreadState_Get();
7210     PyErr_Fetch(&type, &value, &tb);
7211     PyErr_NormalizeException(&type, &value, &tb);
7212     if (PyErr_Occurred())
7213         goto bad;
7214     if (!value) {
7215         value = Py_None;
7216         Py_INCREF(value);
7217     }
7218     tmp_type = tstate->exc_type;
7219     tmp_value = tstate->exc_value;
7220     tmp_tb = tstate->exc_traceback;
7221     tstate->exc_type = type;
7222     tstate->exc_value = value;
7223     tstate->exc_traceback = tb;
7224     /* Make sure tstate is in a consistent state when we XDECREF
7225     these objects (XDECREF may run arbitrary code). */
7226     Py_XDECREF(tmp_type);
7227     Py_XDECREF(tmp_value);
7228     Py_XDECREF(tmp_tb);
7229     result = value;
7230     Py_XINCREF(result);
7231     type = 0;
7232     value = 0;
7233     tb = 0;
7234 bad:
7235     Py_XDECREF(type);
7236     Py_XDECREF(value);
7237     Py_XDECREF(tb);
7238     return result;
7239 }
7240 """)
7241
7242 #------------------------------------------------------------------------------------
7243
7244 type_test_utility_code = UtilityCode(
7245 proto = """
7246 static CYTHON_INLINE int __Pyx_TypeTest(PyObject *obj, PyTypeObject *type); /*proto*/
7247 """,
7248 impl = """
7249 static CYTHON_INLINE int __Pyx_TypeTest(PyObject *obj, PyTypeObject *type) {
7250     if (unlikely(!type)) {
7251         PyErr_Format(PyExc_SystemError, "Missing type object");
7252         return 0;
7253     }
7254     if (likely(PyObject_TypeCheck(obj, type)))
7255         return 1;
7256     PyErr_Format(PyExc_TypeError, "Cannot convert %.200s to %.200s",
7257                  Py_TYPE(obj)->tp_name, type->tp_name);
7258     return 0;
7259 }
7260 """)
7261
7262 #------------------------------------------------------------------------------------
7263
7264 create_class_utility_code = UtilityCode(
7265 proto = """
7266 static PyObject *__Pyx_CreateClass(PyObject *bases, PyObject *dict, PyObject *name,
7267                                    PyObject *modname, PyObject *kwargs); /*proto*/
7268 static int __Pyx_PrepareClass(PyObject *metaclass, PyObject *bases, PyObject *name,
7269                               PyObject *mkw, PyObject *dict); /*proto*/
7270 """,
7271 impl = """
7272 static int __Pyx_PrepareClass(PyObject *metaclass, PyObject *bases, PyObject *name,
7273                               PyObject *mkw, PyObject *dict) {
7274     PyObject *prep;
7275     PyObject *pargs;
7276     PyObject *ns;
7277
7278     prep = PyObject_GetAttrString(metaclass, "__prepare__");
7279     if (prep == NULL) {
7280         if (!PyErr_ExceptionMatches(PyExc_AttributeError))
7281             return -1;
7282         PyErr_Clear();
7283         return 0;
7284     }
7285     pargs = PyTuple_New(2);
7286     if (!pargs) {
7287         Py_DECREF(prep);
7288         return -1;
7289     }
7290     Py_INCREF(name);
7291     Py_INCREF(bases);
7292     PyTuple_SET_ITEM(pargs, 0, name);
7293     PyTuple_SET_ITEM(pargs, 1, bases);
7294     ns = PyEval_CallObjectWithKeywords(prep, pargs, mkw);
7295     Py_DECREF(pargs);
7296     Py_DECREF(prep);
7297     if (ns == NULL)
7298         return -1;
7299     /* XXX: This is hack, merge namespace back to dict,
7300        __prepare__ should be ran before dict initialization */
7301     if (PyDict_Merge(dict, ns, 0)) {
7302         Py_DECREF(ns);
7303         return -1;
7304     }
7305     Py_DECREF(ns);
7306     return 0;
7307 }
7308
7309 static PyObject *__Pyx_CreateClass(PyObject *bases, PyObject *dict, PyObject *name,
7310                                    PyObject *modname, PyObject *kwargs) {
7311     PyObject *result = NULL;
7312     PyObject *metaclass = NULL;
7313     PyObject *mkw = NULL;
7314
7315     if (PyDict_SetItemString(dict, "__module__", modname) < 0)
7316         return NULL;
7317
7318     /* Python3 metaclasses */
7319     if (kwargs) {
7320         mkw = PyDict_Copy(kwargs); /* Don't modify kwargs passed in! */
7321         if (!mkw)
7322             return NULL;
7323         metaclass = PyDict_GetItemString(mkw, "metaclass");
7324         if (metaclass) {
7325             Py_INCREF(metaclass);
7326             if (PyDict_DelItemString(mkw, "metaclass") < 0)
7327                 goto bad;
7328             if (__Pyx_PrepareClass(metaclass, bases, name, mkw, dict))
7329                 goto bad;
7330         }
7331     }
7332     if (!metaclass) {
7333         /* Python2 __metaclass__ */
7334         metaclass = PyDict_GetItemString(dict, "__metaclass__");
7335         if (!metaclass) {
7336             /* Default metaclass */
7337 #if PY_MAJOR_VERSION < 3
7338             if (PyTuple_Check(bases) && PyTuple_GET_SIZE(bases) > 0) {
7339                 PyObject *base = PyTuple_GET_ITEM(bases, 0);
7340                 metaclass = PyObject_GetAttrString(base, "__class__");
7341                 if (!metaclass) {
7342                     PyErr_Clear();
7343                     metaclass = (PyObject *)base->ob_type;
7344                 }
7345             } else
7346                 metaclass = (PyObject *) &PyClass_Type;
7347 #else
7348             if (PyTuple_Check(bases) && PyTuple_GET_SIZE(bases) > 0) {
7349                 PyObject *base = PyTuple_GET_ITEM(bases, 0);
7350                 metaclass = (PyObject *)base->ob_type;
7351             } else
7352                 metaclass = (PyObject *) &PyType_Type;
7353 #endif
7354         }
7355         Py_INCREF(metaclass);
7356     }
7357     if (mkw && PyDict_Size(mkw) > 0) {
7358         PyObject *margs = PyTuple_New(3);
7359         if (!margs)
7360             goto bad;
7361         Py_INCREF(name);
7362         Py_INCREF(bases);
7363         Py_INCREF(dict);
7364         PyTuple_SET_ITEM(margs, 0, name);
7365         PyTuple_SET_ITEM(margs, 1, bases);
7366         PyTuple_SET_ITEM(margs, 2, dict);
7367         result = PyEval_CallObjectWithKeywords(metaclass, margs, mkw);
7368         Py_DECREF(margs);
7369     } else {
7370         result = PyObject_CallFunctionObjArgs(metaclass, name, bases, dict, NULL);
7371     }
7372 bad:
7373     Py_DECREF(metaclass);
7374     Py_XDECREF(mkw);
7375     return result;
7376 }
7377 """)
7378
7379 #------------------------------------------------------------------------------------
7380
7381 cpp_exception_utility_code = UtilityCode(
7382 proto = """
7383 #ifndef __Pyx_CppExn2PyErr
7384 static void __Pyx_CppExn2PyErr() {
7385   try {
7386     if (PyErr_Occurred())
7387       ; // let the latest Python exn pass through and ignore the current one
7388     else
7389       throw;
7390   } catch (const std::invalid_argument& exn) {
7391     // Catch a handful of different errors here and turn them into the
7392     // equivalent Python errors.
7393     // Change invalid_argument to ValueError
7394     PyErr_SetString(PyExc_ValueError, exn.what());
7395   } catch (const std::out_of_range& exn) {
7396     // Change out_of_range to IndexError
7397     PyErr_SetString(PyExc_IndexError, exn.what());
7398   } catch (const std::exception& exn) {
7399     PyErr_SetString(PyExc_RuntimeError, exn.what());
7400   }
7401   catch (...)
7402   {
7403     PyErr_SetString(PyExc_RuntimeError, "Unknown exception");
7404   }
7405 }
7406 #endif
7407 """,
7408 impl = ""
7409 )
7410
7411 pyerr_occurred_withgil_utility_code= UtilityCode(
7412 proto = """
7413 static CYTHON_INLINE int __Pyx_ErrOccurredWithGIL(void); /* proto */
7414 """,
7415 impl = """
7416 static CYTHON_INLINE int __Pyx_ErrOccurredWithGIL(void) {
7417   int err;
7418   #ifdef WITH_THREAD
7419   PyGILState_STATE _save = PyGILState_Ensure();
7420   #endif
7421   err = !!PyErr_Occurred();
7422   #ifdef WITH_THREAD
7423   PyGILState_Release(_save);
7424   #endif
7425   return err;
7426 }
7427 """
7428 )
7429
7430 #------------------------------------------------------------------------------------
7431
7432 raise_noneattr_error_utility_code = UtilityCode(
7433 proto = """
7434 static CYTHON_INLINE void __Pyx_RaiseNoneAttributeError(const char* attrname);
7435 """,
7436 impl = '''
7437 static CYTHON_INLINE void __Pyx_RaiseNoneAttributeError(const char* attrname) {
7438     PyErr_Format(PyExc_AttributeError, "'NoneType' object has no attribute '%s'", attrname);
7439 }
7440 ''')
7441
7442 raise_noneindex_error_utility_code = UtilityCode(
7443 proto = """
7444 static CYTHON_INLINE void __Pyx_RaiseNoneIndexingError(void);
7445 """,
7446 impl = '''
7447 static CYTHON_INLINE void __Pyx_RaiseNoneIndexingError(void) {
7448     PyErr_SetString(PyExc_TypeError, "'NoneType' object is unsubscriptable");
7449 }
7450 ''')
7451
7452 raise_none_iter_error_utility_code = UtilityCode(
7453 proto = """
7454 static CYTHON_INLINE void __Pyx_RaiseNoneNotIterableError(void);
7455 """,
7456 impl = '''
7457 static CYTHON_INLINE void __Pyx_RaiseNoneNotIterableError(void) {
7458     PyErr_SetString(PyExc_TypeError, "'NoneType' object is not iterable");
7459 }
7460 ''')
7461
7462 #------------------------------------------------------------------------------------
7463
7464 getitem_dict_utility_code = UtilityCode(
7465 proto = """
7466
7467 #if PY_MAJOR_VERSION >= 3
7468 static PyObject *__Pyx_PyDict_GetItem(PyObject *d, PyObject* key) {
7469     PyObject *value;
7470     if (unlikely(d == Py_None)) {
7471         __Pyx_RaiseNoneIndexingError();
7472         return NULL;
7473     }
7474     value = PyDict_GetItemWithError(d, key);
7475     if (unlikely(!value)) {
7476         if (!PyErr_Occurred())
7477             PyErr_SetObject(PyExc_KeyError, key);
7478         return NULL;
7479     }
7480     Py_INCREF(value);
7481     return value;
7482 }
7483 #else
7484     #define __Pyx_PyDict_GetItem(d, key) PyObject_GetItem(d, key)
7485 #endif
7486 """, 
7487 requires = [raise_noneindex_error_utility_code])
7488
7489 #------------------------------------------------------------------------------------
7490
7491 getitem_int_pyunicode_utility_code = UtilityCode(
7492 proto = '''
7493 #define __Pyx_GetItemInt_Unicode(o, i, size, to_py_func) (((size) <= sizeof(Py_ssize_t)) ? \\
7494                                                __Pyx_GetItemInt_Unicode_Fast(o, i) : \\
7495                                                __Pyx_GetItemInt_Unicode_Generic(o, to_py_func(i)))
7496
7497 static CYTHON_INLINE Py_UNICODE __Pyx_GetItemInt_Unicode_Fast(PyObject* ustring, Py_ssize_t i) {
7498     if (likely((0 <= i) & (i < PyUnicode_GET_SIZE(ustring)))) {
7499         return PyUnicode_AS_UNICODE(ustring)[i];
7500     } else if ((-PyUnicode_GET_SIZE(ustring) <= i) & (i < 0)) {
7501         i += PyUnicode_GET_SIZE(ustring);
7502         return PyUnicode_AS_UNICODE(ustring)[i];
7503     } else {
7504         PyErr_SetString(PyExc_IndexError, "string index out of range");
7505         return (Py_UNICODE)-1;
7506     }
7507 }
7508
7509 static CYTHON_INLINE Py_UNICODE __Pyx_GetItemInt_Unicode_Generic(PyObject* ustring, PyObject* j) {
7510     Py_UNICODE uchar;
7511     PyObject *uchar_string;
7512     if (!j) return (Py_UNICODE)-1;
7513     uchar_string = PyObject_GetItem(ustring, j);
7514     Py_DECREF(j);
7515     if (!uchar_string) return (Py_UNICODE)-1;
7516     uchar = PyUnicode_AS_UNICODE(uchar_string)[0];
7517     Py_DECREF(uchar_string);
7518     return uchar;
7519 }
7520 ''')
7521
7522 getitem_int_utility_code = UtilityCode(
7523 proto = """
7524
7525 static CYTHON_INLINE PyObject *__Pyx_GetItemInt_Generic(PyObject *o, PyObject* j) {
7526     PyObject *r;
7527     if (!j) return NULL;
7528     r = PyObject_GetItem(o, j);
7529     Py_DECREF(j);
7530     return r;
7531 }
7532
7533 """ + ''.join([
7534 """
7535 #define __Pyx_GetItemInt_%(type)s(o, i, size, to_py_func) (((size) <= sizeof(Py_ssize_t)) ? \\
7536                                                     __Pyx_GetItemInt_%(type)s_Fast(o, i) : \\
7537                                                     __Pyx_GetItemInt_Generic(o, to_py_func(i)))
7538
7539 static CYTHON_INLINE PyObject *__Pyx_GetItemInt_%(type)s_Fast(PyObject *o, Py_ssize_t i) {
7540     if (likely(o != Py_None)) {
7541         if (likely((0 <= i) & (i < Py%(type)s_GET_SIZE(o)))) {
7542             PyObject *r = Py%(type)s_GET_ITEM(o, i);
7543             Py_INCREF(r);
7544             return r;
7545         }
7546         else if ((-Py%(type)s_GET_SIZE(o) <= i) & (i < 0)) {
7547             PyObject *r = Py%(type)s_GET_ITEM(o, Py%(type)s_GET_SIZE(o) + i);
7548             Py_INCREF(r);
7549             return r;
7550         }
7551     }
7552     return __Pyx_GetItemInt_Generic(o, PyInt_FromSsize_t(i));
7553 }
7554 """ % {'type' : type_name} for type_name in ('List', 'Tuple')
7555 ]) + """
7556
7557 #define __Pyx_GetItemInt(o, i, size, to_py_func) (((size) <= sizeof(Py_ssize_t)) ? \\
7558                                                     __Pyx_GetItemInt_Fast(o, i) : \\
7559                                                     __Pyx_GetItemInt_Generic(o, to_py_func(i)))
7560
7561 static CYTHON_INLINE PyObject *__Pyx_GetItemInt_Fast(PyObject *o, Py_ssize_t i) {
7562     PyObject *r;
7563     if (PyList_CheckExact(o) && ((0 <= i) & (i < PyList_GET_SIZE(o)))) {
7564         r = PyList_GET_ITEM(o, i);
7565         Py_INCREF(r);
7566     }
7567     else if (PyTuple_CheckExact(o) && ((0 <= i) & (i < PyTuple_GET_SIZE(o)))) {
7568         r = PyTuple_GET_ITEM(o, i);
7569         Py_INCREF(r);
7570     }
7571     else if (Py_TYPE(o)->tp_as_sequence && Py_TYPE(o)->tp_as_sequence->sq_item && (likely(i >= 0))) {
7572         r = PySequence_GetItem(o, i);
7573     }
7574     else {
7575         r = __Pyx_GetItemInt_Generic(o, PyInt_FromSsize_t(i));
7576     }
7577     return r;
7578 }
7579 """,
7580 impl = """
7581 """)
7582
7583
7584
7585 #------------------------------------------------------------------------------------
7586
7587 setitem_int_utility_code = UtilityCode(
7588 proto = """
7589 #define __Pyx_SetItemInt(o, i, v, size, to_py_func) (((size) <= sizeof(Py_ssize_t)) ? \\
7590                                                     __Pyx_SetItemInt_Fast(o, i, v) : \\
7591                                                     __Pyx_SetItemInt_Generic(o, to_py_func(i), v))
7592
7593 static CYTHON_INLINE int __Pyx_SetItemInt_Generic(PyObject *o, PyObject *j, PyObject *v) {
7594     int r;
7595     if (!j) return -1;
7596     r = PyObject_SetItem(o, j, v);
7597     Py_DECREF(j);
7598     return r;
7599 }
7600
7601 static CYTHON_INLINE int __Pyx_SetItemInt_Fast(PyObject *o, Py_ssize_t i, PyObject *v) {
7602     if (PyList_CheckExact(o) && ((0 <= i) & (i < PyList_GET_SIZE(o)))) {
7603         Py_INCREF(v);
7604         Py_DECREF(PyList_GET_ITEM(o, i));
7605         PyList_SET_ITEM(o, i, v);
7606         return 1;
7607     }
7608     else if (Py_TYPE(o)->tp_as_sequence && Py_TYPE(o)->tp_as_sequence->sq_ass_item && (likely(i >= 0)))
7609         return PySequence_SetItem(o, i, v);
7610     else {
7611         PyObject *j = PyInt_FromSsize_t(i);
7612         return __Pyx_SetItemInt_Generic(o, j, v);
7613     }
7614 }
7615 """,
7616 impl = """
7617 """)
7618
7619 #------------------------------------------------------------------------------------
7620
7621 delitem_int_utility_code = UtilityCode(
7622 proto = """
7623 #define __Pyx_DelItemInt(o, i, size, to_py_func) (((size) <= sizeof(Py_ssize_t)) ? \\
7624                                                     __Pyx_DelItemInt_Fast(o, i) : \\
7625                                                     __Pyx_DelItem_Generic(o, to_py_func(i)))
7626
7627 static CYTHON_INLINE int __Pyx_DelItem_Generic(PyObject *o, PyObject *j) {
7628     int r;
7629     if (!j) return -1;
7630     r = PyObject_DelItem(o, j);
7631     Py_DECREF(j);
7632     return r;
7633 }
7634
7635 static CYTHON_INLINE int __Pyx_DelItemInt_Fast(PyObject *o, Py_ssize_t i) {
7636     if (Py_TYPE(o)->tp_as_sequence && Py_TYPE(o)->tp_as_sequence->sq_ass_item && likely(i >= 0))
7637         return PySequence_DelItem(o, i);
7638     else {
7639         PyObject *j = PyInt_FromSsize_t(i);
7640         return __Pyx_DelItem_Generic(o, j);
7641     }
7642 }
7643 """,
7644 impl = """
7645 """)
7646
7647 #------------------------------------------------------------------------------------
7648
7649 raise_too_many_values_to_unpack = UtilityCode(
7650 proto = """
7651 static CYTHON_INLINE void __Pyx_RaiseTooManyValuesError(Py_ssize_t expected);
7652 """,
7653 impl = '''
7654 static CYTHON_INLINE void __Pyx_RaiseTooManyValuesError(Py_ssize_t expected) {
7655     PyErr_Format(PyExc_ValueError,
7656         #if PY_VERSION_HEX < 0x02050000
7657             "too many values to unpack (expected %d)", (int)expected);
7658         #else
7659             "too many values to unpack (expected %zd)", expected);
7660         #endif
7661 }
7662 ''')
7663
7664 raise_need_more_values_to_unpack = UtilityCode(
7665 proto = """
7666 static CYTHON_INLINE void __Pyx_RaiseNeedMoreValuesError(Py_ssize_t index);
7667 """,
7668 impl = '''
7669 static CYTHON_INLINE void __Pyx_RaiseNeedMoreValuesError(Py_ssize_t index) {
7670     PyErr_Format(PyExc_ValueError,
7671         #if PY_VERSION_HEX < 0x02050000
7672                  "need more than %d value%s to unpack", (int)index,
7673         #else
7674                  "need more than %zd value%s to unpack", index,
7675         #endif
7676                  (index == 1) ? "" : "s");
7677 }
7678 ''')
7679
7680 #------------------------------------------------------------------------------------
7681
7682 tuple_unpacking_error_code = UtilityCode(
7683 proto = """
7684 static void __Pyx_UnpackTupleError(PyObject *, Py_ssize_t index); /*proto*/
7685 """, 
7686 impl = """
7687 static void __Pyx_UnpackTupleError(PyObject *t, Py_ssize_t index) {
7688     if (t == Py_None) {
7689       __Pyx_RaiseNoneNotIterableError();
7690     } else if (PyTuple_GET_SIZE(t) < index) {
7691       __Pyx_RaiseNeedMoreValuesError(PyTuple_GET_SIZE(t));
7692     } else {
7693       __Pyx_RaiseTooManyValuesError(index);
7694     }
7695 }
7696 """, 
7697 requires = [raise_none_iter_error_utility_code,
7698             raise_need_more_values_to_unpack,
7699             raise_too_many_values_to_unpack]
7700 )
7701
7702 unpacking_utility_code = UtilityCode(
7703 proto = """
7704 static PyObject *__Pyx_UnpackItem(PyObject *, Py_ssize_t index); /*proto*/
7705 static int __Pyx_EndUnpack(PyObject *, Py_ssize_t expected); /*proto*/
7706 """,
7707 impl = """
7708 static PyObject *__Pyx_UnpackItem(PyObject *iter, Py_ssize_t index) {
7709     PyObject *item;
7710     if (!(item = PyIter_Next(iter))) {
7711         if (!PyErr_Occurred()) {
7712             __Pyx_RaiseNeedMoreValuesError(index);
7713         }
7714     }
7715     return item;
7716 }
7717
7718 static int __Pyx_EndUnpack(PyObject *iter, Py_ssize_t expected) {
7719     PyObject *item;
7720     if ((item = PyIter_Next(iter))) {
7721         Py_DECREF(item);
7722         __Pyx_RaiseTooManyValuesError(expected);
7723         return -1;
7724     }
7725     else if (!PyErr_Occurred())
7726         return 0;
7727     else
7728         return -1;
7729 }
7730 """,
7731 requires = [raise_need_more_values_to_unpack,
7732             raise_too_many_values_to_unpack]
7733 )
7734
7735 #------------------------------------------------------------------------------------
7736
7737 # CPython supports calling functions with non-dict kwargs by
7738 # converting them to a dict first
7739
7740 kwargs_call_utility_code = UtilityCode(
7741 proto = """
7742 static PyObject* __Pyx_PyEval_CallObjectWithKeywords(PyObject*, PyObject*, PyObject*); /*proto*/
7743 """,
7744 impl = """
7745 static PyObject* __Pyx_PyEval_CallObjectWithKeywords(PyObject *callable, PyObject *args, PyObject *kwargs) {
7746     PyObject* result;
7747     if (likely(PyDict_Check(kwargs))) {
7748         return PyEval_CallObjectWithKeywords(callable, args, kwargs);
7749     } else {
7750         PyObject* real_dict;
7751         real_dict = PyObject_CallFunctionObjArgs((PyObject*)&PyDict_Type, kwargs, NULL);
7752         if (unlikely(!real_dict))
7753             return NULL;
7754         result = PyEval_CallObjectWithKeywords(callable, args, real_dict);
7755         Py_DECREF(real_dict);
7756         return result; /* may be NULL */
7757     }
7758 }
7759 """, 
7760 )
7761
7762
7763 #------------------------------------------------------------------------------------
7764
7765 int_pow_utility_code = UtilityCode(
7766 proto="""
7767 static CYTHON_INLINE %(type)s %(func_name)s(%(type)s, %(type)s); /* proto */
7768 """,
7769 impl="""
7770 static CYTHON_INLINE %(type)s %(func_name)s(%(type)s b, %(type)s e) {
7771     %(type)s t = b;
7772     switch (e) {
7773         case 3:
7774             t *= b;
7775         case 2:
7776             t *= b;
7777         case 1:
7778             return t;
7779         case 0:
7780             return 1;
7781     }
7782     if (unlikely(e<0)) return 0;
7783     t = 1;
7784     while (likely(e)) {
7785         t *= (b * (e&1)) | ((~e)&1);    /* 1 or b */
7786         b *= b;
7787         e >>= 1;
7788     }
7789     return t;
7790 }
7791 """)
7792
7793 # ------------------------------ Division ------------------------------------
7794
7795 div_int_utility_code = UtilityCode(
7796 proto="""
7797 static CYTHON_INLINE %(type)s __Pyx_div_%(type_name)s(%(type)s, %(type)s); /* proto */
7798 """,
7799 impl="""
7800 static CYTHON_INLINE %(type)s __Pyx_div_%(type_name)s(%(type)s a, %(type)s b) {
7801     %(type)s q = a / b;
7802     %(type)s r = a - q*b;
7803     q -= ((r != 0) & ((r ^ b) < 0));
7804     return q;
7805 }
7806 """)
7807
7808 mod_int_utility_code = UtilityCode(
7809 proto="""
7810 static CYTHON_INLINE %(type)s __Pyx_mod_%(type_name)s(%(type)s, %(type)s); /* proto */
7811 """,
7812 impl="""
7813 static CYTHON_INLINE %(type)s __Pyx_mod_%(type_name)s(%(type)s a, %(type)s b) {
7814     %(type)s r = a %% b;
7815     r += ((r != 0) & ((r ^ b) < 0)) * b;
7816     return r;
7817 }
7818 """)
7819
7820 mod_float_utility_code = UtilityCode(
7821 proto="""
7822 static CYTHON_INLINE %(type)s __Pyx_mod_%(type_name)s(%(type)s, %(type)s); /* proto */
7823 """,
7824 impl="""
7825 static CYTHON_INLINE %(type)s __Pyx_mod_%(type_name)s(%(type)s a, %(type)s b) {
7826     %(type)s r = fmod%(math_h_modifier)s(a, b);
7827     r += ((r != 0) & ((r < 0) ^ (b < 0))) * b;
7828     return r;
7829 }
7830 """)
7831
7832 cdivision_warning_utility_code = UtilityCode(
7833 proto="""
7834 static int __Pyx_cdivision_warning(void); /* proto */
7835 """,
7836 impl="""
7837 static int __Pyx_cdivision_warning(void) {
7838     return PyErr_WarnExplicit(PyExc_RuntimeWarning, 
7839                               "division with oppositely signed operands, C and Python semantics differ",
7840                               %(FILENAME)s, 
7841                               %(LINENO)s,
7842                               __Pyx_MODULE_NAME,
7843                               NULL);
7844 }
7845 """ % {
7846     'FILENAME': Naming.filename_cname,
7847     'LINENO':  Naming.lineno_cname,
7848 })
7849
7850 # from intobject.c
7851 division_overflow_test_code = UtilityCode(
7852 proto="""
7853 #define UNARY_NEG_WOULD_OVERFLOW(x)     \
7854         (((x) < 0) & ((unsigned long)(x) == 0-(unsigned long)(x)))
7855 """)
7856
7857
7858 binding_cfunc_utility_code = UtilityCode(
7859 proto="""
7860 #define %(binding_cfunc)s_USED 1
7861
7862 typedef struct {
7863     PyCFunctionObject func;
7864 } %(binding_cfunc)s_object;
7865
7866 PyTypeObject %(binding_cfunc)s_type;
7867 PyTypeObject *%(binding_cfunc)s = NULL;
7868
7869 PyObject *%(binding_cfunc)s_NewEx(PyMethodDef *ml, PyObject *self, PyObject *module); /* proto */
7870 #define %(binding_cfunc)s_New(ml, self) %(binding_cfunc)s_NewEx(ml, self, NULL)
7871
7872 int %(binding_cfunc)s_init(void); /* proto */
7873 """ % Naming.__dict__,
7874 impl="""
7875
7876 PyObject *%(binding_cfunc)s_NewEx(PyMethodDef *ml, PyObject *self, PyObject *module) {
7877         %(binding_cfunc)s_object *op = PyObject_GC_New(%(binding_cfunc)s_object, %(binding_cfunc)s);
7878     if (op == NULL)
7879         return NULL;
7880         op->func.m_ml = ml;
7881         Py_XINCREF(self);
7882         op->func.m_self = self;
7883         Py_XINCREF(module);
7884         op->func.m_module = module;
7885         PyObject_GC_Track(op);
7886         return (PyObject *)op;
7887 }
7888
7889 static void %(binding_cfunc)s_dealloc(%(binding_cfunc)s_object *m) {
7890         PyObject_GC_UnTrack(m);
7891         Py_XDECREF(m->func.m_self);
7892         Py_XDECREF(m->func.m_module);
7893     PyObject_GC_Del(m);
7894 }
7895
7896 static PyObject *%(binding_cfunc)s_descr_get(PyObject *func, PyObject *obj, PyObject *type) {
7897         if (obj == Py_None)
7898                 obj = NULL;
7899         return PyMethod_New(func, obj, type);
7900 }
7901
7902 int %(binding_cfunc)s_init(void) {
7903     %(binding_cfunc)s_type = PyCFunction_Type;
7904     %(binding_cfunc)s_type.tp_name = __Pyx_NAMESTR("cython_binding_builtin_function_or_method");
7905     %(binding_cfunc)s_type.tp_dealloc = (destructor)%(binding_cfunc)s_dealloc;
7906     %(binding_cfunc)s_type.tp_descr_get = %(binding_cfunc)s_descr_get;
7907     if (PyType_Ready(&%(binding_cfunc)s_type) < 0) {
7908         return -1;
7909     }
7910     %(binding_cfunc)s = &%(binding_cfunc)s_type;
7911     return 0;
7912
7913 }
7914 """ % Naming.__dict__)