Version 133 of expr

Updated 2012-11-29 21:38:19 by pooryorick

Summary

expr - Evaluate an expression

Synopsis

expr arg ?arg arg ...?
officieal reference

expr(n) manpage (Tcl 8.4)

tcl_precision

expr(n) manpage , mathfunc(n) manpage , mathop(n) manpage (all Tcl 8.5)

expr concatentates its arguments, evaluates this result as a Tcl In this example, expr concatenates each arg (adding separator spaces between them), evaluates the result as a Tcl expression, and returns the value. The operators permitted in Tcl expressions are a subset of the operators permitted in C expressions (plus a few more) and they have the same meaning and precedence as the corresponding C operators. Expressions almost always yield numeric results (integer or floating-point values). For example, the expression: expr implements a little language that has a syntax separate from Tcl.

expr 8.2 + 6

evaluates to 14.2. Tcl expressions differ from C expressions in the way that operands are specified. Also, Tcl expressions support non-numeric operands and string comparisons. (From: Tcl help - much more there..)

Note that expr attempts to make use of the apparent numeric data type of the variables when deciding what type of math to do. So, if you want a floating point value returned from an operation, and you do not know for certain what type of value may be in your variables, you can ensure at least one of the arguments is a floating point by doing something like this:

 set a 1
 set b 2
 expr {double($a)/$b}

and if you want the result to be an integer, you can be certain by forcing:

 expr {int($a/$b)}

rwm sometimes it is difficult to debug expr calls where the operands are variables. DebuggingExprCalls explains how to wrap expr to help with these cases.


LV Here's an example of using in or ni:

 % set a "abc"
 % set b [list 123 abcd xyz lmnop]
 % expr in $a $b
 missing operand at _@_
 in expression "_@_in abc 123 abcd xyz lm..."
 % expr $a in $b
 invalid bareword "abc"
 in expression "abc in 123 abcd xyz lmnop";
 should be "$abc" or "{abc}" or "abc(...)" or ...
 % expr {$a in $b}
 0
 % expr {$a ni $b}
 1
 % expr \"$a\" in \"$b\"
 0
However, this is not unique to "in":
#DON'T EXECUTE THIS SCRIPT!!!
 % expr $a == "foo" ? true : false
 invalid bareword "abc"
 % expr {$a == "foo" ? true : false}
 false

So, some sort of quoting is required for expr operators to work consistently.

gives a much more reasonable result:

** Operators **

Note that many operators have command-equivalents in the [namespace] '''::[tcl::mathop]''' from Tcl 8.5 onwards.

[[The term '''mathop''' is a misnomer, since some of the operators included in this namespace are string, rather than math, oriented...]]

The '''expr''' operators, in order of precedence (tightest-binding to least-tight binding), are:

