Tcl Programming/Functions

Commands edit


Commands are basically divided into C-defined ones, procedures, and aliases (and, from Tcl 8.5 onwards, ensembles). You can rename any command with

rename oldname newname

To delete a command (make it no more reachable), use the empty string as new name:

rename oldname {}

Introspection: Get a list of all defined commands with

info commands

C-defined commands edit

These are implemented in C and registered to be available in the Tcl interpreter. They can come from the Tcl core, or a loaded shared library (DLL) - for instance Tk.

To get a list of built-in commands, subtract the result of info procs from that of info commands:

set builtins {}
set procs [info procs]
foreach cmd [info commands] {
   if {[lsearch -exact $procs $cmd] == -1} {lappend builtins $cmd}
}

The following C-defined commands are available in a fresh tclsh. For detailed documentation, see the respective man pages, e.g. at http://www.tcl.tk/man/tcl8.5/TclCmd/ - I will characterize each only very briefly:

after
group of commands for timed events
after msec ?script?
waits, or executes the script after, some time
append varName arg..
appends the arguments to a string variable
array
group of commands for arrays
binary
group of commands for binary scanning and formatting
break
terminate current loop
case
deprecated, use switch
catch script ?varName?
catch possible error in script
cd path
change working directory
clock
group of commands dealing with date and time
close handle
closes a channel (file, socket, etc.)
concat list..
make one space-separated list of the arguments
continue
start next turn of current loop
encoding
group of commands dealing with character set encoding
eof handle
1 if channel is at end of file, else 0
error message ?info? ?code?
raise an error with the given message
eval arg..
evaluate the arguments as script
exec file arg..
execute a separate process
exit ?int?
terminate this process, return status 0..127
expr arg..
arithmetic and logic engine, using C-like syntax and functions (variables referenced with $name). In addition, from Tcl 8.4 there are eq and ne operators for string equal or not; from 8.5, also in and ni operators for list inclusion or not
expr {"foo" in {foo bar grill}} == 1

The argument to expr should in most cases be {braced}. This prevents the Tcl parser from substituting variables in advance, while expr itself has to parse the value from the string. In a braced expression expr can parse variable references itself, and get their numeric value directly where possible. Much faster, usually. The only exception, where bracing should not be used, is if you want to substitute operators from variables:

foreach op {+ - * /} {puts [expr 1 $op 2]}
fblocked handle
returns 1 if the last input operation exhausted all available input, else 0
fconfigure handle -option value...
configure a channel, e.g. its encoding or line-end translation
fcopy handle1 handle2
copy data from handle1 to handle2
file
group of commands dealing with files
fileevent
group of commands dealing with events from channels (readable, writable) but not files
flush handle
make sure the channel's buffer is written out. Useful after puts -nonewline
for initbody condition stepbody body
loop, somehow similar to C's for
foreach varlist list ?varlist list...? body
loop over one or more lists, The varlists can be a single or multiple varNames. Example:
% foreach {x y} {1 0  1 2  0 2  0 0} {puts "x:$x, y:$y"}
x:1, y:0
x:1, y:2
x:0, y:2
x:0, y:0
format fstring arg..
put the arguments %-formatted into fstring, similar to C's sprintf()
gets handle ?varName?
read a line from handle. If variable is given, assigns the line to it and returns the number of characters read; else returns the line. Guaranteed to be safe against buffer overflows
glob ?-options? pattern..
list of files matching the glob pattern (which can contain * and ? wildcards)
global varName..
declare the given variable(s) as global
history
list the last interactive commands
if condition ?then? body1 ?elseif condition body2...? ??else? bodyN?
conditional
incr varName ?amount?
increments the integer variable by given amount (defaults to 1). Use negative amount to decrement
info
group of commands for introspection
interp
group of commands for interpreters
join list ?separator?
Turn a list into a string, with separator between elements (defaults to " ")
lappend varName arg..
appends the arguments to the list variable. Can also be used to make sure a variable exists:
lappend x ;# corresponds to: if {![info exists x]} {set x ""}
lindex list int..
retrieve an element from the list by integer index(es)
linsert list int arg..
inserts the arguments at int position into list
list ?arg..?
creates a list from the arguments
llength list
length of the list
load filename ?name?
loads a shared library (DLL)
lrange list from to
returns a sublist at integer indexes from-to
lreplace list from to arg..
replaces the sublist in list with the arguments
lsearch ?-options? list element
searches the list for the element, returns its integer index, or -1 if not found. Can be used to select a subset of elements from a list (using the -all option)
lset varName int.. value
sets an existing element in the named list variable, indexed by integer(s), to the given value
lsort ?-options? list
sorts the list
namespace
group of commands dealing with namespaces
open name ?mode ?permissions??
opens a file or pipe, returns the handle
package
group of commands dealing with packages
pid ?handle?
returns the id of the current process. Can also return the list of pids for a pipeline given the pipeline channel
proc name arglist body
defines a procedure
puts ?-nonewline? ?channel? string
outputs a line to the given channel (default stdout) To prevent errors from closed pipe (like more or head), use
proc puts! str {if [catch {puts $str}] exit}
pwd
returns the current working directory
read handle ?int?
reads int bytes from handle (all if int not given)
regexp ?-options? re string ?varName...?
regular expression matching of re in string, possibly assigning parenthesized submatches to the given variables
regsub ?-options? re value substring ?varName?
substitutes occurrences of the regular expression re in value with substring. If varName is given, assigns the new value to it, and returns the number of substitutions; else returns the new value
rename cmdName1 cmdName2
renames a command from cmdName1 to cmdName2, or deletes cmdName1 if cmdName2 is {}
return ?value?
exits from the current proc or sourced script
scan string format ?varName...?
extracts values by %-format in string to the given variables. Similar to C's sscanf()
seek channelId offset ?origin?
moves pointer in file to the given position
set varName ?value?
sets variable to value if given, and returns the variable's value
socket ?-myaddr addr? ?-myport myport? ?-async? host port
open the client side of a TCP connection as a channel
socket -server command ?-myaddr addr? port
open the server side of a TCP connection, register a handler callbacvk command for client requests
source filename
evaluate the contents of the given file
split list ?charset?
splits a string into a list, using any of the characters in charset string as delimiters (defaults to " ")
string
group of commands dealing with strings
subst ?-options? string
performs command, variable, and/or backslash substitutions in string
switch ?-options? ?--? value alternatives
performs one of the alternatives if the value matches
tell handle
return the byte position inside a file
time body ?int?
runs the body for int times (default 1), returns how many microseconds per iteration were used
trace
group of commands to tie actions to variables or commands
unset varName..
delete the given variable(s)
update ?idletasks?
services events
uplevel ?level? body
evaluates the body up in the call stack
upvar ?level? varName localVarName...
ties the given variables up in the call stack to the given local variables. Used for calling by reference, e.g. for arrays
variable varName ?value ?varName value...??
declare the variables as being non-local in a namespace
vwait varName
suspend execution until the given variable has changed. Starts event loop, if not active yet
while condition body
performs body as long as condition is not 0

Procedures edit

Procedures in Tcl cover what other languages call procedures, subroutines, or functions. They always return a result (even if it is the empty string ""), so to call them functions might be most appropriate. But for historical reasons, the Tcl command to create a function is called proc and thus people most often call them procedures.

proc name argumentlist body

Examples:

proc sum {a b} {return [expr {$a+$b}]}

The return is redundant, as the proc returns anyway when reaching its end, and returning its last result:

proc sum {a b} {expr {$a+$b}}

The following variant is more flexible, as it takes any number of arguments (the special argument name args collects all remaining arguments into a list, which is the value of the parameter args):

proc sum args {
    set res 0
    foreach arg $args {set res [expr {$res + $arg}]}
    return $res
}

An elegant but less efficient alternative builds a string by joining the args with plus signs, and feeds that to expr:

