123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173174175176177178179180181182183184185186187188189190191192193194195196197198199200201202203204205206207208209210211212213214215216217218219220221222223224225226227228229230231232233234235236237238239240241242243244245246247248249250251252253254255256257258259260261262263264265266267268269270271272273274275276277278279280281282283284285286287288289290291292293294295296297298299300301302303304305306307308309310311312313314315316317318319320321322323324325326327328329330331332333334335336337338339340341342343344345346347348349350351352353354355356357358359360361362363364365366367368369370371372373374375376377378379380381382383384385386387388389390391392393394395396397398399400401402403404405406407408409410411412413414415416417418419420421422423424425426427428429430431432433434435436437438439440441442443444445446447448449450451452453454455456457458459460461462463464465466467468469470471472473474475476477478479480481482483484485486487488489490491492493494495496497498499500501502503504505506507508509510511512513514515516517518519520521522523524525526527528529530531532533534535536537538539540541542543544545546547548549550551552553554555556557558559560561562563564565566567568569570571572573574575576577578579580581582583584585586587588589590591592593594595596597598599600601602603604605606607608609610611612613614615616617618619620621622623624625626627628629630631632633634635636637638639640641642643644645646647648649650651652653654655656657658659660661662663664665666667668669670671672673674675676677678679680681682683684685686687688689690691692693694695696697698699700701702703704705706707708709710711712713714715716717718719720721722723724725726727728729730731732733734735736737738739740741742743744745746747748749750751752753754755756757758759760761762763764765766767768769770771772773774775776777778779780781782783784785786787788789790791792793794795796797798799800801802803804805806807808809810811812813814815816817818819820821822823824825826827828829830831832833834835836837838839840841842843844845846847848849850851852853854855856857858859860861862863864865866867868869870871872873874875876877878879880881882883884885886887888889890891892893894895896897898899900901902903904905906907908909910911912913914915916917918919920921922923924925926927928929930931932933934935936937938939940941942943944945946947948949950951952953954955956957958959960961962963964965966967968969970971972973974975976977978979980981982983984985986987988989990991992993994995996997998999100010011002100310041005100610071008100910101011101210131014101510161017101810191020102110221023102410251026102710281029103010311032103310341035103610371038103910401041104210431044104510461047104810491050105110521053105410551056105710581059106010611062106310641065106610671068106910701071107210731074107510761077107810791080108110821083108410851086108710881089109010911092109310941095109610971098109911001101110211031104110511061107110811091110111111121113111411151116111711181119112011211122112311241125112611271128 |
- # safe.tcl --
- #
- # This file provide a safe loading/sourcing mechanism for safe interpreters.
- # It implements a virtual path mecanism to hide the real pathnames from the
- # slave. It runs in a master interpreter and sets up data structure and
- # aliases that will be invoked when used from a slave interpreter.
- #
- # See the safe.n man page for details.
- #
- # Copyright (c) 1996-1997 Sun Microsystems, Inc.
- #
- # See the file "license.terms" for information on usage and redistribution of
- # this file, and for a DISCLAIMER OF ALL WARRANTIES.
- #
- # The implementation is based on namespaces. These naming conventions are
- # followed:
- # Private procs starts with uppercase.
- # Public procs are exported and starts with lowercase
- #
- # Needed utilities package
- package require opt 0.4.1
- # Create the safe namespace
- namespace eval ::safe {
- # Exported API:
- namespace export interpCreate interpInit interpConfigure interpDelete \
- interpAddToAccessPath interpFindInAccessPath setLogCmd
- }
- # Helper function to resolve the dual way of specifying staticsok (either
- # by -noStatics or -statics 0)
- proc ::safe::InterpStatics {} {
- foreach v {Args statics noStatics} {
- upvar $v $v
- }
- set flag [::tcl::OptProcArgGiven -noStatics]
- if {$flag && (!$noStatics == !$statics)
- && ([::tcl::OptProcArgGiven -statics])} {
- return -code error\
- "conflicting values given for -statics and -noStatics"
- }
- if {$flag} {
- return [expr {!$noStatics}]
- } else {
- return $statics
- }
- }
- # Helper function to resolve the dual way of specifying nested loading
- # (either by -nestedLoadOk or -nested 1)
- proc ::safe::InterpNested {} {
- foreach v {Args nested nestedLoadOk} {
- upvar $v $v
- }
- set flag [::tcl::OptProcArgGiven -nestedLoadOk]
- # note that the test here is the opposite of the "InterpStatics" one
- # (it is not -noNested... because of the wanted default value)
- if {$flag && (!$nestedLoadOk != !$nested)
- && ([::tcl::OptProcArgGiven -nested])} {
- return -code error\
- "conflicting values given for -nested and -nestedLoadOk"
- }
- if {$flag} {
- # another difference with "InterpStatics"
- return $nestedLoadOk
- } else {
- return $nested
- }
- }
- ####
- #
- # API entry points that needs argument parsing :
- #
- ####
- # Interface/entry point function and front end for "Create"
- proc ::safe::interpCreate {args} {
- set Args [::tcl::OptKeyParse ::safe::interpCreate $args]
- InterpCreate $slave $accessPath \
- [InterpStatics] [InterpNested] $deleteHook
- }
- proc ::safe::interpInit {args} {
- set Args [::tcl::OptKeyParse ::safe::interpIC $args]
- if {![::interp exists $slave]} {
- return -code error "\"$slave\" is not an interpreter"
- }
- InterpInit $slave $accessPath \
- [InterpStatics] [InterpNested] $deleteHook
- }
- # Check that the given slave is "one of us"
- proc ::safe::CheckInterp {slave} {
- namespace upvar ::safe S$slave state
- if {![info exists state] || ![::interp exists $slave]} {
- return -code error \
- "\"$slave\" is not an interpreter managed by ::safe::"
- }
- }
- # Interface/entry point function and front end for "Configure". This code
- # is awfully pedestrian because it would need more coupling and support
- # between the way we store the configuration values in safe::interp's and
- # the Opt package. Obviously we would like an OptConfigure to avoid
- # duplicating all this code everywhere.
- # -> TODO (the app should share or access easily the program/value stored
- # by opt)
- # This is even more complicated by the boolean flags with no values that
- # we had the bad idea to support for the sake of user simplicity in
- # create/init but which makes life hard in configure...
- # So this will be hopefully written and some integrated with opt1.0
- # (hopefully for tcl8.1 ?)
- proc ::safe::interpConfigure {args} {
- switch [llength $args] {
- 1 {
- # If we have exactly 1 argument the semantic is to return all
- # the current configuration. We still call OptKeyParse though
- # we know that "slave" is our given argument because it also
- # checks for the "-help" option.
- set Args [::tcl::OptKeyParse ::safe::interpIC $args]
- CheckInterp $slave
- namespace upvar ::safe S$slave state
- return [join [list \
- [list -accessPath $state(access_path)] \
- [list -statics $state(staticsok)] \
- [list -nested $state(nestedok)] \
- [list -deleteHook $state(cleanupHook)]]]
- }
- 2 {
- # If we have exactly 2 arguments the semantic is a "configure
- # get"
- lassign $args slave arg
- # get the flag sub program (we 'know' about Opt's internal
- # representation of data)
- set desc [lindex [::tcl::OptKeyGetDesc ::safe::interpIC] 2]
- set hits [::tcl::OptHits desc $arg]
- if {$hits > 1} {
- return -code error [::tcl::OptAmbigous $desc $arg]
- } elseif {$hits == 0} {
- return -code error [::tcl::OptFlagUsage $desc $arg]
- }
- CheckInterp $slave
- namespace upvar ::safe S$slave state
- set item [::tcl::OptCurDesc $desc]
- set name [::tcl::OptName $item]
- switch -exact -- $name {
- -accessPath {return [list -accessPath $state(access_path)]}
- -statics {return [list -statics $state(staticsok)]}
- -nested {return [list -nested $state(nestedok)]}
- -deleteHook {return [list -deleteHook $state(cleanupHook)]}
- -noStatics {
- # it is most probably a set in fact but we would need
- # then to jump to the set part and it is not *sure*
- # that it is a set action that the user want, so force
- # it to use the unambigous -statics ?value? instead:
- return -code error\
- "ambigous query (get or set -noStatics ?)\
- use -statics instead"
- }
- -nestedLoadOk {
- return -code error\
- "ambigous query (get or set -nestedLoadOk ?)\
- use -nested instead"
- }
- default {
- return -code error "unknown flag $name (bug)"
- }
- }
- }
- default {
- # Otherwise we want to parse the arguments like init and
- # create did
- set Args [::tcl::OptKeyParse ::safe::interpIC $args]
- CheckInterp $slave
- namespace upvar ::safe S$slave state
- # Get the current (and not the default) values of whatever has
- # not been given:
- if {![::tcl::OptProcArgGiven -accessPath]} {
- set doreset 1
- set accessPath $state(access_path)
- } else {
- set doreset 0
- }
- if {
- ![::tcl::OptProcArgGiven -statics]
- && ![::tcl::OptProcArgGiven -noStatics]
- } {
- set statics $state(staticsok)
- } else {
- set statics [InterpStatics]
- }
- if {
- [::tcl::OptProcArgGiven -nested] ||
- [::tcl::OptProcArgGiven -nestedLoadOk]
- } {
- set nested [InterpNested]
- } else {
- set nested $state(nestedok)
- }
- if {![::tcl::OptProcArgGiven -deleteHook]} {
- set deleteHook $state(cleanupHook)
- }
- # we can now reconfigure :
- InterpSetConfig $slave $accessPath $statics $nested $deleteHook
- # auto_reset the slave (to completly synch the new access_path)
- if {$doreset} {
- if {[catch {::interp eval $slave {auto_reset}} msg]} {
- Log $slave "auto_reset failed: $msg"
- } else {
- Log $slave "successful auto_reset" NOTICE
- }
- }
- }
- }
- }
- ####
- #
- # Functions that actually implements the exported APIs
- #
- ####
- #
- # safe::InterpCreate : doing the real job
- #
- # This procedure creates a safe slave and initializes it with the safe
- # base aliases.
- # NB: slave name must be simple alphanumeric string, no spaces, no (), no
- # {},... {because the state array is stored as part of the name}
- #
- # Returns the slave name.
- #
- # Optional Arguments :
- # + slave name : if empty, generated name will be used
- # + access_path: path list controlling where load/source can occur,
- # if empty: the master auto_path will be used.
- # + staticsok : flag, if 0 :no static package can be loaded (load {} Xxx)
- # if 1 :static packages are ok.
- # + nestedok: flag, if 0 :no loading to sub-sub interps (load xx xx sub)
- # if 1 : multiple levels are ok.
- # use the full name and no indent so auto_mkIndex can find us
- proc ::safe::InterpCreate {
- slave
- access_path
- staticsok
- nestedok
- deletehook
- } {
- # Create the slave.
- if {$slave ne ""} {
- ::interp create -safe $slave
- } else {
- # empty argument: generate slave name
- set slave [::interp create -safe]
- }
- Log $slave "Created" NOTICE
- # Initialize it. (returns slave name)
- InterpInit $slave $access_path $staticsok $nestedok $deletehook
- }
- #
- # InterpSetConfig (was setAccessPath) :
- # Sets up slave virtual auto_path and corresponding structure within
- # the master. Also sets the tcl_library in the slave to be the first
- # directory in the path.
- # NB: If you change the path after the slave has been initialized you
- # probably need to call "auto_reset" in the slave in order that it gets
- # the right auto_index() array values.
- proc ::safe::InterpSetConfig {slave access_path staticsok nestedok deletehook} {
- global auto_path
- # determine and store the access path if empty
- if {$access_path eq ""} {
- set access_path $auto_path
- # Make sure that tcl_library is in auto_path and at the first
- # position (needed by setAccessPath)
- set where [lsearch -exact $access_path [info library]]
- if {$where == -1} {
- # not found, add it.
- set access_path [linsert $access_path 0 [info library]]
- Log $slave "tcl_library was not in auto_path,\
- added it to slave's access_path" NOTICE
- } elseif {$where != 0} {
- # not first, move it first
- set access_path [linsert \
- [lreplace $access_path $where $where] \
- 0 [info library]]
- Log $slave "tcl_libray was not in first in auto_path,\
- moved it to front of slave's access_path" NOTICE
- }
- # Add 1st level sub dirs (will searched by auto loading from tcl
- # code in the slave using glob and thus fail, so we add them here
- # so by default it works the same).
- set access_path [AddSubDirs $access_path]
- }
- Log $slave "Setting accessPath=($access_path) staticsok=$staticsok\
- nestedok=$nestedok deletehook=($deletehook)" NOTICE
- namespace upvar ::safe S$slave state
- # clear old autopath if it existed
- # build new one
- # Extend the access list with the paths used to look for Tcl Modules.
- # We save the virtual form separately as well, as syncing it with the
- # slave has to be defered until the necessary commands are present for
- # setup.
- set norm_access_path {}
- set slave_access_path {}
- set map_access_path {}
- set remap_access_path {}
- set slave_tm_path {}
- set i 0
- foreach dir $access_path {
- set token [PathToken $i]
- lappend slave_access_path $token
- lappend map_access_path $token $dir
- lappend remap_access_path $dir $token
- lappend norm_access_path [file normalize $dir]
- incr i
- }
- set morepaths [::tcl::tm::list]
- while {[llength $morepaths]} {
- set addpaths $morepaths
- set morepaths {}
- foreach dir $addpaths {
- # Prevent the addition of dirs on the tm list to the
- # result if they are already known.
- if {[dict exists $remap_access_path $dir]} {
- continue
- }
- set token [PathToken $i]
- lappend access_path $dir
- lappend slave_access_path $token
- lappend map_access_path $token $dir
- lappend remap_access_path $dir $token
- lappend norm_access_path [file normalize $dir]
- lappend slave_tm_path $token
- incr i
- # [Bug 2854929]
- # Recursively find deeper paths which may contain
- # modules. Required to handle modules with names like
- # 'platform::shell', which translate into
- # 'platform/shell-X.tm', i.e arbitrarily deep
- # subdirectories.
- lappend morepaths {*}[glob -nocomplain -directory $dir -type d *]
- }
- }
- set state(access_path) $access_path
- set state(access_path,map) $map_access_path
- set state(access_path,remap) $remap_access_path
- set state(access_path,norm) $norm_access_path
- set state(access_path,slave) $slave_access_path
- set state(tm_path_slave) $slave_tm_path
- set state(staticsok) $staticsok
- set state(nestedok) $nestedok
- set state(cleanupHook) $deletehook
- SyncAccessPath $slave
- }
- #
- #
- # FindInAccessPath:
- # Search for a real directory and returns its virtual Id (including the
- # "$")
- proc ::safe::interpFindInAccessPath {slave path} {
- namespace upvar ::safe S$slave state
- if {![dict exists $state(access_path,remap) $path]} {
- return -code error "$path not found in access path $access_path"
- }
- return [dict get $state(access_path,remap) $path]
- }
- #
- # addToAccessPath:
- # add (if needed) a real directory to access path and return its
- # virtual token (including the "$").
- proc ::safe::interpAddToAccessPath {slave path} {
- # first check if the directory is already in there
- # (inlined interpFindInAccessPath).
- namespace upvar ::safe S$slave state
- if {[dict exists $state(access_path,remap) $path]} {
- return [dict get $state(access_path,remap) $path]
- }
- # new one, add it:
- set token [PathToken [llength $state(access_path)]]
- lappend state(access_path) $path
- lappend state(access_path,slave) $token
- lappend state(access_path,map) $token $path
- lappend state(access_path,remap) $path $token
- lappend state(access_path,norm) [file normalize $path]
- SyncAccessPath $slave
- return $token
- }
- # This procedure applies the initializations to an already existing
- # interpreter. It is useful when you want to install the safe base aliases
- # into a preexisting safe interpreter.
- proc ::safe::InterpInit {
- slave
- access_path
- staticsok
- nestedok
- deletehook
- } {
- # Configure will generate an access_path when access_path is empty.
- InterpSetConfig $slave $access_path $staticsok $nestedok $deletehook
- # NB we need to add [namespace current], aliases are always absolute
- # paths.
- # These aliases let the slave load files to define new commands
- # This alias lets the slave use the encoding names, convertfrom,
- # convertto, and system, but not "encoding system <name>" to set the
- # system encoding.
- # Handling Tcl Modules, we need a restricted form of Glob.
- # This alias interposes on the 'exit' command and cleanly terminates
- # the slave.
- foreach {command alias} {
- source AliasSource
- load AliasLoad
- encoding AliasEncoding
- exit interpDelete
- glob AliasGlob
- } {
- ::interp alias $slave $command {} [namespace current]::$alias $slave
- }
- # This alias lets the slave have access to a subset of the 'file'
- # command functionality.
- AliasSubset $slave file \
- file dir.* join root.* ext.* tail path.* split
- # Subcommands of info
- foreach {subcommand alias} {
- nameofexecutable AliasExeName
- } {
- ::interp alias $slave ::tcl::info::$subcommand \
- {} [namespace current]::$alias $slave
- }
- # The allowed slave variables already have been set by Tcl_MakeSafe(3)
- # Source init.tcl and tm.tcl into the slave, to get auto_load and
- # other procedures defined:
- if {[catch {::interp eval $slave {
- source [file join $tcl_library init.tcl]
- }} msg]} {
- Log $slave "can't source init.tcl ($msg)"
- return -code error "can't source init.tcl into slave $slave ($msg)"
- }
- if {[catch {::interp eval $slave {
- source [file join $tcl_library tm.tcl]
- }} msg]} {
- Log $slave "can't source tm.tcl ($msg)"
- return -code error "can't source tm.tcl into slave $slave ($msg)"
- }
- # Sync the paths used to search for Tcl modules. This can be done only
- # now, after tm.tcl was loaded.
- namespace upvar ::safe S$slave state
- if {[llength $state(tm_path_slave)] > 0} {
- ::interp eval $slave [list \
- ::tcl::tm::add {*}[lreverse $state(tm_path_slave)]]
- }
- return $slave
- }
- # Add (only if needed, avoid duplicates) 1 level of sub directories to an
- # existing path list. Also removes non directories from the returned
- # list.
- proc ::safe::AddSubDirs {pathList} {
- set res {}
- foreach dir $pathList {
- if {[file isdirectory $dir]} {
- # check that we don't have it yet as a children of a previous
- # dir
- if {$dir ni $res} {
- lappend res $dir
- }
- foreach sub [glob -directory $dir -nocomplain *] {
- if {[file isdirectory $sub] && ($sub ni $res)} {
- # new sub dir, add it !
- lappend res $sub
- }
- }
- }
- }
- return $res
- }
- # This procedure deletes a safe slave managed by Safe Tcl and cleans up
- # associated state:
- proc ::safe::interpDelete {slave} {
- Log $slave "About to delete" NOTICE
- namespace upvar ::safe S$slave state
- # If the slave has a cleanup hook registered, call it. Check the
- # existance because we might be called to delete an interp which has
- # not been registered with us at all
- if {[info exists state(cleanupHook)]} {
- set hook $state(cleanupHook)
- if {[llength $hook]} {
- # remove the hook now, otherwise if the hook calls us somehow,
- # we'll loop
- unset state(cleanupHook)
- if {[catch {
- {*}$hook $slave
- } err]} {
- Log $slave "Delete hook error ($err)"
- }
- }
- }
- # Discard the global array of state associated with the slave, and
- # delete the interpreter.
- if {[info exists state]} {
- unset state
- }
- # if we have been called twice, the interp might have been deleted
- # already
- if {[::interp exists $slave]} {
- ::interp delete $slave
- Log $slave "Deleted" NOTICE
- }
- return
- }
- # Set (or get) the logging mecanism
- proc ::safe::setLogCmd {args} {
- variable Log
- set la [llength $args]
- if {$la == 0} {
- return $Log
- } elseif {$la == 1} {
- set Log [lindex $args 0]
- } else {
- set Log $args
- }
- if {$Log eq ""} {
- # Disable logging completely. Calls to it will be compiled out
- # of all users.
- proc ::safe::Log {args} {}
- } else {
- # Activate logging, define proper command.
- proc ::safe::Log {slave msg {type ERROR}} {
- variable Log
- {*}$Log "$type for slave $slave : $msg"
- return
- }
- }
- }
- # ------------------- END OF PUBLIC METHODS ------------
- #
- # Sets the slave auto_path to the master recorded value. Also sets
- # tcl_library to the first token of the virtual path.
- #
- proc ::safe::SyncAccessPath {slave} {
- namespace upvar ::safe S$slave state
- set slave_access_path $state(access_path,slave)
- ::interp eval $slave [list set auto_path $slave_access_path]
- Log $slave "auto_path in $slave has been set to $slave_access_path"\
- NOTICE
- # This code assumes that info library is the first element in the
- # list of auto_path's. See -> InterpSetConfig for the code which
- # ensures this condition.
- ::interp eval $slave [list \
- set tcl_library [lindex $slave_access_path 0]]
- }
- # Returns the virtual token for directory number N.
- proc ::safe::PathToken {n} {
- # We need to have a ":" in the token string so [file join] on the
- # mac won't turn it into a relative path.
- return "\$p(:$n:)" ;# Form tested by case 7.2
- }
- #
- # translate virtual path into real path
- #
- proc ::safe::TranslatePath {slave path} {
- namespace upvar ::safe S$slave state
- # somehow strip the namespaces 'functionality' out (the danger is that
- # we would strip valid macintosh "../" queries... :
- if {[string match "*::*" $path] || [string match "*..*" $path]} {
- return -code error "invalid characters in path $path"
- }
- # Use a cached map instead of computed local vars and subst.
- return [string map $state(access_path,map) $path]
- }
- # file name control (limit access to files/resources that should be a
- # valid tcl source file)
- proc ::safe::CheckFileName {slave file} {
- # This used to limit what can be sourced to ".tcl" and forbid files
- # with more than 1 dot and longer than 14 chars, but I changed that
- # for 8.4 as a safe interp has enough internal protection already to
- # allow sourcing anything. - hobbs
- if {![file exists $file]} {
- # don't tell the file path
- return -code error "no such file or directory"
- }
- if {![file readable $file]} {
- # don't tell the file path
- return -code error "not readable"
- }
- }
- # AliasGlob is the target of the "glob" alias in safe interpreters.
- proc ::safe::AliasGlob {slave args} {
- Log $slave "GLOB ! $args" NOTICE
- set cmd {}
- set at 0
- array set got {
- -directory 0
- -nocomplain 0
- -join 0
- -tails 0
- -- 0
- }
- if {$::tcl_platform(platform) eq "windows"} {
- set dirPartRE {^(.*)[\\/]([^\\/]*)$}
- } else {
- set dirPartRE {^(.*)/([^/]*)$}
- }
- set dir {}
- set virtualdir {}
- while {$at < [llength $args]} {
- switch -glob -- [set opt [lindex $args $at]] {
- -nocomplain - -- - -join - -tails {
- lappend cmd $opt
- set got($opt) 1
- incr at
- }
- -types - -type {
- lappend cmd -types [lindex $args [incr at]]
- incr at
- }
- -directory {
- if {$got($opt)} {
- return -code error \
- {"-directory" cannot be used with "-path"}
- }
- set got($opt) 1
- set virtualdir [lindex $args [incr at]]
- incr at
- }
- pkgIndex.tcl {
- # Oops, this is globbing a subdirectory in regular package
- # search. That is not wanted. Abort, handler does catch
- # already (because glob was not defined before). See
- # package.tcl, lines 484ff in tclPkgUnknown.
- return -code error "unknown command glob"
- }
- -* {
- Log $slave "Safe base rejecting glob option '$opt'"
- return -code error "Safe base rejecting glob option '$opt'"
- }
- default {
- break
- }
- }
- if {$got(--)} break
- }
- # Get the real path from the virtual one and check that the path is in the
- # access path of that slave. Done after basic argument processing so that
- # we know if -nocomplain is set.
- if {$got(-directory)} {
- if {[catch {
- set dir [TranslatePath $slave $virtualdir]
- DirInAccessPath $slave $dir
- } msg]} {
- Log $slave $msg
- if {$got(-nocomplain)} {
- return
- }
- return -code error "permission denied"
- }
- lappend cmd -directory $dir
- }
- # Apply the -join semantics ourselves
- if {$got(-join)} {
- set args [lreplace $args $at end [join [lrange $args $at end] "/"]]
- }
- # Process remaining pattern arguments
- set firstPattern [llength $cmd]
- foreach opt [lrange $args $at end] {
- if {![regexp $dirPartRE $opt -> thedir thefile]} {
- set thedir .
- }
- if {$thedir eq "*"} {
- set mapped 0
- foreach d [glob -directory [TranslatePath $slave $virtualdir] \
- -types d -tails *] {
- catch {
- DirInAccessPath $slave \
- [TranslatePath $slave [file join $virtualdir $d]]
- if {$thefile eq "pkgIndex.tcl" || $thefile eq "*.tm"} {
- lappend cmd [file join $d $thefile]
- set mapped 1
- }
- }
- }
- if {$mapped} continue
- }
- if {[catch {
- set thedir [file join $virtualdir $thedir]
- DirInAccessPath $slave [TranslatePath $slave $thedir]
- } msg]} {
- Log $slave $msg
- if {$got(-nocomplain)} continue
- return -code error "permission denied"
- }
- lappend cmd $opt
- }
- Log $slave "GLOB = $cmd" NOTICE
- if {$got(-nocomplain) && [llength $cmd] eq $firstPattern} {
- return
- }
- if {[catch {
- ::interp invokehidden $slave glob {*}$cmd
- } msg]} {
- Log $slave $msg
- return -code error "script error"
- }
- Log $slave "GLOB < $msg" NOTICE
- # Translate path back to what the slave should see.
- set res {}
- set l [string length $dir]
- foreach p $msg {
- if {[string equal -length $l $dir $p]} {
- set p [string replace $p 0 [expr {$l-1}] $virtualdir]
- }
- lappend res $p
- }
- Log $slave "GLOB > $res" NOTICE
- return $res
- }
- # AliasSource is the target of the "source" alias in safe interpreters.
- proc ::safe::AliasSource {slave args} {
- set argc [llength $args]
- # Extended for handling of Tcl Modules to allow not only "source
- # filename", but "source -encoding E filename" as well.
- if {[lindex $args 0] eq "-encoding"} {
- incr argc -2
- set encoding [lindex $args 1]
- set at 2
- if {$encoding eq "identity"} {
- Log $slave "attempt to use the identity encoding"
- return -code error "permission denied"
- }
- } else {
- set at 0
- set encoding {}
- }
- if {$argc != 1} {
- set msg "wrong # args: should be \"source ?-encoding E? fileName\""
- Log $slave "$msg ($args)"
- return -code error $msg
- }
- set file [lindex $args $at]
- # get the real path from the virtual one.
- if {[catch {
- set realfile [TranslatePath $slave $file]
- } msg]} {
- Log $slave $msg
- return -code error "permission denied"
- }
- # check that the path is in the access path of that slave
- if {[catch {
- FileInAccessPath $slave $realfile
- } msg]} {
- Log $slave $msg
- return -code error "permission denied"
- }
- # do the checks on the filename :
- if {[catch {
- CheckFileName $slave $realfile
- } msg]} {
- Log $slave "$realfile:$msg"
- return -code error $msg
- }
- # Passed all the tests, lets source it. Note that we do this all manually
- # because we want to control [info script] in the slave so information
- # doesn't leak so much. [Bug 2913625]
- set old [::interp eval $slave {info script}]
- set code [catch {
- set f [open $realfile]
- fconfigure $f -eofchar \032
- if {$encoding ne ""} {
- fconfigure $f -encoding $encoding
- }
- set contents [read $f]
- close $f
- ::interp eval $slave [list info script $file]
- ::interp eval $slave $contents
- } msg opt]
- catch {interp eval $slave [list info script $old]}
- # Note that all non-errors are fine result codes from [source], so we must
- # take a little care to do it properly. [Bug 2923613]
- if {$code == 1} {
- Log $slave $msg
- return -code error "script error"
- }
- return -code $code -options $opt $msg
- }
- # AliasLoad is the target of the "load" alias in safe interpreters.
- proc ::safe::AliasLoad {slave file args} {
- set argc [llength $args]
- if {$argc > 2} {
- set msg "load error: too many arguments"
- Log $slave "$msg ($argc) {$file $args}"
- return -code error $msg
- }
- # package name (can be empty if file is not).
- set package [lindex $args 0]
- namespace upvar ::safe S$slave state
- # Determine where to load. load use a relative interp path and {}
- # means self, so we can directly and safely use passed arg.
- set target [lindex $args 1]
- if {$target ne ""} {
- # we will try to load into a sub sub interp; check that we want to
- # authorize that.
- if {!$state(nestedok)} {
- Log $slave "loading to a sub interp (nestedok)\
- disabled (trying to load $package to $target)"
- return -code error "permission denied (nested load)"
- }
- }
- # Determine what kind of load is requested
- if {$file eq ""} {
- # static package loading
- if {$package eq ""} {
- set msg "load error: empty filename and no package name"
- Log $slave $msg
- return -code error $msg
- }
- if {!$state(staticsok)} {
- Log $slave "static packages loading disabled\
- (trying to load $package to $target)"
- return -code error "permission denied (static package)"
- }
- } else {
- # file loading
- # get the real path from the virtual one.
- if {[catch {
- set file [TranslatePath $slave $file]
- } msg]} {
- Log $slave $msg
- return -code error "permission denied"
- }
- # check the translated path
- if {[catch {
- FileInAccessPath $slave $file
- } msg]} {
- Log $slave $msg
- return -code error "permission denied (path)"
- }
- }
- if {[catch {
- ::interp invokehidden $slave load $file $package $target
- } msg]} {
- Log $slave $msg
- return -code error $msg
- }
- return $msg
- }
- # FileInAccessPath raises an error if the file is not found in the list of
- # directories contained in the (master side recorded) slave's access path.
- # the security here relies on "file dirname" answering the proper
- # result... needs checking ?
- proc ::safe::FileInAccessPath {slave file} {
- namespace upvar ::safe S$slave state
- set access_path $state(access_path)
- if {[file isdirectory $file]} {
- return -code error "\"$file\": is a directory"
- }
- set parent [file dirname $file]
- # Normalize paths for comparison since lsearch knows nothing of
- # potential pathname anomalies.
- set norm_parent [file normalize $parent]
- namespace upvar ::safe S$slave state
- if {$norm_parent ni $state(access_path,norm)} {
- return -code error "\"$file\": not in access_path"
- }
- }
- proc ::safe::DirInAccessPath {slave dir} {
- namespace upvar ::safe S$slave state
- set access_path $state(access_path)
- if {[file isfile $dir]} {
- return -code error "\"$dir\": is a file"
- }
- # Normalize paths for comparison since lsearch knows nothing of
- # potential pathname anomalies.
- set norm_dir [file normalize $dir]
- namespace upvar ::safe S$slave state
- if {$norm_dir ni $state(access_path,norm)} {
- return -code error "\"$dir\": not in access_path"
- }
- }
- # This procedure enables access from a safe interpreter to only a subset
- # of the subcommands of a command:
- proc ::safe::Subset {slave command okpat args} {
- set subcommand [lindex $args 0]
- if {[regexp $okpat $subcommand]} {
- return [$command {*}$args]
- }
- set msg "not allowed to invoke subcommand $subcommand of $command"
- Log $slave $msg
- return -code error $msg
- }
- # This procedure installs an alias in a slave that invokes "safesubset" in
- # the master to execute allowed subcommands. It precomputes the pattern of
- # allowed subcommands; you can use wildcards in the pattern if you wish to
- # allow subcommand abbreviation.
- #
- # Syntax is: AliasSubset slave alias target subcommand1 subcommand2...
- proc ::safe::AliasSubset {slave alias target args} {
- set pat "^([join $args |])\$"
- ::interp alias $slave $alias {}\
- [namespace current]::Subset $slave $target $pat
- }
- # AliasEncoding is the target of the "encoding" alias in safe interpreters.
- proc ::safe::AliasEncoding {slave option args} {
- # Careful; do not want empty option to get through to the [string equal]
- if {[regexp {^(name.*|convert.*|)$} $option]} {
- return [::interp invokehidden $slave encoding $option {*}$args]
- }
- if {[string equal -length [string length $option] $option "system"]} {
- if {[llength $args] == 0} {
- # passed all the tests , lets source it:
- if {[catch {
- set sysenc [::interp invokehidden $slave encoding system]
- } msg]} {
- Log $slave $msg
- return -code error "script error"
- }
- return $sysenc
- }
- set msg "wrong # args: should be \"encoding system\""
- set code {TCL WRONGARGS}
- } else {
- set msg "bad option \"$option\": must be convertfrom, convertto, names, or system"
- set code [list TCL LOOKUP INDEX option $option]
- }
- Log $slave $msg
- return -code error -errorcode $code $msg
- }
- # Various minor hiding of platform features. [Bug 2913625]
- proc ::safe::AliasExeName {slave} {
- return ""
- }
- proc ::safe::Setup {} {
- ####
- #
- # Setup the arguments parsing
- #
- ####
- # Share the descriptions
- set temp [::tcl::OptKeyRegister {
- {-accessPath -list {} "access path for the slave"}
- {-noStatics "prevent loading of statically linked pkgs"}
- {-statics true "loading of statically linked pkgs"}
- {-nestedLoadOk "allow nested loading"}
- {-nested false "nested loading"}
- {-deleteHook -script {} "delete hook"}
- }]
- # create case (slave is optional)
- ::tcl::OptKeyRegister {
- {?slave? -name {} "name of the slave (optional)"}
- } ::safe::interpCreate
- # adding the flags sub programs to the command program (relying on Opt's
- # internal implementation details)
- lappend ::tcl::OptDesc(::safe::interpCreate) $::tcl::OptDesc($temp)
- # init and configure (slave is needed)
- ::tcl::OptKeyRegister {
- {slave -name {} "name of the slave"}
- } ::safe::interpIC
- # adding the flags sub programs to the command program (relying on Opt's
- # internal implementation details)
- lappend ::tcl::OptDesc(::safe::interpIC) $::tcl::OptDesc($temp)
- # temp not needed anymore
- ::tcl::OptKeyDelete $temp
- ####
- #
- # Default: No logging.
- #
- ####
- setLogCmd {}
- # Log eventually.
- # To enable error logging, set Log to {puts stderr} for instance,
- # via setLogCmd.
- return
- }
- namespace eval ::safe {
- # internal variables
- # Log command, set via 'setLogCmd'. Logging is disabled when empty.
- variable Log {}
- # The package maintains a state array per slave interp under its
- # control. The name of this array is S<interp-name>. This array is
- # brought into scope where needed, using 'namespace upvar'. The S
- # prefix is used to avoid that a slave interp called "Log" smashes
- # the "Log" variable.
- #
- # The array's elements are:
- #
- # access_path : List of paths accessible to the slave.
- # access_path,norm : Ditto, in normalized form.
- # access_path,slave : Ditto, as the path tokens as seen by the slave.
- # access_path,map : dict ( token -> path )
- # access_path,remap : dict ( path -> token )
- # tm_path_slave : List of TM root directories, as tokens seen by the slave.
- # staticsok : Value of option -statics
- # nestedok : Value of option -nested
- # cleanupHook : Value of option -deleteHook
- }
- ::safe::Setup
|