&| [-] [+] [~] [!] | Unary operators; specifically a negation operation, a non-negation operation (I see little point in this one), a bit-wise NOT operation (every bit in the input value gets replaced by its inverse) and a logical NOT operation (non-zero maps to zero, and zero maps to one.) |&
&| [*] [/] [%] | Multiplication, division and ''integer'' remainder (see fmod() below.) |&
&| [+] [-] | Addition and subtraction. |&
&| [<<] [>>] | Left and right shift.  Equivalent to multiplying or dividing by a suitable power of two, and then reducing the result to the range representable in an integer on the host platform. |&
&| [<] [>] [<=] [>=] | Ordering relations (less than, greater than, less than or equal, greater than or equal.)   Note that these operations work on strings as well as numbers, but you are probably better off testing the result of [string compare] instead as that is more predictable in the case of a string that looks like a number. |&
&| [==] [!=] | Equality and inequality.   Note that these operations work on strings as well as numbers, but you are probably better off testing the result of [string equal] instead as that is more predictable in the case of a string that looks like a number.  For example, [string equal] considers "6" and "06" to be different strings, but expr's == considers them to be equivalent numbers. |&
&| [eq] [ne] | (2004-07-08 added): From Tcl 8.4 on. The same as before, but arguments only strings. Will find "6" and "06" (as well as 1 and 1.0) to be different. |&
&| [**] | exponential. From Tcl 8.5 on |&
&| [in] [ni] | Item (argument 1) in/not in list (argument 2). From Tcl 8.5 on |&
&| [&] | Bit-wise AND.  A bit is set in the result when the corresponding bit is set in both the arguments. |&
&| [^] | Bit-wise exclusive OR.  A bit is set in the result when the corresponding bit is set in ''precisely one'' of the arguments. |&
&| [<<pipe>>] | Bit-wise OR.   A bit is set in the result when the corresponding bit is set in either of the arguments. |&
&| [&&] | Logical AND.   The result is a one (true) when both of the arguments are non-zero (true), and zero (false) otherwise.  Note that this operation is a ''short-circuiting'' operation, and will only evaluate its second argument when the first argument is non-zero.  This includes the expansion of Tcl commands in square brackets, but this delay in evaluation only occurs if the whole expression is enclosed in curly braces. |&
&| [<<pipe>><<pipe>>] | Logical OR.   The result is a zero (false) when both of the arguments are zero (false), and one (true) otherwise.  Note that this operation is a ''short-circuiting'' operation, and will only evaluate its second argument when the first argument is zero.  This includes the expansion of Tcl commands in square brackets, but this delay in evaluation only occurs if the whole expression is enclosed in curly braces. |&
&| x'''?'''y''':'''z | If-then-else, as in C (where x,y,z are expressions).   If the value x is non-zero (true) then the expression y is evaluated to produce the result, and otherwise the expression z is evaluated to produce the result.  Note that this operation is a ''short-circuiting'' operation, and will not evaluate expression y if x is zero (false) and will not evaluate expression z if x is non-zero (true).  This includes the expansion of Tcl commands in square brackets, but this delay in evaluation only occurs if the whole expression is enclosed in curly braces.  It is usually clearer and easier to maintain (and no slower - the generated bytecode is identical) to use the Tcl [if] command instead of this. |&
<<discussion>>

***More about X?Y:Z***

'' The '''x?y:z''' operator is also known as "ternary operator". ''

[DGP] Well..... ''ternary operator'' literally means nothing
more than an operator that takes three operands.  The
'''arithmetic if (... ? ... : ...)''' does take three operands,
so it is an example of a ternary operator.  It's also the only
ternary operator in Tcl's [[expr]] grammar, so one can sensibly
mention "the" ternary operator, but ''ternary operator'' is
still really a general descriptive term, not the specific name
of the arithmetic-if operator.

'' Fine with me, so long as it shows up in the search engine''  :-)

----

The '''x?y:z''' operator can be used for considerable control structures (see [Binary trees]):

expr {

    [llength $bt]?
          $root > $x? [btsearch [lindex $bt 1] $x]
        : $root < $x? [btsearch [lindex $bt 2] $x]
        : 1
     : 0

} ;# RS

----
[Silas] - 2005.10.29

When you use the ternary operator to compare numbers, the following format is valid:

set result expr ($number eq $secondnumber) ? true_result : false_result

But to compare non-numeric values, you must to surround everything with curly braces:

set result expr {($string eq $secondstring) ? true_result : false_result}

[Lars H]: This has nothing to do with ?: as such -- you would see the same difference just between

set result expr ($number eq $secondnumber) set result expr {$string eq $secondstring}

What happens is that in the first case the variables are being substituted by the Tcl parser, whereas in the second case they are being substituted by the expr parser. In the first case this means the values will also have to survive a trip through the expr parser, and that requires strings to be quoted. The following will work most of the time
 set result [expr ("$string"eq"$secondstring")]
