/[dtapublic]/projs/dtats/trunk/shared_source/c_tcl_base_7_5_w_mods/tclint.h
ViewVC logotype

Annotation of /projs/dtats/trunk/shared_source/c_tcl_base_7_5_w_mods/tclint.h

Parent Directory Parent Directory | Revision Log Revision Log


Revision 71 - (hide annotations) (download)
Sat Nov 5 11:07:06 2016 UTC (8 years, 1 month ago) by dashley
Original Path: projs/trunk/shared_source/c_tcl_base_7_5_w_mods/tclint.h
File MIME type: text/plain
File size: 90672 byte(s)
Set EOL properties appropriately to facilitate simultaneous Linux and Windows development.
1 dashley 71 /* $Header$ */
2     /*
3     * tclInt.h --
4     *
5     * Declarations of things used internally by the Tcl interpreter.
6     *
7     * Copyright (c) 1987-1993 The Regents of the University of California.
8     * Copyright (c) 1993-1997 Lucent Technologies.
9     * Copyright (c) 1994-1998 Sun Microsystems, Inc.
10     * Copyright (c) 1998-1999 by Scriptics Corporation.
11     *
12     * See the file "license.terms" for information on usage and redistribution
13     * of this file, and for a DISCLAIMER OF ALL WARRANTIES.
14     *
15     * RCS: @(#) $Id: tclint.h,v 1.1.1.1 2001/06/13 04:40:00 dtashley Exp $
16     */
17    
18     #ifndef _TCLINT
19     #define _TCLINT
20    
21     /*
22     * Common include files needed by most of the Tcl source files are
23     * included here, so that system-dependent personalizations for the
24     * include files only have to be made in once place. This results
25     * in a few extra includes, but greater modularity. The order of
26     * the three groups of #includes is important. For example, stdio.h
27     * is needed by tcl.h, and the _ANSI_ARGS_ declaration in tcl.h is
28     * needed by stdlib.h in some configurations.
29     */
30    
31     #include <stdio.h>
32    
33     #ifndef _TCL
34     #include "tcl.h"
35     #endif
36    
37     #include <ctype.h>
38     #ifdef NO_LIMITS_H
39     # include "../compat/limits.h"
40     #else
41     # include <limits.h>
42     #endif
43     #ifdef NO_STDLIB_H
44     # include "../compat/stdlib.h"
45     #else
46     # include <stdlib.h>
47     #endif
48     #ifdef NO_STRING_H
49     #include "../compat/string.h"
50     #else
51     #include <string.h>
52     #endif
53    
54     #undef TCL_STORAGE_CLASS
55     #ifdef BUILD_tcl
56     # define TCL_STORAGE_CLASS DLLEXPORT
57     #else
58     # ifdef USE_TCL_STUBS
59     # define TCL_STORAGE_CLASS
60     # else
61     # define TCL_STORAGE_CLASS DLLIMPORT
62     # endif
63     #endif
64    
65     /*
66     * The following procedures allow namespaces to be customized to
67     * support special name resolution rules for commands/variables.
68     *
69     */
70    
71     struct Tcl_ResolvedVarInfo;
72    
73     typedef Tcl_Var (Tcl_ResolveRuntimeVarProc) _ANSI_ARGS_((
74     Tcl_Interp* interp, struct Tcl_ResolvedVarInfo *vinfoPtr));
75    
76     typedef void (Tcl_ResolveVarDeleteProc) _ANSI_ARGS_((
77     struct Tcl_ResolvedVarInfo *vinfoPtr));
78    
79     /*
80     * The following structure encapsulates the routines needed to resolve a
81     * variable reference at runtime. Any variable specific state will typically
82     * be appended to this structure.
83     */
84    
85    
86     typedef struct Tcl_ResolvedVarInfo {
87     Tcl_ResolveRuntimeVarProc *fetchProc;
88     Tcl_ResolveVarDeleteProc *deleteProc;
89     } Tcl_ResolvedVarInfo;
90    
91    
92    
93     typedef int (Tcl_ResolveCompiledVarProc) _ANSI_ARGS_((
94     Tcl_Interp* interp, char* name, int length,
95     Tcl_Namespace *context, Tcl_ResolvedVarInfo **rPtr));
96    
97     typedef int (Tcl_ResolveVarProc) _ANSI_ARGS_((
98     Tcl_Interp* interp, char* name, Tcl_Namespace *context,
99     int flags, Tcl_Var *rPtr));
100    
101     typedef int (Tcl_ResolveCmdProc) _ANSI_ARGS_((Tcl_Interp* interp,
102     char* name, Tcl_Namespace *context, int flags,
103     Tcl_Command *rPtr));
104    
105     typedef struct Tcl_ResolverInfo {
106     Tcl_ResolveCmdProc *cmdResProc; /* Procedure handling command name
107     * resolution. */
108     Tcl_ResolveVarProc *varResProc; /* Procedure handling variable name
109     * resolution for variables that
110     * can only be handled at runtime. */
111     Tcl_ResolveCompiledVarProc *compiledVarResProc;
112     /* Procedure handling variable name
113     * resolution at compile time. */
114     } Tcl_ResolverInfo;
115    
116     /*
117     *----------------------------------------------------------------
118     * Data structures related to namespaces.
119     *----------------------------------------------------------------
120     */
121    
122     /*
123     * The structure below defines a namespace.
124     * Note: the first five fields must match exactly the fields in a
125     * Tcl_Namespace structure (see tcl.h). If you change one, be sure to
126     * change the other.
127     */
128    
129     typedef struct Namespace {
130     char *name; /* The namespace's simple (unqualified)
131     * name. This contains no ::'s. The name of
132     * the global namespace is "" although "::"
133     * is an synonym. */
134     char *fullName; /* The namespace's fully qualified name.
135     * This starts with ::. */
136     ClientData clientData; /* An arbitrary value associated with this
137     * namespace. */
138     Tcl_NamespaceDeleteProc *deleteProc;
139     /* Procedure invoked when deleting the
140     * namespace to, e.g., free clientData. */
141     struct Namespace *parentPtr; /* Points to the namespace that contains
142     * this one. NULL if this is the global
143     * namespace. */
144     Tcl_HashTable childTable; /* Contains any child namespaces. Indexed
145     * by strings; values have type
146     * (Namespace *). */
147     long nsId; /* Unique id for the namespace. */
148     Tcl_Interp *interp; /* The interpreter containing this
149     * namespace. */
150     int flags; /* OR-ed combination of the namespace
151     * status flags NS_DYING and NS_DEAD
152     * listed below. */
153     int activationCount; /* Number of "activations" or active call
154     * frames for this namespace that are on
155     * the Tcl call stack. The namespace won't
156     * be freed until activationCount becomes
157     * zero. */
158     int refCount; /* Count of references by namespaceName *
159     * objects. The namespace can't be freed
160     * until refCount becomes zero. */
161     Tcl_HashTable cmdTable; /* Contains all the commands currently
162     * registered in the namespace. Indexed by
163     * strings; values have type (Command *).
164     * Commands imported by Tcl_Import have
165     * Command structures that point (via an
166     * ImportedCmdRef structure) to the
167     * Command structure in the source
168     * namespace's command table. */
169     Tcl_HashTable varTable; /* Contains all the (global) variables
170     * currently in this namespace. Indexed
171     * by strings; values have type (Var *). */
172     char **exportArrayPtr; /* Points to an array of string patterns
173     * specifying which commands are exported.
174     * A pattern may include "string match"
175     * style wildcard characters to specify
176     * multiple commands; however, no namespace
177     * qualifiers are allowed. NULL if no
178     * export patterns are registered. */
179     int numExportPatterns; /* Number of export patterns currently
180     * registered using "namespace export". */
181     int maxExportPatterns; /* Mumber of export patterns for which
182     * space is currently allocated. */
183     int cmdRefEpoch; /* Incremented if a newly added command
184     * shadows a command for which this
185     * namespace has already cached a Command *
186     * pointer; this causes all its cached
187     * Command* pointers to be invalidated. */
188     int resolverEpoch; /* Incremented whenever the name resolution
189     * rules change for this namespace; this
190     * invalidates all byte codes compiled in
191     * the namespace, causing the code to be
192     * recompiled under the new rules. */
193     Tcl_ResolveCmdProc *cmdResProc;
194     /* If non-null, this procedure overrides
195     * the usual command resolution mechanism
196     * in Tcl. This procedure is invoked
197     * within Tcl_FindCommand to resolve all
198     * command references within the namespace. */
199     Tcl_ResolveVarProc *varResProc;
200     /* If non-null, this procedure overrides
201     * the usual variable resolution mechanism
202     * in Tcl. This procedure is invoked
203     * within Tcl_FindNamespaceVar to resolve all
204     * variable references within the namespace
205     * at runtime. */
206     Tcl_ResolveCompiledVarProc *compiledVarResProc;
207     /* If non-null, this procedure overrides
208     * the usual variable resolution mechanism
209     * in Tcl. This procedure is invoked
210     * within LookupCompiledLocal to resolve
211     * variable references within the namespace
212     * at compile time. */
213     } Namespace;
214    
215     /*
216     * Flags used to represent the status of a namespace:
217     *
218     * NS_DYING - 1 means Tcl_DeleteNamespace has been called to delete the
219     * namespace but there are still active call frames on the Tcl
220     * stack that refer to the namespace. When the last call frame
221     * referring to it has been popped, it's variables and command
222     * will be destroyed and it will be marked "dead" (NS_DEAD).
223     * The namespace can no longer be looked up by name.
224     * NS_DEAD - 1 means Tcl_DeleteNamespace has been called to delete the
225     * namespace and no call frames still refer to it. Its
226     * variables and command have already been destroyed. This bit
227     * allows the namespace resolution code to recognize that the
228     * namespace is "deleted". When the last namespaceName object
229     * in any byte code code unit that refers to the namespace has
230     * been freed (i.e., when the namespace's refCount is 0), the
231     * namespace's storage will be freed.
232     */
233    
234     #define NS_DYING 0x01
235     #define NS_DEAD 0x02
236    
237     /*
238     * Flag passed to TclGetNamespaceForQualName to have it create all namespace
239     * components of a namespace-qualified name that cannot be found. The new
240     * namespaces are created within their specified parent. Note that this
241     * flag's value must not conflict with the values of the flags
242     * TCL_GLOBAL_ONLY, TCL_NAMESPACE_ONLY, and FIND_ONLY_NS (defined in
243     * tclNamesp.c).
244     */
245    
246     #define CREATE_NS_IF_UNKNOWN 0x800
247    
248     /*
249     *----------------------------------------------------------------
250     * Data structures related to variables. These are used primarily
251     * in tclVar.c
252     *----------------------------------------------------------------
253     */
254    
255     /*
256     * The following structure defines a variable trace, which is used to
257     * invoke a specific C procedure whenever certain operations are performed
258     * on a variable.
259     */
260    
261     typedef struct VarTrace {
262     Tcl_VarTraceProc *traceProc;/* Procedure to call when operations given
263     * by flags are performed on variable. */
264     ClientData clientData; /* Argument to pass to proc. */
265     int flags; /* What events the trace procedure is
266     * interested in: OR-ed combination of
267     * TCL_TRACE_READS, TCL_TRACE_WRITES,
268     * TCL_TRACE_UNSETS and TCL_TRACE_ARRAY. */
269     struct VarTrace *nextPtr; /* Next in list of traces associated with
270     * a particular variable. */
271     } VarTrace;
272    
273     /*
274     * When a variable trace is active (i.e. its associated procedure is
275     * executing), one of the following structures is linked into a list
276     * associated with the variable's interpreter. The information in
277     * the structure is needed in order for Tcl to behave reasonably
278     * if traces are deleted while traces are active.
279     */
280    
281     typedef struct ActiveVarTrace {
282     struct Var *varPtr; /* Variable that's being traced. */
283     struct ActiveVarTrace *nextPtr;
284     /* Next in list of all active variable
285     * traces for the interpreter, or NULL
286     * if no more. */
287     VarTrace *nextTracePtr; /* Next trace to check after current
288     * trace procedure returns; if this
289     * trace gets deleted, must update pointer
290     * to avoid using free'd memory. */
291     } ActiveVarTrace;
292    
293     /*
294     * The following structure describes an enumerative search in progress on
295     * an array variable; this are invoked with options to the "array"
296     * command.
297     */
298    
299     typedef struct ArraySearch {
300     int id; /* Integer id used to distinguish among
301     * multiple concurrent searches for the
302     * same array. */
303     struct Var *varPtr; /* Pointer to array variable that's being
304     * searched. */
305     Tcl_HashSearch search; /* Info kept by the hash module about
306     * progress through the array. */
307     Tcl_HashEntry *nextEntry; /* Non-null means this is the next element
308     * to be enumerated (it's leftover from
309     * the Tcl_FirstHashEntry call or from
310     * an "array anymore" command). NULL
311     * means must call Tcl_NextHashEntry
312     * to get value to return. */
313     struct ArraySearch *nextPtr;/* Next in list of all active searches
314     * for this variable, or NULL if this is
315     * the last one. */
316     } ArraySearch;
317    
318     /*
319     * The structure below defines a variable, which associates a string name
320     * with a Tcl_Obj value. These structures are kept in procedure call frames
321     * (for local variables recognized by the compiler) or in the heap (for
322     * global variables and any variable not known to the compiler). For each
323     * Var structure in the heap, a hash table entry holds the variable name and
324     * a pointer to the Var structure.
325     */
326    
327     typedef struct Var {
328     union {
329     Tcl_Obj *objPtr; /* The variable's object value. Used for
330     * scalar variables and array elements. */
331     Tcl_HashTable *tablePtr;/* For array variables, this points to
332     * information about the hash table used
333     * to implement the associative array.
334     * Points to malloc-ed data. */
335     struct Var *linkPtr; /* If this is a global variable being
336     * referred to in a procedure, or a variable
337     * created by "upvar", this field points to
338     * the referenced variable's Var struct. */
339     } value;
340     char *name; /* NULL if the variable is in a hashtable,
341     * otherwise points to the variable's
342     * name. It is used, e.g., by TclLookupVar
343     * and "info locals". The storage for the
344     * characters of the name is not owned by
345     * the Var and must not be freed when
346     * freeing the Var. */
347     Namespace *nsPtr; /* Points to the namespace that contains
348     * this variable or NULL if the variable is
349     * a local variable in a Tcl procedure. */
350     Tcl_HashEntry *hPtr; /* If variable is in a hashtable, either the
351     * hash table entry that refers to this
352     * variable or NULL if the variable has been
353     * detached from its hash table (e.g. an
354     * array is deleted, but some of its
355     * elements are still referred to in
356     * upvars). NULL if the variable is not in a
357     * hashtable. This is used to delete an
358     * variable from its hashtable if it is no
359     * longer needed. */
360     int refCount; /* Counts number of active uses of this
361     * variable, not including its entry in the
362     * call frame or the hash table: 1 for each
363     * additional variable whose linkPtr points
364     * here, 1 for each nested trace active on
365     * variable, and 1 if the variable is a
366     * namespace variable. This record can't be
367     * deleted until refCount becomes 0. */
368     VarTrace *tracePtr; /* First in list of all traces set for this
369     * variable. */
370     ArraySearch *searchPtr; /* First in list of all searches active
371     * for this variable, or NULL if none. */
372     int flags; /* Miscellaneous bits of information about
373     * variable. See below for definitions. */
374     } Var;
375    
376     /*
377     * Flag bits for variables. The first three (VAR_SCALAR, VAR_ARRAY, and
378     * VAR_LINK) are mutually exclusive and give the "type" of the variable.
379     * VAR_UNDEFINED is independent of the variable's type.
380     *
381     * VAR_SCALAR - 1 means this is a scalar variable and not
382     * an array or link. The "objPtr" field points
383     * to the variable's value, a Tcl object.
384     * VAR_ARRAY - 1 means this is an array variable rather
385     * than a scalar variable or link. The
386     * "tablePtr" field points to the array's
387     * hashtable for its elements.
388     * VAR_LINK - 1 means this Var structure contains a
389     * pointer to another Var structure that
390     * either has the real value or is itself
391     * another VAR_LINK pointer. Variables like
392     * this come about through "upvar" and "global"
393     * commands, or through references to variables
394     * in enclosing namespaces.
395     * VAR_UNDEFINED - 1 means that the variable is in the process
396     * of being deleted. An undefined variable
397     * logically does not exist and survives only
398     * while it has a trace, or if it is a global
399     * variable currently being used by some
400     * procedure.
401     * VAR_IN_HASHTABLE - 1 means this variable is in a hashtable and
402     * the Var structure is malloced. 0 if it is
403     * a local variable that was assigned a slot
404     * in a procedure frame by the compiler so the
405     * Var storage is part of the call frame.
406     * VAR_TRACE_ACTIVE - 1 means that trace processing is currently
407     * underway for a read or write access, so
408     * new read or write accesses should not cause
409     * trace procedures to be called and the
410     * variable can't be deleted.
411     * VAR_ARRAY_ELEMENT - 1 means that this variable is an array
412     * element, so it is not legal for it to be
413     * an array itself (the VAR_ARRAY flag had
414     * better not be set).
415     * VAR_NAMESPACE_VAR - 1 means that this variable was declared
416     * as a namespace variable. This flag ensures
417     * it persists until its namespace is
418     * destroyed or until the variable is unset;
419     * it will persist even if it has not been
420     * initialized and is marked undefined.
421     * The variable's refCount is incremented to
422     * reflect the "reference" from its namespace.
423     *
424     * The following additional flags are used with the CompiledLocal type
425     * defined below:
426     *
427     * VAR_ARGUMENT - 1 means that this variable holds a procedure
428     * argument.
429     * VAR_TEMPORARY - 1 if the local variable is an anonymous
430     * temporary variable. Temporaries have a NULL
431     * name.
432     * VAR_RESOLVED - 1 if name resolution has been done for this
433     * variable.
434     */
435    
436     #define VAR_SCALAR 0x1
437     #define VAR_ARRAY 0x2
438     #define VAR_LINK 0x4
439     #define VAR_UNDEFINED 0x8
440     #define VAR_IN_HASHTABLE 0x10
441     #define VAR_TRACE_ACTIVE 0x20
442     #define VAR_ARRAY_ELEMENT 0x40
443     #define VAR_NAMESPACE_VAR 0x80
444    
445     #define VAR_ARGUMENT 0x100
446     #define VAR_TEMPORARY 0x200
447     #define VAR_RESOLVED 0x400
448    
449     /*
450     * Macros to ensure that various flag bits are set properly for variables.
451     * The ANSI C "prototypes" for these macros are:
452     *
453     * EXTERN void TclSetVarScalar _ANSI_ARGS_((Var *varPtr));
454     * EXTERN void TclSetVarArray _ANSI_ARGS_((Var *varPtr));
455     * EXTERN void TclSetVarLink _ANSI_ARGS_((Var *varPtr));
456     * EXTERN void TclSetVarArrayElement _ANSI_ARGS_((Var *varPtr));
457     * EXTERN void TclSetVarUndefined _ANSI_ARGS_((Var *varPtr));
458     * EXTERN void TclClearVarUndefined _ANSI_ARGS_((Var *varPtr));
459     */
460    
461     #define TclSetVarScalar(varPtr) \
462     (varPtr)->flags = ((varPtr)->flags & ~(VAR_ARRAY|VAR_LINK)) | VAR_SCALAR
463    
464     #define TclSetVarArray(varPtr) \
465     (varPtr)->flags = ((varPtr)->flags & ~(VAR_SCALAR|VAR_LINK)) | VAR_ARRAY
466    
467     #define TclSetVarLink(varPtr) \
468     (varPtr)->flags = ((varPtr)->flags & ~(VAR_SCALAR|VAR_ARRAY)) | VAR_LINK
469    
470     #define TclSetVarArrayElement(varPtr) \
471     (varPtr)->flags = ((varPtr)->flags & ~VAR_ARRAY) | VAR_ARRAY_ELEMENT
472    
473     #define TclSetVarUndefined(varPtr) \
474     (varPtr)->flags |= VAR_UNDEFINED
475    
476     #define TclClearVarUndefined(varPtr) \
477     (varPtr)->flags &= ~VAR_UNDEFINED
478    
479     /*
480     * Macros to read various flag bits of variables.
481     * The ANSI C "prototypes" for these macros are:
482     *
483     * EXTERN int TclIsVarScalar _ANSI_ARGS_((Var *varPtr));
484     * EXTERN int TclIsVarLink _ANSI_ARGS_((Var *varPtr));
485     * EXTERN int TclIsVarArray _ANSI_ARGS_((Var *varPtr));
486     * EXTERN int TclIsVarUndefined _ANSI_ARGS_((Var *varPtr));
487     * EXTERN int TclIsVarArrayElement _ANSI_ARGS_((Var *varPtr));
488     * EXTERN int TclIsVarTemporary _ANSI_ARGS_((Var *varPtr));
489     * EXTERN int TclIsVarArgument _ANSI_ARGS_((Var *varPtr));
490     * EXTERN int TclIsVarResolved _ANSI_ARGS_((Var *varPtr));
491     */
492    
493     #define TclIsVarScalar(varPtr) \
494     ((varPtr)->flags & VAR_SCALAR)
495    
496     #define TclIsVarLink(varPtr) \
497     ((varPtr)->flags & VAR_LINK)
498    
499     #define TclIsVarArray(varPtr) \
500     ((varPtr)->flags & VAR_ARRAY)
501    
502     #define TclIsVarUndefined(varPtr) \
503     ((varPtr)->flags & VAR_UNDEFINED)
504    
505     #define TclIsVarArrayElement(varPtr) \
506     ((varPtr)->flags & VAR_ARRAY_ELEMENT)
507    
508     #define TclIsVarTemporary(varPtr) \
509     ((varPtr)->flags & VAR_TEMPORARY)
510    
511     #define TclIsVarArgument(varPtr) \
512     ((varPtr)->flags & VAR_ARGUMENT)
513    
514     #define TclIsVarResolved(varPtr) \
515     ((varPtr)->flags & VAR_RESOLVED)
516    
517     /*
518     *----------------------------------------------------------------
519     * Data structures related to procedures. These are used primarily
520     * in tclProc.c, tclCompile.c, and tclExecute.c.
521     *----------------------------------------------------------------
522     */
523    
524     /*
525     * Forward declaration to prevent an error when the forward reference to
526     * Command is encountered in the Proc and ImportRef types declared below.
527     */
528    
529     struct Command;
530    
531     /*
532     * The variable-length structure below describes a local variable of a
533     * procedure that was recognized by the compiler. These variables have a
534     * name, an element in the array of compiler-assigned local variables in the
535     * procedure's call frame, and various other items of information. If the
536     * local variable is a formal argument, it may also have a default value.
537     * The compiler can't recognize local variables whose names are
538     * expressions (these names are only known at runtime when the expressions
539     * are evaluated) or local variables that are created as a result of an
540     * "upvar" or "uplevel" command. These other local variables are kept
541     * separately in a hash table in the call frame.
542     */
543    
544     typedef struct CompiledLocal {
545     struct CompiledLocal *nextPtr;
546     /* Next compiler-recognized local variable
547     * for this procedure, or NULL if this is
548     * the last local. */
549     int nameLength; /* The number of characters in local
550     * variable's name. Used to speed up
551     * variable lookups. */
552     int frameIndex; /* Index in the array of compiler-assigned
553     * variables in the procedure call frame. */
554     int flags; /* Flag bits for the local variable. Same as
555     * the flags for the Var structure above,
556     * although only VAR_SCALAR, VAR_ARRAY,
557     * VAR_LINK, VAR_ARGUMENT, VAR_TEMPORARY, and
558     * VAR_RESOLVED make sense. */
559     Tcl_Obj *defValuePtr; /* Pointer to the default value of an
560     * argument, if any. NULL if not an argument
561     * or, if an argument, no default value. */
562     Tcl_ResolvedVarInfo *resolveInfo;
563     /* Customized variable resolution info
564     * supplied by the Tcl_ResolveCompiledVarProc
565     * associated with a namespace. Each variable
566     * is marked by a unique ClientData tag
567     * during compilation, and that same tag
568     * is used to find the variable at runtime. */
569     char name[4]; /* Name of the local variable starts here.
570     * If the name is NULL, this will just be
571     * '\0'. The actual size of this field will
572     * be large enough to hold the name. MUST
573     * BE THE LAST FIELD IN THE STRUCTURE! */
574     } CompiledLocal;
575    
576     /*
577     * The structure below defines a command procedure, which consists of a
578     * collection of Tcl commands plus information about arguments and other
579     * local variables recognized at compile time.
580     */
581    
582     typedef struct Proc {
583     struct Interp *iPtr; /* Interpreter for which this command
584     * is defined. */
585     int refCount; /* Reference count: 1 if still present
586     * in command table plus 1 for each call
587     * to the procedure that is currently
588     * active. This structure can be freed
589     * when refCount becomes zero. */
590     struct Command *cmdPtr; /* Points to the Command structure for
591     * this procedure. This is used to get
592     * the namespace in which to execute
593     * the procedure. */
594     Tcl_Obj *bodyPtr; /* Points to the ByteCode object for
595     * procedure's body command. */
596     int numArgs; /* Number of formal parameters. */
597     int numCompiledLocals; /* Count of local variables recognized by
598     * the compiler including arguments and
599     * temporaries. */
600     CompiledLocal *firstLocalPtr; /* Pointer to first of the procedure's
601     * compiler-allocated local variables, or
602     * NULL if none. The first numArgs entries
603     * in this list describe the procedure's
604     * formal arguments. */
605     CompiledLocal *lastLocalPtr; /* Pointer to the last allocated local
606     * variable or NULL if none. This has
607     * frame index (numCompiledLocals-1). */
608     } Proc;
609    
610     /*
611     * The structure below defines a command trace. This is used to allow Tcl
612     * clients to find out whenever a command is about to be executed.
613     */
614    
615     typedef struct Trace {
616     int level; /* Only trace commands at nesting level
617     * less than or equal to this. */
618     Tcl_CmdTraceProc *proc; /* Procedure to call to trace command. */
619     ClientData clientData; /* Arbitrary value to pass to proc. */
620     struct Trace *nextPtr; /* Next in list of traces for this interp. */
621     } Trace;
622    
623     /*
624     * The structure below defines an entry in the assocData hash table which
625     * is associated with an interpreter. The entry contains a pointer to a
626     * function to call when the interpreter is deleted, and a pointer to
627     * a user-defined piece of data.
628     */
629    
630     typedef struct AssocData {
631     Tcl_InterpDeleteProc *proc; /* Proc to call when deleting. */
632     ClientData clientData; /* Value to pass to proc. */
633     } AssocData;
634    
635     /*
636     * The structure below defines a call frame. A call frame defines a naming
637     * context for a procedure call: its local naming scope (for local
638     * variables) and its global naming scope (a namespace, perhaps the global
639     * :: namespace). A call frame can also define the naming context for a
640     * namespace eval or namespace inscope command: the namespace in which the
641     * command's code should execute. The Tcl_CallFrame structures exist only
642     * while procedures or namespace eval/inscope's are being executed, and
643     * provide a kind of Tcl call stack.
644     *
645     * WARNING!! The structure definition must be kept consistent with the
646     * Tcl_CallFrame structure in tcl.h. If you change one, change the other.
647     */
648    
649     typedef struct CallFrame {
650     Namespace *nsPtr; /* Points to the namespace used to resolve
651     * commands and global variables. */
652     int isProcCallFrame; /* If nonzero, the frame was pushed to
653     * execute a Tcl procedure and may have
654     * local vars. If 0, the frame was pushed
655     * to execute a namespace command and var
656     * references are treated as references to
657     * namespace vars; varTablePtr and
658     * compiledLocals are ignored. */
659     int objc; /* This and objv below describe the
660     * arguments for this procedure call. */
661     Tcl_Obj *CONST *objv; /* Array of argument objects. */
662     struct CallFrame *callerPtr;
663     /* Value of interp->framePtr when this
664     * procedure was invoked (i.e. next higher
665     * in stack of all active procedures). */
666     struct CallFrame *callerVarPtr;
667     /* Value of interp->varFramePtr when this
668     * procedure was invoked (i.e. determines
669     * variable scoping within caller). Same
670     * as callerPtr unless an "uplevel" command
671     * or something equivalent was active in
672     * the caller). */
673     int level; /* Level of this procedure, for "uplevel"
674     * purposes (i.e. corresponds to nesting of
675     * callerVarPtr's, not callerPtr's). 1 for
676     * outermost procedure, 0 for top-level. */
677     Proc *procPtr; /* Points to the structure defining the
678     * called procedure. Used to get information
679     * such as the number of compiled local
680     * variables (local variables assigned
681     * entries ["slots"] in the compiledLocals
682     * array below). */
683     Tcl_HashTable *varTablePtr; /* Hash table containing local variables not
684     * recognized by the compiler, or created at
685     * execution time through, e.g., upvar.
686     * Initially NULL and created if needed. */
687     int numCompiledLocals; /* Count of local variables recognized by
688     * the compiler including arguments. */
689     Var* compiledLocals; /* Points to the array of local variables
690     * recognized by the compiler. The compiler
691     * emits code that refers to these variables
692     * using an index into this array. */
693     } CallFrame;
694    
695     /*
696     *----------------------------------------------------------------
697     * Data structures and procedures related to TclHandles, which
698     * are a very lightweight method of preserving enough information
699     * to determine if an arbitrary malloc'd block has been deleted.
700     *----------------------------------------------------------------
701     */
702    
703     typedef VOID **TclHandle;
704    
705     EXTERN TclHandle TclHandleCreate _ANSI_ARGS_((VOID *ptr));
706     EXTERN void TclHandleFree _ANSI_ARGS_((TclHandle handle));
707     EXTERN TclHandle TclHandlePreserve _ANSI_ARGS_((TclHandle handle));
708     EXTERN void TclHandleRelease _ANSI_ARGS_((TclHandle handle));
709    
710     /*
711     *----------------------------------------------------------------
712     * Data structures related to history. These are used primarily
713     * in tclHistory.c
714     *----------------------------------------------------------------
715     */
716    
717     /*
718     * The structure below defines one history event (a previously-executed
719     * command that can be re-executed in whole or in part).
720     */
721    
722     typedef struct {
723     char *command; /* String containing previously-executed
724     * command. */
725     int bytesAvl; /* Total # of bytes available at *event (not
726     * all are necessarily in use now). */
727     } HistoryEvent;
728    
729     /*
730     * The structure below defines a pending revision to the most recent
731     * history event. Changes are linked together into a list and applied
732     * during the next call to Tcl_RecordHistory. See the comments at the
733     * beginning of tclHistory.c for information on revisions.
734     */
735    
736     typedef struct HistoryRev {
737     int firstIndex; /* Index of the first byte to replace in
738     * current history event. */
739     int lastIndex; /* Index of last byte to replace in
740     * current history event. */
741     int newSize; /* Number of bytes in newBytes. */
742     char *newBytes; /* Replacement for the range given by
743     * firstIndex and lastIndex (malloced). */
744     struct HistoryRev *nextPtr; /* Next in chain of revisions to apply, or
745     * NULL for end of list. */
746     } HistoryRev;
747    
748     /*
749     *----------------------------------------------------------------
750     * Data structures related to expressions. These are used only in
751     * tclExpr.c.
752     *----------------------------------------------------------------
753     */
754    
755     /*
756     * The data structure below defines a math function (e.g. sin or hypot)
757     * for use in Tcl expressions.
758     */
759    
760     #define MAX_MATH_ARGS 5
761     typedef struct MathFunc {
762     int builtinFuncIndex; /* If this is a builtin math function, its
763     * index in the array of builtin functions.
764     * (tclCompilation.h lists these indices.)
765     * The value is -1 if this is a new function
766     * defined by Tcl_CreateMathFunc. The value
767     * is also -1 if a builtin function is
768     * replaced by a Tcl_CreateMathFunc call. */
769     int numArgs; /* Number of arguments for function. */
770     Tcl_ValueType argTypes[MAX_MATH_ARGS];
771     /* Acceptable types for each argument. */
772     Tcl_MathProc *proc; /* Procedure that implements this function.
773     * NULL if isBuiltinFunc is 1. */
774     ClientData clientData; /* Additional argument to pass to the
775     * function when invoking it. NULL if
776     * isBuiltinFunc is 1. */
777     } MathFunc;
778    
779     /*
780     * These are a thin layer over TclpThreadKeyDataGet and TclpThreadKeyDataSet
781     * when threads are used, or an emulation if there are no threads. These
782     * are really internal and Tcl clients should use Tcl_GetThreadData.
783     */
784    
785     EXTERN VOID *TclThreadDataKeyGet _ANSI_ARGS_((Tcl_ThreadDataKey *keyPtr));
786     EXTERN void TclThreadDataKeySet _ANSI_ARGS_((Tcl_ThreadDataKey *keyPtr, VOID *data));
787    
788     /*
789     * This is a convenience macro used to initialize a thread local storage ptr.
790     */
791     #define TCL_TSD_INIT(keyPtr) (ThreadSpecificData *)Tcl_GetThreadData((keyPtr), sizeof(ThreadSpecificData))
792    
793    
794     /*
795     *----------------------------------------------------------------
796     * Data structures related to bytecode compilation and execution.
797     * These are used primarily in tclCompile.c, tclExecute.c, and
798     * tclBasic.c.
799     *----------------------------------------------------------------
800     */
801    
802     /*
803     * Forward declaration to prevent errors when the forward references to
804     * Tcl_Parse and CompileEnv are encountered in the procedure type
805     * CompileProc declared below.
806     */
807    
808     struct CompileEnv;
809    
810     /*
811     * The type of procedures called by the Tcl bytecode compiler to compile
812     * commands. Pointers to these procedures are kept in the Command structure
813     * describing each command. When a CompileProc returns, the interpreter's
814     * result is set to error information, if any. In addition, the CompileProc
815     * returns an integer value, which is one of the following:
816     *
817     * TCL_OK Compilation completed normally.
818     * TCL_ERROR Compilation failed because of an error;
819     * the interpreter's result describes what went wrong.
820     * TCL_OUT_LINE_COMPILE Compilation failed because, e.g., the command is
821     * too complex for effective inline compilation. The
822     * CompileProc believes the command is legal but
823     * should be compiled "out of line" by emitting code
824     * to invoke its command procedure at runtime.
825     */
826    
827     #define TCL_OUT_LINE_COMPILE (TCL_CONTINUE + 1)
828    
829     typedef int (CompileProc) _ANSI_ARGS_((Tcl_Interp *interp,
830     Tcl_Parse *parsePtr, struct CompileEnv *compEnvPtr));
831    
832     /*
833     * The type of procedure called from the compilation hook point in
834     * SetByteCodeFromAny.
835     */
836    
837     typedef int (CompileHookProc) _ANSI_ARGS_((Tcl_Interp *interp,
838     struct CompileEnv *compEnvPtr, ClientData clientData));
839    
840     /*
841     * The data structure defining the execution environment for ByteCode's.
842     * There is one ExecEnv structure per Tcl interpreter. It holds the
843     * evaluation stack that holds command operands and results. The stack grows
844     * towards increasing addresses. The "stackTop" member is cached by
845     * TclExecuteByteCode in a local variable: it must be set before calling
846     * TclExecuteByteCode and will be restored by TclExecuteByteCode before it
847     * returns.
848     */
849    
850     typedef struct ExecEnv {
851     Tcl_Obj **stackPtr; /* Points to the first item in the
852     * evaluation stack on the heap. */
853     int stackTop; /* Index of current top of stack; -1 when
854     * the stack is empty. */
855     int stackEnd; /* Index of last usable item in stack. */
856     } ExecEnv;
857    
858     /*
859     * The definitions for the LiteralTable and LiteralEntry structures. Each
860     * interpreter contains a LiteralTable. It is used to reduce the storage
861     * needed for all the Tcl objects that hold the literals of scripts compiled
862     * by the interpreter. A literal's object is shared by all the ByteCodes
863     * that refer to the literal. Each distinct literal has one LiteralEntry
864     * entry in the LiteralTable. A literal table is a specialized hash table
865     * that is indexed by the literal's string representation, which may contain
866     * null characters.
867     *
868     * Note that we reduce the space needed for literals by sharing literal
869     * objects both within a ByteCode (each ByteCode contains a local
870     * LiteralTable) and across all an interpreter's ByteCodes (with the
871     * interpreter's global LiteralTable).
872     */
873    
874     typedef struct LiteralEntry {
875     struct LiteralEntry *nextPtr; /* Points to next entry in this
876     * hash bucket or NULL if end of
877     * chain. */
878     Tcl_Obj *objPtr; /* Points to Tcl object that
879     * holds the literal's bytes and
880     * length. */
881     int refCount; /* If in an interpreter's global
882     * literal table, the number of
883     * ByteCode structures that share
884     * the literal object; the literal
885     * entry can be freed when refCount
886     * drops to 0. If in a local literal
887     * table, -1. */
888     } LiteralEntry;
889    
890     typedef struct LiteralTable {
891     LiteralEntry **buckets; /* Pointer to bucket array. Each
892     * element points to first entry in
893     * bucket's hash chain, or NULL. */
894     LiteralEntry *staticBuckets[TCL_SMALL_HASH_TABLE];
895     /* Bucket array used for small
896     * tables to avoid mallocs and
897     * frees. */
898     int numBuckets; /* Total number of buckets allocated
899     * at **buckets. */
900     int numEntries; /* Total number of entries present
901     * in table. */
902     int rebuildSize; /* Enlarge table when numEntries
903     * gets to be this large. */
904     int mask; /* Mask value used in hashing
905     * function. */
906     } LiteralTable;
907    
908     /*
909     * The following structure defines for each Tcl interpreter various
910     * statistics-related information about the bytecode compiler and
911     * interpreter's operation in that interpreter.
912     */
913    
914     #ifdef TCL_COMPILE_STATS
915     typedef struct ByteCodeStats {
916     long numExecutions; /* Number of ByteCodes executed. */
917     long numCompilations; /* Number of ByteCodes created. */
918     long numByteCodesFreed; /* Number of ByteCodes destroyed. */
919     long instructionCount[256]; /* Number of times each instruction was
920     * executed. */
921    
922     double totalSrcBytes; /* Total source bytes ever compiled. */
923     double totalByteCodeBytes; /* Total bytes for all ByteCodes. */
924     double currentSrcBytes; /* Src bytes for all current ByteCodes. */
925     double currentByteCodeBytes; /* Code bytes in all current ByteCodes. */
926    
927     long srcCount[32]; /* Source size distribution: # of srcs of
928     * size [2**(n-1)..2**n), n in [0..32). */
929     long byteCodeCount[32]; /* ByteCode size distribution. */
930     long lifetimeCount[32]; /* ByteCode lifetime distribution (ms). */
931    
932     double currentInstBytes; /* Instruction bytes-current ByteCodes. */
933     double currentLitBytes; /* Current literal bytes. */
934     double currentExceptBytes; /* Current exception table bytes. */
935     double currentAuxBytes; /* Current auxiliary information bytes. */
936     double currentCmdMapBytes; /* Current src<->code map bytes. */
937    
938     long numLiteralsCreated; /* Total literal objects ever compiled. */
939     double totalLitStringBytes; /* Total string bytes in all literals. */
940     double currentLitStringBytes; /* String bytes in current literals. */
941     long literalCount[32]; /* Distribution of literal string sizes. */
942     } ByteCodeStats;
943     #endif /* TCL_COMPILE_STATS */
944    
945     /*
946     *----------------------------------------------------------------
947     * Data structures related to commands.
948     *----------------------------------------------------------------
949     */
950    
951     /*
952     * An imported command is created in an namespace when it imports a "real"
953     * command from another namespace. An imported command has a Command
954     * structure that points (via its ClientData value) to the "real" Command
955     * structure in the source namespace's command table. The real command
956     * records all the imported commands that refer to it in a list of ImportRef
957     * structures so that they can be deleted when the real command is deleted. */
958    
959     typedef struct ImportRef {
960     struct Command *importedCmdPtr;
961     /* Points to the imported command created in
962     * an importing namespace; this command
963     * redirects its invocations to the "real"
964     * command. */
965     struct ImportRef *nextPtr; /* Next element on the linked list of
966     * imported commands that refer to the
967     * "real" command. The real command deletes
968     * these imported commands on this list when
969     * it is deleted. */
970     } ImportRef;
971    
972     /*
973     * Data structure used as the ClientData of imported commands: commands
974     * created in an namespace when it imports a "real" command from another
975     * namespace.
976     */
977    
978     typedef struct ImportedCmdData {
979     struct Command *realCmdPtr; /* "Real" command that this imported command
980     * refers to. */
981     struct Command *selfPtr; /* Pointer to this imported command. Needed
982     * only when deleting it in order to remove
983     * it from the real command's linked list of
984     * imported commands that refer to it. */
985     } ImportedCmdData;
986    
987     /*
988     * A Command structure exists for each command in a namespace. The
989     * Tcl_Command opaque type actually refers to these structures.
990     */
991    
992     typedef struct Command {
993     Tcl_HashEntry *hPtr; /* Pointer to the hash table entry that
994     * refers to this command. The hash table is
995     * either a namespace's command table or an
996     * interpreter's hidden command table. This
997     * pointer is used to get a command's name
998     * from its Tcl_Command handle. NULL means
999     * that the hash table entry has been
1000     * removed already (this can happen if
1001     * deleteProc causes the command to be
1002     * deleted or recreated). */
1003     Namespace *nsPtr; /* Points to the namespace containing this
1004     * command. */
1005     int refCount; /* 1 if in command hashtable plus 1 for each
1006     * reference from a CmdName Tcl object
1007     * representing a command's name in a
1008     * ByteCode instruction sequence. This
1009     * structure can be freed when refCount
1010     * becomes zero. */
1011     int cmdEpoch; /* Incremented to invalidate any references
1012     * that point to this command when it is
1013     * renamed, deleted, hidden, or exposed. */
1014     CompileProc *compileProc; /* Procedure called to compile command. NULL
1015     * if no compile proc exists for command. */
1016     Tcl_ObjCmdProc *objProc; /* Object-based command procedure. */
1017     ClientData objClientData; /* Arbitrary value passed to object proc. */
1018     Tcl_CmdProc *proc; /* String-based command procedure. */
1019     ClientData clientData; /* Arbitrary value passed to string proc. */
1020     Tcl_CmdDeleteProc *deleteProc;
1021     /* Procedure invoked when deleting command
1022     * to, e.g., free all client data. */
1023     ClientData deleteData; /* Arbitrary value passed to deleteProc. */
1024     int deleted; /* Means that the command is in the process
1025     * of being deleted (its deleteProc is
1026     * currently executing). Other attempts to
1027     * delete the command should be ignored. */
1028     ImportRef *importRefPtr; /* List of each imported Command created in
1029     * another namespace when this command is
1030     * imported. These imported commands
1031     * redirect invocations back to this
1032     * command. The list is used to remove all
1033     * those imported commands when deleting
1034     * this "real" command. */
1035     } Command;
1036    
1037     /*
1038     *----------------------------------------------------------------
1039     * Data structures related to name resolution procedures.
1040     *----------------------------------------------------------------
1041     */
1042    
1043     /*
1044     * The interpreter keeps a linked list of name resolution schemes.
1045     * The scheme for a namespace is consulted first, followed by the
1046     * list of schemes in an interpreter, followed by the default
1047     * name resolution in Tcl. Schemes are added/removed from the
1048     * interpreter's list by calling Tcl_AddInterpResolver and
1049     * Tcl_RemoveInterpResolver.
1050     */
1051    
1052     typedef struct ResolverScheme {
1053     char *name; /* Name identifying this scheme. */
1054     Tcl_ResolveCmdProc *cmdResProc;
1055     /* Procedure handling command name
1056     * resolution. */
1057     Tcl_ResolveVarProc *varResProc;
1058     /* Procedure handling variable name
1059     * resolution for variables that
1060     * can only be handled at runtime. */
1061     Tcl_ResolveCompiledVarProc *compiledVarResProc;
1062     /* Procedure handling variable name
1063     * resolution at compile time. */
1064    
1065     struct ResolverScheme *nextPtr;
1066     /* Pointer to next record in linked list. */
1067     } ResolverScheme;
1068    
1069     /*
1070     *----------------------------------------------------------------
1071     * This structure defines an interpreter, which is a collection of
1072     * commands plus other state information related to interpreting
1073     * commands, such as variable storage. Primary responsibility for
1074     * this data structure is in tclBasic.c, but almost every Tcl
1075     * source file uses something in here.
1076     *----------------------------------------------------------------
1077     */
1078    
1079     typedef struct Interp {
1080    
1081     /*
1082     * Note: the first three fields must match exactly the fields in
1083     * a Tcl_Interp struct (see tcl.h). If you change one, be sure to
1084     * change the other.
1085     *
1086     * The interpreter's result is held in both the string and the
1087     * objResultPtr fields. These fields hold, respectively, the result's
1088     * string or object value. The interpreter's result is always in the
1089     * result field if that is non-empty, otherwise it is in objResultPtr.
1090     * The two fields are kept consistent unless some C code sets
1091     * interp->result directly. Programs should not access result and
1092     * objResultPtr directly; instead, they should always get and set the
1093     * result using procedures such as Tcl_SetObjResult, Tcl_GetObjResult,
1094     * and Tcl_GetStringResult. See the SetResult man page for details.
1095     */
1096    
1097     char *result; /* If the last command returned a string
1098     * result, this points to it. Should not be
1099     * accessed directly; see comment above. */
1100     Tcl_FreeProc *freeProc; /* Zero means a string result is statically
1101     * allocated. TCL_DYNAMIC means string
1102     * result was allocated with ckalloc and
1103     * should be freed with ckfree. Other values
1104     * give address of procedure to invoke to
1105     * free the string result. Tcl_Eval must
1106     * free it before executing next command. */
1107     int errorLine; /* When TCL_ERROR is returned, this gives
1108     * the line number in the command where the
1109     * error occurred (1 means first line). */
1110     struct TclStubs *stubTable;
1111     /* Pointer to the exported Tcl stub table.
1112     * On previous versions of Tcl this is a
1113     * pointer to the objResultPtr or a pointer
1114     * to a buckets array in a hash table. We
1115     * therefore have to do some careful checking
1116     * before we can use this. */
1117    
1118     TclHandle handle; /* Handle used to keep track of when this
1119     * interp is deleted. */
1120    
1121     Namespace *globalNsPtr; /* The interpreter's global namespace. */
1122     Tcl_HashTable *hiddenCmdTablePtr;
1123     /* Hash table used by tclBasic.c to keep
1124     * track of hidden commands on a per-interp
1125     * basis. */
1126     ClientData interpInfo; /* Information used by tclInterp.c to keep
1127     * track of master/slave interps on
1128     * a per-interp basis. */
1129     Tcl_HashTable mathFuncTable;/* Contains all the math functions currently
1130     * defined for the interpreter. Indexed by
1131     * strings (function names); values have
1132     * type (MathFunc *). */
1133    
1134    
1135    
1136     /*
1137     * Information related to procedures and variables. See tclProc.c
1138     * and tclvar.c for usage.
1139     */
1140    
1141     int numLevels; /* Keeps track of how many nested calls to
1142     * Tcl_Eval are in progress for this
1143     * interpreter. It's used to delay deletion
1144     * of the table until all Tcl_Eval
1145     * invocations are completed. */
1146     int maxNestingDepth; /* If numLevels exceeds this value then Tcl
1147     * assumes that infinite recursion has
1148     * occurred and it generates an error. */
1149     CallFrame *framePtr; /* Points to top-most in stack of all nested
1150     * procedure invocations. NULL means there
1151     * are no active procedures. */
1152     CallFrame *varFramePtr; /* Points to the call frame whose variables
1153     * are currently in use (same as framePtr
1154     * unless an "uplevel" command is
1155     * executing). NULL means no procedure is
1156     * active or "uplevel 0" is executing. */
1157     ActiveVarTrace *activeTracePtr;
1158     /* First in list of active traces for
1159     * interp, or NULL if no active traces. */
1160     int returnCode; /* Completion code to return if current
1161     * procedure exits with TCL_RETURN code. */
1162     char *errorInfo; /* Value to store in errorInfo if returnCode
1163     * is TCL_ERROR. Malloc'ed, may be NULL */
1164     char *errorCode; /* Value to store in errorCode if returnCode
1165     * is TCL_ERROR. Malloc'ed, may be NULL */
1166    
1167     /*
1168     * Information used by Tcl_AppendResult to keep track of partial
1169     * results. See Tcl_AppendResult code for details.
1170     */
1171    
1172     char *appendResult; /* Storage space for results generated
1173     * by Tcl_AppendResult. Malloc-ed. NULL
1174     * means not yet allocated. */
1175     int appendAvl; /* Total amount of space available at
1176     * partialResult. */
1177     int appendUsed; /* Number of non-null bytes currently
1178     * stored at partialResult. */
1179    
1180     /*
1181     * Information about packages. Used only in tclPkg.c.
1182     */
1183    
1184     Tcl_HashTable packageTable; /* Describes all of the packages loaded
1185     * in or available to this interpreter.
1186     * Keys are package names, values are
1187     * (Package *) pointers. */
1188     char *packageUnknown; /* Command to invoke during "package
1189     * require" commands for packages that
1190     * aren't described in packageTable.
1191     * Malloc'ed, may be NULL. */
1192    
1193     /*
1194     * Miscellaneous information:
1195     */
1196    
1197     int cmdCount; /* Total number of times a command procedure
1198     * has been called for this interpreter. */
1199     int evalFlags; /* Flags to control next call to Tcl_Eval.
1200     * Normally zero, but may be set before
1201     * calling Tcl_Eval. See below for valid
1202     * values. */
1203     int termOffset; /* Offset of character just after last one
1204     * compiled or executed by Tcl_EvalObj. */
1205     LiteralTable literalTable; /* Contains LiteralEntry's describing all
1206     * Tcl objects holding literals of scripts
1207     * compiled by the interpreter. Indexed by
1208     * the string representations of literals.
1209     * Used to avoid creating duplicate
1210     * objects. */
1211     int compileEpoch; /* Holds the current "compilation epoch"
1212     * for this interpreter. This is
1213     * incremented to invalidate existing
1214     * ByteCodes when, e.g., a command with a
1215     * compile procedure is redefined. */
1216     Proc *compiledProcPtr; /* If a procedure is being compiled, a
1217     * pointer to its Proc structure; otherwise,
1218     * this is NULL. Set by ObjInterpProc in
1219     * tclProc.c and used by tclCompile.c to
1220     * process local variables appropriately. */
1221     ResolverScheme *resolverPtr;
1222     /* Linked list of name resolution schemes
1223     * added to this interpreter. Schemes
1224     * are added/removed by calling
1225     * Tcl_AddInterpResolvers and
1226     * Tcl_RemoveInterpResolver. */
1227     char *scriptFile; /* NULL means there is no nested source
1228     * command active; otherwise this points to
1229     * the name of the file being sourced (it's
1230     * not malloc-ed: it points to an argument
1231     * to Tcl_EvalFile. */
1232     int flags; /* Various flag bits. See below. */
1233     long randSeed; /* Seed used for rand() function. */
1234     Trace *tracePtr; /* List of traces for this interpreter. */
1235     Tcl_HashTable *assocData; /* Hash table for associating data with
1236     * this interpreter. Cleaned up when
1237     * this interpreter is deleted. */
1238     struct ExecEnv *execEnvPtr; /* Execution environment for Tcl bytecode
1239     * execution. Contains a pointer to the
1240     * Tcl evaluation stack. */
1241     Tcl_Obj *emptyObjPtr; /* Points to an object holding an empty
1242     * string. Returned by Tcl_ObjSetVar2 when
1243     * variable traces change a variable in a
1244     * gross way. */
1245     char resultSpace[TCL_RESULT_SIZE+1];
1246     /* Static space holding small results. */
1247     Tcl_Obj *objResultPtr; /* If the last command returned an object
1248     * result, this points to it. Should not be
1249     * accessed directly; see comment above. */
1250     Tcl_ThreadId threadId; /* ID of thread that owns the interpreter */
1251    
1252     /*
1253     * Statistical information about the bytecode compiler and interpreter's
1254     * operation.
1255     */
1256    
1257     #ifdef TCL_COMPILE_STATS
1258     ByteCodeStats stats; /* Holds compilation and execution
1259     * statistics for this interpreter. */
1260     #endif /* TCL_COMPILE_STATS */
1261     } Interp;
1262    
1263     /*
1264     * EvalFlag bits for Interp structures:
1265     *
1266     * TCL_BRACKET_TERM 1 means that the current script is terminated by
1267     * a close bracket rather than the end of the string.
1268     * TCL_ALLOW_EXCEPTIONS 1 means it's OK for the script to terminate with
1269     * a code other than TCL_OK or TCL_ERROR; 0 means
1270     * codes other than these should be turned into errors.
1271     */
1272    
1273     #define TCL_BRACKET_TERM 1
1274     #define TCL_ALLOW_EXCEPTIONS 4
1275    
1276     /*
1277     * Flag bits for Interp structures:
1278     *
1279     * DELETED: Non-zero means the interpreter has been deleted:
1280     * don't process any more commands for it, and destroy
1281     * the structure as soon as all nested invocations of
1282     * Tcl_Eval are done.
1283     * ERR_IN_PROGRESS: Non-zero means an error unwind is already in
1284     * progress. Zero means a command proc has been
1285     * invoked since last error occured.
1286     * ERR_ALREADY_LOGGED: Non-zero means information has already been logged
1287     * in $errorInfo for the current Tcl_Eval instance,
1288     * so Tcl_Eval needn't log it (used to implement the
1289     * "error message log" command).
1290     * ERROR_CODE_SET: Non-zero means that Tcl_SetErrorCode has been
1291     * called to record information for the current
1292     * error. Zero means Tcl_Eval must clear the
1293     * errorCode variable if an error is returned.
1294     * EXPR_INITIALIZED: Non-zero means initialization specific to
1295     * expressions has been carried out.
1296     * DONT_COMPILE_CMDS_INLINE: Non-zero means that the bytecode compiler
1297     * should not compile any commands into an inline
1298     * sequence of instructions. This is set 1, for
1299     * example, when command traces are requested.
1300     * RAND_SEED_INITIALIZED: Non-zero means that the randSeed value of the
1301     * interp has not be initialized. This is set 1
1302     * when we first use the rand() or srand() functions.
1303     * SAFE_INTERP: Non zero means that the current interp is a
1304     * safe interp (ie it has only the safe commands
1305     * installed, less priviledge than a regular interp).
1306     * USE_EVAL_DIRECT: Non-zero means don't use the compiler or byte-code
1307     * interpreter; instead, have Tcl_EvalObj call
1308     * Tcl_EvalEx. Used primarily for testing the
1309     * new parser.
1310     */
1311    
1312     #define DELETED 1
1313     #define ERR_IN_PROGRESS 2
1314     #define ERR_ALREADY_LOGGED 4
1315     #define ERROR_CODE_SET 8
1316     #define EXPR_INITIALIZED 0x10
1317     #define DONT_COMPILE_CMDS_INLINE 0x20
1318     #define RAND_SEED_INITIALIZED 0x40
1319     #define SAFE_INTERP 0x80
1320     #define USE_EVAL_DIRECT 0x100
1321    
1322     /*
1323     *----------------------------------------------------------------
1324     * Data structures related to command parsing. These are used in
1325     * tclParse.c and its clients.
1326     *----------------------------------------------------------------
1327     */
1328    
1329     /*
1330     * The following data structure is used by various parsing procedures
1331     * to hold information about where to store the results of parsing
1332     * (e.g. the substituted contents of a quoted argument, or the result
1333     * of a nested command). At any given time, the space available
1334     * for output is fixed, but a procedure may be called to expand the
1335     * space available if the current space runs out.
1336     */
1337    
1338     typedef struct ParseValue {
1339     char *buffer; /* Address of first character in
1340     * output buffer. */
1341     char *next; /* Place to store next character in
1342     * output buffer. */
1343     char *end; /* Address of the last usable character
1344     * in the buffer. */
1345     void (*expandProc) _ANSI_ARGS_((struct ParseValue *pvPtr, int needed));
1346     /* Procedure to call when space runs out;
1347     * it will make more space. */
1348     ClientData clientData; /* Arbitrary information for use of
1349     * expandProc. */
1350     } ParseValue;
1351    
1352    
1353     /*
1354     * Maximum number of levels of nesting permitted in Tcl commands (used
1355     * to catch infinite recursion).
1356     */
1357    
1358     #define MAX_NESTING_DEPTH 1000
1359    
1360     /*
1361     * The macro below is used to modify a "char" value (e.g. by casting
1362     * it to an unsigned character) so that it can be used safely with
1363     * macros such as isspace.
1364     */
1365    
1366     #define UCHAR(c) ((unsigned char) (c))
1367    
1368     /*
1369     * This macro is used to determine the offset needed to safely allocate any
1370     * data structure in memory. Given a starting offset or size, it "rounds up"
1371     * or "aligns" the offset to the next 8-byte boundary so that any data
1372     * structure can be placed at the resulting offset without fear of an
1373     * alignment error.
1374     *
1375     * WARNING!! DO NOT USE THIS MACRO TO ALIGN POINTERS: it will produce
1376     * the wrong result on platforms that allocate addresses that are divisible
1377     * by 4 or 2. Only use it for offsets or sizes.
1378     */
1379    
1380     #define TCL_ALIGN(x) (((int)(x) + 7) & ~7)
1381    
1382     /*
1383     * The following macros are used to specify the runtime platform
1384     * setting of the tclPlatform variable.
1385     */
1386    
1387     typedef enum {
1388     TCL_PLATFORM_UNIX, /* Any Unix-like OS. */
1389     TCL_PLATFORM_MAC, /* MacOS. */
1390     TCL_PLATFORM_WINDOWS /* Any Microsoft Windows OS. */
1391     } TclPlatformType;
1392    
1393     /*
1394     * Flags for TclInvoke:
1395     *
1396     * TCL_INVOKE_HIDDEN Invoke a hidden command; if not set,
1397     * invokes an exposed command.
1398     * TCL_INVOKE_NO_UNKNOWN If set, "unknown" is not invoked if
1399     * the command to be invoked is not found.
1400     * Only has an effect if invoking an exposed
1401     * command, i.e. if TCL_INVOKE_HIDDEN is not
1402     * also set.
1403     * TCL_INVOKE_NO_TRACEBACK Does not record traceback information if
1404     * the invoked command returns an error. Used
1405     * if the caller plans on recording its own
1406     * traceback information.
1407     */
1408    
1409     #define TCL_INVOKE_HIDDEN (1<<0)
1410     #define TCL_INVOKE_NO_UNKNOWN (1<<1)
1411     #define TCL_INVOKE_NO_TRACEBACK (1<<2)
1412    
1413     /*
1414     * The structure used as the internal representation of Tcl list
1415     * objects. This is an array of pointers to the element objects. This array
1416     * is grown (reallocated and copied) as necessary to hold all the list's
1417     * element pointers. The array might contain more slots than currently used
1418     * to hold all element pointers. This is done to make append operations
1419     * faster.
1420     */
1421    
1422     typedef struct List {
1423     int maxElemCount; /* Total number of element array slots. */
1424     int elemCount; /* Current number of list elements. */
1425     Tcl_Obj **elements; /* Array of pointers to element objects. */
1426     } List;
1427    
1428    
1429     /*
1430     * The following types are used for getting and storing platform-specific
1431     * file attributes in tclFCmd.c and the various platform-versions of
1432     * that file. This is done to have as much common code as possible
1433     * in the file attributes code. For more information about the callbacks,
1434     * see TclFileAttrsCmd in tclFCmd.c.
1435     */
1436    
1437     typedef int (TclGetFileAttrProc) _ANSI_ARGS_((Tcl_Interp *interp,
1438     int objIndex, CONST char *fileName, Tcl_Obj **attrObjPtrPtr));
1439     typedef int (TclSetFileAttrProc) _ANSI_ARGS_((Tcl_Interp *interp,
1440     int objIndex, CONST char *fileName, Tcl_Obj *attrObjPtr));
1441    
1442     typedef struct TclFileAttrProcs {
1443     TclGetFileAttrProc *getProc; /* The procedure for getting attrs. */
1444     TclSetFileAttrProc *setProc; /* The procedure for setting attrs. */
1445     } TclFileAttrProcs;
1446    
1447     /*
1448     * Opaque handle used in pipeline routines to encapsulate platform-dependent
1449     * state.
1450     */
1451    
1452     typedef struct TclFile_ *TclFile;
1453    
1454     /*
1455     *----------------------------------------------------------------
1456     * Data structures related to hooking 'TclStat(...)' and
1457     * 'TclAccess(...)'.
1458     *----------------------------------------------------------------
1459     */
1460    
1461     typedef int (TclStatProc_) _ANSI_ARGS_((CONST char *path, struct stat *buf));
1462     typedef int (TclAccessProc_) _ANSI_ARGS_((CONST char *path, int mode));
1463     typedef Tcl_Channel (TclOpenFileChannelProc_) _ANSI_ARGS_((Tcl_Interp *interp,
1464     char *fileName, char *modeString,
1465     int permissions));
1466    
1467     typedef int (*TclCmdProcType) _ANSI_ARGS_((ClientData clientData,
1468     Tcl_Interp *interp, int argc, char *argv[]));
1469     typedef int (*TclObjCmdProcType) _ANSI_ARGS_((ClientData clientData,
1470     Tcl_Interp *interp, int objc, struct Tcl_Obj * CONST objv[]));
1471    
1472     /*
1473     * Opaque names for platform specific types.
1474     */
1475    
1476     typedef struct TclpTime_t_ *TclpTime_t;
1477    
1478     /*
1479     * The following structure is used to pass glob type data amongst
1480     * the various glob routines and TclpMatchFilesTypes. Currently
1481     * most of the fields are ignored. However they will be used in
1482     * a future release to implement glob's ability to find files
1483     * of particular types/permissions/etc only.
1484     */
1485     typedef struct GlobTypeData {
1486     /* Corresponds to bcdpfls as in 'find -t' */
1487     int type;
1488     /* Corresponds to file permissions */
1489     int perm;
1490     /* Acceptable mac type */
1491     Tcl_Obj* macType;
1492     /* Acceptable mac creator */
1493     Tcl_Obj* macCreator;
1494     } GlobTypeData;
1495    
1496     /*
1497     * type and permission definitions for glob command
1498     */
1499     #define TCL_GLOB_TYPE_BLOCK (1<<0)
1500     #define TCL_GLOB_TYPE_CHAR (1<<1)
1501     #define TCL_GLOB_TYPE_DIR (1<<2)
1502     #define TCL_GLOB_TYPE_PIPE (1<<3)
1503     #define TCL_GLOB_TYPE_FILE (1<<4)
1504     #define TCL_GLOB_TYPE_LINK (1<<5)
1505     #define TCL_GLOB_TYPE_SOCK (1<<6)
1506    
1507     #define TCL_GLOB_PERM_RONLY (1<<0)
1508     #define TCL_GLOB_PERM_HIDDEN (1<<1)
1509     #define TCL_GLOB_PERM_R (1<<2)
1510     #define TCL_GLOB_PERM_W (1<<3)
1511     #define TCL_GLOB_PERM_X (1<<4)
1512    
1513     /*
1514     *----------------------------------------------------------------
1515     * Variables shared among Tcl modules but not used by the outside world.
1516     *----------------------------------------------------------------
1517     */
1518    
1519     extern Tcl_Time tclBlockTime;
1520     extern int tclBlockTimeSet;
1521     extern char * tclExecutableName;
1522     extern char * tclNativeExecutableName;
1523     extern char * tclDefaultEncodingDir;
1524     extern Tcl_ChannelType tclFileChannelType;
1525     extern char * tclMemDumpFileName;
1526     extern TclPlatformType tclPlatform;
1527     extern char * tclpFileAttrStrings[];
1528     extern CONST TclFileAttrProcs tclpFileAttrProcs[];
1529    
1530     /*
1531     * Variables denoting the Tcl object types defined in the core.
1532     */
1533    
1534     extern Tcl_ObjType tclBooleanType;
1535     extern Tcl_ObjType tclByteArrayType;
1536     extern Tcl_ObjType tclByteCodeType;
1537     extern Tcl_ObjType tclDoubleType;
1538     extern Tcl_ObjType tclIntType;
1539     extern Tcl_ObjType tclListType;
1540     extern Tcl_ObjType tclProcBodyType;
1541     extern Tcl_ObjType tclStringType;
1542    
1543     /*
1544     * The head of the list of free Tcl objects, and the total number of Tcl
1545     * objects ever allocated and freed.
1546     */
1547    
1548     extern Tcl_Obj * tclFreeObjList;
1549    
1550     #ifdef TCL_COMPILE_STATS
1551     extern long tclObjsAlloced;
1552     extern long tclObjsFreed;
1553     #endif /* TCL_COMPILE_STATS */
1554    
1555     /*
1556     * Pointer to a heap-allocated string of length zero that the Tcl core uses
1557     * as the value of an empty string representation for an object. This value
1558     * is shared by all new objects allocated by Tcl_NewObj.
1559     */
1560    
1561     extern char * tclEmptyStringRep;
1562    
1563     /*
1564     *----------------------------------------------------------------
1565     * Procedures shared among Tcl modules but not used by the outside
1566     * world:
1567     *----------------------------------------------------------------
1568     */
1569    
1570     EXTERN int TclAccess _ANSI_ARGS_((CONST char *path,
1571     int mode));
1572     EXTERN int TclAccessDeleteProc _ANSI_ARGS_((TclAccessProc_ *proc));
1573     EXTERN int TclAccessInsertProc _ANSI_ARGS_((TclAccessProc_ *proc));
1574     EXTERN void TclAllocateFreeObjects _ANSI_ARGS_((void));
1575     EXTERN int TclArraySet _ANSI_ARGS_((Tcl_Interp *interp,
1576     Tcl_Obj *arrayNameObj, Tcl_Obj *arrayElemObj));
1577     EXTERN int TclCheckBadOctal _ANSI_ARGS_((Tcl_Interp *interp,
1578     char *value));
1579     EXTERN int TclCleanupChildren _ANSI_ARGS_((Tcl_Interp *interp,
1580     int numPids, Tcl_Pid *pidPtr,
1581     Tcl_Channel errorChan));
1582     EXTERN void TclCleanupCommand _ANSI_ARGS_((Command *cmdPtr));
1583     EXTERN int TclCopyChannel _ANSI_ARGS_((Tcl_Interp *interp,
1584     Tcl_Channel inChan, Tcl_Channel outChan,
1585     int toRead, Tcl_Obj *cmdPtr));
1586     /*
1587     * TclCreatePipeline unofficially exported for use by BLT.
1588     */
1589     EXTERN int TclCreatePipeline _ANSI_ARGS_((Tcl_Interp *interp,
1590     int argc, char **argv, Tcl_Pid **pidArrayPtr,
1591     TclFile *inPipePtr, TclFile *outPipePtr,
1592     TclFile *errFilePtr));
1593     EXTERN int TclCreateProc _ANSI_ARGS_((Tcl_Interp *interp,
1594     Namespace *nsPtr, char *procName,
1595     Tcl_Obj *argsPtr, Tcl_Obj *bodyPtr,
1596     Proc **procPtrPtr));
1597     EXTERN void TclDeleteCompiledLocalVars _ANSI_ARGS_((
1598     Interp *iPtr, CallFrame *framePtr));
1599     EXTERN void TclDeleteVars _ANSI_ARGS_((Interp *iPtr,
1600     Tcl_HashTable *tablePtr));
1601     EXTERN int TclDoGlob _ANSI_ARGS_((Tcl_Interp *interp,
1602     char *separators, Tcl_DString *headPtr,
1603     char *tail, GlobTypeData *types));
1604     EXTERN void TclDumpMemoryInfo _ANSI_ARGS_((FILE *outFile));
1605     EXTERN void TclExpandTokenArray _ANSI_ARGS_((
1606     Tcl_Parse *parsePtr));
1607     EXTERN void TclExprFloatError _ANSI_ARGS_((Tcl_Interp *interp,
1608     double value));
1609     EXTERN int TclFileAttrsCmd _ANSI_ARGS_((Tcl_Interp *interp,
1610     int objc, Tcl_Obj *CONST objv[]));
1611     EXTERN int TclFileCopyCmd _ANSI_ARGS_((Tcl_Interp *interp,
1612     int argc, char **argv)) ;
1613     EXTERN int TclFileDeleteCmd _ANSI_ARGS_((Tcl_Interp *interp,
1614     int argc, char **argv));
1615     EXTERN int TclFileMakeDirsCmd _ANSI_ARGS_((Tcl_Interp *interp,
1616     int argc, char **argv)) ;
1617     EXTERN int TclFileRenameCmd _ANSI_ARGS_((Tcl_Interp *interp,
1618     int argc, char **argv)) ;
1619     EXTERN void TclFinalizeAllocSubsystem _ANSI_ARGS_((void));
1620     EXTERN void TclFinalizeCompExecEnv _ANSI_ARGS_((void));
1621     EXTERN void TclFinalizeCompilation _ANSI_ARGS_((void));
1622     EXTERN void TclFinalizeEncodingSubsystem _ANSI_ARGS_((void));
1623     EXTERN void TclFinalizeEnvironment _ANSI_ARGS_((void));
1624     EXTERN void TclFinalizeExecution _ANSI_ARGS_((void));
1625     EXTERN void TclFinalizeIOSubsystem _ANSI_ARGS_((void));
1626     EXTERN void TclFinalizeLoad _ANSI_ARGS_((void));
1627     EXTERN void TclFinalizeMemorySubsystem _ANSI_ARGS_((void));
1628     EXTERN void TclFinalizeNotifier _ANSI_ARGS_((void));
1629     EXTERN void TclFinalizeSynchronization _ANSI_ARGS_((void));
1630     EXTERN void TclFinalizeThreadData _ANSI_ARGS_((void));
1631     EXTERN void TclFindEncodings _ANSI_ARGS_((CONST char *argv0));
1632     EXTERN Proc * TclFindProc _ANSI_ARGS_((Interp *iPtr,
1633     char *procName));
1634     EXTERN int TclFormatInt _ANSI_ARGS_((char *buffer, long n));
1635     EXTERN void TclFreePackageInfo _ANSI_ARGS_((Interp *iPtr));
1636     EXTERN int TclGetDate _ANSI_ARGS_((char *p,
1637     unsigned long now, long zone,
1638     unsigned long *timePtr));
1639     EXTERN Tcl_Obj * TclGetElementOfIndexedArray _ANSI_ARGS_((
1640     Tcl_Interp *interp, int localIndex,
1641     Tcl_Obj *elemPtr, int leaveErrorMsg));
1642     EXTERN char * TclGetExtension _ANSI_ARGS_((char *name));
1643     EXTERN int TclGetFrame _ANSI_ARGS_((Tcl_Interp *interp,
1644     char *string, CallFrame **framePtrPtr));
1645     EXTERN TclCmdProcType TclGetInterpProc _ANSI_ARGS_((void));
1646     EXTERN int TclGetIntForIndex _ANSI_ARGS_((Tcl_Interp *interp,
1647     Tcl_Obj *objPtr, int endValue, int *indexPtr));
1648     EXTERN Tcl_Obj * TclGetIndexedScalar _ANSI_ARGS_((Tcl_Interp *interp,
1649     int localIndex, int leaveErrorMsg));
1650     EXTERN int TclGetLong _ANSI_ARGS_((Tcl_Interp *interp,
1651     char *string, long *longPtr));
1652     EXTERN int TclGetLoadedPackages _ANSI_ARGS_((
1653     Tcl_Interp *interp, char *targetName));
1654     EXTERN int TclGetNamespaceForQualName _ANSI_ARGS_((
1655     Tcl_Interp *interp, char *qualName,
1656     Namespace *cxtNsPtr, int flags,
1657     Namespace **nsPtrPtr, Namespace **altNsPtrPtr,
1658     Namespace **actualCxtPtrPtr,
1659     char **simpleNamePtr));
1660     EXTERN TclObjCmdProcType TclGetObjInterpProc _ANSI_ARGS_((void));
1661     EXTERN int TclGetOpenMode _ANSI_ARGS_((Tcl_Interp *interp,
1662     char *string, int *seekFlagPtr));
1663     EXTERN Tcl_Command TclGetOriginalCommand _ANSI_ARGS_((
1664     Tcl_Command command));
1665     EXTERN int TclGlob _ANSI_ARGS_((Tcl_Interp *interp,
1666     char *pattern, char *unquotedPrefix,
1667     int globFlags, GlobTypeData* types));
1668     EXTERN int TclGlobalInvoke _ANSI_ARGS_((Tcl_Interp *interp,
1669     int argc, char **argv, int flags));
1670     EXTERN int TclGuessPackageName _ANSI_ARGS_((char *fileName,
1671     Tcl_DString *bufPtr));
1672     EXTERN int TclHideUnsafeCommands _ANSI_ARGS_((
1673     Tcl_Interp *interp));
1674     EXTERN int TclInExit _ANSI_ARGS_((void));
1675     EXTERN Tcl_Obj * TclIncrElementOfIndexedArray _ANSI_ARGS_((
1676     Tcl_Interp *interp, int localIndex,
1677     Tcl_Obj *elemPtr, long incrAmount));
1678     EXTERN Tcl_Obj * TclIncrIndexedScalar _ANSI_ARGS_((
1679     Tcl_Interp *interp, int localIndex,
1680     long incrAmount));
1681     EXTERN Tcl_Obj * TclIncrVar2 _ANSI_ARGS_((Tcl_Interp *interp,
1682     Tcl_Obj *part1Ptr, Tcl_Obj *part2Ptr,
1683     long incrAmount, int flags));
1684     EXTERN void TclInitAlloc _ANSI_ARGS_((void));
1685     EXTERN void TclInitCompiledLocals _ANSI_ARGS_((
1686     Tcl_Interp *interp, CallFrame *framePtr,
1687     Namespace *nsPtr));
1688     EXTERN void TclInitDbCkalloc _ANSI_ARGS_((void));
1689     EXTERN void TclInitEncodingSubsystem _ANSI_ARGS_((void));
1690     EXTERN void TclInitIOSubsystem _ANSI_ARGS_((void));
1691     EXTERN void TclInitNamespaceSubsystem _ANSI_ARGS_((void));
1692     EXTERN void TclInitNotifier _ANSI_ARGS_((void));
1693     EXTERN void TclInitObjSubsystem _ANSI_ARGS_((void));
1694     EXTERN void TclInitSubsystems _ANSI_ARGS_((CONST char *argv0));
1695     EXTERN int TclInvoke _ANSI_ARGS_((Tcl_Interp *interp,
1696     int argc, char **argv, int flags));
1697     EXTERN int TclInvokeObjectCommand _ANSI_ARGS_((
1698     ClientData clientData, Tcl_Interp *interp,
1699     int argc, char **argv));
1700     EXTERN int TclInvokeStringCommand _ANSI_ARGS_((
1701     ClientData clientData, Tcl_Interp *interp,
1702     int objc, Tcl_Obj *CONST objv[]));
1703     EXTERN int TclIsLocalScalar _ANSI_ARGS_((CONST char *src,
1704     int len));
1705     EXTERN Proc * TclIsProc _ANSI_ARGS_((Command *cmdPtr));
1706     EXTERN Var * TclLookupVar _ANSI_ARGS_((Tcl_Interp *interp,
1707     char *part1, char *part2, int flags, char *msg,
1708     int createPart1, int createPart2,
1709     Var **arrayPtrPtr));
1710     EXTERN int TclMathInProgress _ANSI_ARGS_((void));
1711     EXTERN int TclNeedSpace _ANSI_ARGS_((char *start, char *end));
1712     EXTERN Tcl_Obj * TclNewProcBodyObj _ANSI_ARGS_((Proc *procPtr));
1713     EXTERN int TclObjCommandComplete _ANSI_ARGS_((Tcl_Obj *cmdPtr));
1714     EXTERN int TclObjInterpProc _ANSI_ARGS_((ClientData clientData,
1715     Tcl_Interp *interp, int objc,
1716     Tcl_Obj *CONST objv[]));
1717     EXTERN int TclObjInvoke _ANSI_ARGS_((Tcl_Interp *interp,
1718     int objc, Tcl_Obj *CONST objv[], int flags));
1719     EXTERN int TclObjInvokeGlobal _ANSI_ARGS_((Tcl_Interp *interp,
1720     int objc, Tcl_Obj *CONST objv[], int flags));
1721     EXTERN int TclOpenFileChannelDeleteProc _ANSI_ARGS_((
1722     TclOpenFileChannelProc_ *proc));
1723     EXTERN int TclOpenFileChannelInsertProc _ANSI_ARGS_((
1724     TclOpenFileChannelProc_ *proc));
1725     EXTERN int TclpAccess _ANSI_ARGS_((CONST char *filename,
1726     int mode));
1727     EXTERN char * TclpAlloc _ANSI_ARGS_((unsigned int size));
1728     EXTERN int TclpCheckStackSpace _ANSI_ARGS_((void));
1729     EXTERN int TclpCopyFile _ANSI_ARGS_((CONST char *source,
1730     CONST char *dest));
1731     EXTERN int TclpCopyDirectory _ANSI_ARGS_((CONST char *source,
1732     CONST char *dest, Tcl_DString *errorPtr));
1733     EXTERN int TclpCreateDirectory _ANSI_ARGS_((CONST char *path));
1734     EXTERN int TclpDeleteFile _ANSI_ARGS_((CONST char *path));
1735     EXTERN void TclpExit _ANSI_ARGS_((int status));
1736     EXTERN void TclpFinalizeCondition _ANSI_ARGS_((
1737     Tcl_Condition *condPtr));
1738     EXTERN void TclpFinalizeMutex _ANSI_ARGS_((Tcl_Mutex *mutexPtr));
1739     EXTERN void TclpFinalizeThreadData _ANSI_ARGS_((
1740     Tcl_ThreadDataKey *keyPtr));
1741     EXTERN void TclpFinalizeThreadDataKey _ANSI_ARGS_((
1742     Tcl_ThreadDataKey *keyPtr));
1743     EXTERN char * TclpFindExecutable _ANSI_ARGS_((
1744     CONST char *argv0));
1745     EXTERN int TclpFindVariable _ANSI_ARGS_((CONST char *name,
1746     int *lengthPtr));
1747     EXTERN void TclpFree _ANSI_ARGS_((char *ptr));
1748     EXTERN unsigned long TclpGetClicks _ANSI_ARGS_((void));
1749     EXTERN Tcl_Channel TclpGetDefaultStdChannel _ANSI_ARGS_((int type));
1750     EXTERN unsigned long TclpGetSeconds _ANSI_ARGS_((void));
1751     EXTERN void TclpGetTime _ANSI_ARGS_((Tcl_Time *time));
1752     EXTERN int TclpGetTimeZone _ANSI_ARGS_((unsigned long time));
1753     EXTERN char * TclpGetUserHome _ANSI_ARGS_((CONST char *name,
1754     Tcl_DString *bufferPtr));
1755     EXTERN int TclpHasSockets _ANSI_ARGS_((Tcl_Interp *interp));
1756     EXTERN void TclpInitLibraryPath _ANSI_ARGS_((CONST char *argv0));
1757     EXTERN void TclpInitLock _ANSI_ARGS_((void));
1758     EXTERN void TclpInitPlatform _ANSI_ARGS_((void));
1759     EXTERN void TclpInitUnlock _ANSI_ARGS_((void));
1760     EXTERN int TclpListVolumes _ANSI_ARGS_((Tcl_Interp *interp));
1761     EXTERN void TclpMasterLock _ANSI_ARGS_((void));
1762     EXTERN void TclpMasterUnlock _ANSI_ARGS_((void));
1763     EXTERN int TclpMatchFiles _ANSI_ARGS_((Tcl_Interp *interp,
1764     char *separators, Tcl_DString *dirPtr,
1765     char *pattern, char *tail));
1766     EXTERN Tcl_Channel TclpOpenFileChannel _ANSI_ARGS_((Tcl_Interp *interp,
1767     char *fileName, char *modeString,
1768     int permissions));
1769     EXTERN char * TclpReadlink _ANSI_ARGS_((CONST char *fileName,
1770     Tcl_DString *linkPtr));
1771     EXTERN char * TclpRealloc _ANSI_ARGS_((char *ptr,
1772     unsigned int size));
1773     EXTERN void TclpReleaseFile _ANSI_ARGS_((TclFile file));
1774     EXTERN int TclpRemoveDirectory _ANSI_ARGS_((CONST char *path,
1775     int recursive, Tcl_DString *errorPtr));
1776     EXTERN int TclpRenameFile _ANSI_ARGS_((CONST char *source,
1777     CONST char *dest));
1778     EXTERN void TclpSetInitialEncodings _ANSI_ARGS_((void));
1779     EXTERN void TclpSetVariables _ANSI_ARGS_((Tcl_Interp *interp));
1780     EXTERN VOID * TclpSysAlloc _ANSI_ARGS_((long size, int isBin));
1781     EXTERN void TclpSysFree _ANSI_ARGS_((VOID *ptr));
1782     EXTERN VOID * TclpSysRealloc _ANSI_ARGS_((VOID *cp,
1783     unsigned int size));
1784     EXTERN void TclpUnloadFile _ANSI_ARGS_((ClientData clientData));
1785     EXTERN char * TclPrecTraceProc _ANSI_ARGS_((ClientData clientData,
1786     Tcl_Interp *interp, char *name1, char *name2,
1787     int flags));
1788     EXTERN int TclPreventAliasLoop _ANSI_ARGS_((Tcl_Interp *interp,
1789     Tcl_Interp *cmdInterp, Tcl_Command cmd));
1790     EXTERN void TclProcCleanupProc _ANSI_ARGS_((Proc *procPtr));
1791     EXTERN int TclProcCompileProc _ANSI_ARGS_((Tcl_Interp *interp,
1792     Proc *procPtr, Tcl_Obj *bodyPtr, Namespace *nsPtr,
1793     CONST char *description, CONST char *procName));
1794     EXTERN void TclProcDeleteProc _ANSI_ARGS_((ClientData clientData));
1795     EXTERN int TclProcInterpProc _ANSI_ARGS_((ClientData clientData,
1796     Tcl_Interp *interp, int argc, char **argv));
1797     EXTERN VOID * TclpThreadDataKeyGet _ANSI_ARGS_((
1798     Tcl_ThreadDataKey *keyPtr));
1799     EXTERN void TclpThreadDataKeyInit _ANSI_ARGS_((
1800     Tcl_ThreadDataKey *keyPtr));
1801     EXTERN void TclpThreadDataKeySet _ANSI_ARGS_((
1802     Tcl_ThreadDataKey *keyPtr, VOID *data));
1803     EXTERN void TclpThreadExit _ANSI_ARGS_((int status));
1804     EXTERN void TclRememberCondition _ANSI_ARGS_((Tcl_Condition *mutex));
1805     EXTERN void TclRememberDataKey _ANSI_ARGS_((Tcl_ThreadDataKey *mutex));
1806     EXTERN void TclRememberMutex _ANSI_ARGS_((Tcl_Mutex *mutex));
1807     EXTERN int TclRenameCommand _ANSI_ARGS_((Tcl_Interp *interp,
1808     char *oldName, char *newName)) ;
1809     EXTERN void TclResetShadowedCmdRefs _ANSI_ARGS_((
1810     Tcl_Interp *interp, Command *newCmdPtr));
1811     EXTERN int TclServiceIdle _ANSI_ARGS_((void));
1812     EXTERN Tcl_Obj * TclSetElementOfIndexedArray _ANSI_ARGS_((
1813     Tcl_Interp *interp, int localIndex,
1814     Tcl_Obj *elemPtr, Tcl_Obj *objPtr,
1815     int leaveErrorMsg));
1816     EXTERN Tcl_Obj * TclSetIndexedScalar _ANSI_ARGS_((Tcl_Interp *interp,
1817     int localIndex, Tcl_Obj *objPtr,
1818     int leaveErrorMsg));
1819     EXTERN char * TclSetPreInitScript _ANSI_ARGS_((char *string));
1820     EXTERN void TclSetupEnv _ANSI_ARGS_((Tcl_Interp *interp));
1821     EXTERN int TclSockGetPort _ANSI_ARGS_((Tcl_Interp *interp,
1822     char *string, char *proto, int *portPtr));
1823     EXTERN int TclSockMinimumBuffers _ANSI_ARGS_((int sock,
1824     int size));
1825     EXTERN int TclStat _ANSI_ARGS_((CONST char *path,
1826     struct stat *buf));
1827     EXTERN int TclStatDeleteProc _ANSI_ARGS_((TclStatProc_ *proc));
1828     EXTERN int TclStatInsertProc _ANSI_ARGS_((TclStatProc_ *proc));
1829     EXTERN void TclTeardownNamespace _ANSI_ARGS_((Namespace *nsPtr));
1830     EXTERN void TclTransferResult _ANSI_ARGS_((Tcl_Interp *sourceInterp,
1831     int result, Tcl_Interp *targetInterp));
1832     EXTERN int TclUpdateReturnInfo _ANSI_ARGS_((Interp *iPtr));
1833    
1834     /*
1835     *----------------------------------------------------------------
1836     * Command procedures in the generic core:
1837     *----------------------------------------------------------------
1838     */
1839    
1840     EXTERN int Tcl_AfterObjCmd _ANSI_ARGS_((ClientData clientData,
1841     Tcl_Interp *interp, int objc, Tcl_Obj *CONST objv[]));
1842     EXTERN int Tcl_AppendObjCmd _ANSI_ARGS_((ClientData clientData,
1843     Tcl_Interp *interp, int objc, Tcl_Obj *CONST objv[]));
1844     EXTERN int Tcl_ArrayObjCmd _ANSI_ARGS_((ClientData clientData,
1845     Tcl_Interp *interp, int objc, Tcl_Obj *CONST objv[]));
1846     EXTERN int Tcl_BinaryObjCmd _ANSI_ARGS_((ClientData clientData,
1847     Tcl_Interp *interp, int objc, Tcl_Obj *CONST objv[]));
1848     EXTERN int Tcl_BreakObjCmd _ANSI_ARGS_((ClientData clientData,
1849     Tcl_Interp *interp, int objc, Tcl_Obj *CONST objv[]));
1850     EXTERN int Tcl_CaseObjCmd _ANSI_ARGS_((ClientData clientData,
1851     Tcl_Interp *interp, int objc, Tcl_Obj *CONST objv[]));
1852     EXTERN int Tcl_CatchObjCmd _ANSI_ARGS_((ClientData clientData,
1853     Tcl_Interp *interp, int objc, Tcl_Obj *CONST objv[]));
1854     EXTERN int Tcl_CdObjCmd _ANSI_ARGS_((ClientData clientData,
1855     Tcl_Interp *interp, int objc, Tcl_Obj *CONST objv[]));
1856     EXTERN int Tcl_ClockObjCmd _ANSI_ARGS_((ClientData clientData,
1857     Tcl_Interp *interp, int objc, Tcl_Obj *CONST objv[]));
1858     EXTERN int Tcl_CloseObjCmd _ANSI_ARGS_((ClientData clientData,
1859     Tcl_Interp *interp, int objc, Tcl_Obj *CONST objv[]));
1860     EXTERN int Tcl_ConcatObjCmd _ANSI_ARGS_((ClientData clientData,
1861     Tcl_Interp *interp, int objc, Tcl_Obj *CONST objv[]));
1862     EXTERN int Tcl_ContinueObjCmd _ANSI_ARGS_((ClientData clientData,
1863     Tcl_Interp *interp, int objc, Tcl_Obj *CONST objv[]));
1864     EXTERN int Tcl_EncodingObjCmd _ANSI_ARGS_((ClientData clientData,
1865     Tcl_Interp *interp, int objc, Tcl_Obj *CONST objv[]));
1866     EXTERN int Tcl_EofObjCmd _ANSI_ARGS_((ClientData clientData,
1867     Tcl_Interp *interp, int objc, Tcl_Obj *CONST objv[]));
1868     EXTERN int Tcl_ErrorObjCmd _ANSI_ARGS_((ClientData clientData,
1869     Tcl_Interp *interp, int objc, Tcl_Obj *CONST objv[]));
1870     EXTERN int Tcl_EvalObjCmd _ANSI_ARGS_((ClientData clientData,
1871     Tcl_Interp *interp, int objc, Tcl_Obj *CONST objv[]));
1872     EXTERN int Tcl_ExecObjCmd _ANSI_ARGS_((ClientData clientData,
1873     Tcl_Interp *interp, int objc, Tcl_Obj *CONST objv[]));
1874     EXTERN int Tcl_ExitObjCmd _ANSI_ARGS_((ClientData clientData,
1875     Tcl_Interp *interp, int objc, Tcl_Obj *CONST objv[]));
1876     EXTERN int Tcl_ExprObjCmd _ANSI_ARGS_((ClientData clientData,
1877     Tcl_Interp *interp, int objc, Tcl_Obj *CONST objv[]));
1878     EXTERN int Tcl_FblockedObjCmd _ANSI_ARGS_((ClientData clientData,
1879     Tcl_Interp *interp, int objc, Tcl_Obj *CONST objv[]));
1880     EXTERN int Tcl_FconfigureObjCmd _ANSI_ARGS_((ClientData clientData,
1881     Tcl_Interp *interp, int objc, Tcl_Obj *CONST objv[]));
1882     EXTERN int Tcl_FcopyObjCmd _ANSI_ARGS_((ClientData dummy,
1883     Tcl_Interp *interp, int objc, Tcl_Obj *CONST objv[]));
1884     EXTERN int Tcl_FileObjCmd _ANSI_ARGS_((ClientData dummy,
1885     Tcl_Interp *interp, int objc, Tcl_Obj *CONST objv[]));
1886     EXTERN int Tcl_FileEventObjCmd _ANSI_ARGS_((ClientData clientData,
1887     Tcl_Interp *interp, int objc, Tcl_Obj *CONST objv[]));
1888     EXTERN int Tcl_FlushObjCmd _ANSI_ARGS_((ClientData clientData,
1889     Tcl_Interp *interp, int objc, Tcl_Obj *CONST objv[]));
1890     EXTERN int Tcl_ForObjCmd _ANSI_ARGS_((ClientData clientData,
1891     Tcl_Interp *interp, int objc, Tcl_Obj *CONST objv[]));
1892     EXTERN int Tcl_ForeachObjCmd _ANSI_ARGS_((ClientData clientData,
1893     Tcl_Interp *interp, int objc, Tcl_Obj *CONST objv[]));
1894     EXTERN int Tcl_FormatObjCmd _ANSI_ARGS_((ClientData dummy,
1895     Tcl_Interp *interp, int objc, Tcl_Obj *CONST objv[]));
1896     EXTERN int Tcl_GetsObjCmd _ANSI_ARGS_((ClientData clientData,
1897     Tcl_Interp *interp, int objc, Tcl_Obj *CONST objv[]));
1898     EXTERN int Tcl_GlobalObjCmd _ANSI_ARGS_((ClientData clientData,
1899     Tcl_Interp *interp, int objc, Tcl_Obj *CONST objv[]));
1900     EXTERN int Tcl_GlobObjCmd _ANSI_ARGS_((ClientData clientData,
1901     Tcl_Interp *interp, int objc, Tcl_Obj *CONST objv[]));
1902     EXTERN int Tcl_IfObjCmd _ANSI_ARGS_((ClientData clientData,
1903     Tcl_Interp *interp, int objc, Tcl_Obj *CONST objv[]));
1904     EXTERN int Tcl_IncrObjCmd _ANSI_ARGS_((ClientData clientData,
1905     Tcl_Interp *interp, int objc, Tcl_Obj *CONST objv[]));
1906     EXTERN int Tcl_InfoObjCmd _ANSI_ARGS_((ClientData clientData,
1907     Tcl_Interp *interp, int objc, Tcl_Obj *CONST objv[]));
1908     EXTERN int Tcl_InterpObjCmd _ANSI_ARGS_((ClientData clientData,
1909     Tcl_Interp *interp, int argc, Tcl_Obj *CONST objv[]));
1910     EXTERN int Tcl_JoinObjCmd _ANSI_ARGS_((ClientData clientData,
1911     Tcl_Interp *interp, int objc, Tcl_Obj *CONST objv[]));
1912     EXTERN int Tcl_LappendObjCmd _ANSI_ARGS_((ClientData clientData,
1913     Tcl_Interp *interp, int objc, Tcl_Obj *CONST objv[]));
1914     EXTERN int Tcl_LindexObjCmd _ANSI_ARGS_((ClientData clientData,
1915     Tcl_Interp *interp, int objc, Tcl_Obj *CONST objv[]));
1916     EXTERN int Tcl_LinsertObjCmd _ANSI_ARGS_((ClientData clientData,
1917     Tcl_Interp *interp, int objc, Tcl_Obj *CONST objv[]));
1918     EXTERN int Tcl_LlengthObjCmd _ANSI_ARGS_((ClientData clientData,
1919     Tcl_Interp *interp, int objc, Tcl_Obj *CONST objv[]));
1920     EXTERN int Tcl_ListObjCmd _ANSI_ARGS_((ClientData clientData,
1921     Tcl_Interp *interp, int objc, Tcl_Obj *CONST objv[]));
1922     EXTERN int Tcl_LoadObjCmd _ANSI_ARGS_((ClientData clientData,
1923     Tcl_Interp *interp, int objc, Tcl_Obj *CONST objv[]));
1924     EXTERN int Tcl_LrangeObjCmd _ANSI_ARGS_((ClientData clientData,
1925     Tcl_Interp *interp, int objc, Tcl_Obj *CONST objv[]));
1926     EXTERN int Tcl_LreplaceObjCmd _ANSI_ARGS_((ClientData clientData,
1927     Tcl_Interp *interp, int objc, Tcl_Obj *CONST objv[]));
1928     EXTERN int Tcl_LsearchObjCmd _ANSI_ARGS_((ClientData clientData,
1929     Tcl_Interp *interp, int objc, Tcl_Obj *CONST objv[]));
1930     EXTERN int Tcl_LsortObjCmd _ANSI_ARGS_((ClientData clientData,
1931     Tcl_Interp *interp, int objc, Tcl_Obj *CONST objv[]));
1932     EXTERN int Tcl_NamespaceObjCmd _ANSI_ARGS_((ClientData clientData,
1933     Tcl_Interp *interp, int objc, Tcl_Obj *CONST objv[]));
1934     EXTERN int Tcl_OpenObjCmd _ANSI_ARGS_((ClientData clientData,
1935     Tcl_Interp *interp, int objc, Tcl_Obj *CONST objv[]));
1936     EXTERN int Tcl_PackageObjCmd _ANSI_ARGS_((ClientData clientData,
1937     Tcl_Interp *interp, int objc, Tcl_Obj *CONST objv[]));
1938     EXTERN int Tcl_PidObjCmd _ANSI_ARGS_((ClientData clientData,
1939     Tcl_Interp *interp, int objc, Tcl_Obj *CONST objv[]));
1940     EXTERN int Tcl_PutsObjCmd _ANSI_ARGS_((ClientData clientData,
1941     Tcl_Interp *interp, int objc, Tcl_Obj *CONST objv[]));
1942     EXTERN int Tcl_PwdObjCmd _ANSI_ARGS_((ClientData clientData,
1943     Tcl_Interp *interp, int objc, Tcl_Obj *CONST objv[]));
1944     EXTERN int Tcl_ReadObjCmd _ANSI_ARGS_((ClientData clientData,
1945     Tcl_Interp *interp, int objc, Tcl_Obj *CONST objv[]));
1946     EXTERN int Tcl_RegexpObjCmd _ANSI_ARGS_((ClientData clientData,
1947     Tcl_Interp *interp, int objc, Tcl_Obj *CONST objv[]));
1948     EXTERN int Tcl_RegsubObjCmd _ANSI_ARGS_((ClientData clientData,
1949     Tcl_Interp *interp, int objc, Tcl_Obj *CONST objv[]));
1950     EXTERN int Tcl_RenameObjCmd _ANSI_ARGS_((ClientData clientData,
1951     Tcl_Interp *interp, int objc, Tcl_Obj *CONST objv[]));
1952     EXTERN int Tcl_ReturnObjCmd _ANSI_ARGS_((ClientData clientData,
1953     Tcl_Interp *interp, int objc, Tcl_Obj *CONST objv[]));
1954     EXTERN int Tcl_ScanObjCmd _ANSI_ARGS_((ClientData clientData,
1955     Tcl_Interp *interp, int objc, Tcl_Obj *CONST objv[]));
1956     EXTERN int Tcl_SeekObjCmd _ANSI_ARGS_((ClientData clientData,
1957     Tcl_Interp *interp, int objc, Tcl_Obj *CONST objv[]));
1958     EXTERN int Tcl_SetObjCmd _ANSI_ARGS_((ClientData clientData,
1959     Tcl_Interp *interp, int objc, Tcl_Obj *CONST objv[]));
1960     EXTERN int Tcl_SplitObjCmd _ANSI_ARGS_((ClientData clientData,
1961     Tcl_Interp *interp, int objc, Tcl_Obj *CONST objv[]));
1962     EXTERN int Tcl_SocketObjCmd _ANSI_ARGS_((ClientData clientData,
1963     Tcl_Interp *interp, int objc, Tcl_Obj *CONST objv[]));
1964     EXTERN int Tcl_SourceObjCmd _ANSI_ARGS_((ClientData clientData,
1965     Tcl_Interp *interp, int objc, Tcl_Obj *CONST objv[]));
1966     EXTERN int Tcl_StringObjCmd _ANSI_ARGS_((ClientData clientData,
1967     Tcl_Interp *interp, int objc, Tcl_Obj *CONST objv[]));
1968     EXTERN int Tcl_SubstObjCmd _ANSI_ARGS_((ClientData clientData,
1969     Tcl_Interp *interp, int objc, Tcl_Obj *CONST objv[]));
1970     EXTERN int Tcl_SwitchObjCmd _ANSI_ARGS_((ClientData clientData,
1971     Tcl_Interp *interp, int objc, Tcl_Obj *CONST objv[]));
1972     EXTERN int Tcl_TellObjCmd _ANSI_ARGS_((ClientData clientData,
1973     Tcl_Interp *interp, int objc, Tcl_Obj *CONST objv[]));
1974     EXTERN int Tcl_TimeObjCmd _ANSI_ARGS_((ClientData clientData,
1975     Tcl_Interp *interp, int objc, Tcl_Obj *CONST objv[]));
1976     EXTERN int Tcl_TraceObjCmd _ANSI_ARGS_((ClientData clientData,
1977     Tcl_Interp *interp, int objc, Tcl_Obj *CONST objv[]));
1978     EXTERN int Tcl_UnsetObjCmd _ANSI_ARGS_((ClientData clientData,
1979     Tcl_Interp *interp, int objc, Tcl_Obj *CONST objv[]));
1980     EXTERN int Tcl_UpdateObjCmd _ANSI_ARGS_((ClientData clientData,
1981     Tcl_Interp *interp, int objc, Tcl_Obj *CONST objv[]));
1982     EXTERN int Tcl_UplevelObjCmd _ANSI_ARGS_((ClientData clientData,
1983     Tcl_Interp *interp, int objc, Tcl_Obj *CONST objv[]));
1984     EXTERN int Tcl_UpvarObjCmd _ANSI_ARGS_((ClientData clientData,
1985     Tcl_Interp *interp, int objc, Tcl_Obj *CONST objv[]));
1986     EXTERN int Tcl_VariableObjCmd _ANSI_ARGS_((ClientData clientData,
1987     Tcl_Interp *interp, int objc, Tcl_Obj *CONST objv[]));
1988     EXTERN int Tcl_VwaitObjCmd _ANSI_ARGS_((ClientData clientData,
1989     Tcl_Interp *interp, int objc, Tcl_Obj *CONST objv[]));
1990     EXTERN int Tcl_WhileObjCmd _ANSI_ARGS_((ClientData clientData,
1991     Tcl_Interp *interp, int objc, Tcl_Obj *CONST objv[]));
1992    
1993     /*
1994     *----------------------------------------------------------------
1995     * Command procedures found only in the Mac version of the core:
1996     *----------------------------------------------------------------
1997     */
1998    
1999     #ifdef MAC_TCL
2000     EXTERN int Tcl_EchoCmd _ANSI_ARGS_((ClientData clientData,
2001     Tcl_Interp *interp, int argc, char **argv));
2002     EXTERN int Tcl_LsObjCmd _ANSI_ARGS_((ClientData clientData,
2003     Tcl_Interp *interp, int objc, Tcl_Obj *CONST objv[]));
2004     EXTERN int Tcl_BeepObjCmd _ANSI_ARGS_((ClientData clientData,
2005     Tcl_Interp *interp, int objc, Tcl_Obj *CONST objv[]));
2006     EXTERN int Tcl_MacSourceObjCmd _ANSI_ARGS_((ClientData clientData,
2007     Tcl_Interp *interp, int objc, Tcl_Obj *CONST objv[]));
2008     EXTERN int Tcl_ResourceObjCmd _ANSI_ARGS_((ClientData clientData,
2009     Tcl_Interp *interp, int objc, Tcl_Obj *CONST objv[]));
2010     #endif
2011    
2012     /*
2013     *----------------------------------------------------------------
2014     * Compilation procedures for commands in the generic core:
2015     *----------------------------------------------------------------
2016     */
2017    
2018     EXTERN int TclCompileBreakCmd _ANSI_ARGS_((Tcl_Interp *interp,
2019     Tcl_Parse *parsePtr, struct CompileEnv *envPtr));
2020     EXTERN int TclCompileCatchCmd _ANSI_ARGS_((Tcl_Interp *interp,
2021     Tcl_Parse *parsePtr, struct CompileEnv *envPtr));
2022     EXTERN int TclCompileContinueCmd _ANSI_ARGS_((Tcl_Interp *interp,
2023     Tcl_Parse *parsePtr, struct CompileEnv *envPtr));
2024     EXTERN int TclCompileExprCmd _ANSI_ARGS_((Tcl_Interp *interp,
2025     Tcl_Parse *parsePtr, struct CompileEnv *envPtr));
2026     EXTERN int TclCompileForCmd _ANSI_ARGS_((Tcl_Interp *interp,
2027     Tcl_Parse *parsePtr, struct CompileEnv *envPtr));
2028     EXTERN int TclCompileForeachCmd _ANSI_ARGS_((Tcl_Interp *interp,
2029     Tcl_Parse *parsePtr, struct CompileEnv *envPtr));
2030     EXTERN int TclCompileIfCmd _ANSI_ARGS_((Tcl_Interp *interp,
2031     Tcl_Parse *parsePtr, struct CompileEnv *envPtr));
2032     EXTERN int TclCompileIncrCmd _ANSI_ARGS_((Tcl_Interp *interp,
2033     Tcl_Parse *parsePtr, struct CompileEnv *envPtr));
2034     EXTERN int TclCompileSetCmd _ANSI_ARGS_((Tcl_Interp *interp,
2035     Tcl_Parse *parsePtr, struct CompileEnv *envPtr));
2036     EXTERN int TclCompileWhileCmd _ANSI_ARGS_((Tcl_Interp *interp,
2037     Tcl_Parse *parsePtr, struct CompileEnv *envPtr));
2038    
2039     /*
2040     *----------------------------------------------------------------
2041     * Macros used by the Tcl core to create and release Tcl objects.
2042     * TclNewObj(objPtr) creates a new object denoting an empty string.
2043     * TclDecrRefCount(objPtr) decrements the object's reference count,
2044     * and frees the object if its reference count is zero.
2045     * These macros are inline versions of Tcl_NewObj() and
2046     * Tcl_DecrRefCount(). Notice that the names differ in not having
2047     * a "_" after the "Tcl". Notice also that these macros reference
2048     * their argument more than once, so you should avoid calling them
2049     * with an expression that is expensive to compute or has
2050     * side effects. The ANSI C "prototypes" for these macros are:
2051     *
2052     * EXTERN void TclNewObj _ANSI_ARGS_((Tcl_Obj *objPtr));
2053     * EXTERN void TclDecrRefCount _ANSI_ARGS_((Tcl_Obj *objPtr));
2054     *----------------------------------------------------------------
2055     */
2056    
2057     #ifdef TCL_COMPILE_STATS
2058     # define TclIncrObjsAllocated() \
2059     tclObjsAlloced++
2060     # define TclIncrObjsFreed() \
2061     tclObjsFreed++
2062     #else
2063     # define TclIncrObjsAllocated()
2064     # define TclIncrObjsFreed()
2065     #endif /* TCL_COMPILE_STATS */
2066    
2067     #ifdef TCL_MEM_DEBUG
2068     # define TclNewObj(objPtr) \
2069     (objPtr) = (Tcl_Obj *) \
2070     Tcl_DbCkalloc(sizeof(Tcl_Obj), __FILE__, __LINE__); \
2071     (objPtr)->refCount = 0; \
2072     (objPtr)->bytes = tclEmptyStringRep; \
2073     (objPtr)->length = 0; \
2074     (objPtr)->typePtr = NULL; \
2075     TclIncrObjsAllocated()
2076    
2077     # define TclDbNewObj(objPtr, file, line) \
2078     (objPtr) = (Tcl_Obj *) Tcl_DbCkalloc(sizeof(Tcl_Obj), (file), (line)); \
2079     (objPtr)->refCount = 0; \
2080     (objPtr)->bytes = tclEmptyStringRep; \
2081     (objPtr)->length = 0; \
2082     (objPtr)->typePtr = NULL; \
2083     TclIncrObjsAllocated()
2084    
2085     # define TclDecrRefCount(objPtr) \
2086     if (--(objPtr)->refCount <= 0) { \
2087     if ((objPtr)->refCount < -1) \
2088     panic("Reference count for %lx was negative: %s line %d", \
2089     (objPtr), __FILE__, __LINE__); \
2090     if (((objPtr)->bytes != NULL) \
2091     && ((objPtr)->bytes != tclEmptyStringRep)) { \
2092     ckfree((char *) (objPtr)->bytes); \
2093     } \
2094     if (((objPtr)->typePtr != NULL) \
2095     && ((objPtr)->typePtr->freeIntRepProc != NULL)) { \
2096     (objPtr)->typePtr->freeIntRepProc(objPtr); \
2097     } \
2098     ckfree((char *) (objPtr)); \
2099     TclIncrObjsFreed(); \
2100     }
2101    
2102     #else /* not TCL_MEM_DEBUG */
2103    
2104     #ifdef TCL_THREADS
2105     extern Tcl_Mutex tclObjMutex;
2106     #endif
2107    
2108     # define TclNewObj(objPtr) \
2109     Tcl_MutexLock(&tclObjMutex); \
2110     if (tclFreeObjList == NULL) { \
2111     TclAllocateFreeObjects(); \
2112     } \
2113     (objPtr) = tclFreeObjList; \
2114     tclFreeObjList = (Tcl_Obj *) \
2115     tclFreeObjList->internalRep.otherValuePtr; \
2116     (objPtr)->refCount = 0; \
2117     (objPtr)->bytes = tclEmptyStringRep; \
2118     (objPtr)->length = 0; \
2119     (objPtr)->typePtr = NULL; \
2120     TclIncrObjsAllocated(); \
2121     Tcl_MutexUnlock(&tclObjMutex)
2122    
2123     # define TclDecrRefCount(objPtr) \
2124     if (--(objPtr)->refCount <= 0) { \
2125     if (((objPtr)->bytes != NULL) \
2126     && ((objPtr)->bytes != tclEmptyStringRep)) { \
2127     ckfree((char *) (objPtr)->bytes); \
2128     } \
2129     if (((objPtr)->typePtr != NULL) \
2130     && ((objPtr)->typePtr->freeIntRepProc != NULL)) { \
2131     (objPtr)->typePtr->freeIntRepProc(objPtr); \
2132     } \
2133     Tcl_MutexLock(&tclObjMutex); \
2134     (objPtr)->internalRep.otherValuePtr = (VOID *) tclFreeObjList; \
2135     tclFreeObjList = (objPtr); \
2136     TclIncrObjsFreed(); \
2137     Tcl_MutexUnlock(&tclObjMutex); \
2138     }
2139     #endif /* TCL_MEM_DEBUG */
2140    
2141     /*
2142     *----------------------------------------------------------------
2143     * Macro used by the Tcl core to set a Tcl_Obj's string representation
2144     * to a copy of the "len" bytes starting at "bytePtr". This code
2145     * works even if the byte array contains NULLs as long as the length
2146     * is correct. Because "len" is referenced multiple times, it should
2147     * be as simple an expression as possible. The ANSI C "prototype" for
2148     * this macro is:
2149     *
2150     * EXTERN void TclInitStringRep _ANSI_ARGS_((Tcl_Obj *objPtr,
2151     * char *bytePtr, int len));
2152     *----------------------------------------------------------------
2153     */
2154    
2155     #define TclInitStringRep(objPtr, bytePtr, len) \
2156     if ((len) == 0) { \
2157     (objPtr)->bytes = tclEmptyStringRep; \
2158     (objPtr)->length = 0; \
2159     } else { \
2160     (objPtr)->bytes = (char *) ckalloc((unsigned) ((len) + 1)); \
2161     memcpy((VOID *) (objPtr)->bytes, (VOID *) (bytePtr), \
2162     (unsigned) (len)); \
2163     (objPtr)->bytes[len] = '\0'; \
2164     (objPtr)->length = (len); \
2165     }
2166    
2167     /*
2168     *----------------------------------------------------------------
2169     * Macro used by the Tcl core to get the string representation's
2170     * byte array pointer from a Tcl_Obj. This is an inline version
2171     * of Tcl_GetString(). The macro's expression result is the string
2172     * rep's byte pointer which might be NULL. The bytes referenced by
2173     * this pointer must not be modified by the caller.
2174     * The ANSI C "prototype" for this macro is:
2175     *
2176     * EXTERN char * TclGetString _ANSI_ARGS_((Tcl_Obj *objPtr));
2177     *----------------------------------------------------------------
2178     */
2179    
2180     #define TclGetString(objPtr) \
2181     ((objPtr)->bytes? (objPtr)->bytes : Tcl_GetString((objPtr)))
2182    
2183     #include "tclIntDecls.h"
2184    
2185     # undef TCL_STORAGE_CLASS
2186     # define TCL_STORAGE_CLASS DLLIMPORT
2187    
2188     #endif /* _TCLINT */
2189    
2190     /* End of tclint.h */

Properties

Name Value
svn:eol-style native
svn:keywords Header

dashley@gmail.com
ViewVC Help
Powered by ViewVC 1.1.25