proc sum args {expr [join $args +]}

If an argument in a proc definition is a list of two elements, the second is taken as default value if not given in the call ("Sir" in this example):

proc greet {time {person Sir}} {return "good $time, $person"}
% greet morning John
good morning, John
% greet evening
good evening, Sir

Introspection: Get the names of all defined procedures with

info procs

There are also info subcommands to get the argument list, and possible default arguments, and body of a proc. The following example combines them to recreate the textual form of a proc, given its name (corp being proc in reverse):

proc corp name {
   set argl {}
   foreach arg [info args $name] {
      if [info default $name $arg def] {lappend arg $def}
      lappend argl $arg
   }
   list proc $name $argl [info body $name]
}

Using rename, you can overload any command, including the C-coded ones. First rename the original command to something else, then reimplement it with the same signature, where ultimately the original is called. Here is for instance an overloaded proc that reports if a procedure is defined more than once with same name:

rename proc _proc
_proc proc {name argl body} {
   if {[info procs $name] eq $name} {
       puts "proc $name redefined in [info script]"
   }
   _proc $name $argl $body
}

Named arguments: Arguments to commands are mostly by position. But it's very easy to add the behavior known from Python or Ada, that arguments can be named in function calls, which documents the code a bit better, and allows any order of arguments.

The idea (as found in Welch's book) is to use an array (here called "" - the "anonymous array") keyed by argument names. Initially, you can set some default values, and possibly override them with the args of the proc (which has to be paired, i.e. contain an even number of elements):

proc named {args defaults} {
   upvar 1 "" ""
   array set "" $defaults
   foreach {key value} $args {
     if {![info exists ($key)]} {
        set names [lsort [array names ""]]
        error "bad option '$key', should be one of: $names"
     }
     set ($key) $value
   }
}

Usage example:

proc replace {s args} {
  named $args {-from 0 -to end -with ""}
  string replace $s $(-from) $(-to) $(-with)
}

Testing:

% replace suchenwirth -from 4 -to 6 -with xx
suchxxirth
% replace suchenwirth -from 4 -to 6 -witha xx
bad option '-witha', should be one of: -from -to -with

Argument passing by name or value edit

Normally, arguments to commands are passed by value (as constants, or with $ prefixed to a variable name). This securely prevents side-effects, as the command will only get a copy of the value, and not be able to change the variable.

However, sometimes just that is wanted. Imagine you want a custom command to set a variable to zero. In this case, at call time specify the name of the variable (without $), and in the proc use upvar to link the name (in the scope "1 up", i.e. the caller's) to a local variable. I usually put a "_" before arguments that are variable names (e.g. _var), and upvar to the same name without "_" (e.g. var):

% proc zero _var {upvar 1 $_var var; set var 0}
% set try 42
42
% zero try
0
% set try
0

If you often use call by reference, you could indicate such arguments with a special pattern (e.g. &arg) and have the following code generate the necessary upvars:

proc use_refs { {char &}} {
   foreach v [uplevel 1 {info locals}] {
       if [string match $char* $v] {
           uplevel 1 "upvar 1 \${$v} [string range $v 1 end]"
       }
   }
}

That's all. This command is preferably called first inside a proc, and upvars all arguments that begin with a specific character, the default being "&" - it runs code like

upvar 1 ${&foo} foo

in the caller's scope. Testing:

proc test_refs {a &b} {
   use_refs
   puts a=$a,b=$b
   set b new_value
}
% set bar 42
42
% test_refs foo bar
a=foo,b=42

So the values of a (by value) and b (by reference) are readable; and the side effect of changing b in the caller did also happen:

% set bar
new_value

Variable scope edit

Inside procedures, variables are by default local. They exist only in the proc, and are cleared up on return. However, you can tie local variables to others higher in the call stack (e.g. in the caller), up to the topmost global scope. Examples:

proc demo arg {
   global g
   set    g 0            ;# will effect a lasting change in g
   set local 1           ;# will disappear soon
   set ::anotherGlobal 2 ;# another way to address a global variable
   upvar 1 $arg myArg    ;# make myArg point at a variable 1-up
   set          myArg 3  ;# changes that variable in the calling scope
}

Aliases edit

One can also define a command as an alias to a sequence of one or more words, which will be substituted for it before execution. (The funny {} arguments are names of the source and target interpreter, which typically is the current one, named by the empty string {} or ""). Examples:

interp alias {} strlen {} string length
interp alias {} cp     {} file copy -force

Introspection: Get the names of all defined aliases with

interp aliases

Advanced concepts edit


Interpreters edit

Tcl being an interpreted (plus on-the-fly byte-compiled) language, an interpreter is of course a central kind of object. Every time Tcl is running, at least one interpreter is running, who takes scripts and evaluates them.

One can also create further "slave" interpreters to encapsulate data and processes, which again can have their "sub-slaves", etc., ultimately forming a tree hierarchy. Examples:

% interp create helper
helper
% helper eval {expr 7*6}
42
% interp delete helper
% helper eval {expr 1+2}
invalid command name "helper"

By deleting an interpreter, all its global (and namespaced) variables are freed too, so you can use this for modularisation and encapsulation, if needed.

In particular, safe interpreters have intentionally limited capabilities (for instance, access to the file system or the Web) so that possibly malicious code from over the Web cannot create major havoc.

Introspection: The following command lists the sub-interpreters ("slaves") of the current interpreter:

% interp slaves

Ensembles edit

Ensembles, (from Tcl 8.5 on), are commands that are composed out of sub-commands according to a standard pattern. Examples include Tcl's built-in chan and clock commands. Dispatching of subcommands, as well as informative error message for non-existing subcommands, is built-in. Subcommands are in a dict structure called "-map", with alternating name and action. Very simple example:

namespace ensemble create -command foo -map \
      {bar {puts Hello} grill {puts World}}

creates a command foo that can be called like

% foo bar
Hello
% foo grill
World
% foo help
unknown or ambiguous subcommand "help": must be foo, or bar

Obviously, ensembles are also a good base for implementing object orientation, where the command is the name of the objects, and the map contains its methods.

Introspection: Serialize an ensemble's map with

namespace ensemble configure $name -map

Namespaces edit

Namespaces are containers for procedures, non-local variables, and other namespaces. They form a tree structure, with the root at the global namespace named "::". Their names are built with :: as separators too, so ::foo::bar is a child of ::foo, which is a child of :: (similar to pathnames on Unix, where / is the separator as well as the root).

In a nutshell, a namespace is a separate area, or scope, where procedures and variables are visible and private to that scope.

To create a namespace, just evaluate some script (which may be empty) in it:

namespace eval ::foo {}

Now you can use it to define procedures or variables:

proc ::foo::test {} {puts Hello!}
set  ::foo::var 42

To get rid of a namespace (and clean up all its variables, procs, and child namespaces):

namespace delete ::foo

Introspection:

namespace children ::
info var namespace::*
info commands namespace::*

The following code gives an approximate size in bytes consumed by the variables and children of a Tcl namespace (of which ::, the global namespace, is of particular interest - all the (grand)*children are also added). If you call this proc repeatedly, you can observe whether data are piling up:

proc namespace'size ns {
  set sum [expr wide(0)]
  foreach var [info vars ${ns}::*] {
      if {[info exists $var]} {
          upvar #0 $var v
          if {[array exists v]} {
              incr sum [string bytelength [array get v]]
          } else {
              incr sum [string bytelength $v]
          }
      }
  }
  foreach child [namespace children $ns] {
      incr sum [namespace'size $child]
  }
  set sum
}

Usage example:

% puts [namespace'size ::]
179914

Threads edit

Tcl users have traditionally been skeptical about threads (lightweight concurrent sub-processes) - the event loop model has proved pretty powerful, and simpler to debug. Originally from Tk, the event loop has moved into Tcl and serves

  • fileevents (more on channels than real files)
  • timed events
  • UI events (mouse or keyboard actions by the user)

However, there is a growing tendency to enable threads in Tcl builds. The underlying model is that every thread runs in an interpreter of its own, so it is mostly encapsulated from the rest of the world. Communication between threads must be done with explicit methods.

Packages and extensions edit

Packages are Tcl's recommended way to modularize software, especially supportive libraries. The user most often uses the command

package require name ?version?

One can write packages in pure Tcl, or as wrappers for extensions which come with one or more compiled shared libraries (plus optionally one or more Tcl scripts). Popular extensions are:

  • BWidget (adds useful widgets to Tk - more below)
  • Expect (supports remote execution over networks)
  • Img (adds support of additional image file formats to Tk)
  • snack (sound input/output)
  • Snit (OO extension, with support for "megawidgets" in Tk)
  • sqlite (a tiny yet powerful SQL database)
  • tcllib (a collection of pure-Tcl packages - see below)
  • TclOO (the canonical object-orientation extension from 8.5)
  • tcltcc (a built-in C compiler - see below)
  • TclX (collection of system-related extensions, like signal handling)
  • tdom (XML parser, SAX or DOM, with XPath query support)
  • Tk (the cross-platform GUI toolkit, see below)
  • tkcon (a vastly extended console)
  • XOTcl (advanced dynamic OO extension)

A little example package edit

The following script creates the trivial but educational package futil, which in a namespace of the same name implements two procs for reading and writing complete text files, and the little introspection helper function, futil::?. The command to register the package (package provide) is executed only after all went well - this way, buggy source code, which raises an error during package require, will not be registered. (Other bugs you'd have to spot and fix for yourself...)

Common Tcl distribution practice has the good habit of profound testing, typically in a separate test directory. On the other hand, including a self-test in the same file with the code makes editing easier, so after the package provide comes a section only executed if this file is sourced as a top- level script, which exercises the commands defined in futil. Whether the string read should be equal to the string written is debatable - the present implementation appends \n to the string if it doesn't end in one, because some tools complain or misbehave if they don't see a final newline.

If the tests do not run into an error either, even the required construction of a package index is fired - assuming the simplified case that the directory contains only one package. Otherwise, you'd better remove these lines, and take care of index creation yourself.

A script that uses this package will only have to contain the two lines

lappend ::auto_path <directory of this file>
package require futil

You can even omit the first line, if you install (copy) the directory with the source and pkgIndex.tcl below ${tcl_install_directory}/lib. }

namespace eval futil {
    set version 0.1
}

But now back to the single script that makes up the package (it would make sense to save it as futil.tcl). We provide a read and a write function in the futil namespace, plus a little introspection function ? that returns the names of available functions:

proc futil::read {filename} {
   set fp [open $filename]
   set string [::read $fp] ;# prevent name conflict with itself
   close $fp
   return $string
}
proc futil::write {filename string} {
   set fp [open $filename w]
   if {[string index $string end]!="\n"} {append string \n}
   puts -nonewline $fp $string
   close $fp
}
proc futil::? {} {lsort [info procs ::futil::*]}
# If execution comes this far, we have succeeded ;-)
package provide futil $futil::version
#--------------------------- Self-test code
if {[info ex argv0] && [file tail [info script]] == [file tail $argv0]} {
   puts "package futil contains [futil::?]"
   set teststring {
       This is a teststring
       in several lines...}
   puts teststring:'$teststring'
   futil::write test.tmp $teststring
   set string2 [futil::read test.tmp]
   puts string2:'$string2'
   puts "strings are [expr {$teststring==$string2? {}:{not}}] equal"
   file delete test.tmp ;# don't leave traces of testing
   # Simple index generator, if the directory contains only this package
   pkg_mkIndex -verbose [file dirn [info scr]] [file tail [info scr]]
}

Tcllib edit

Tcllib is a collection of packages in pure Tcl. It can be obtained from sourceForge, but is also part of ActiveTcl. The following list of contained packages may not be complete, as Tcllib is steadily growing...

  • aes - Advanced Encryption Standard.
  • asn - asn.1 BER encoder/decoder
  • http/autoproxy - code to automate the use of HTTP proxy servers
  • base64 - Base64 encoding and decoding of strings and files.
  • bee - BitTorrent serialization encoder/decoder.
  • bibtex - Neil Madden's parser for bibtex files. Not fully complete yet, therefore not set for installation.
  • calendar - Calendar operations (see also tcllib calendar module).
  • cmdline - Various form of command line and option processing.
  • comm - Socket based interprocess communication. Emulates the form of Tk's send command.
  • control - procedures for tcl flow structures such as assert, do/until, do/while, no-op
  • counter - procedures for counters and histograms
  • crc - Computation of various CRC checksums for strings and files.
  • csv - manipulate comma separated value data
  • des - Data Encryption Standard. ::DES::des (not yet installed)
  • dns - interact with the Domain Name Service. dns::address, dns::cleanup, dns::cname, dns::configure, dns::name, dns::reset, dns::resolve, dns::status, dns::wait,
  • doctools - System for writing manpages/documentation in a simple, yet powerful format.
  • exif - exif::analyze exif::fieldnames
  • fileutil - Utilities for operating on files, emulating various unix command line applications (cat, find, file(type), touch, ...).
  • ftp - Client side implementation of FTP (File Transfer Protocol). In dire need of a rewrite.
  • ftpd - Server side implementation of FTP
  • grammar_fa - Operations on finite automatons.
  • html - generate HTML from a Tcl script. html::author, html::author, html::bodyTag, html::cell, html::checkbox, html::checkSet, html::checkValue, html::closeTag, html::default, html::description, html::description, html::end, html::eval, html::extractParam, html::font, html::for, html::foreach, html::formValue, html::getFormInfo, html::getTitle, html::h, html::h1, html::h2, html::h3, html::h4, html::h5, html::h6, html::hdrRow, html::head, html::head, html::headTag, html::if, html::init, html::init, html::keywords, html::keywords, html::mailto, html::meta, html::meta, html::minorList, html::minorMenu, html::openTag, html::paramRow, html::passwordInput, html::passwordInputRow, html::radioSet, html::radioValue, html::refresh, html::refresh, html::row, html::select, html::selectPlain, html::set, html::submit, html::tableFromArray, html::tableFromList, html::tagParam, html::textarea, html::textInput, html::textInputRow, html::title, html::title, html::urlParent, html::varEmpty, html::while,
  • htmldoc - This is not a true module but the place where tcllib 1.3 installed the tcllib documentation in HTML format.
  • htmlparse - procedures to permit limited manipulation of strings containing HTML. ::htmlparse::parse, ::htmlparse::debugCallback, ::htmlparse::mapEscapes, ::htmlparse::2tree, ::htmlparse::removeVisualFluff, ::htmlparse::removeFormDefs,
  • ident - RFC 1413 ident client protocol implementation
  • imap4 - currently undocumented code for interacting with an IMAP server
  • inifile - code to manipulate an initialization file. ::ini::open, ::ini::close, ::ini::commit, ::ini::sections, ::ini::keys, ::ini::value
  • dns/ip - Manipulation of IP addresses. ::ip::version, ::ip::is, ::ip::normalize, ::ip::equal, ::ip::prefix
  • irc - Internet Relay Chat procedures. irc::config, irc::connection,
  • javascript - generate Javascript for including in HTML pages. javascript::BeginJS, javascript::EndJS, javascript::MakeMultiSel, javascript::MakeClickProc, javascript::makeSelectorWidget, javascript::makeSubmitButton, javascript::makeProtectedSubmitButton, javascript::makeMasterButton, javascript::makeParentCheckbox, javascript::makeChildCheckbox
  • jpeg - edit comment blocks, get image dimensions and information, read exif data of images in the JPG format
  • ldap - Client side implementation of LDAP (Lightweight Directory Access Protocol).
  • log - general procedures for adding log entries to files ::log::levels, ::log::logMsg, ::log::lv2longform, ::log::lv2color,::log::lv2priority,
  • logger - ::logger::walk, ::logger::services, ::logger::enable, ::logger::disable (part of the log module)
  • math - general mathematical procedures. ::math::calculus, ::math::combinatorics, ::math::cov, ::math::fibonacci, ::math::integrate, ::math::interpolate, ::math::max, ::math::mean, ::math::min, ::math::optimize, ::math::product, ::math::random, ::math::sigma, ::math::statistics, ::math::stats, ::math::sum
  • md4 -  ::md4::md4, ::md4::hmac, ::md4::MD4Init, ::md4::MD4Update, ::md4::MD4Final
  • md5 - [fill in the description of this module] ::md5::md5, ::md5::hmac, ::md5::test, ::md5::time, ::md5::<<<
  • md5crypt -  ::md5crypt::md5crypt, ::md5crypt::aprcrypt
  • mime - ::mime::initialize, ::mime::parsepart, ::mime::finalize, ::smtp::sendmessage
  • multiplexer - [fill in the external interfaces]
  • ncgi - procedures for use in a CGI application. ::ncgi::reset, ::ncgi::urlStub, ::ncgi::urlStub
  • nntp - routines for interacting with a usenet news server. ::nntp::nntp, ::nntp::NntpProc, ::nntp::NntpProc, ::nntp::okprint, ::nntp::message,
  • ntp - network time protocol procedure ::ntp::time
  • png - edit comment blocks, get image dimensions and information for Portable Network Graphics format.
  • pop3 - Post Office Protocol functions for reading mail from a pop3 server. ::pop3::open, ::pop3::close, ::pop3::status,
  • pop3d - Post Office Protocol Server. pop3d::new
  • profiler -  ::profiler::tZero, ::profiler::tMark, ::profiler::stats, ::profiler::Handler, ::profiler::profProc, ::profiler::init
  • rc4 - stream encryption. ::rc4::rc4
  • report - format text in various report styles. ::report::report , ::report::defstyle, ::report::rmstyle,
  • sha1 -  ::sha1::sha1, ::sha1::hmac
  • smtpd - ::smtpd::start, ::smtpd::stop, ::smtpd::configure, ::smtpd::cget
  • snit - Snit's Not Incr Tcl - OO package. Delegation based. ::snit::type, ::snit::widget, ::snit::widgetadaptor
  • soundex::knuth - string matching based on theoretical sound of the letters
  • stooop - OO package. stooop::class, stooop::virtual, stooop::new, stooop::delete, stooop::classof
  • struct1 - Version 1 of struct (see below), provided for backward compatibility.
struct::list, ::struct::graph, ::struct::matrix, ::struct::queue, ::struct::stack, ::struct::Tree, ::struct::record, ::struct::skiplist, ::struct::prioqueue, new: ::struct::sets
  • tar - untar, list, and stat files in tarballs and create new tarballs
  • textutil - Utilities for working with larger bodies of texts. textutil::expand - the core for the expand macro processor.
  • tie - Persistence for Tcl arrays.
  • treeql - Tree Query Language, inspired by COST.
  • uri - Handling of uri/urls (splitting, joining, ...)
  • uuid - Creation of unique identifiers.

TclOO edit

TclOO is a loadable package to provide a foundation for object orientation, designed so that specific OO flavors like Itcl, Snit, or XOTcl can build on it. But it's a usable OO system in itself, offering classes, multiple inheritance, mixins and filters. Here is some example code to give you an impression:

#!/usr/bin/env tclsh85
package require TclOO
namespace import oo::*
class create Account {
   constructor { {ownerName undisclosed}} {
       my variable total overdrawLimit owner
       set total 0
       set overdrawLimit 10
       set owner $ownerName
   }
   method deposit amount {
       my variable total
       set total [expr {$total + $amount}]
   }
   method withdraw amount {
       my variable {*}[info object vars [self]] ;# "auto-import" all variables
       if {($amount - $total) > $overdrawLimit} {
           error "Can't overdraw - total: $total, limit: $overdrawLimit"
       }
       set total [expr {$total - $amount}]
   }
   method transfer {amount targetAccount} {
       my variable total
       my withdraw $amount
       $targetAccount deposit $amount
       set total
   }
   destructor {
       my variable total
       if {$total} {puts "remaining $total will be given to charity"}
   }
}

tcltcc edit

Tcltcc is a loadable package that wraps the Tiny C compiler (tcc) for use with Tcl. It can be used to

  • compile C code directly to memory
  • produce dynamic loadable libraries (DLLs) or executable files.

Convenience functions generate wrapper code, so that the user needs only write the really substantial C code.

Examples:

Wrap a C function into a Tcl command "on the fly" (here shown in an interactive session):

% package require tcc
0.2
% namespace import tcc::*
% cproc sigmsg {int i} char* {return Tcl_SignalMsg(i);} 
% sigmsg 4
illegal instruction

Produce a DLL with a fast implementation of Fibonacci numbers:

% set d [tcc::dll]
% $d ccode {
     static int fib(int n) {return n <= 2? 1 : fib(n-1) + fib(n-2);}
  }
% $d cproc fiboy {int n} int {return fib(n);}
% $d write -name fiboy
% load fiboy[info sharedlibextension]
% fiboy 20
6765

Produce a tclsh with an extra square command:

% set code [tcc::wrapCmd square {double x} double x_square {return x*x;}]
% append code {
    int AppInit(Tcl_Interp *interp) {
       int rc;
       rc = Tcl_CreateObjCommand(interp,"square",x_square,NULL,NULL);
           return Tcl_Init(interp);
    }
    int main(int argc, char *argv[]) {
        Tcl_Main(argc, argv, AppInit);
        return 0;
    }
}
% tcc $::tcc::dir exe t
% t add_file    $::tcc::dir/c/crt1.c
% t add_library tcl8.5
% t compile     $code
% t output_file mytclsh.exe
% exec mytclsh.exe {<<puts [square 5]}
25.0

Tcltcc is open source, LGPL licensed, available at http://code.google.com/p/tcltcc/ . The full functionality is at the current early stage (October 2007) only available on Windows 95/XP platforms, but in-memory compilation works on Linux too.

tDOM edit

tDOM is a popular extension for XML/HTML processing, allowing both SAX-style "on-the-fly" parsing and the DOM approach of representing a whole XML element in memory.

Here is an example of a SAX-style application. The expat parser that comes with tDOM is instrumented with callbacks for element start, character data, and processing instructions. Elements, attributes, characters and processing instructions are counted, plus a tally for each element type is done.

 #!/usr/bin/env tclsh
 package require tdom
 #--- Callbacks for certain parser events
 proc el {name attlist} {
     global g
     incr ::nEl
     incr ::nAtt [llength $attlist]
     inc g($name)
 }
 proc ch data {
    incr ::nChar [string length $data]
 }
 proc pi {target data} {
    incr ::nPi
 }
 proc inc {varName {increment 1}} {
    upvar 1 $varName var
    if {![info exists var]} {set var 0}
    incr var $increment
 }
 #--- "main" loop
 if ![llength $argv] {puts "usage: $argv0 file..."}
 foreach file $argv {
     foreach i {nEl nAtt nChar nPi} {set $i 0} ;# reset counters
     array unset g
     set p [expat -elementstartcommand el \
            -characterdatacommand          ch \
            -processinginstructioncommand  pi ]
     if [catch {$p parsefile $file} res] {
                puts "error:$res"
     } else {
        puts "$file:\n$nEl elements, $nAtt attributes, $nChar characters,\
            $nPi processing instructions"
        foreach name [lsort [array names g]] {
            puts [format %-20s%7d $name $g($name)]
        }
    }
    $p free
 }