Planet
navi homePPSaboutscreenshotsdownloaddevelopmentforum

source: data/media/tcl8.5/init.tcl @ 5582

Last change on this file since 5582 was 5582, checked in by landauf, 15 years ago

small fix (and a future feature) in init.tcl (for now just v8.5, it doesn't matter anyway)

  • Property svn:eol-style set to native
File size: 26.4 KB
Line 
1# init.tcl --
2#
3# Default system startup file for Tcl-based applications.  Defines
4# "unknown" procedure and auto-load facilities.
5#
6# RCS: @(#) $Id: init.tcl,v 1.104 2008/03/28 17:31:44 dgp Exp $
7#
8# Copyright (c) 1991-1993 The Regents of the University of California.
9# Copyright (c) 1994-1996 Sun Microsystems, Inc.
10# Copyright (c) 1998-1999 Scriptics Corporation.
11# Copyright (c) 2004 by Kevin B. Kenny.  All rights reserved.
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
17if {[info commands package] == ""} {
18    error "version mismatch: library\nscripts expect Tcl version 7.5b1 or later but the loaded version is\nonly [info patchlevel]"
19}
20package require -exact Tcl 8.5.2
21
22# Compute the auto path to use in this interpreter.
23# The values on the path come from several locations:
24#
25# The environment variable TCLLIBPATH
26#
27# tcl_library, which is the directory containing this init.tcl script.
28# [tclInit] (Tcl_Init()) searches around for the directory containing this
29# init.tcl and defines tcl_library to that location before sourcing it.
30#
31# The parent directory of tcl_library. Adding the parent
32# means that packages in peer directories will be found automatically.
33#
34# Also add the directory ../lib relative to the directory where the
35# executable is located.  This is meant to find binary packages for the
36# same architecture as the current executable.
37#
38# tcl_pkgPath, which is set by the platform-specific initialization routines
39#       On UNIX it is compiled in
40#       On Windows, it is not used
41
42if {![info exists auto_path]} {
43    if {[info exists env(TCLLIBPATH)]} {
44        set auto_path $env(TCLLIBPATH)
45    } else {
46        set auto_path ""
47    }
48}
49namespace eval tcl {
50    variable Dir
51    foreach Dir [list $::tcl_library [file dirname $::tcl_library]] {
52        if {$Dir ni $::auto_path} {
53            lappend ::auto_path $Dir
54        }
55    }
56    set Dir [file join [file dirname [file dirname \
57            [info nameofexecutable]]] lib]
58    if {$Dir ni $::auto_path} {
59        lappend ::auto_path $Dir
60    }
61    catch {
62        foreach Dir $::tcl_pkgPath {
63            if {$Dir ni $::auto_path} {
64                lappend ::auto_path $Dir
65            }
66        }
67    }
68
69    if {![interp issafe]} {
70        variable Path [encoding dirs]
71        set Dir [file join $::tcl_library encoding]
72        if {$Dir ni $Path} {
73            lappend Path $Dir
74            encoding dirs $Path
75        }
76    }
77
78    # TIP #255 min and max functions
79    namespace eval mathfunc {
80        proc min {args} {
81            if {[llength $args] == 0} {
82                return -code error \
83                    "too few arguments to math function \"min\""
84            }
85            set val Inf
86            foreach arg $args {
87                # This will handle forcing the numeric value without
88                # ruining the internal type of a numeric object
89                if {[catch {expr {double($arg)}} err]} {
90                    return -code error $err
91                }
92                if {$arg < $val} { set val $arg }
93            }
94            return $val
95        }
96        proc max {args} {
97            if {[llength $args] == 0} {
98                return -code error \
99                    "too few arguments to math function \"max\""
100            }
101            set val -Inf
102            foreach arg $args {
103                # This will handle forcing the numeric value without
104                # ruining the internal type of a numeric object
105                if {[catch {expr {double($arg)}} err]} {
106                    return -code error $err
107                }
108                if {$arg > $val} { set val $arg }
109            }
110            return $val
111        }
112    }
113}
114
115# Windows specific end of initialization
116
117if {(![interp issafe]) && ($tcl_platform(platform) eq "windows")} {
118    namespace eval tcl {
119        proc EnvTraceProc {lo n1 n2 op} {
120            set x $::env($n2)
121            set ::env($lo) $x
122            set ::env([string toupper $lo]) $x
123        }
124        proc InitWinEnv {} {
125            global env tcl_platform
126            foreach p [array names env] {
127                set u [string toupper $p]
128                if {$u ne $p} {
129                    switch -- $u {
130                        COMSPEC -
131                        PATH {
132                            if {![info exists env($u)]} {
133                                set env($u) $env($p)
134                            }
135                            trace add variable env($p) write \
136                                    [namespace code [list EnvTraceProc $p]]
137                            trace add variable env($u) write \
138                                    [namespace code [list EnvTraceProc $p]]
139                        }
140                    }
141                }
142            }
143            if {![info exists env(COMSPEC)]} {
144                if {$tcl_platform(os) eq "Windows NT"} {
145                    set env(COMSPEC) cmd.exe
146                } else {
147                    set env(COMSPEC) command.com
148                }
149            }
150        }
151        InitWinEnv
152    }
153}
154
155# Setup the unknown package handler
156
157
158if {[interp issafe]} {
159    package unknown ::tclPkgUnknown
160} else {
161    # Set up search for Tcl Modules (TIP #189).
162    # and setup platform specific unknown package handlers
163    if {$::tcl_platform(os) eq "Darwin"
164            && $::tcl_platform(platform) eq "unix"} {
165        package unknown {::tcl::tm::UnknownHandler \
166                {::tcl::MacOSXPkgUnknown ::tclPkgUnknown}}
167    } else {
168        package unknown {::tcl::tm::UnknownHandler ::tclPkgUnknown}
169    }
170
171    # Set up the 'clock' ensemble
172
173    namespace eval ::tcl::clock [list variable TclLibDir $::tcl_library]
174
175    proc clock args {
176        namespace eval ::tcl::clock [list namespace ensemble create -command \
177                [uplevel 1 [list namespace origin [lindex [info level 0] 0]]] \
178                -subcommands {
179                    add clicks format microseconds milliseconds scan seconds
180                }]
181       
182        # Auto-loading stubs for 'clock.tcl'
183       
184        foreach cmd {add format scan} {
185            proc ::tcl::clock::$cmd args {
186                variable TclLibDir
187                source -encoding utf-8 [file join $TclLibDir clock.tcl]
188                return [uplevel 1 [info level 0]]
189            }
190        }
191
192        return [uplevel 1 [info level 0]]
193    }
194}
195
196# Conditionalize for presence of exec.
197
198if {[namespace which -command exec] eq ""} {
199
200    # Some machines do not have exec. Also, on all
201    # platforms, safe interpreters do not have exec.
202
203    set auto_noexec 1
204}
205
206# Define a log command (which can be overwitten to log errors
207# differently, specially when stderr is not available)
208
209if {[namespace which -command tclLog] eq ""} {
210    proc tclLog {string} {
211        catch {puts stderr $string}
212    }
213}
214
215# query --
216# Sends a query to the CommandExecutor of Orxonox and
217# waits for the response.
218# This procedure will be changed to it's real function
219# by Orxonox itself.
220#
221# Arguments:
222# args - The command to send to Orxonox
223
224proc query args {
225    return -code error "Can't query Orxonox now"
226}
227
228# crossquery --
229# Sends a query to another Tcl-interpreter in Orxonox and
230# waits for the response.
231# This procedure will be changed to it's real function
232# by Orxonox itself.
233#
234# Arguments:
235# id   - The ID of the other interpreter
236# args - The command to send to Orxonox
237
238proc crossquery {id args} {
239    return -code error "Can't query interpreter with ID $id now"
240}
241
242# execute --
243# This procedure will be changed by Orxonox itself.
244# execute calls a command in Orxonox.
245#
246# Arguments:
247# args - The command
248
249proc execute args {
250}
251
252# crossexecute --
253# This procedure will be changed by Orxonox itself.
254# Sends a command to another Tcl-interpreter in Orxonox.
255#
256# Arguments:
257# id   - The ID of the other interpreter
258# args - The command
259
260proc crossexecute {id args} {
261}
262
263# redef_puts --
264# Redefines puts to write directly into the Orxonox console
265# if the channel is stdout or stderr.
266
267proc redef_puts {} {
268    if ![llength [info command ::tcl::puts]] {
269        rename puts ::tcl::puts
270        proc puts args {
271            set la [llength $args]
272            if {$la<1 || $la>3} {
273                error "usage: puts ?-nonewline? ?channel? string"
274            }
275            set nl \n
276            if {[lindex $args 0]=="-nonewline"} {
277                set nl ""
278                set args [lrange $args 1 end]
279            }
280            if {[llength $args]==1} {
281                set args [list stdout [join $args]] ;
282            }
283            foreach {channel s} $args break
284            if {$channel=="stdout" || $channel=="stderr"} {
285                set cmd "execute puts"
286                if {$nl==""} {lappend cmd 0} else {lappend cmd 1}
287                lappend cmd $s
288                eval $cmd
289            } else {
290                set cmd ::tcl::puts
291                if {$nl==""} {lappend cmd -nonewline}
292                lappend cmd $channel $s
293                eval $cmd
294            }
295        }
296    }
297}
298
299# unknown --
300# This procedure is called when a Tcl command is invoked that doesn't
301# exist in the interpreter.  It takes the following steps to make the
302# command available:
303#
304#       1. See if the command has the form "namespace inscope ns cmd" and
305#          if so, concatenate its arguments onto the end and evaluate it.
306#       2. See if the autoload facility can locate the command in a
307#          Tcl script file.  If so, load it and execute it.
308#       3. If the command was invoked interactively at top-level:
309#           (a) see if the command exists as an executable UNIX program.
310#               If so, "exec" the command.
311#           (b) see if the command requests csh-like history substitution
312#               in one of the common forms !!, !<number>, or ^old^new.  If
313#               so, emulate csh's history substitution.
314#           (c) see if the command is a unique abbreviation for another
315#               command.  If so, invoke the command.
316#
317# Arguments:
318# args -        A list whose elements are the words of the original
319#               command, including the command name.
320
321proc unknown args {
322    variable ::tcl::UnknownPending
323    global auto_noexec auto_noload env tcl_interactive
324
325    # If the command word has the form "namespace inscope ns cmd"
326    # then concatenate its arguments onto the end and evaluate it.
327
328    set cmd [lindex $args 0]
329    if {[regexp "^:*namespace\[ \t\n\]+inscope" $cmd] && [llength $cmd] == 4} {
330        #return -code error "You need an {*}"
331        set arglist [lrange $args 1 end]
332        set ret [catch {uplevel 1 ::$cmd $arglist} result opts]
333        dict unset opts -errorinfo
334        dict incr opts -level
335        return -options $opts $result
336    }
337
338    catch {set savedErrorInfo $::errorInfo}
339    catch {set savedErrorCode $::errorCode}
340    set name $cmd
341    if {![info exists auto_noload]} {
342        #
343        # Make sure we're not trying to load the same proc twice.
344        #
345        if {[info exists UnknownPending($name)]} {
346            return -code error "self-referential recursion\
347                    in \"unknown\" for command \"$name\"";
348        }
349        set UnknownPending($name) pending;
350        set ret [catch {
351                auto_load $name [uplevel 1 {::namespace current}]
352        } msg opts]
353        unset UnknownPending($name);
354        if {$ret != 0} {
355            dict append opts -errorinfo "\n    (autoloading \"$name\")"
356            return -options $opts $msg
357        }
358        if {![array size UnknownPending]} {
359            unset UnknownPending
360        }
361        if {$msg} {
362            catch {set ::errorCode $savedErrorCode}
363            catch {set ::errorInfo $savedErrorInfo}
364            set code [catch {uplevel 1 $args} msg opts]
365            if {$code ==  1} {
366                #
367                # Compute stack trace contribution from the [uplevel].
368                # Note the dependence on how Tcl_AddErrorInfo, etc.
369                # construct the stack trace.
370                #
371                set errorInfo [dict get $opts -errorinfo]
372                set errorCode [dict get $opts -errorcode]
373                set cinfo $args
374                if {[string bytelength $cinfo] > 150} {
375                    set cinfo [string range $cinfo 0 150]
376                    while {[string bytelength $cinfo] > 150} {
377                        set cinfo [string range $cinfo 0 end-1]
378                    }
379                    append cinfo ...
380                }
381                append cinfo "\"\n    (\"uplevel\" body line 1)"
382                append cinfo "\n    invoked from within"
383                append cinfo "\n\"uplevel 1 \$args\""
384                #
385                # Try each possible form of the stack trace
386                # and trim the extra contribution from the matching case
387                #
388                set expect "$msg\n    while executing\n\"$cinfo"
389                if {$errorInfo eq $expect} {
390                    #
391                    # The stack has only the eval from the expanded command
392                    # Do not generate any stack trace here.
393                    #
394                    dict unset opts -errorinfo
395                    dict incr opts -level
396                    return -options $opts $msg
397                }
398                #
399                # Stack trace is nested, trim off just the contribution
400                # from the extra "eval" of $args due to the "catch" above.
401                #
402                set expect "\n    invoked from within\n\"$cinfo"
403                set exlen [string length $expect]
404                set eilen [string length $errorInfo]
405                set i [expr {$eilen - $exlen - 1}]
406                set einfo [string range $errorInfo 0 $i]
407                #
408                # For now verify that $errorInfo consists of what we are about
409                # to return plus what we expected to trim off.
410                #
411                if {$errorInfo ne "$einfo$expect"} {
412                    error "Tcl bug: unexpected stack trace in \"unknown\"" {} \
413                        [list CORE UNKNOWN BADTRACE $einfo $expect $errorInfo]
414                }
415                return -code error -errorcode $errorCode \
416                        -errorinfo $einfo $msg
417            } else {
418                dict incr opts -level
419                return -options $opts $msg
420            }
421        }
422    }
423
424    if {([info level] == 1) && ([info script] eq "") \
425            && [info exists tcl_interactive] && $tcl_interactive} {
426        if {![info exists auto_noexec]} {
427            set new [auto_execok $name]
428            if {$new ne ""} {
429                set redir ""
430                if {[namespace which -command console] eq ""} {
431                    set redir ">&@stdout <@stdin"
432                }
433                uplevel 1 [list ::catch \
434                        [concat exec $redir $new [lrange $args 1 end]] \
435                        ::tcl::UnknownResult ::tcl::UnknownOptions]
436                dict incr ::tcl::UnknownOptions -level
437                return -options $::tcl::UnknownOptions $::tcl::UnknownResult
438            }
439        }
440        if {$name eq "!!"} {
441            set newcmd [history event]
442        } elseif {[regexp {^!(.+)$} $name -> event]} {
443            set newcmd [history event $event]
444        } elseif {[regexp {^\^([^^]*)\^([^^]*)\^?$} $name -> old new]} {
445            set newcmd [history event -1]
446            catch {regsub -all -- $old $newcmd $new newcmd}
447        }
448        if {[info exists newcmd]} {
449            tclLog $newcmd
450            history change $newcmd 0
451            uplevel 1 [list ::catch $newcmd \
452                    ::tcl::UnknownResult ::tcl::UnknownOptions]
453            dict incr ::tcl::UnknownOptions -level
454            return -options $::tcl::UnknownOptions $::tcl::UnknownResult
455        }
456
457        set ret [catch {set candidates [info commands $name*]} msg]
458        if {$name eq "::"} {
459            set name ""
460        }
461        if {$ret != 0} {
462            dict append opts -errorinfo \
463                    "\n    (expanding command prefix \"$name\" in unknown)"
464            return -options $opts $msg
465        }
466        # Filter out bogus matches when $name contained
467        # a glob-special char [Bug 946952]
468        if {$name eq ""} {
469            # Handle empty $name separately due to strangeness
470            # in [string first] (See RFE 1243354)
471            set cmds $candidates
472        } else {
473            set cmds [list]
474            foreach x $candidates {
475                if {[string first $name $x] == 0} {
476                    lappend cmds $x
477                }
478            }
479        }
480        if {[llength $cmds] == 1} {
481            uplevel 1 [list ::catch [lreplace $args 0 0 [lindex $cmds 0]] \
482                    ::tcl::UnknownResult ::tcl::UnknownOptions]
483            dict incr ::tcl::UnknownOptions -level
484            return -options $::tcl::UnknownOptions $::tcl::UnknownResult
485        }
486        if {[llength $cmds]} {
487            return -code error "ambiguous command name \"$name\": [lsort $cmds]"
488        }
489    }
490#    return -code error "invalid command name \"$name\""
491    return [query $args]
492}
493
494# auto_load --
495# Checks a collection of library directories to see if a procedure
496# is defined in one of them.  If so, it sources the appropriate
497# library file to create the procedure.  Returns 1 if it successfully
498# loaded the procedure, 0 otherwise.
499#
500# Arguments:
501# cmd -                 Name of the command to find and load.
502# namespace (optional)  The namespace where the command is being used - must be
503#                       a canonical namespace as returned [namespace current]
504#                       for instance. If not given, namespace current is used.
505
506proc auto_load {cmd {namespace {}}} {
507    global auto_index auto_path
508
509    if {$namespace eq ""} {
510        set namespace [uplevel 1 [list ::namespace current]]
511    }
512    set nameList [auto_qualify $cmd $namespace]
513    # workaround non canonical auto_index entries that might be around
514    # from older auto_mkindex versions
515    lappend nameList $cmd
516    foreach name $nameList {
517        if {[info exists auto_index($name)]} {
518            namespace eval :: $auto_index($name)
519            # There's a couple of ways to look for a command of a given
520            # name.  One is to use
521            #    info commands $name
522            # Unfortunately, if the name has glob-magic chars in it like *
523            # or [], it may not match.  For our purposes here, a better
524            # route is to use
525            #    namespace which -command $name
526            if {[namespace which -command $name] ne ""} {
527                return 1
528            }
529        }
530    }
531    if {![info exists auto_path]} {
532        return 0
533    }
534
535    if {![auto_load_index]} {
536        return 0
537    }
538    foreach name $nameList {
539        if {[info exists auto_index($name)]} {
540            namespace eval :: $auto_index($name)
541            if {[namespace which -command $name] ne ""} {
542                return 1
543            }
544        }
545    }
546    return 0
547}
548
549# auto_load_index --
550# Loads the contents of tclIndex files on the auto_path directory
551# list.  This is usually invoked within auto_load to load the index
552# of available commands.  Returns 1 if the index is loaded, and 0 if
553# the index is already loaded and up to date.
554#
555# Arguments:
556# None.
557
558proc auto_load_index {} {
559    variable ::tcl::auto_oldpath
560    global auto_index auto_path
561
562    if {[info exists auto_oldpath] && ($auto_oldpath eq $auto_path)} {
563        return 0
564    }
565    set auto_oldpath $auto_path
566
567    # Check if we are a safe interpreter. In that case, we support only
568    # newer format tclIndex files.
569
570    set issafe [interp issafe]
571    for {set i [expr {[llength $auto_path] - 1}]} {$i >= 0} {incr i -1} {
572        set dir [lindex $auto_path $i]
573        set f ""
574        if {$issafe} {
575            catch {source [file join $dir tclIndex]}
576        } elseif {[catch {set f [open [file join $dir tclIndex]]}]} {
577            continue
578        } else {
579            set error [catch {
580                set id [gets $f]
581                if {$id eq "# Tcl autoload index file, version 2.0"} {
582                    eval [read $f]
583                } elseif {$id eq "# Tcl autoload index file: each line identifies a Tcl"} {
584                    while {[gets $f line] >= 0} {
585                        if {([string index $line 0] eq "#") \
586                                || ([llength $line] != 2)} {
587                            continue
588                        }
589                        set name [lindex $line 0]
590                        set auto_index($name) \
591                                "source [file join $dir [lindex $line 1]]"
592                    }
593                } else {
594                    error "[file join $dir tclIndex] isn't a proper Tcl index file"
595                }
596            } msg opts]
597            if {$f ne ""} {
598                close $f
599            }
600            if {$error} {
601                return -options $opts $msg
602            }
603        }
604    }
605    return 1
606}
607
608# auto_qualify --
609#
610# Compute a fully qualified names list for use in the auto_index array.
611# For historical reasons, commands in the global namespace do not have leading
612# :: in the index key. The list has two elements when the command name is
613# relative (no leading ::) and the namespace is not the global one. Otherwise
614# only one name is returned (and searched in the auto_index).
615#
616# Arguments -
617# cmd           The command name. Can be any name accepted for command
618#               invocations (Like "foo::::bar").
619# namespace     The namespace where the command is being used - must be
620#               a canonical namespace as returned by [namespace current]
621#               for instance.
622
623proc auto_qualify {cmd namespace} {
624
625    # count separators and clean them up
626    # (making sure that foo:::::bar will be treated as foo::bar)
627    set n [regsub -all {::+} $cmd :: cmd]
628
629    # Ignore namespace if the name starts with ::
630    # Handle special case of only leading ::
631
632    # Before each return case we give an example of which category it is
633    # with the following form :
634    # ( inputCmd, inputNameSpace) -> output
635
636    if {[string match ::* $cmd]} {
637        if {$n > 1} {
638            # ( ::foo::bar , * ) -> ::foo::bar
639            return [list $cmd]
640        } else {
641            # ( ::global , * ) -> global
642            return [list [string range $cmd 2 end]]
643        }
644    }
645   
646    # Potentially returning 2 elements to try  :
647    # (if the current namespace is not the global one)
648
649    if {$n == 0} {
650        if {$namespace eq "::"} {
651            # ( nocolons , :: ) -> nocolons
652            return [list $cmd]
653        } else {
654            # ( nocolons , ::sub ) -> ::sub::nocolons nocolons
655            return [list ${namespace}::$cmd $cmd]
656        }
657    } elseif {$namespace eq "::"} {
658        #  ( foo::bar , :: ) -> ::foo::bar
659        return [list ::$cmd]
660    } else {
661        # ( foo::bar , ::sub ) -> ::sub::foo::bar ::foo::bar
662        return [list ${namespace}::$cmd ::$cmd]
663    }
664}
665
666# auto_import --
667#
668# Invoked during "namespace import" to make see if the imported commands
669# reside in an autoloaded library.  If so, the commands are loaded so
670# that they will be available for the import links.  If not, then this
671# procedure does nothing.
672#
673# Arguments -
674# pattern       The pattern of commands being imported (like "foo::*")
675#               a canonical namespace as returned by [namespace current]
676
677proc auto_import {pattern} {
678    global auto_index
679
680    # If no namespace is specified, this will be an error case
681
682    if {![string match *::* $pattern]} {
683        return
684    }
685
686    set ns [uplevel 1 [list ::namespace current]]
687    set patternList [auto_qualify $pattern $ns]
688
689    auto_load_index
690
691    foreach pattern $patternList {
692        foreach name [array names auto_index $pattern] {
693            if {([namespace which -command $name] eq "")
694                    && ([namespace qualifiers $pattern] eq [namespace qualifiers $name])} {
695                namespace eval :: $auto_index($name)
696            }
697        }
698    }
699}
700
701# auto_execok --
702#
703# Returns string that indicates name of program to execute if
704# name corresponds to a shell builtin or an executable in the
705# Windows search path, or "" otherwise.  Builds an associative
706# array auto_execs that caches information about previous checks,
707# for speed.
708#
709# Arguments:
710# name -                        Name of a command.
711
712if {$tcl_platform(platform) eq "windows"} {
713# Windows version.
714#
715# Note that info executable doesn't work under Windows, so we have to
716# look for files with .exe, .com, or .bat extensions.  Also, the path
717# may be in the Path or PATH environment variables, and path
718# components are separated with semicolons, not colons as under Unix.
719#
720proc auto_execok name {
721    global auto_execs env tcl_platform
722
723    if {[info exists auto_execs($name)]} {
724        return $auto_execs($name)
725    }
726    set auto_execs($name) ""
727
728    set shellBuiltins [list cls copy date del erase dir echo mkdir \
729            md rename ren rmdir rd time type ver vol]
730    if {$tcl_platform(os) eq "Windows NT"} {
731        # NT includes the 'start' built-in
732        lappend shellBuiltins "start"
733    }
734    if {[info exists env(PATHEXT)]} {
735        # Add an initial ; to have the {} extension check first.
736        set execExtensions [split ";$env(PATHEXT)" ";"]
737    } else {
738        set execExtensions [list {} .com .exe .bat]
739    }
740
741    if {$name in $shellBuiltins} {
742        # When this is command.com for some reason on Win2K, Tcl won't
743        # exec it unless the case is right, which this corrects.  COMSPEC
744        # may not point to a real file, so do the check.
745        set cmd $env(COMSPEC)
746        if {[file exists $cmd]} {
747            set cmd [file attributes $cmd -shortname]
748        }
749        return [set auto_execs($name) [list $cmd /c $name]]
750    }
751
752    if {[llength [file split $name]] != 1} {
753        foreach ext $execExtensions {
754            set file ${name}${ext}
755            if {[file exists $file] && ![file isdirectory $file]} {
756                return [set auto_execs($name) [list $file]]
757            }
758        }
759        return ""
760    }
761
762    set path "[file dirname [info nameof]];.;"
763    if {[info exists env(WINDIR)]} {
764        set windir $env(WINDIR) 
765    }
766    if {[info exists windir]} {
767        if {$tcl_platform(os) eq "Windows NT"} {
768            append path "$windir/system32;"
769        }
770        append path "$windir/system;$windir;"
771    }
772
773    foreach var {PATH Path path} {
774        if {[info exists env($var)]} {
775            append path ";$env($var)"
776        }
777    }
778
779    foreach dir [split $path {;}] {
780        # Skip already checked directories
781        if {[info exists checked($dir)] || ($dir eq {})} { continue }
782        set checked($dir) {}
783        foreach ext $execExtensions {
784            set file [file join $dir ${name}${ext}]
785            if {[file exists $file] && ![file isdirectory $file]} {
786                return [set auto_execs($name) [list $file]]
787            }
788        }
789    }
790    return ""
791}
792
793} else {
794# Unix version.
795#
796proc auto_execok name {
797    global auto_execs env
798
799    if {[info exists auto_execs($name)]} {
800        return $auto_execs($name)
801    }
802    set auto_execs($name) ""
803    if {[llength [file split $name]] != 1} {
804        if {[file executable $name] && ![file isdirectory $name]} {
805            set auto_execs($name) [list $name]
806        }
807        return $auto_execs($name)
808    }
809    foreach dir [split $env(PATH) :] {
810        if {$dir eq ""} {
811            set dir .
812        }
813        set file [file join $dir $name]
814        if {[file executable $file] && ![file isdirectory $file]} {
815            set auto_execs($name) [list $file]
816            return $auto_execs($name)
817        }
818    }
819    return ""
820}
821
822}
823
824# ::tcl::CopyDirectory --
825#
826# This procedure is called by Tcl's core when attempts to call the
827# filesystem's copydirectory function fail.  The semantics of the call
828# are that 'dest' does not yet exist, i.e. dest should become the exact
829# image of src.  If dest does exist, we throw an error. 
830#
831# Note that making changes to this procedure can change the results
832# of running Tcl's tests.
833#
834# Arguments:
835# action -              "renaming" or "copying"
836# src -                 source directory
837# dest -                destination directory
838proc tcl::CopyDirectory {action src dest} {
839    set nsrc [file normalize $src]
840    set ndest [file normalize $dest]
841
842    if {$action eq "renaming"} {
843        # Can't rename volumes.  We could give a more precise
844        # error message here, but that would break the test suite.
845        if {$nsrc in [file volumes]} {
846            return -code error "error $action \"$src\" to\
847              \"$dest\": trying to rename a volume or move a directory\
848              into itself"
849        }
850    }
851    if {[file exists $dest]} {
852        if {$nsrc eq $ndest} {
853            return -code error "error $action \"$src\" to\
854              \"$dest\": trying to rename a volume or move a directory\
855              into itself"
856        }
857        if {$action eq "copying"} {
858            # We used to throw an error here, but, looking more closely
859            # at the core copy code in tclFCmd.c, if the destination
860            # exists, then we should only call this function if -force
861            # is true, which means we just want to over-write.  So,
862            # the following code is now commented out.
863            #
864            # return -code error "error $action \"$src\" to\
865            # \"$dest\": file already exists"
866        } else {
867            # Depending on the platform, and on the current
868            # working directory, the directories '.', '..'
869            # can be returned in various combinations.  Anyway,
870            # if any other file is returned, we must signal an error.
871            set existing [glob -nocomplain -directory $dest * .*]
872            lappend existing {*}[glob -nocomplain -directory $dest \
873                    -type hidden * .*]
874            foreach s $existing {
875                if {([file tail $s] ne ".") && ([file tail $s] ne "..")} {
876                    return -code error "error $action \"$src\" to\
877                      \"$dest\": file already exists"
878                }
879            }
880        }
881    } else {
882        if {[string first $nsrc $ndest] != -1} {
883            set srclen [expr {[llength [file split $nsrc]] -1}]
884            set ndest [lindex [file split $ndest] $srclen]
885            if {$ndest eq [file tail $nsrc]} {
886                return -code error "error $action \"$src\" to\
887                  \"$dest\": trying to rename a volume or move a directory\
888                  into itself"
889            }
890        }
891        file mkdir $dest
892    }
893    # Have to be careful to capture both visible and hidden files.
894    # We will also be more generous to the file system and not
895    # assume the hidden and non-hidden lists are non-overlapping.
896    #
897    # On Unix 'hidden' files begin with '.'.  On other platforms
898    # or filesystems hidden files may have other interpretations.
899    set filelist [concat [glob -nocomplain -directory $src *] \
900      [glob -nocomplain -directory $src -types hidden *]]
901
902    foreach s [lsort -unique $filelist] {
903        if {([file tail $s] ne ".") && ([file tail $s] ne "..")} {
904            file copy -force $s [file join $dest [file tail $s]]
905        }
906    }
907    return
908}
Note: See TracBrowser for help on using the repository browser.