/[dtapublic]/to_be_filed/sf_code/esrgpcpj/shared/tcl_base/tclint.h
ViewVC logotype

Annotation of /to_be_filed/sf_code/esrgpcpj/shared/tcl_base/tclint.h

Parent Directory Parent Directory | Revision Log Revision Log


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

dashley@gmail.com
ViewVC Help
Powered by ViewVC 1.1.25