OSDN Git Service

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