but there's little point in tarrying with such edge cases. '''Always brace your expressions!''' The result runs faster and offers fewer possibilities for strange errors.

[LV] A thread on the tcl-core includes this related information:

 Date: Thu, 13 Sep 2007 18:50:51 +0200
 From: Gustaf Neumann <[email protected]>
 Subject: [TCLCORE] string expressions
 To: Tcl Core List <[email protected]>
 Message-ID: <[email protected]>

Hi everybody,

a short question about error triggered by the ternary expr operator  .. ? .. : .. and conditional expressions.
Conditional assignments are often prefered over lengthy if statements, if all the programmer wants is to assign to a variable conditionally one or the other value.

In Tcl "expr" is unsafe for this purpose for various reasons, especially, when the rhs might contain free content. The following is safe,

set a 1 set b 2 set t 1 set x expr {$t ? $a : $b}

but having  e.g.

set a nan

causes: ''domain error: argument not in valid range''

The expr on the rhs causes the problem, same as

expr {$a}

The eval on the rhs of the ternary operator might as well lead to unwanted conversions in a conditional assignment in string expressions.

By looking for alternatives, one of the better approaches that came to my mind was

set x if {$t} {set a} {set b}

but in cases where the rhs contains literals, one needs either some hack like

set x if {1} {set "" hello} {set b}

or cleaner:

proc literal x {return $x} set x if {1} {literal hello} {set b}

% time {time {set x expr {1 ? $a : $b}} 1000000} 590777 microseconds per iteration % time {time {set x if {1} {set a} {set b}} 1000000} 466926 microseconds per iteration % time {time {set x if {1} {set "" hello} {set b}} 1000000} 507825 microseconds per iteration % proc literal x {return $x} % time {time {set x if {1} {literal hello} {set b}} 1000000} 805762 microseconds per iteration

 made a C implementation of the [K] operator, which is better than the tcl proc (no wonder) but slower than byte compiled code (no wonder).

% time {time {set x if {1} {K hello} {set b}} 1000000} 583736 microseconds per iteration

One can also do a lindex on the expr

set x lindex [list $b hello [expr {$cond}]

but this is neither obvious nor fast.

Are there better options?
Eg. a unary "string prefix operator", telling expr that the argument is a string to skip the evaluation?

Or recognizing some quoting in expr?

Or defining a string expression as subcommand of string, like "string expr <cond> <cond-true-result> <cond-false-result>" ?

I could not find good discussions about this topic... Is everybody happy with the current situation?

-gustaf




------------------------------

 Message: 2
 Date: Thu, 13 Sep 2007 13:42:45 -0400
 From: [email protected]
 Subject: Re: [TCLCORE] string expressions
 To: Gustaf Neumann <[email protected]>
 Cc: Tcl Core List <[email protected]>
 Message-ID: <[email protected]>
 Content-Type: text/plain; charset=ISO-8859-1

 Quoting Gustaf Neumann <[email protected]>:
 >  proc literal x {return $x}
 >  set x [if {1} {literal hello} {set b}]
 ..
 > Are there better options?

Some other options you might try are:

 interp alias {} literal {} return -level 0

 interp alias {} literal {} subst -nobackslashes -nocommands -novariables

 interp alias {} literal {} format %s

I would guess that this question arises most often in template substitution type applications?  Perhaps someone with background in that has some other ideas?

DGP



<<discussion>>

** Functions **
See the mathfunc man page, listed above, for the Tcl 8.5 man page information on '''expr''' builtin functions.

'''BUILTIN FUNCTIONS'''
   '''[abs]'''(x):   Absolute value (negate if negative.)
   '''[acos]'''(x):   Inverse cosine (result in radians.)
   '''[asin]'''(x):   Inverse sine (result in radians.)
   '''[atan]'''(x):   Inverse tangent (result in radians.)
   '''[atan2]'''(y,x):   Inverse tangent.  Can handle cases which plain atan() can't (due to division by zero) and has a larger output range (result in radians.)
   '''[bool]'''(x):   Accept any numeric value or string (acceptable to [string] is boolean), and return the corresponding boolean value 0 or 1
   '''[ceil]'''(x):   Ceiling (defined over floating point numbers.)  If the input value is not a whole number, return the next ''larger'' whole number. '''Surprise''': The return value is a float, not an integer.
   '''[cos]'''(x):   Cosine (input in radians.)
   '''[cosh]'''(x):   Hyperbolic cosine.
   '''[double]'''(x):   Convert number to floating point.
   '''[entier]'''(x):   Take any numeric value and return the integer part of the argument, as an unlimited value string
   '''[exp]'''(x):   Exponential function.  Returns e**inputValue (using the FORTRAN-style notation) where e is the base of natural logarithms.
   '''[floor]'''(x):   Floor (defined over floating point numbers.)  If the input value is not a whole number, return the next ''smaller'' whole number. '''Surprise''': The return value is a float, not an integer.
   '''[fmod]'''(x, y):   Floating point remainder of x divided by y.
   '''[hypot]'''(x,y):   Hypotenuse calculator.  If the projection of a straight line segment onto the X axis is x units long, and the projection of that line segment onto the Y axis is y units long, then the line segment is hypot(x,y) units long (assuming boring old Euclidean geometry.)  Equivalent to sqrt(x*x+y*y).
   '''[int]'''(x):   Convert number to integer by truncation.
   '''[isqrt]'''(x):   Compute the integer part of the square root of x.
   '''[log]'''(x):   Natural logarithm.
   '''[log10]'''(x):   Logarithm with respect to base 10.
   '''[max]'''(x,...):   Return the one argument with the greatest value
   '''[min]'''(x,...):   Return the one argument with the least value
   '''[pow]'''(x,y):   Power function.  In FORTRAN notation, x[**]y.
   '''[rand]'''():   Random number.  Uses uniform distribution over the range [0,1).  ''This RNG is not suitable for cryptography.''
   '''[round]'''(x):   Round to nearest whole number.  ''Not suitable for financial rounding.''
   '''[sin]'''(x):   Sine (input in radians.)
   '''[sinh]'''(x):   Hyperbolic sine.
   '''[sqrt]'''(x):   Square root (well, the positive square root only.  And Tcl doesn't do complex math, so the input had better be positive...)
   '''[srand]'''(x):   Seeds the random number generator with the given value.  Each interpreter has its own random number generator, which starts out seeded with the current time.
   '''[tan]'''(x):   Tangent (input in radians.)
   '''[tanh]'''(x):   Hyperbolic tangent.kjh
   '''[wide]'''(x):   Take any numeric value, and return the low order 64 bits of the integer value of the argument
<<discussion>>
History corner: on 1992-12-28 [JO] published the voting results 37 : 8 in favor of embedded functions() vs. separate [[commands]] - [http://groups.google.com/groups?q=group:comp.lang.tcl+author:ousterhout&start=900&hl=de&lr=&newwindow=1&scoring=d&selm=1hn9tvINNqod%40agate.berkeley.edu&rnum=922]

** See also **

   [if]
   [for]
   [while]
   [Brace
   [expr problems with int]:   limits of number representation (both integer and float) inherited from C
   [Importing expr functions]:   use expr's functions without explicitly calling that, see [Importing expr functions].
   [A real problem]:   
   [Math function help]:   
   [How can I do math in Tcl]:   
   [Additional math functions]:   
   [double substitution]:   
   [Modeling COND with expr]:   Braced expressions can span several lines
   [A little math language]:   adds features & sugar to expr
   [compute]:   more sugar for expr
See also [if], [for], [while], and "[Brace your expr-essions]".

** Caveats **

expr's parsing of decimals may be hampered by [locale] - you might get an
''syntax error in expression 1.0''

** Discussion **

[[Perhaps people can insert here some examples of expr, along with any cautions or explanations as needed]]
[RS] 2003-04-24: Here's a tiny wrapper for friends of infix assignment:
 set a [expr 1 + 2]                         ; # Simple addition
 set a [expr sqrt(4) ]                      ; # Invoke expr function.

 set a [expr {" 2 " == [string trim " 2 "]}]; # returns 1, because
                                              # " 2 " will be converted to 2
                                              # [Martin Lemburg]

 set a [expr {-2**2}]                        ; # returns 4, rather than -4 as some
                                          # might expect

 set a [expr {5&2==2}]                        ; # returns 1 because 2==2 is
                                          # evaluated first

There are subtle differences between the Tcl parser and the somewhat limited, but more efficient parser inside expr. You can choose between them by bracing or not bracing expr's argument. A simple test case:

 set x 1; set j 2
 expr $x/$j.
 # works: 0.5; j is cast to float by trailing dot (Tcl parser)
 expr {$x/$j.}
 # error: syntax error in expression "$x/$j."  (expr parser)

Of course, coercing a number to real by simply appending a decimal point is poor practice. Far better is:

 expr { $x / double($j) }

It's faster, too:

 set script1 {
    set x 1
    set j 2
    set k [expr $x/$j.]
 }
 set script2 {
    set x 1
    set j 2
    set k [expr { $x / double($j) }]
 }
 foreach v { script1 script2 } {
    puts "$v: [time [set $v] 10000]"
 }
 script1: 38 microseconds per iteration
 script2: 9 microseconds per iteration

It's also safer: consider what would happen if this script were actually working with user input:

 set x {[exec format C:\\]}
 set j {[puts Sucker!]}
 set k [expr $x / $j.]        ;# DON'T EXECUTE THIS SCRIPT!!!!

(Hint: By the time it detects the syntax error, C:\ is gone!)

On the other hand,

set k [expr { $x / double($j) }]

gives a much more reasonable result:

 argument to math function didn't have numeric value
    while executing
 "expr { $x / double($y) }"
    invoked from within
 "set k [expr { $x / double($y) }]
 "
     (file "foo.tcl" line 3)

RS: This was just to demonstrate the differences between the regular Tcl parser and expr's parser, not recommended practice. Another example is substitution of operators:

 set op "+"
 expr 4 $op 5
 9
 expr {4 $op 5}
 syntax error in expression "4 $op 5"

See the for page on a case where that helped.


expr conditions (like those used in if or while) take 0 to mean false and all other numbers to mean true. In addition, the following string constants can be used:

  • true, on, yes
  • false, off, no

man Tcl_GetBoolean: "Any of these values may be abbreviated, and upper-case spellings are also acceptable." Beware that if you need code to run in Tcl releases as old as 8.3, you have to quote these if you use them directly as constants, as Donald Porter noted: [expr] tries to interpret "bare" strings as function names, such as cos($x). You must quote the string "true". Then it behaves as you expect in 8.3.3.

Refer to the Operands section [L1 ] of the expr man page for the syntax rules.



See also if, for, while, and "Brace your expr-essions".


RS: Would it make sense to extend the expr parser? I also see the funny behavior:

 % set y 2*3; puts [expr {$y}]  ==> 2*3 (so y is not checked), but:
 % set y 2*3; puts [expr {$y+0}] ==> can't use non-numeric string as operand of "+"

Maybe before raising that error, expr's arguments could be reparsed, so it comes out like with the unbraced

 % set y 2*3; puts [expr $y+0] ==> 6

2003-04-24 - ..and here's a tiny wrapper for friends of infix assignment:

 % proc let {var = args} {uplevel 1 set $var \[expr $args\]} ;#RS
 % let i = 1
 1
 % let j = $i + 1
 2
 % let k = {$i + $j}
 3

AM The problem with variables whose values are actually expressions is that they change the whole expression in which they are used. The performance gain for caching the parsed expression will then be lost.

----
During March of 2005, a developer mentions surprise at the fact that
 expr int(36.37*100)
returns an unexpected value.  After the traditional observation concerning
inability to represent some floating points exactly, [Bruce Stephens]
also makes a couple more observations:

"Yet another way of thinking about it is that "expr int($a)" is almost
always wrong.  It's been poor style for a long time, and the various
Tcl checking programs have warned about it.  So really (almost) nobody
should be writing "expr int($a)".

"Just as nobody would write:

     if $i<10 { ...

nobody ought to be writing "expr int($a)".  You almost always should
write

     if {$a<10} { ...

and "expr {int($a)}".

[RS] Hmm...
 % expr 36.37*100
 3637.0 ;#-- good enough...
 % expr {36.37*100}
 3637.0 ;#-- the same
 % expr {int(36.37*100)}
 3636   ;#-- Hmm
 % expr int(36.37*100)
 3636   ;#-- the same
 % info pa
 8.4.9

[LV] My response on [comp.lang.tcl] was that I thought it was a shame
that expr (or perhaps it is Tcl) didn't use the same mechanism for
both calculations of 36.37 * 100 ; that way, the results would at least
be consistent.  Even if they were consistently '''wrong''', one would
be able to at least to live within the ''law of least surprise''.
As it is, until one experiments, one won't know which way that Tcl
is going to ''round'' results.

[EPSJ] This may be a side effect of the IEEE floating point standard. This is done in hardware to guarantee the convergence in the case of a series of math algorithms. The rule is that the mantissa of a floating point number must be rounded to the nearest even number. As 36.37 cannot be represented exactly in float point it ends up being a small fraction below the intended number. On the other side 36.38 moves on the other direction. Look the following result:

 () 60 % expr int(36.380*100)
 3638
 () 61 % expr int(36.370*100)
 3636

x86 floating point hardware allows this to be configurable to nearest even, nearest odd, and a few more options. But usually nearest even is the default. The result may seem inconsistent, but it is intentional.


[RS] My point was that braced or not, [expr] returns the same (string rep of) double as well as int() result, so I don't see this as an argument why one has to brace (though I know there are...)
----
'''(Outdated) Expr [Gotchas]'''

Addition

 % expr (1<<31)-1
 2147483647

 % expr 2147483647 + 2147483647
 -2

Multiplication

 % expr sqrt((1<<31)-1)
 46340.9500011

 expr 46341*46341
 -2147479015

These are results of Tcl 8.4 and older versions using a 32-bit representation for integers.  Check out http://tip.tcl.tk/237 , an implemented [TIP] describing arbitrary-precision Integers for Tcl. This is available in Tcl 8.5.

----
[LES] on July 23 2005:
 % expr pow(5,6)
 15625.0

 % expr 5**6
 15625

Two syntaxes, two slightly different results. Is that intentional? [RS] Yes - while pow() always goes for double logarithms, '**' tries to do integer exponentiation where possible.

----
[RS] 2006-06-19 A word of warning: [expr] may normalize strings that look like octals to decimal, even if no arithmetic operation was performed on them:
 %set bond james
 % expr {$bond eq ""? "-": "$bond"}
 james
 % set bond 0070
 % expr {$bond eq ""? "-": "$bond"}
 56
But no complaints if the string cannot be parsed as octal:
 % set bond 008
 % expr {$bond eq ""? "-": "$bond"}
 008
In such cases it's better and more robust to use [if]:
 if {$bond eq ""} {set bond -}

[HE] 2006-06-20 Strange behavior! The manpage of expr says:
 eq ne
  Boolean string equal and string not equal.
  Each operator produces a zero/one result.
  The operand types are interpreted only as strings.
There is no mention about this behavior. (I remember weakly this two operators are added exactly to avoid this problem)
More interesting: The manpage of if says:
 The if command evaluates expr1 as an expression (in the same way that expr evaluates its argument).
Is there something wrong?

[JMN] 2006-10-19
Not really.. This normalization isn't occurring in the 'eq' operation - it happens when expr returns the result.
This may make it clearer:

 %expr {$bond eq ""? "-": "hello $bond"}
 hello 0070
 %expr {$bond}
 56
 %expr {$bond eq 56}
 0
 %expr {$bond == 56}
 1

[LV] Note the previous discussions on this page regarding the precautions one should keep in mind when using eq on tcl variables which contain numeric values. I am not certain I can think of a case where one would use eq when comparing numeric values...

----
[LV] Note that there are a few TIPs detailing new functionality for expr.  For instance:
   * TIP #123 [http://tip.tcl.tk/123] Adding an Exponentiation Operator to the expr Command
   * TIP #182 [http://tip.tcl.tk/182] Add 'expr bool' Math Function
   * TIP #201 [http://tip.tcl.tk/201] Add 'in' Operator to expr
   * TIP #232 [http://tip.tcl.tk/232] Creating New Math Functions for the 'expr' Command ([tcl::mathfunc])

[AMG]: Also related:

   * TIP #174 [http://tip.tcl.tk/174] [Math Operators as Commands]

   * TIP #237 [http://tip.tcl.tk/237] Arbitrary-Precision Integers for Tcl

----
[davou] what is the precision of expr's functions, and how can it be expanded upon?

[Lars H]: That's generally determined by the [C] library functions that implement them, i.e., it depends on where (and against what) Tcl is compiled. For "real" numbers that means '''double'''s, which are floating-point numbers of typically about 17 decimal digits precision (but how many of these are correct varies between functions and platforms). For integers Tcl has traditionally used '''long'''s, which in most cases means 32-bit two's complement integers ($tcl_platform(wordSize) tells you the actual number of bytes), but as of Tcl 8.5 it supports (almost) arbitrarily large integers ([googol magnitude] is no problem anymore, whereas googolplex magnitude wouldn't fit in the computer memory anyway). As for extending what the core provides, [tcllib] provides math::bignum and [math::bigfloat].

----
At least as of Tcl 8.5, [NaN] and [Inf] are potential values returning from expr.
Also in Tcl 8.5, [in] and [ni] are new string operators.
----

[LV] [Roy Terry] writes this example in a thread about whether strings need to be quoted in Tcl, over on [comp.lang.tcl]:

 %  if {joe eq mike} {puts wow}
 syntax error in expression "joe eq mike": variable references require preceding $
 %  if {"joe" eq "mike"} {puts "wow"}
 %  if {{joe} eq {mike}} {puts {wow}}
 %

This is an example of a context where a Tcl ''bareword'' string needs to quoted in some manner.

There are other cases in Tcl where this quoting need not happen.
 % puts wow
 wow
 % set a abc
 abc
 %

If you prefer consistency, then always quote the strings.

----------------------------------------------------------------------------------------------------------------------

[Wookie] I had some trouble recently using expr to calculate time offsets. I had 2 time stamps in the form hh:mm
So I had 4 variables h1, m1, h2, m2 and one of my `expr` functions was
So I had 4 variables h1, m1, h2, m2 and one of my expr functions was
   set result [expr ($m1 + $m2)]

As many of you may be thinking, you fool! what about 08 and 09, which will get As many of you may be thinking, you fool! what about 08 and 09, which will get treated as invalid octal. So after some grumbling I thought okay so I have to trimleft them. Bit verbose but who cares:

   set m1 [string trimleft $m1 0]
   set m2 [string trimleft $m2 0]
   set result [expr ($m1 + $m2)]
Now what could possibly go wrong with that... well obviously 00 becomes the
Now what could possibly go wrong with that... well obviously 00 becomes "", which causes unexpected closed parameter in the expr. So now I have to check for "". So...
   set m1 [string trimleft $m1 0]
   if {$m1==""} { set m1 0 }

set m2 string trimleft $m2 0

   set m2 [string trimleft $m2 0]
   if {$m2==""} { set m2 0 }

set result expr {$m1 + $m2}

   set result [expr ($m1 + $m2)]

... and then repeat it for the hours. It all seemed very clumsy. So I came up ... and then repeat it for the hours. It all seemed very clumsy. So I came up with this, which may solve many of the conversion issues in this section.

   scan "$h1:$m1 $h2:$m2" "%d:%d %d:%d" h1 m1 h2 m2
   set result [expr ($m1 + $m2)]
All the conversions to int have been done and leading 0's have been stripped
All the conversions to int have been done and leading 0's have been stripped and returns 0 if the value is all 0s. This works for float and probably double (though I've not tried). Can anyone see any problems with this approach?
[glennj]: No, `[scan]` is definitely the way to parse numbers out of dates
[glennj] No, [scan] is definitely the way to parse numbers out of dates and times.  However, for date arithmetic, nothing beats [clock].  
 # adding a delta to a time
 set h1 12; set m1 45
 set h2 3; set m2 30
 clock format [clock add [clock scan "$h1:$m1" -format "%H:%M"] $h2 hours $m2 minutes] -format %T ;# ==> 16:15:00